LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zgecon()

subroutine zgecon ( character  norm,
integer  n,
complex*16, dimension( lda, * )  a,
integer  lda,
double precision  anorm,
double precision  rcond,
complex*16, dimension( * )  work,
double precision, dimension( * )  rwork,
integer  info 
)

ZGECON

Download ZGECON + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 ZGECON estimates the reciprocal of the condition number of a general
 complex matrix A, in either the 1-norm or the infinity-norm, using
 the LU factorization computed by ZGETRF.

 An estimate is obtained for norm(inv(A)), and the reciprocal of the
 condition number is computed as
    RCOND = 1 / ( norm(A) * norm(inv(A)) ).
Parameters
[in]NORM
          NORM is CHARACTER*1
          Specifies whether the 1-norm condition number or the
          infinity-norm condition number is required:
          = '1' or 'O':  1-norm;
          = 'I':         Infinity-norm.
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in]A
          A is COMPLEX*16 array, dimension (LDA,N)
          The factors L and U from the factorization A = P*L*U
          as computed by ZGETRF.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[in]ANORM
          ANORM is DOUBLE PRECISION
          If NORM = '1' or 'O', the 1-norm of the original matrix A.
          If NORM = 'I', the infinity-norm of the original matrix A.
[out]RCOND
          RCOND is DOUBLE PRECISION
          The reciprocal of the condition number of the matrix A,
          computed as RCOND = 1/(norm(A) * norm(inv(A))).
[out]WORK
          WORK is COMPLEX*16 array, dimension (2*N)
[out]RWORK
          RWORK is DOUBLE PRECISION array, dimension (2*N)
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -i, the i-th argument had an illegal value.
                NaNs are illegal values for ANORM, and they propagate to
                the output parameter RCOND.
                Infinity is illegal for ANORM, and it propagates to the output
                parameter RCOND as 0.
          = 1:  if RCOND = NaN, or
                   RCOND = Inf, or
                   the computed norm of the inverse of A is 0.
                In the latter, RCOND = 0 is returned.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 130 of file zgecon.f.

