128 SUBROUTINE dtpcon( NORM, UPLO, DIAG, N, AP, RCOND, WORK, IWORK,
136 CHARACTER DIAG, NORM, UPLO
138 DOUBLE PRECISION RCOND
142 DOUBLE PRECISION AP( * ), WORK( * )
148 DOUBLE PRECISION ONE, ZERO
149 parameter( one = 1.0d+0, zero = 0.0d+0 )
152 LOGICAL NOUNIT, ONENRM, UPPER
154 INTEGER IX, KASE, KASE1
155 DOUBLE PRECISION AINVNM, ANORM, SCALE, SMLNUM, XNORM
163 DOUBLE PRECISION DLAMCH, DLANTP
164 EXTERNAL lsame, idamax, dlamch, dlantp
170 INTRINSIC abs, dble, max
177 upper = lsame( uplo,
'U' )
178 onenrm = norm.EQ.
'1' .OR. lsame( norm,
'O' )
179 nounit = lsame( diag,
'N' )
181 IF( .NOT.onenrm .AND. .NOT.lsame( norm,
'I' ) )
THEN
183 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo,
'L' ) )
THEN
185 ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag,
'U' ) )
THEN
187 ELSE IF( n.LT.0 )
THEN
191 CALL xerbla(
'DTPCON', -info )
203 smlnum = dlamch(
'Safe minimum' )*dble( max( 1, n ) )
207 anorm = dlantp( norm, uplo, diag, n, ap, work )
211 IF( anorm.GT.zero )
THEN
224 CALL dlacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
226 IF( kase.EQ.kase1 )
THEN
230 CALL dlatps( uplo,
'No transpose', diag, normin, n, ap,
231 $ work, scale, work( 2*n+1 ), info )
236 CALL dlatps( uplo,
'Transpose', diag, normin, n, ap,
237 $ work, scale, work( 2*n+1 ), info )
243 IF( scale.NE.one )
THEN
244 ix = idamax( n, work, 1 )
245 xnorm = abs( work( ix ) )
246 IF( scale.LT.xnorm*smlnum .OR. scale.EQ.zero )
248 CALL drscl( n, scale, work, 1 )
256 $ 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 dlatps(uplo, trans, diag, normin, n, ap, x, scale, cnorm, info)
DLATPS solves a triangular system of equations with the matrix held in packed storage.
subroutine drscl(n, sa, sx, incx)
DRSCL multiplies a vector by the reciprocal of a real scalar.
subroutine dtpcon(norm, uplo, diag, n, ap, rcond, work, iwork, info)
DTPCON