226 SUBROUTINE sptsvx( FACT, N, NRHS, D, E, DF, EF, B, LDB, X, LDX,
227 $ RCOND, FERR, BERR, WORK, INFO )
235 INTEGER INFO, LDB, LDX, N, NRHS
239 REAL B( LDB, * ), BERR( * ), D( * ), DF( * ),
240 $ e( * ), ef( * ), ferr( * ), work( * ),
248 parameter( zero = 0.0e+0 )
257 EXTERNAL lsame, slamch, slanst
271 nofact = lsame( fact,
'N' )
272 IF( .NOT.nofact .AND. .NOT.lsame( fact,
'F' ) )
THEN
274 ELSE IF( n.LT.0 )
THEN
276 ELSE IF( nrhs.LT.0 )
THEN
278 ELSE IF( ldb.LT.max( 1, n ) )
THEN
280 ELSE IF( ldx.LT.max( 1, n ) )
THEN
284 CALL xerbla(
'SPTSVX', -info )
292 CALL scopy( n, d, 1, df, 1 )
294 $
CALL scopy( n-1, e, 1, ef, 1 )
295 CALL spttrf( n, df, ef, info )
307 anorm = slanst(
'1', n, d, e )
311 CALL sptcon( n, df, ef, anorm, rcond, work, info )
315 CALL slacpy(
'Full', n, nrhs, b, ldb, x, ldx )
316 CALL spttrs( n, nrhs, df, ef, x, ldx, info )
321 CALL sptrfs( n, nrhs, d, e, df, ef, b, ldb, x, ldx, ferr, berr,
326 IF( rcond.LT.slamch(
'Epsilon' ) )
subroutine xerbla(srname, info)
subroutine scopy(n, sx, incx, sy, incy)
SCOPY
subroutine slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
subroutine sptcon(n, d, e, anorm, rcond, work, info)
SPTCON
subroutine sptrfs(n, nrhs, d, e, df, ef, b, ldb, x, ldx, ferr, berr, work, info)
SPTRFS
subroutine sptsvx(fact, n, nrhs, d, e, df, ef, b, ldb, x, ldx, rcond, ferr, berr, work, info)
SPTSVX computes the solution to system of linear equations A * X = B for PT matrices
subroutine spttrf(n, d, e, info)
SPTTRF
subroutine spttrs(n, nrhs, d, e, b, ldb, info)
SPTTRS