LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zgecon.f
Go to the documentation of this file.
1 *> \brief \b ZGECON
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZGECON + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgecon.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgecon.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgecon.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
22 * INFO )
23 *
24 * .. Scalar Arguments ..
25 * CHARACTER NORM
26 * INTEGER INFO, LDA, N
27 * DOUBLE PRECISION ANORM, RCOND
28 * ..
29 * .. Array Arguments ..
30 * DOUBLE PRECISION RWORK( * )
31 * COMPLEX*16 A( LDA, * ), WORK( * )
32 * ..
33 *
34 *
35 *> \par Purpose:
36 * =============
37 *>
38 *> \verbatim
39 *>
40 *> ZGECON estimates the reciprocal of the condition number of a general
41 *> complex matrix A, in either the 1-norm or the infinity-norm, using
42 *> the LU factorization computed by ZGETRF.
43 *>
44 *> An estimate is obtained for norm(inv(A)), and the reciprocal of the
45 *> condition number is computed as
46 *> RCOND = 1 / ( norm(A) * norm(inv(A)) ).
47 *> \endverbatim
48 *
49 * Arguments:
50 * ==========
51 *
52 *> \param[in] NORM
53 *> \verbatim
54 *> NORM is CHARACTER*1
55 *> Specifies whether the 1-norm condition number or the
56 *> infinity-norm condition number is required:
57 *> = '1' or 'O': 1-norm;
58 *> = 'I': Infinity-norm.
59 *> \endverbatim
60 *>
61 *> \param[in] N
62 *> \verbatim
63 *> N is INTEGER
64 *> The order of the matrix A. N >= 0.
65 *> \endverbatim
66 *>
67 *> \param[in] A
68 *> \verbatim
69 *> A is COMPLEX*16 array, dimension (LDA,N)
70 *> The factors L and U from the factorization A = P*L*U
71 *> as computed by ZGETRF.
72 *> \endverbatim
73 *>
74 *> \param[in] LDA
75 *> \verbatim
76 *> LDA is INTEGER
77 *> The leading dimension of the array A. LDA >= max(1,N).
78 *> \endverbatim
79 *>
80 *> \param[in] ANORM
81 *> \verbatim
82 *> ANORM is DOUBLE PRECISION
83 *> If NORM = '1' or 'O', the 1-norm of the original matrix A.
84 *> If NORM = 'I', the infinity-norm of the original matrix A.
85 *> \endverbatim
86 *>
87 *> \param[out] RCOND
88 *> \verbatim
89 *> RCOND is DOUBLE PRECISION
90 *> The reciprocal of the condition number of the matrix A,
91 *> computed as RCOND = 1/(norm(A) * norm(inv(A))).
92 *> \endverbatim
93 *>
94 *> \param[out] WORK
95 *> \verbatim
96 *> WORK is COMPLEX*16 array, dimension (2*N)
97 *> \endverbatim
98 *>
99 *> \param[out] RWORK
100 *> \verbatim
101 *> RWORK is DOUBLE PRECISION array, dimension (2*N)
102 *> \endverbatim
103 *>
104 *> \param[out] INFO
105 *> \verbatim
106 *> INFO is INTEGER
107 *> = 0: successful exit
108 *> < 0: if INFO = -i, the i-th argument had an illegal value
109 *> \endverbatim
110 *
111 * Authors:
112 * ========
113 *
114 *> \author Univ. of Tennessee
115 *> \author Univ. of California Berkeley
116 *> \author Univ. of Colorado Denver
117 *> \author NAG Ltd.
118 *
119 *> \date November 2011
120 *
121 *> \ingroup complex16GEcomputational
122 *
123 * =====================================================================
124  SUBROUTINE zgecon( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
125  $ info )
126 *
127 * -- LAPACK computational routine (version 3.4.0) --
128 * -- LAPACK is a software package provided by Univ. of Tennessee, --
129 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
130 * November 2011
131 *
132 * .. Scalar Arguments ..
133  CHARACTER NORM
134  INTEGER INFO, LDA, N
135  DOUBLE PRECISION ANORM, RCOND
136 * ..
137 * .. Array Arguments ..
138  DOUBLE PRECISION RWORK( * )
139  COMPLEX*16 A( lda, * ), WORK( * )
140 * ..
141 *
142 * =====================================================================
143 *
144 * .. Parameters ..
145  DOUBLE PRECISION ONE, ZERO
146  parameter ( one = 1.0d+0, zero = 0.0d+0 )
147 * ..
148 * .. Local Scalars ..
149  LOGICAL ONENRM
150  CHARACTER NORMIN
151  INTEGER IX, KASE, KASE1
152  DOUBLE PRECISION AINVNM, SCALE, SL, SMLNUM, SU
153  COMPLEX*16 ZDUM
154 * ..
155 * .. Local Arrays ..
156  INTEGER ISAVE( 3 )
157 * ..
158 * .. External Functions ..
159  LOGICAL LSAME
160  INTEGER IZAMAX
161  DOUBLE PRECISION DLAMCH
162  EXTERNAL lsame, izamax, dlamch
163 * ..
164 * .. External Subroutines ..
165  EXTERNAL xerbla, zdrscl, zlacn2, zlatrs
166 * ..
167 * .. Intrinsic Functions ..
168  INTRINSIC abs, dble, dimag, max
169 * ..
170 * .. Statement Functions ..
171  DOUBLE PRECISION CABS1
172 * ..
173 * .. Statement Function definitions ..
174  cabs1( zdum ) = abs( dble( zdum ) ) + abs( dimag( zdum ) )
175 * ..
176 * .. Executable Statements ..
177 *
178 * Test the input parameters.
179 *
180  info = 0
181  onenrm = norm.EQ.'1' .OR. lsame( norm, 'O' )
182  IF( .NOT.onenrm .AND. .NOT.lsame( norm, 'I' ) ) THEN
183  info = -1
184  ELSE IF( n.LT.0 ) THEN
185  info = -2
186  ELSE IF( lda.LT.max( 1, n ) ) THEN
187  info = -4
188  ELSE IF( anorm.LT.zero ) THEN
189  info = -5
190  END IF
191  IF( info.NE.0 ) THEN
192  CALL xerbla( 'ZGECON', -info )
193  RETURN
194  END IF
195 *
196 * Quick return if possible
197 *
198  rcond = zero
199  IF( n.EQ.0 ) THEN
200  rcond = one
201  RETURN
202  ELSE IF( anorm.EQ.zero ) THEN
203  RETURN
204  END IF
205 *
206  smlnum = dlamch( 'Safe minimum' )
207 *
208 * Estimate the norm of inv(A).
209 *
210  ainvnm = zero
211  normin = 'N'
212  IF( onenrm ) THEN
213  kase1 = 1
214  ELSE
215  kase1 = 2
216  END IF
217  kase = 0
218  10 CONTINUE
219  CALL zlacn2( n, work( n+1 ), work, ainvnm, kase, isave )
220  IF( kase.NE.0 ) THEN
221  IF( kase.EQ.kase1 ) THEN
222 *
223 * Multiply by inv(L).
224 *
225  CALL zlatrs( 'Lower', 'No transpose', 'Unit', normin, n, a,
226  $ lda, work, sl, rwork, info )
227 *
228 * Multiply by inv(U).
229 *
230  CALL zlatrs( 'Upper', 'No transpose', 'Non-unit', normin, n,
231  $ a, lda, work, su, rwork( n+1 ), info )
232  ELSE
233 *
234 * Multiply by inv(U**H).
235 *
236  CALL zlatrs( 'Upper', 'Conjugate transpose', 'Non-unit',
237  $ normin, n, a, lda, work, su, rwork( n+1 ),
238  $ info )
239 *
240 * Multiply by inv(L**H).
241 *
242  CALL zlatrs( 'Lower', 'Conjugate transpose', 'Unit', normin,
243  $ n, a, lda, work, sl, rwork, info )
244  END IF
245 *
246 * Divide X by 1/(SL*SU) if doing so will not cause overflow.
247 *
248  scale = sl*su
249  normin = 'Y'
250  IF( scale.NE.one ) THEN
251  ix = izamax( n, work, 1 )
252  IF( scale.LT.cabs1( work( ix ) )*smlnum .OR. scale.EQ.zero )
253  $ GO TO 20
254  CALL zdrscl( n, scale, work, 1 )
255  END IF
256  GO TO 10
257  END IF
258 *
259 * Compute the estimate of the reciprocal condition number.
260 *
261  IF( ainvnm.NE.zero )
262  $ rcond = ( one / ainvnm ) / anorm
263 *
264  20 CONTINUE
265  RETURN
266 *
267 * End of ZGECON
268 *
269  END
subroutine zdrscl(N, SA, SX, INCX)
ZDRSCL multiplies a vector by the reciprocal of a real scalar.
Definition: zdrscl.f:86
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine zlacn2(N, V, X, EST, KASE, ISAVE)
ZLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
Definition: zlacn2.f:135
subroutine zgecon(NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK, INFO)
ZGECON
Definition: zgecon.f:126
subroutine zlatrs(UPLO, TRANS, DIAG, NORMIN, N, A, LDA, X, SCALE, CNORM, INFO)
ZLATRS solves a triangular system of equations with the scale factor set to prevent overflow...
Definition: zlatrs.f:241