291 SUBROUTINE cgtsvx( FACT, TRANS, N, NRHS, DL, D, DU, DLF, DF, DUF,
292 $ DU2, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR,
293 $ WORK, RWORK, INFO )
300 CHARACTER FACT, TRANS
301 INTEGER INFO, LDB, LDX, N, NRHS
306 REAL BERR( * ), FERR( * ), RWORK( * )
307 COMPLEX B( LDB, * ), D( * ), DF( * ), DL( * ),
308 $ dlf( * ), du( * ), du2( * ), duf( * ),
309 $ work( * ), x( ldx, * )
316 PARAMETER ( ZERO = 0.0e+0 )
319 LOGICAL NOFACT, NOTRAN
326 EXTERNAL lsame, clangt, slamch
338 nofact = lsame( fact,
'N' )
339 notran = lsame( trans,
'N' )
340 IF( .NOT.nofact .AND. .NOT.lsame( fact,
'F' ) )
THEN
342 ELSE IF( .NOT.notran .AND. .NOT.lsame( trans,
'T' ) .AND. .NOT.
343 $ lsame( trans,
'C' ) )
THEN
345 ELSE IF( n.LT.0 )
THEN
347 ELSE IF( nrhs.LT.0 )
THEN
349 ELSE IF( ldb.LT.max( 1, n ) )
THEN
351 ELSE IF( ldx.LT.max( 1, n ) )
THEN
355 CALL xerbla(
'CGTSVX', -info )
363 CALL ccopy( n, d, 1, df, 1 )
365 CALL ccopy( n-1, dl, 1, dlf, 1 )
366 CALL ccopy( n-1, du, 1, duf, 1 )
368 CALL cgttrf( n, dlf, df, duf, du2, ipiv, info )
385 anorm = clangt( norm, n, dl, d, du )
389 CALL cgtcon( norm, n, dlf, df, duf, du2, ipiv, anorm, rcond, work,
394 CALL clacpy(
'Full', n, nrhs, b, ldb, x, ldx )
395 CALL cgttrs( trans, n, nrhs, dlf, df, duf, du2, ipiv, x, ldx,
401 CALL cgtrfs( trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv,
402 $ b, ldb, x, ldx, ferr, berr, work, rwork, info )
406 IF( rcond.LT.slamch(
'Epsilon' ) )
subroutine xerbla(srname, info)
subroutine ccopy(n, cx, incx, cy, incy)
CCOPY
subroutine cgtcon(norm, n, dl, d, du, du2, ipiv, anorm, rcond, work, info)
CGTCON
subroutine cgtrfs(trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv, b, ldb, x, ldx, ferr, berr, work, rwork, info)
CGTRFS
subroutine cgtsvx(fact, trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
CGTSVX computes the solution to system of linear equations A * X = B for GT matrices
subroutine cgttrf(n, dl, d, du, du2, ipiv, info)
CGTTRF
subroutine cgttrs(trans, n, nrhs, dl, d, du, du2, ipiv, b, ldb, info)
CGTTRS
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.