126 SUBROUTINE dtpcon( NORM, UPLO, DIAG, N, AP, RCOND, WORK, IWORK,
134 CHARACTER DIAG, NORM, UPLO
136 DOUBLE PRECISION RCOND
140 DOUBLE PRECISION AP( * ), WORK( * )
146 DOUBLE PRECISION ONE, ZERO
147 parameter( one = 1.0d+0, zero = 0.0d+0 )
150 LOGICAL NOUNIT, ONENRM, UPPER
152 INTEGER IX, KASE, KASE1
153 DOUBLE PRECISION AINVNM, ANORM, SCALE, SMLNUM, XNORM
161 DOUBLE PRECISION DLAMCH, DLANTP
162 EXTERNAL lsame, idamax, dlamch, dlantp
168 INTRINSIC abs, dble, max
175 upper = lsame( uplo,
'U' )
176 onenrm = norm.EQ.
'1' .OR. lsame( norm,
'O' )
177 nounit = lsame( diag,
'N' )
179 IF( .NOT.onenrm .AND. .NOT.lsame( norm,
'I' ) )
THEN
181 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo,
'L' ) )
THEN
183 ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag,
'U' ) )
THEN
185 ELSE IF( n.LT.0 )
THEN
189 CALL xerbla(
'DTPCON', -info )
201 smlnum = dlamch(
'Safe minimum' )*dble( max( 1, n ) )
205 anorm = dlantp( norm, uplo, diag, n, ap, work )
209 IF( anorm.GT.zero )
THEN
222 CALL dlacn2( n, work( n+1 ), work, iwork, ainvnm, kase,
225 IF( kase.EQ.kase1 )
THEN
229 CALL dlatps( uplo,
'No transpose', diag, normin, n,
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 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