228 SUBROUTINE sptsvx( FACT, N, NRHS, D, E, DF, EF, B, LDB, X, LDX,
229 $ rcond, ferr, berr, work, info )
238 INTEGER INFO, LDB, LDX, N, NRHS
242 REAL B( ldb, * ), BERR( * ), D( * ), DF( * ),
243 $ e( * ), ef( * ), ferr( * ), work( * ),
251 parameter ( zero = 0.0e+0 )
260 EXTERNAL lsame, slamch, slanst
274 nofact = lsame( fact,
'N' )
275 IF( .NOT.nofact .AND. .NOT.lsame( fact,
'F' ) )
THEN
277 ELSE IF( n.LT.0 )
THEN
279 ELSE IF( nrhs.LT.0 )
THEN
281 ELSE IF( ldb.LT.max( 1, n ) )
THEN
283 ELSE IF( ldx.LT.max( 1, n ) )
THEN
287 CALL xerbla(
'SPTSVX', -info )
295 CALL scopy( n, d, 1, df, 1 )
297 $
CALL scopy( n-1, e, 1, ef, 1 )
298 CALL spttrf( n, df, ef, info )
310 anorm = slanst(
'1', n, d, e )
314 CALL sptcon( n, df, ef, anorm, rcond, work, info )
318 CALL slacpy(
'Full', n, nrhs, b, ldb, x, ldx )
319 CALL spttrs( n, nrhs, df, ef, x, ldx, info )
324 CALL sptrfs( n, nrhs, d, e, df, ef, b, ldb, x, ldx, ferr, berr,
329 IF( rcond.LT.slamch(
'Epsilon' ) )
subroutine spttrf(N, D, E, INFO)
SPTTRF
subroutine sptcon(N, D, E, ANORM, RCOND, WORK, INFO)
SPTCON
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 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 sptrfs(N, NRHS, D, E, DF, EF, B, LDB, X, LDX, FERR, BERR, WORK, INFO)
SPTRFS
subroutine spttrs(N, NRHS, D, E, B, LDB, INFO)
SPTTRS
subroutine scopy(N, SX, INCX, SY, INCY)
SCOPY