289 SUBROUTINE cgtsvx( FACT, TRANS, N, NRHS, DL, D, DU, DLF, DF,
291 $ DU2, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR,
292 $ WORK, RWORK, INFO )
299 CHARACTER FACT, TRANS
300 INTEGER INFO, LDB, LDX, N, NRHS
305 REAL BERR( * ), FERR( * ), RWORK( * )
306 COMPLEX B( LDB, * ), D( * ), DF( * ), DL( * ),
307 $ dlf( * ), du( * ), du2( * ), duf( * ),
308 $ work( * ), x( ldx, * )
315 PARAMETER ( ZERO = 0.0e+0 )
318 LOGICAL NOFACT, NOTRAN
325 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,
395 CALL clacpy(
'Full', n, nrhs, b, ldb, x, ldx )
396 CALL cgttrs( trans, n, nrhs, dlf, df, duf, du2, ipiv, x, ldx,
402 CALL cgtrfs( trans, n, nrhs, dl, d, du, dlf, df, duf, du2,
404 $ b, ldb, x, ldx, ferr, berr, work, rwork, info )
408 IF( rcond.LT.slamch(
'Epsilon' ) )
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 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.