LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 126 of file zgecon.f.

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 *
subroutine zdrscl(N, SA, SX, INCX)
ZDRSCL multiplies a vector by the reciprocal of a real scalar.
Definition: zdrscl.f:86
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:65
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
integer function izamax(N, ZX, INCX)
IZAMAX
Definition: izamax.f:53
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
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: