128 SUBROUTINE stpcon( NORM, UPLO, DIAG, N, AP, RCOND, WORK, IWORK,
136 CHARACTER DIAG, NORM, UPLO
142 REAL AP( * ), WORK( * )
149 parameter( one = 1.0e+0, zero = 0.0e+0 )
152 LOGICAL NOUNIT, ONENRM, UPPER
154 INTEGER IX, KASE, KASE1
155 REAL AINVNM, ANORM, SCALE, SMLNUM, XNORM
164 EXTERNAL lsame, isamax, slamch,
slantp
170 INTRINSIC abs,
max, real
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.NOT..AND..NOT.
ELSE IF( NOUNIT LSAME( DIAG, 'u
' ) ) THEN
187.LT.
ELSE IF( N0 ) THEN
191 CALL XERBLA( 'stpcon', -INFO )
203 SMLNUM = SLAMCH( 'safe minimum
' )*REAL( MAX( 1, N ) )
207 ANORM = SLANTP( NORM, UPLO, DIAG, N, AP, WORK )
211.GT.
IF( ANORMZERO ) THEN
224 CALL SLACN2( N, WORK( N+1 ), WORK, IWORK, AINVNM, KASE, ISAVE )
226.EQ.
IF( KASEKASE1 ) THEN
230 CALL SLATPS( UPLO, 'no transpose
', DIAG, NORMIN, N, AP,
231 $ WORK, SCALE, WORK( 2*N+1 ), INFO )
236 CALL SLATPS( UPLO, 'transpose
', DIAG, NORMIN, N, AP,
237 $ WORK, SCALE, WORK( 2*N+1 ), INFO )
243.NE.
IF( SCALEONE ) THEN
244 IX = ISAMAX( N, WORK, 1 )
245 XNORM = ABS( WORK( IX ) )
246.LT..OR..EQ.
IF( SCALEXNORM*SMLNUM SCALEZERO )
248 CALL SRSCL( N, SCALE, WORK, 1 )
256 $ RCOND = ( ONE / ANORM ) / AINVNM
subroutine xerbla(srname, info)
XERBLA
subroutine srscl(n, sa, sx, incx)
SRSCL multiplies a vector by the reciprocal of a real scalar.
subroutine slatps(uplo, trans, diag, normin, n, ap, x, scale, cnorm, info)
SLATPS solves a triangular system of equations with the matrix held in packed storage.
real function slantp(norm, uplo, diag, n, ap, work)
SLANTP returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
subroutine slacn2(n, v, x, isgn, est, kase, isave)
SLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
subroutine stpcon(norm, uplo, diag, n, ap, rcond, work, iwork, info)
STPCON