230 SUBROUTINE cptsvx( FACT, N, NRHS, D, E, DF, EF, B, LDB, X, LDX,
231 $ RCOND, FERR, BERR, WORK, RWORK, INFO )
239 INTEGER INFO, LDB, LDX, N, NRHS
243 REAL BERR( * ), D( * ), DF( * ), FERR( * ),
245 COMPLEX B( LDB, * ), E( * ), EF( * ), WORK( * ),
253 parameter( zero = 0.0e+0 )
262 EXTERNAL lsame, clanht, slamch
277 nofact = lsame( fact,
'N' )
278 IF( .NOT.nofact .AND. .NOT.lsame( fact,
'F' ) )
THEN
280 ELSE IF( n.LT.0 )
THEN
282 ELSE IF( nrhs.LT.0 )
THEN
284 ELSE IF( ldb.LT.max( 1, n ) )
THEN
286 ELSE IF( ldx.LT.max( 1, n ) )
THEN
290 CALL xerbla(
'CPTSVX', -info )
298 CALL scopy( n, d, 1, df, 1 )
300 $
CALL ccopy( n-1, e, 1, ef, 1 )
301 CALL cpttrf( n, df, ef, info )
313 anorm = clanht(
'1', n, d, e )
317 CALL cptcon( n, df, ef, anorm, rcond, rwork, info )
321 CALL clacpy(
'Full', n, nrhs, b, ldb, x, ldx )
322 CALL cpttrs(
'Lower', n, nrhs, df, ef, x, ldx, info )
327 CALL cptrfs(
'Lower', n, nrhs, d, e, df, ef, b, ldb, x, ldx,
329 $ berr, work, rwork, info )
333 IF( rcond.LT.slamch(
'Epsilon' ) )
subroutine xerbla(srname, info)
subroutine scopy(n, sx, incx, sy, incy)
SCOPY
subroutine ccopy(n, cx, incx, cy, incy)
CCOPY
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.
subroutine cptcon(n, d, e, anorm, rcond, rwork, info)
CPTCON
subroutine cptrfs(uplo, n, nrhs, d, e, df, ef, b, ldb, x, ldx, ferr, berr, work, rwork, info)
CPTRFS
subroutine cptsvx(fact, n, nrhs, d, e, df, ef, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
CPTSVX computes the solution to system of linear equations A * X = B for PT matrices
subroutine cpttrf(n, d, e, info)
CPTTRF
subroutine cpttrs(uplo, n, nrhs, d, e, b, ldb, info)
CPTTRS