122 SUBROUTINE cgecon( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
136 COMPLEX A( LDA, * ), ( * )
143 parameter( one = 1.0e+0, zero = 0.0e+0 )
148 INTEGER IX, KASE, KASE1
149 REAL AINVNM, SCALE, SL, SMLNUM, SU
159 EXTERNAL lsame, icamax, slamch
165 INTRINSIC abs, aimag,
max, real
171 cabs1( zdum ) = abs( real( zdum ) ) + abs( aimag( zdum ) )
178 onenrm = norm.EQ.
'1' .OR. lsame( norm,
'O' )
179 IF( .NOT.onenrm .AND. .NOT.lsame( norm,
'I' ) )
THEN
181 ELSE IF( n.LT.0 )
THEN
183 ELSE IF( lda.LT.
max( 1, n ) )
THEN
185 ELSE IF( anorm.LT.zero )
THEN
199.EQ.
ELSE IF( ANORMZERO ) THEN
203 SMLNUM = SLAMCH( 'safe minimum
' )
216 CALL CLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
218.EQ.
IF( KASEKASE1 ) THEN
222 CALL CLATRS( 'lower
', 'no transpose
', 'unit
', NORMIN, N, A,
223 $ LDA, WORK, SL, RWORK, INFO )
227 CALL CLATRS( 'upper
', 'no transpose
', 'non-unit
', NORMIN, N,
228 $ A, LDA, WORK, SU, RWORK( N+1 ), INFO )
233 CALL CLATRS( 'upper
', 'conjugate transpose
', 'non-unit
',
234 $ NORMIN, N, A, LDA, WORK, SU, RWORK( N+1 ),
239 CALL CLATRS( 'lower
', 'conjugate transpose
', 'unit
', NORMIN,
240 $ N, A, LDA, WORK, SL, RWORK, INFO )
247.NE.
IF( SCALEONE ) THEN
248 IX = ICAMAX( N, WORK, 1 )
249.LT..OR..EQ.
IF( SCALECABS1( WORK( IX ) )*SMLNUM SCALEZERO )
251 CALL CSRSCL( N, SCALE, WORK, 1 )
259 $ RCOND = ( ONE / AINVNM ) / ANORM
subroutine xerbla(srname, info)
XERBLA
subroutine cgecon(norm, n, a, lda, anorm, rcond, work, rwork, info)
CGECON
subroutine csrscl(n, sa, sx, incx)
CSRSCL multiplies a vector by the reciprocal of a real scalar.
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 clacn2(n, v, x, est, kase, isave)
CLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...