290 SUBROUTINE dgtsvx( FACT, TRANS, N, NRHS, DL, D, DU, DLF, DF, DUF,
291 $ DU2, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR,
292 $ WORK, IWORK, INFO )
299 CHARACTER FACT, TRANS
300 INTEGER INFO, LDB, LDX, N, NRHS
301 DOUBLE PRECISION RCOND
304 INTEGER IPIV( * ), IWORK( * )
305 DOUBLE PRECISION B( LDB, * ), BERR( * ), D( * ), DF( * ),
306 $ dl( * ), dlf( * ), du( * ), du2( * ), duf( * ),
307 $ ferr( * ), work( * ), x( ldx, * )
313 DOUBLE PRECISION ZERO
314 PARAMETER ( ZERO = 0.0d+0 )
317 LOGICAL NOFACT, NOTRAN
319 DOUBLE PRECISION ANORM
323 DOUBLE PRECISION DLAMCH, DLANGT
324 EXTERNAL lsame, dlamch, dlangt
336 nofact = lsame( fact,
'N' )
337 notran = lsame( trans,
'N' )
338 IF( .NOT.nofact .AND. .NOT.lsame( fact,
'F' ) )
THEN
340 ELSE IF( .NOT.notran .AND. .NOT.lsame( trans,
'T' ) .AND. .NOT.
341 $ lsame( trans,
'C' ) )
THEN
343 ELSE IF( n.LT.0 )
THEN
345 ELSE IF( nrhs.LT.0 )
THEN
347 ELSE IF( ldb.LT.max( 1, n ) )
THEN
349 ELSE IF( ldx.LT.max( 1, n ) )
THEN
353 CALL xerbla(
'DGTSVX', -info )
361 CALL dcopy( n, d, 1, df, 1 )
363 CALL dcopy( n-1, dl, 1, dlf, 1 )
364 CALL dcopy( n-1, du, 1, duf, 1 )
366 CALL dgttrf( n, dlf, df, duf, du2, ipiv, info )
383 anorm = dlangt( norm, n, dl, d, du )
387 CALL dgtcon( norm, n, dlf, df, duf, du2, ipiv, anorm, rcond, work,
392 CALL dlacpy(
'Full', n, nrhs, b, ldb, x, ldx )
393 CALL dgttrs( trans, n, nrhs, dlf, df, duf, du2, ipiv, x, ldx,
399 CALL dgtrfs( trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv,
400 $ b, ldb, x, ldx, ferr, berr, work, iwork, info )
404 IF( rcond.LT.dlamch(
'Epsilon' ) )
subroutine xerbla(srname, info)
subroutine dcopy(n, dx, incx, dy, incy)
DCOPY
subroutine dgtcon(norm, n, dl, d, du, du2, ipiv, anorm, rcond, work, iwork, info)
DGTCON
subroutine dgtrfs(trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv, b, ldb, x, ldx, ferr, berr, work, iwork, info)
DGTRFS
subroutine dgtsvx(fact, trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, iwork, info)
DGTSVX computes the solution to system of linear equations A * X = B for GT matrices
subroutine dgttrf(n, dl, d, du, du2, ipiv, info)
DGTTRF
subroutine dgttrs(trans, n, nrhs, dl, d, du, du2, ipiv, b, ldb, info)
DGTTRS
subroutine dlacpy(uplo, m, n, a, lda, b, ldb)
DLACPY copies all or part of one two-dimensional array to another.