LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
checon_3.f
Go to the documentation of this file.
1 *> \brief \b CHECON_3
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CHECON_3 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/checon_3.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/checon_3.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/checon_3.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE CHECON_3( UPLO, N, A, LDA, E, IPIV, ANORM, RCOND,
22 * WORK, INFO )
23 *
24 * .. Scalar Arguments ..
25 * CHARACTER UPLO
26 * INTEGER INFO, LDA, N
27 * REAL ANORM, RCOND
28 * ..
29 * .. Array Arguments ..
30 * INTEGER IPIV( * )
31 * COMPLEX A( LDA, * ), E ( * ), WORK( * )
32 * ..
33 *
34 *
35 *> \par Purpose:
36 * =============
37 *>
38 *> \verbatim
39 *> CHECON_3 estimates the reciprocal of the condition number (in the
40 *> 1-norm) of a complex Hermitian matrix A using the factorization
41 *> computed by CHETRF_RK or CHETRF_BK:
42 *>
43 *> A = P*U*D*(U**H)*(P**T) or A = P*L*D*(L**H)*(P**T),
44 *>
45 *> where U (or L) is unit upper (or lower) triangular matrix,
46 *> U**H (or L**H) is the conjugate of U (or L), P is a permutation
47 *> matrix, P**T is the transpose of P, and D is Hermitian and block
48 *> diagonal with 1-by-1 and 2-by-2 diagonal blocks.
49 *>
50 *> An estimate is obtained for norm(inv(A)), and the reciprocal of the
51 *> condition number is computed as RCOND = 1 / (ANORM * norm(inv(A))).
52 *> This routine uses BLAS3 solver CHETRS_3.
53 *> \endverbatim
54 *
55 * Arguments:
56 * ==========
57 *
58 *> \param[in] UPLO
59 *> \verbatim
60 *> UPLO is CHARACTER*1
61 *> Specifies whether the details of the factorization are
62 *> stored as an upper or lower triangular matrix:
63 *> = 'U': Upper triangular, form is A = P*U*D*(U**H)*(P**T);
64 *> = 'L': Lower triangular, form is A = P*L*D*(L**H)*(P**T).
65 *> \endverbatim
66 *>
67 *> \param[in] N
68 *> \verbatim
69 *> N is INTEGER
70 *> The order of the matrix A. N >= 0.
71 *> \endverbatim
72 *>
73 *> \param[in] A
74 *> \verbatim
75 *> A is COMPLEX array, dimension (LDA,N)
76 *> Diagonal of the block diagonal matrix D and factors U or L
77 *> as computed by CHETRF_RK and CHETRF_BK:
78 *> a) ONLY diagonal elements of the Hermitian block diagonal
79 *> matrix D on the diagonal of A, i.e. D(k,k) = A(k,k);
80 *> (superdiagonal (or subdiagonal) elements of D
81 *> should be provided on entry in array E), and
82 *> b) If UPLO = 'U': factor U in the superdiagonal part of A.
83 *> If UPLO = 'L': factor L in the subdiagonal part of A.
84 *> \endverbatim
85 *>
86 *> \param[in] LDA
87 *> \verbatim
88 *> LDA is INTEGER
89 *> The leading dimension of the array A. LDA >= max(1,N).
90 *> \endverbatim
91 *>
92 *> \param[in] E
93 *> \verbatim
94 *> E is COMPLEX array, dimension (N)
95 *> On entry, contains the superdiagonal (or subdiagonal)
96 *> elements of the Hermitian block diagonal matrix D
97 *> with 1-by-1 or 2-by-2 diagonal blocks, where
98 *> If UPLO = 'U': E(i) = D(i-1,i),i=2:N, E(1) not referenced;
99 *> If UPLO = 'L': E(i) = D(i+1,i),i=1:N-1, E(N) not referenced.
100 *>
101 *> NOTE: For 1-by-1 diagonal block D(k), where
102 *> 1 <= k <= N, the element E(k) is not referenced in both
103 *> UPLO = 'U' or UPLO = 'L' cases.
104 *> \endverbatim
105 *>
106 *> \param[in] IPIV
107 *> \verbatim
108 *> IPIV is INTEGER array, dimension (N)
109 *> Details of the interchanges and the block structure of D
110 *> as determined by CHETRF_RK or CHETRF_BK.
111 *> \endverbatim
112 *>
113 *> \param[in] ANORM
114 *> \verbatim
115 *> ANORM is REAL
116 *> The 1-norm of the original matrix A.
117 *> \endverbatim
118 *>
119 *> \param[out] RCOND
120 *> \verbatim
121 *> RCOND is REAL
122 *> The reciprocal of the condition number of the matrix A,
123 *> computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is an
124 *> estimate of the 1-norm of inv(A) computed in this routine.
125 *> \endverbatim
126 *>
127 *> \param[out] WORK
128 *> \verbatim
129 *> WORK is COMPLEX array, dimension (2*N)
130 *> \endverbatim
131 *>
132 *> \param[out] INFO
133 *> \verbatim
134 *> INFO is INTEGER
135 *> = 0: successful exit
136 *> < 0: if INFO = -i, the i-th argument had an illegal value
137 *> \endverbatim
138 *
139 * Authors:
140 * ========
141 *
142 *> \author Univ. of Tennessee
143 *> \author Univ. of California Berkeley
144 *> \author Univ. of Colorado Denver
145 *> \author NAG Ltd.
146 *
147 *> \date June 2017
148 *
149 *> \ingroup complexHEcomputational
150 *
151 *> \par Contributors:
152 * ==================
153 *> \verbatim
154 *>
155 *> June 2017, Igor Kozachenko,
156 *> Computer Science Division,
157 *> University of California, Berkeley
158 *>
159 *> September 2007, Sven Hammarling, Nicholas J. Higham, Craig Lucas,
160 *> School of Mathematics,
161 *> University of Manchester
162 *>
163 *> \endverbatim
164 *
165 * =====================================================================
166  SUBROUTINE checon_3( UPLO, N, A, LDA, E, IPIV, ANORM, RCOND,
167  $ WORK, INFO )
168 *
169 * -- LAPACK computational routine (version 3.7.1) --
170 * -- LAPACK is a software package provided by Univ. of Tennessee, --
171 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
172 * June 2017
173 *
174 * .. Scalar Arguments ..
175  CHARACTER UPLO
176  INTEGER INFO, LDA, N
177  REAL ANORM, RCOND
178 * ..
179 * .. Array Arguments ..
180  INTEGER IPIV( * )
181  COMPLEX A( LDA, * ), E( * ), WORK( * )
182 * ..
183 *
184 * =====================================================================
185 *
186 * .. Parameters ..
187  REAL ONE, ZERO
188  parameter( one = 1.0e+0, zero = 0.0e+0 )
189 * ..
190 * .. Local Scalars ..
191  LOGICAL UPPER
192  INTEGER I, KASE
193  REAL AINVNM
194 * ..
195 * .. Local Arrays ..
196  INTEGER ISAVE( 3 )
197 * ..
198 * .. External Functions ..
199  LOGICAL LSAME
200  EXTERNAL lsame
201 * ..
202 * .. External Subroutines ..
203  EXTERNAL chetrs_3, clacn2, xerbla
204 * ..
205 * .. Intrinsic Functions ..
206  INTRINSIC max
207 * ..
208 * .. Executable Statements ..
209 *
210 * Test the input parameters.
211 *
212  info = 0
213  upper = lsame( uplo, 'U' )
214  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
215  info = -1
216  ELSE IF( n.LT.0 ) THEN
217  info = -2
218  ELSE IF( lda.LT.max( 1, n ) ) THEN
219  info = -4
220  ELSE IF( anorm.LT.zero ) THEN
221  info = -7
222  END IF
223  IF( info.NE.0 ) THEN
224  CALL xerbla( 'CHECON_3', -info )
225  RETURN
226  END IF
227 *
228 * Quick return if possible
229 *
230  rcond = zero
231  IF( n.EQ.0 ) THEN
232  rcond = one
233  RETURN
234  ELSE IF( anorm.LE.zero ) THEN
235  RETURN
236  END IF
237 *
238 * Check that the diagonal matrix D is nonsingular.
239 *
240  IF( upper ) THEN
241 *
242 * Upper triangular storage: examine D from bottom to top
243 *
244  DO i = n, 1, -1
245  IF( ipiv( i ).GT.0 .AND. a( i, i ).EQ.zero )
246  $ RETURN
247  END DO
248  ELSE
249 *
250 * Lower triangular storage: examine D from top to bottom.
251 *
252  DO i = 1, n
253  IF( ipiv( i ).GT.0 .AND. a( i, i ).EQ.zero )
254  $ RETURN
255  END DO
256  END IF
257 *
258 * Estimate the 1-norm of the inverse.
259 *
260  kase = 0
261  30 CONTINUE
262  CALL clacn2( n, work( n+1 ), work, ainvnm, kase, isave )
263  IF( kase.NE.0 ) THEN
264 *
265 * Multiply by inv(L*D*L**H) or inv(U*D*U**H).
266 *
267  CALL chetrs_3( uplo, n, 1, a, lda, e, ipiv, work, n, info )
268  GO TO 30
269  END IF
270 *
271 * Compute the estimate of the reciprocal condition number.
272 *
273  IF( ainvnm.NE.zero )
274  $ rcond = ( one / ainvnm ) / anorm
275 *
276  RETURN
277 *
278 * End of CHECON_3
279 *
280  END
chetrs_3
subroutine chetrs_3(UPLO, N, NRHS, A, LDA, E, IPIV, B, LDB, INFO)
CHETRS_3
Definition: chetrs_3.f:167
checon_3
subroutine checon_3(UPLO, N, A, LDA, E, IPIV, ANORM, RCOND, WORK, INFO)
CHECON_3
Definition: checon_3.f:168
clacn2
subroutine clacn2(N, V, X, EST, KASE, ISAVE)
CLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
Definition: clacn2.f:135
xerbla
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62