130 SUBROUTINE cgecon( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
144 COMPLEX A( LDA, * ), WORK( * )
151 parameter( one = 1.0e+0, zero = 0.0e+0 )
156 INTEGER IX, KASE, KASE1
157 REAL AINVNM, SCALE, SL, SMLNUM, SU, HUGEVAL
164 LOGICAL LSAME, SISNAN
167 EXTERNAL lsame, icamax, slamch, sisnan
173 INTRINSIC abs, aimag, max, real
179 cabs1( zdum ) = abs( real( zdum ) ) + abs( aimag( zdum ) )
183 hugeval = slamch(
'Overflow' )
188 onenrm = norm.EQ.
'1' .OR. lsame( norm,
'O' )
189 IF( .NOT.onenrm .AND. .NOT.lsame( norm,
'I' ) )
THEN
191 ELSE IF( n.LT.0 )
THEN
193 ELSE IF( lda.LT.max( 1, n ) )
THEN
195 ELSE IF( anorm.LT.zero )
THEN
199 CALL xerbla(
'CGECON', -info )
209 ELSE IF( anorm.EQ.zero )
THEN
211 ELSE IF( sisnan( anorm ) )
THEN
215 ELSE IF( anorm.GT.hugeval )
THEN
220 smlnum = slamch(
'Safe minimum' )
233 CALL clacn2( n, work( n+1 ), work, ainvnm, kase, isave )
235 IF( kase.EQ.kase1 )
THEN
239 CALL clatrs(
'Lower',
'No transpose',
'Unit', normin, n, a,
240 $ lda, work, sl, rwork, info )
244 CALL clatrs(
'Upper',
'No transpose',
'Non-unit', normin, n,
245 $ a, lda, work, su, rwork( n+1 ), info )
250 CALL clatrs(
'Upper',
'Conjugate transpose',
'Non-unit',
251 $ normin, n, a, lda, work, su, rwork( n+1 ),
256 CALL clatrs(
'Lower',
'Conjugate transpose',
'Unit', normin,
257 $ n, a, lda, work, sl, rwork, info )
264 IF( scale.NE.one )
THEN
265 ix = icamax( n, work, 1 )
266 IF( scale.LT.cabs1( work( ix ) )*smlnum .OR. scale.EQ.zero )
268 CALL csrscl( n, scale, work, 1 )
275 IF( ainvnm.NE.zero )
THEN
276 rcond = ( one / ainvnm ) / anorm
284 IF( sisnan( rcond ) .OR. rcond.GT.hugeval )
subroutine xerbla(srname, info)
subroutine cgecon(norm, n, a, lda, anorm, rcond, work, rwork, info)
CGECON
subroutine clacn2(n, v, x, est, kase, isave)
CLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
subroutine clatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)
CLATRS solves a triangular system of equations with the scale factor set to prevent overflow.
subroutine csrscl(n, sa, sx, incx)
CSRSCL multiplies a vector by the reciprocal of a real scalar.