135 SUBROUTINE ctrcon( NORM, UPLO, DIAG, N, A, LDA, RCOND, WORK,
143 CHARACTER DIAG, NORM, UPLO
149 COMPLEX A( LDA, * ), WORK( * )
156 parameter( one = 1.0e+0, zero = 0.0e+0 )
159 LOGICAL NOUNIT, ONENRM, UPPER
161 INTEGER IX, KASE, KASE1
162 REAL AINVNM, ANORM, SCALE, SMLNUM, XNORM
172 EXTERNAL lsame, icamax, clantr, slamch
178 INTRINSIC abs, aimag, max, real
184 cabs1( zdum ) = abs( real( zdum ) ) + abs( aimag( zdum ) )
191 upper = lsame( uplo,
'U' )
192 onenrm = norm.EQ.
'1' .OR. lsame( norm,
'O' )
193 nounit = lsame( diag,
'N' )
195 IF( .NOT.onenrm .AND. .NOT.lsame( norm,
'I' ) )
THEN
197 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo,
'L' ) )
THEN
199 ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag,
'U' ) )
THEN
201 ELSE IF( n.LT.0 )
THEN
203 ELSE IF( lda.LT.max( 1, n ) )
THEN
207 CALL xerbla(
'CTRCON', -info )
219 smlnum = slamch(
'Safe minimum' )*real( max( 1, n ) )
223 anorm = clantr( norm, uplo, diag, n, n, a, lda, rwork )
227 IF( anorm.GT.zero )
THEN
240 CALL clacn2( n, work( n+1 ), work, ainvnm, kase, isave )
242 IF( kase.EQ.kase1 )
THEN
246 CALL clatrs( uplo,
'No transpose', diag, normin, n, a,
247 $ lda, work, scale, rwork, info )
252 CALL clatrs( uplo,
'Conjugate transpose', diag, normin,
253 $ n, a, lda, work, scale, rwork, info )
259 IF( scale.NE.one )
THEN
260 ix = icamax( n, work, 1 )
261 xnorm = cabs1( work( ix ) )
262 IF( scale.LT.xnorm*smlnum .OR. scale.EQ.zero )
264 CALL csrscl( n, scale, work, 1 )
272 $ rcond = ( one / anorm ) / ainvnm
subroutine xerbla(srname, info)
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