281 SUBROUTINE dsysvx( FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B,
282 $ LDB, X, LDX, RCOND, FERR, BERR, WORK, LWORK,
291 INTEGER INFO, LDA, LDAF, LDB, LDX, LWORK, N, NRHS
292 DOUBLE PRECISION RCOND
295 INTEGER IPIV( * ), IWORK( * )
296 DOUBLE PRECISION A( LDA, * ), AF( LDAF, * ), B( LDB, * ),
297 $ berr( * ), ferr( * ), work( * ), x( ldx, * )
303 DOUBLE PRECISION ZERO
304 PARAMETER ( ZERO = 0.0d+0 )
307 LOGICAL LQUERY, NOFACT
309 DOUBLE PRECISION ANORM
314 DOUBLE PRECISION DLAMCH, DLANSY
315 EXTERNAL lsame, ilaenv, dlamch, dlansy
328 nofact = lsame( fact,
'N' )
329 lquery = ( lwork.EQ.-1 )
330 IF( .NOT.nofact .AND. .NOT.lsame( fact,
'F' ) )
THEN
332 ELSE IF( .NOT.lsame( uplo,
'U' ) .AND. .NOT.lsame( uplo,
'L' ) )
335 ELSE IF( n.LT.0 )
THEN
337 ELSE IF( nrhs.LT.0 )
THEN
339 ELSE IF( lda.LT.max( 1, n ) )
THEN
341 ELSE IF( ldaf.LT.max( 1, n ) )
THEN
343 ELSE IF( ldb.LT.max( 1, n ) )
THEN
345 ELSE IF( ldx.LT.max( 1, n ) )
THEN
347 ELSE IF( lwork.LT.max( 1, 3*n ) .AND. .NOT.lquery )
THEN
352 lwkopt = max( 1, 3*n )
354 nb = ilaenv( 1,
'DSYTRF', uplo, n, -1, -1, -1 )
355 lwkopt = max( lwkopt, n*nb )
361 CALL xerbla(
'DSYSVX', -info )
363 ELSE IF( lquery )
THEN
371 CALL dlacpy( uplo, n, n, a, lda, af, ldaf )
372 CALL dsytrf( uplo, n, af, ldaf, ipiv, work, lwork, info )
384 anorm = dlansy(
'I', uplo, n, a, lda, work )
388 CALL dsycon( uplo, n, af, ldaf, ipiv, anorm, rcond, work, iwork,
393 CALL dlacpy(
'Full', n, nrhs, b, ldb, x, ldx )
394 CALL dsytrs( uplo, n, nrhs, af, ldaf, ipiv, x, ldx, info )
399 CALL dsyrfs( uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x,
400 $ ldx, ferr, berr, work, iwork, info )
404 IF( rcond.LT.dlamch(
'Epsilon' ) )
subroutine xerbla(srname, info)
subroutine dsycon(uplo, n, a, lda, ipiv, anorm, rcond, work, iwork, info)
DSYCON
subroutine dsyrfs(uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, ferr, berr, work, iwork, info)
DSYRFS
subroutine dsysvx(fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, lwork, iwork, info)
DSYSVX computes the solution to system of linear equations A * X = B for SY matrices
subroutine dsytrf(uplo, n, a, lda, ipiv, work, lwork, info)
DSYTRF
subroutine dsytrs(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)
DSYTRS
subroutine dlacpy(uplo, m, n, a, lda, b, ldb)
DLACPY copies all or part of one two-dimensional array to another.