277 SUBROUTINE sspsvx( FACT, UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X,
278 $ ldx, rcond, ferr, berr, work, iwork, info )
287 INTEGER INFO, LDB, LDX, N, NRHS
291 INTEGER IPIV( * ), IWORK( * )
292 REAL AFP( * ), AP( * ), B( ldb, * ), BERR( * ),
293 $ ferr( * ), work( * ), x( ldx, * )
300 parameter ( zero = 0.0e+0 )
309 EXTERNAL lsame, slamch, slansp
323 nofact = lsame( fact,
'N' )
324 IF( .NOT.nofact .AND. .NOT.lsame( fact,
'F' ) )
THEN
326 ELSE IF( .NOT.lsame( uplo,
'U' ) .AND. .NOT.lsame( uplo,
'L' ) )
329 ELSE IF( n.LT.0 )
THEN
331 ELSE IF( nrhs.LT.0 )
THEN
333 ELSE IF( ldb.LT.max( 1, n ) )
THEN
335 ELSE IF( ldx.LT.max( 1, n ) )
THEN
339 CALL xerbla(
'SSPSVX', -info )
347 CALL scopy( n*( n+1 ) / 2, ap, 1, afp, 1 )
348 CALL ssptrf( uplo, n, afp, ipiv, info )
360 anorm = slansp(
'I', uplo, n, ap, work )
364 CALL sspcon( uplo, n, afp, ipiv, anorm, rcond, work, iwork, info )
368 CALL slacpy(
'Full', n, nrhs, b, ldb, x, ldx )
369 CALL ssptrs( uplo, n, nrhs, afp, ipiv, x, ldx, info )
374 CALL ssprfs( uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, ferr,
375 $ berr, work, iwork, info )
379 IF( rcond.LT.slamch(
'Epsilon' ) )
subroutine ssptrs(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
SSPTRS
subroutine xerbla(SRNAME, INFO)
XERBLA
subroutine slacpy(UPLO, M, N, A, LDA, B, LDB)
SLACPY copies all or part of one two-dimensional array to another.
subroutine sspsvx(FACT, UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO)
SSPSVX computes the solution to system of linear equations A * X = B for OTHER matrices ...
subroutine ssprfs(UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, IWORK, INFO)
SSPRFS
subroutine ssptrf(UPLO, N, AP, IPIV, INFO)
SSPTRF
subroutine sspcon(UPLO, N, AP, IPIV, ANORM, RCOND, WORK, IWORK, INFO)
SSPCON
subroutine scopy(N, SX, INCX, SY, INCY)
SCOPY