132*
133* -- LAPACK computational routine --
134* -- LAPACK is a software package provided by Univ. of Tennessee, --
135* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
136*
137* .. Scalar Arguments ..
138 CHARACTER NORM
139 INTEGER INFO, LDA, N
140 DOUBLE PRECISION ANORM, RCOND
141* ..
142* .. Array Arguments ..
143 DOUBLE PRECISION RWORK( * )
144 COMPLEX*16 A( LDA, * ), WORK( * )
145* ..
146*
147* =====================================================================
148*
149* .. Parameters ..
150 DOUBLE PRECISION ONE, ZERO
151 parameter( one = 1.0d+0, zero = 0.0d+0 )
152* ..
153* .. Local Scalars ..
154 LOGICAL ONENRM
155 CHARACTER NORMIN
156 INTEGER IX, KASE, KASE1
157 DOUBLE PRECISION AINVNM, SCALE, SL, SMLNUM, SU, HUGEVAL
158 COMPLEX*16 ZDUM
159* ..
160* .. Local Arrays ..
161 INTEGER ISAVE( 3 )
162* ..
163* .. External Functions ..
164 LOGICAL LSAME, DISNAN
165 INTEGER IZAMAX
166 DOUBLE PRECISION DLAMCH
167 EXTERNAL lsame, izamax, dlamch, disnan
168* ..
169* .. External Subroutines ..
170 EXTERNAL xerbla, zdrscl, zlacn2, zlatrs
171* ..
172* .. Intrinsic Functions ..
173 INTRINSIC abs, dble, dimag, max
174* ..
175* .. Statement Functions ..
176 DOUBLE PRECISION CABS1
177* ..
178* .. Statement Function definitions ..
179 cabs1( zdum ) = abs( dble( zdum ) ) + abs( dimag( zdum ) )
180* ..
181* .. Executable Statements ..
182*
183 hugeval = dlamch( 'Overflow' )
184*
185* Test the input parameters.
186*
187 info = 0
188 onenrm = norm.EQ.'1' .OR. lsame( norm, 'O' )
189 IF( .NOT.onenrm .AND. .NOT.lsame( norm, 'I' ) ) THEN
190 info = -1
191 ELSE IF( n.LT.0 ) THEN
192 info = -2
193 ELSE IF( lda.LT.max( 1, n ) ) THEN
194 info = -4
195 ELSE IF( anorm.LT.zero ) THEN
196 info = -5
197 END IF
198 IF( info.NE.0 ) THEN
199 CALL xerbla( 'ZGECON', -info )
200 RETURN
201 END IF
202*
203* Quick return if possible
204*
205 rcond = zero
206 IF( n.EQ.0 ) THEN
207 rcond = one
208 RETURN
209 ELSE IF( anorm.EQ.zero ) THEN
210 RETURN
211 ELSE IF( disnan( anorm ) ) THEN
212 rcond = anorm
213 info = -5
214 RETURN
215 ELSE IF( anorm.GT.hugeval ) THEN
216 info = -5
217 RETURN
218 END IF
219*
220 smlnum = dlamch( 'Safe minimum' )
221*
222* Estimate the norm of inv(A).
223*
224 ainvnm = zero
225 normin = 'N'
226 IF( onenrm ) THEN
227 kase1 = 1
228 ELSE
229 kase1 = 2
230 END IF
231 kase = 0
232 10 CONTINUE
233 CALL zlacn2( n, work( n+1 ), work, ainvnm, kase, isave )
234 IF( kase.NE.0 ) THEN
235 IF( kase.EQ.kase1 ) THEN
236*
237* Multiply by inv(L).
238*
239 CALL zlatrs( 'Lower', 'No transpose', 'Unit', normin, n, a,
240 $ lda, work, sl, rwork, info )
241*
242* Multiply by inv(U).
243*
244 CALL zlatrs( 'Upper', 'No transpose', 'Non-unit', normin, n,
245 $ a, lda, work, su, rwork( n+1 ), info )
246 ELSE
247*
248* Multiply by inv(U**H).
249*
250 CALL zlatrs( 'Upper', 'Conjugate transpose', 'Non-unit',
251 $ normin, n, a, lda, work, su, rwork( n+1 ),
252 $ info )
253*
254* Multiply by inv(L**H).
255*
256 CALL zlatrs( 'Lower', 'Conjugate transpose', 'Unit', normin,
257 $ n, a, lda, work, sl, rwork, info )
258 END IF
259*
260* Divide X by 1/(SL*SU) if doing so will not cause overflow.
261*
262 scale = sl*su
263 normin = 'Y'
264 IF( scale.NE.one ) THEN
265 ix = izamax( n, work, 1 )
266 IF( scale.LT.cabs1( work( ix ) )*smlnum .OR. scale.EQ.zero )
267 $ GO TO 20
268 CALL zdrscl( n, scale, work, 1 )
269 END IF
270 GO TO 10
271 END IF
272*
273* Compute the estimate of the reciprocal condition number.
274*
275 IF( ainvnm.NE.zero ) THEN
276 rcond = ( one / ainvnm ) / anorm
277 ELSE
278 info = 1
279 RETURN
280 END IF
281*
282* Check for NaNs and Infs
283*
284 IF( disnan( rcond ) .OR. rcond.GT.hugeval )
285 $ info = 1
286*
287 20 CONTINUE
288 RETURN
289*
290* End of ZGECON
291*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function izamax(n, zx, incx)
IZAMAX
Definition izamax.f:71
logical function disnan(din)
DISNAN tests input for NaN.
Definition disnan.f:59
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:133
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
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:239
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine zdrscl(n, sa, sx, incx)
ZDRSCL multiplies a vector by the reciprocal of a real scalar.
Definition zdrscl.f:84
Here is the call graph for this function:
Here is the caller graph for this function: