117 SUBROUTINE sppcon( UPLO, N, AP, ANORM, RCOND, WORK, IWORK, INFO )
130 REAL AP( * ), WORK( * )
137 parameter( one = 1.0e+0, zero = 0.0e+0 )
143 REAL AINVNM, SCALE, SCALEL, SCALEU, SMLNUM
152 EXTERNAL lsame, isamax, slamch
165 upper = lsame( uplo,
'U' )
166 IF( .NOT.upper .AND. .NOT.lsame( uplo,
'L' ) )
THEN
168 ELSE IF( n.LT.0 )
THEN
170 ELSE IF( anorm.LT.zero )
THEN
174 CALL xerbla(
'SPPCON', -info )
184 ELSE IF( anorm.EQ.zero )
THEN
188 smlnum = slamch(
'Safe minimum' )
195 CALL slacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
201 CALL slatps(
'Upper',
'Transpose',
'Non-unit', normin, n,
202 $ ap, work, scalel, work( 2*n+1 ), info )
207 CALL slatps( 'upper
', 'no transpose
', 'non-unit
', NORMIN, N,
208 $ AP, WORK, SCALEU, WORK( 2*N+1 ), INFO )
213 CALL SLATPS( 'lower
', 'no transpose
', 'non-unit
', NORMIN, N,
214 $ AP, WORK, SCALEL, WORK( 2*N+1 ), INFO )
219 CALL SLATPS( 'lower
', 'transpose
', 'non-unit
', NORMIN, N,
220 $ AP, WORK, SCALEU, WORK( 2*N+1 ), INFO )
225 SCALE = SCALEL*SCALEU
226.NE.
IF( SCALEONE ) THEN
227 IX = ISAMAX( N, WORK, 1 )
228.LT..OR..EQ.
IF( SCALEABS( WORK( IX ) )*SMLNUM SCALEZERO )
230 CALL SRSCL( N, SCALE, WORK, 1 )
238 $ RCOND = ( ONE / AINVNM ) / ANORM
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.
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 sppcon(uplo, n, ap, anorm, rcond, work, iwork, info)
SPPCON