504 SUBROUTINE zsysvxx( FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV,
505 $ equed, s, b, ldb, x, ldx, rcond, rpvgrw, berr,
506 $ n_err_bnds, err_bnds_norm, err_bnds_comp,
507 $ nparams, params, work, rwork, info )
515 CHARACTER equed, fact, uplo
516 INTEGER info, lda, ldaf, ldb, ldx, n, nrhs, nparams,
518 DOUBLE PRECISION rcond, rpvgrw
522 COMPLEX*16 a( lda, * ), af( ldaf, * ), b( ldb, * ),
523 $ x( ldx, * ), work( * )
524 DOUBLE PRECISION s( * ), params( * ), berr( * ),
525 $ err_bnds_norm( nrhs, * ),
526 $ err_bnds_comp( nrhs, * ), rwork( * )
532 DOUBLE PRECISION zero, one
533 parameter( zero = 0.0d+0, one = 1.0d+0 )
534 INTEGER final_nrm_err_i, final_cmp_err_i, berr_i
535 INTEGER rcond_i, nrm_rcond_i, nrm_err_i, cmp_rcond_i
536 INTEGER cmp_err_i, piv_growth_i
537 parameter( final_nrm_err_i = 1, final_cmp_err_i = 2,
539 parameter( rcond_i = 4, nrm_rcond_i = 5, nrm_err_i = 6 )
540 parameter( cmp_rcond_i = 7, cmp_err_i = 8,
544 LOGICAL equil, nofact, rcequ
546 DOUBLE PRECISION amax, bignum, smin, smax, scond, smlnum
563 nofact =
lsame( fact,
'N' )
564 equil =
lsame( fact,
'E' )
565 smlnum =
dlamch(
'Safe minimum' )
566 bignum = one / smlnum
567 IF( nofact .OR. equil )
THEN
571 rcequ =
lsame( equed,
'Y' )
582 IF( .NOT.nofact .AND. .NOT.equil .AND. .NOT.
583 $
lsame( fact,
'F' ) )
THEN
585 ELSE IF( .NOT.
lsame(uplo,
'U') .AND.
586 $ .NOT.
lsame(uplo,
'L') )
THEN
588 ELSE IF( n.LT.0 )
THEN
590 ELSE IF( nrhs.LT.0 )
THEN
592 ELSE IF( lda.LT.max( 1, n ) )
THEN
594 ELSE IF( ldaf.LT.max( 1, n ) )
THEN
596 ELSE IF(
lsame( fact,
'F' ) .AND. .NOT.
597 $ ( rcequ .OR.
lsame( equed,
'N' ) ) )
THEN
604 smin = min( smin, s( j ) )
605 smax = max( smax, s( j ) )
607 IF( smin.LE.zero )
THEN
609 ELSE IF( n.GT.0 )
THEN
610 scond = max( smin, smlnum ) / min( smax, bignum )
616 IF( ldb.LT.max( 1, n ) )
THEN
618 ELSE IF( ldx.LT.max( 1, n ) )
THEN
625 CALL
xerbla(
'ZSYSVXX', -info )
633 CALL
zsyequb( uplo, n, a, lda, s, scond, amax, work, infequ )
634 IF( infequ.EQ.0 )
THEN
638 CALL
zlaqsy( uplo, n, a, lda, s, scond, amax, equed )
639 rcequ =
lsame( equed,
'Y' )
646 IF( rcequ ) CALL
zlascl2( n, nrhs, s, b, ldb )
648 IF( nofact .OR. equil )
THEN
652 CALL
zlacpy( uplo, n, n, a, lda, af, ldaf )
653 CALL
zsytrf( uplo, n, af, ldaf, ipiv, work, 5*max(1,n), info )
665 $ ldaf, ipiv, rwork )
673 $ rpvgrw =
zla_syrpvgrw( uplo, n, info, a, lda, af, ldaf,
678 CALL
zlacpy(
'Full', n, nrhs, b, ldb, x, ldx )
679 CALL
zsytrs( uplo, n, nrhs, af, ldaf, ipiv, x, ldx, info )
684 CALL
zsyrfsx( uplo, equed, n, nrhs, a, lda, af, ldaf, ipiv,
685 $ s, b, ldb, x, ldx, rcond, berr, n_err_bnds, err_bnds_norm,
686 $ err_bnds_comp, nparams, params, work, rwork, info )
691 CALL
zlascl2(n, nrhs, s, x, ldx )