133 SUBROUTINE ctrcon( NORM, UPLO, DIAG, N, A, LDA, RCOND, WORK,
141 CHARACTER DIAG, NORM, UPLO
147 COMPLEX A( LDA, * ), WORK( * )
154 parameter( one = 1.0e+0, zero = 0.0e+0 )
157 LOGICAL NOUNIT, ONENRM, UPPER
159 INTEGER IX, KASE, KASE1
160 REAL AINVNM, ANORM, SCALE, SMLNUM, XNORM
170 EXTERNAL lsame, icamax, clantr, slamch
176 INTRINSIC abs, aimag, max, real
182 cabs1( zdum ) = abs( real( zdum ) ) + abs( aimag( zdum ) )
189 upper = lsame( uplo,
'U' )
190 onenrm = norm.EQ.
'1' .OR. lsame( norm,
'O' )
191 nounit = lsame( diag,
'N' )
193 IF( .NOT.onenrm .AND. .NOT.lsame( norm,
'I' ) )
THEN
195 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo,
'L' ) )
THEN
197 ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag,
'U' ) )
THEN
199 ELSE IF( n.LT.0 )
THEN
201 ELSE IF( lda.LT.max( 1, n ) )
THEN
205 CALL xerbla(
'CTRCON', -info )
217 smlnum = slamch(
'Safe minimum' )*real( max( 1, n ) )
221 anorm = clantr( norm, uplo, diag, n, n, a, lda, rwork )
225 IF( anorm.GT.zero )
THEN
238 CALL clacn2( n, work( n+1 ), work, ainvnm, kase, isave )
240 IF( kase.EQ.kase1 )
THEN
244 CALL clatrs( uplo,
'No transpose', diag, normin, n, a,
245 $ lda, work, scale, rwork, info )
250 CALL clatrs( uplo,
'Conjugate transpose', diag,
252 $ n, a, lda, work, scale, rwork, info )
258 IF( scale.NE.one )
THEN
259 ix = icamax( n, work, 1 )
260 xnorm = cabs1( work( ix ) )
261 IF( scale.LT.xnorm*smlnum .OR. scale.EQ.zero )
263 CALL csrscl( n, scale, work, 1 )
271 $ rcond = ( one / anorm ) / ainvnm
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.
subroutine ctrcon(norm, uplo, diag, n, a, lda, rcond, work, rwork, info)
CTRCON