292 SUBROUTINE sgtsvx( FACT, TRANS, N, NRHS, DL, D, DU, DLF, DF, DUF,
293 $ du2, ipiv, b, ldb, x, ldx, rcond, ferr, berr,
294 $ work, iwork, info )
302 CHARACTER FACT, TRANS
303 INTEGER INFO, LDB, LDX, N, NRHS
307 INTEGER IPIV( * ), IWORK( * )
308 REAL B( ldb, * ), BERR( * ), D( * ), DF( * ),
309 $ dl( * ), dlf( * ), du( * ), du2( * ), duf( * ),
310 $ ferr( * ), work( * ), x( ldx, * )
317 parameter ( zero = 0.0e+0 )
320 LOGICAL NOFACT, NOTRAN
327 EXTERNAL lsame, slamch, slangt
339 nofact = lsame( fact,
'N' )
340 notran = lsame( trans,
'N' )
341 IF( .NOT.nofact .AND. .NOT.lsame( fact,
'F' ) )
THEN
343 ELSE IF( .NOT.notran .AND. .NOT.lsame( trans,
'T' ) .AND. .NOT.
344 $ lsame( trans,
'C' ) )
THEN
346 ELSE IF( n.LT.0 )
THEN
348 ELSE IF( nrhs.LT.0 )
THEN
350 ELSE IF( ldb.LT.max( 1, n ) )
THEN
352 ELSE IF( ldx.LT.max( 1, n ) )
THEN
356 CALL xerbla(
'SGTSVX', -info )
364 CALL scopy( n, d, 1, df, 1 )
366 CALL scopy( n-1, dl, 1, dlf, 1 )
367 CALL scopy( n-1, du, 1, duf, 1 )
369 CALL sgttrf( n, dlf, df, duf, du2, ipiv, info )
386 anorm = slangt( norm, n, dl, d, du )
390 CALL sgtcon( norm, n, dlf, df, duf, du2, ipiv, anorm, rcond, work,
395 CALL slacpy(
'Full', n, nrhs, b, ldb, x, ldx )
396 CALL sgttrs( trans, n, nrhs, dlf, df, duf, du2, ipiv, x, ldx,
402 CALL sgtrfs( trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv,
403 $ b, ldb, x, ldx, ferr, berr, work, iwork, info )
407 IF( rcond.LT.slamch(
'Epsilon' ) )
subroutine sgtrfs(TRANS, N, NRHS, DL, D, DU, DLF, DF, DUF, DU2, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, IWORK, INFO)
SGTRFS
subroutine sgtcon(NORM, N, DL, D, DU, DU2, IPIV, ANORM, RCOND, WORK, IWORK, INFO)
SGTCON
subroutine sgttrf(N, DL, D, DU, DU2, IPIV, INFO)
SGTTRF
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 sgttrs(TRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB, INFO)
SGTTRS
subroutine scopy(N, SX, INCX, SY, INCY)
SCOPY
subroutine sgtsvx(FACT, TRANS, N, NRHS, DL, D, DU, DLF, DF, DUF, DU2, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO)
SGTSVX computes the solution to system of linear equations A * X = B for GT matrices ...