293 SUBROUTINE cgtsvx( FACT, TRANS, N, NRHS, DL, D, DU, DLF, DF, DUF,
294 $ du2, ipiv, b, ldb, x, ldx, rcond, ferr, berr,
295 $ work, rwork, info )
303 CHARACTER FACT, TRANS
304 INTEGER INFO, LDB, LDX, N, NRHS
309 REAL BERR( * ), FERR( * ), RWORK( * )
310 COMPLEX B( ldb, * ), D( * ), DF( * ), DL( * ),
311 $ dlf( * ), du( * ), du2( * ), duf( * ),
312 $ work( * ), x( ldx, * )
319 parameter ( zero = 0.0e+0 )
322 LOGICAL NOFACT, NOTRAN
329 EXTERNAL lsame, clangt, slamch
341 nofact = lsame( fact,
'N' )
342 notran = lsame( trans,
'N' )
343 IF( .NOT.nofact .AND. .NOT.lsame( fact,
'F' ) )
THEN
345 ELSE IF( .NOT.notran .AND. .NOT.lsame( trans,
'T' ) .AND. .NOT.
346 $ lsame( trans,
'C' ) )
THEN
348 ELSE IF( n.LT.0 )
THEN
350 ELSE IF( nrhs.LT.0 )
THEN
352 ELSE IF( ldb.LT.max( 1, n ) )
THEN
354 ELSE IF( ldx.LT.max( 1, n ) )
THEN
358 CALL xerbla(
'CGTSVX', -info )
366 CALL ccopy( n, d, 1, df, 1 )
368 CALL ccopy( n-1, dl, 1, dlf, 1 )
369 CALL ccopy( n-1, du, 1, duf, 1 )
371 CALL cgttrf( n, dlf, df, duf, du2, ipiv, info )
388 anorm = clangt( norm, n, dl, d, du )
392 CALL cgtcon( norm, n, dlf, df, duf, du2, ipiv, anorm, rcond, work,
397 CALL clacpy(
'Full', n, nrhs, b, ldb, x, ldx )
398 CALL cgttrs( trans, n, nrhs, dlf, df, duf, du2, ipiv, x, ldx,
404 CALL cgtrfs( trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv,
405 $ b, ldb, x, ldx, ferr, berr, work, rwork, info )
409 IF( rcond.LT.slamch(
'Epsilon' ) )
subroutine cgttrf(N, DL, D, DU, DU2, IPIV, INFO)
CGTTRF
subroutine cgtcon(NORM, N, DL, D, DU, DU2, IPIV, ANORM, RCOND, WORK, INFO)
CGTCON
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 xerbla(SRNAME, INFO)
XERBLA
subroutine cgtrfs(TRANS, N, NRHS, DL, D, DU, DLF, DF, DUF, DU2, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CGTRFS
subroutine clacpy(UPLO, M, N, A, LDA, B, LDB)
CLACPY copies all or part of one two-dimensional array to another.
subroutine ccopy(N, CX, INCX, CY, INCY)
CCOPY