135 SUBROUTINE dtrcon( NORM, UPLO, DIAG, N, A, LDA, RCOND, WORK,
143 CHARACTER DIAG, NORM, UPLO
145 DOUBLE PRECISION RCOND
149 DOUBLE PRECISION A( LDA, * ), WORK( * )
155 DOUBLE PRECISION ONE, ZERO
156 parameter( one = 1.0d+0, zero = 0.0d+0 )
159 LOGICAL NOUNIT, ONENRM, UPPER
161 INTEGER IX, KASE, KASE1
162 DOUBLE PRECISION AINVNM, ANORM, SCALE, SMLNUM, XNORM
170 DOUBLE PRECISION DLAMCH, DLANTR
171 EXTERNAL lsame, idamax, dlamch, dlantr
177 INTRINSIC abs, dble, max
184 upper = lsame( uplo,
'U' )
185 onenrm = norm.EQ.
'1' .OR. lsame( norm,
'O' )
186 nounit = lsame( diag,
'N' )
188 IF( .NOT.onenrm .AND. .NOT.lsame( norm,
'I' ) )
THEN
190 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo,
'L' ) )
THEN
192 ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag,
'U' ) )
THEN
194 ELSE IF( n.LT.0 )
THEN
196 ELSE IF( lda.LT.max( 1, n ) )
THEN
200 CALL xerbla(
'DTRCON', -info )
212 smlnum = dlamch(
'Safe minimum' )*dble( max( 1, n ) )
216 anorm = dlantr( norm, uplo, diag, n, n, a, lda, work )
220 IF( anorm.GT.zero )
THEN
233 CALL dlacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
235 IF( kase.EQ.kase1 )
THEN
239 CALL dlatrs( uplo,
'No transpose', diag, normin, n, a,
240 $ lda, work, scale, work( 2*n+1 ), info )
245 CALL dlatrs( uplo,
'Transpose', diag, normin, n, a, lda,
246 $ work, scale, work( 2*n+1 ), info )
252 IF( scale.NE.one )
THEN
253 ix = idamax( n, work, 1 )
254 xnorm = abs( work( ix ) )
255 IF( scale.LT.xnorm*smlnum .OR. scale.EQ.zero )
257 CALL drscl( n, scale, work, 1 )
265 $ rcond = ( one / anorm ) / ainvnm
subroutine xerbla(srname, info)
subroutine dlacn2(n, v, x, isgn, est, kase, isave)
DLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
subroutine dlatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)
DLATRS solves a triangular system of equations with the scale factor set to prevent overflow.
subroutine drscl(n, sa, sx, incx)
DRSCL multiplies a vector by the reciprocal of a real scalar.
subroutine dtrcon(norm, uplo, diag, n, a, lda, rcond, work, iwork, info)
DTRCON