128 SUBROUTINE cgecon( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
142 COMPLEX A( LDA, * ), WORK( * )
149 parameter( one = 1.0e+0, zero = 0.0e+0 )
154 INTEGER IX, KASE, KASE1
155 REAL AINVNM, SCALE, SL, SMLNUM, SU, HUGEVAL
162 LOGICAL LSAME, SISNAN
165 EXTERNAL lsame, icamax, slamch, sisnan
171 INTRINSIC abs, aimag, max, real
177 cabs1( zdum ) = abs( real( zdum ) ) + abs( aimag( zdum ) )
181 hugeval = slamch(
'Overflow' )
186 onenrm = norm.EQ.
'1' .OR. lsame( norm,
'O' )
187 IF( .NOT.onenrm .AND. .NOT.lsame( norm,
'I' ) )
THEN
189 ELSE IF( n.LT.0 )
THEN
191 ELSE IF( lda.LT.max( 1, n ) )
THEN
193 ELSE IF( anorm.LT.zero )
THEN
197 CALL xerbla(
'CGECON', -info )
207 ELSE IF( anorm.EQ.zero )
THEN
209 ELSE IF( sisnan( anorm ) )
THEN
213 ELSE IF( anorm.GT.hugeval )
THEN
218 smlnum = slamch(
'Safe minimum' )
231 CALL clacn2( n, work( n+1 ), work, ainvnm, kase, isave )
233 IF( kase.EQ.kase1 )
THEN
237 CALL clatrs(
'Lower',
'No transpose',
'Unit', normin, n,
239 $ lda, work, sl, rwork, info )
243 CALL clatrs(
'Upper',
'No transpose',
'Non-unit', normin,
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',
258 $ n, a, lda, work, sl, rwork, info )
265 IF( scale.NE.one )
THEN
266 ix = icamax( n, work, 1 )
267 IF( scale.LT.cabs1( work( ix ) )*smlnum .OR. scale.EQ.zero )
269 CALL csrscl( n, scale, work, 1 )
276 IF( ainvnm.NE.zero )
THEN
277 rcond = ( one / ainvnm ) / anorm
285 IF( sisnan( rcond ) .OR. rcond.GT.hugeval )
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.