230 SUBROUTINE zptsvx( 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
240 DOUBLE PRECISION RCOND
243 DOUBLE PRECISION BERR( * ), D( * ), DF( * ), FERR( * ),
245 COMPLEX*16 B( LDB, * ), E( * ), EF( * ), WORK( * ),
252 DOUBLE PRECISION ZERO
253 parameter( zero = 0.0d+0 )
257 DOUBLE PRECISION ANORM
261 DOUBLE PRECISION DLAMCH, ZLANHT
262 EXTERNAL lsame, dlamch, zlanht
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(
'ZPTSVX', -info )
298 CALL dcopy( n, d, 1, df, 1 )
300 $
CALL zcopy( n-1, e, 1, ef, 1 )
301 CALL zpttrf( n, df, ef, info )
313 anorm = zlanht(
'1', n, d, e )
317 CALL zptcon( n, df, ef, anorm, rcond, rwork, info )
321 CALL zlacpy(
'Full', n, nrhs, b, ldb, x, ldx )
322 CALL zpttrs(
'Lower', n, nrhs, df, ef, x, ldx, info )
327 CALL zptrfs(
'Lower', n, nrhs, d, e, df, ef, b, ldb, x, ldx,
329 $ berr, work, rwork, info )
333 IF( rcond.LT.dlamch(
'Epsilon' ) )
subroutine xerbla(srname, info)
subroutine zcopy(n, zx, incx, zy, incy)
ZCOPY
subroutine dcopy(n, dx, incx, dy, incy)
DCOPY
subroutine zlacpy(uplo, m, n, a, lda, b, ldb)
ZLACPY copies all or part of one two-dimensional array to another.
subroutine zptcon(n, d, e, anorm, rcond, rwork, info)
ZPTCON
subroutine zptrfs(uplo, n, nrhs, d, e, df, ef, b, ldb, x, ldx, ferr, berr, work, rwork, info)
ZPTRFS
subroutine zptsvx(fact, n, nrhs, d, e, df, ef, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
ZPTSVX computes the solution to system of linear equations A * X = B for PT matrices
subroutine zpttrf(n, d, e, info)
ZPTTRF
subroutine zpttrs(uplo, n, nrhs, d, e, b, ldb, info)
ZPTTRS