533 SUBROUTINE zgesvxx( FACT, TRANS, N, NRHS, A, LDA, AF, LDAF,
535 $ EQUED, R, C, B, LDB, X, LDX, RCOND, RPVGRW,
536 $ BERR, N_ERR_BNDS, ERR_BNDS_NORM,
537 $ ERR_BNDS_COMP, NPARAMS, PARAMS, WORK, RWORK,
545 CHARACTER EQUED, FACT, TRANS
546 INTEGER INFO, LDA, LDAF, LDB, LDX, N, NRHS, NPARAMS,
548 DOUBLE PRECISION RCOND, RPVGRW
552 COMPLEX*16 A( LDA, * ), AF( LDAF, * ), B( LDB, * ),
553 $ x( ldx , * ),work( * )
554 DOUBLE PRECISION R( * ), C( * ), PARAMS( * ), BERR( * ),
555 $ ERR_BNDS_NORM( NRHS, * ),
556 $ err_bnds_comp( nrhs, * ), rwork( * )
562 DOUBLE PRECISION ZERO, ONE
563 PARAMETER ( ZERO = 0.0d+0, one = 1.0d+0 )
564 INTEGER FINAL_NRM_ERR_I, FINAL_CMP_ERR_I, BERR_I
565 INTEGER RCOND_I, NRM_RCOND_I, NRM_ERR_I, CMP_RCOND_I
566 INTEGER CMP_ERR_I, PIV_GROWTH_I
567 parameter( final_nrm_err_i = 1, final_cmp_err_i = 2,
569 parameter( rcond_i = 4, nrm_rcond_i = 5, nrm_err_i = 6 )
570 parameter( cmp_rcond_i = 7, cmp_err_i = 8,
574 LOGICAL COLEQU, EQUIL, NOFACT, NOTRAN, ROWEQU
576 DOUBLE PRECISION AMAX, BIGNUM, COLCND, RCMAX, RCMIN,
582 DOUBLE PRECISION DLAMCH, ZLA_GERPVGRW
595 nofact = lsame( fact,
'N' )
596 equil = lsame( fact,
'E' )
597 notran = lsame( trans,
'N' )
598 smlnum = dlamch(
'Safe minimum' )
599 bignum = one / smlnum
600 IF( nofact .OR. equil )
THEN
605 rowequ = lsame( equed,
'R' ) .OR. lsame( equed,
'B' )
606 colequ = lsame( equed,
'C' ) .OR. lsame( equed,
'B' )
617 IF( .NOT.nofact .AND. .NOT.equil .AND. .NOT.
618 $ lsame( fact,
'F' ) )
THEN
620 ELSE IF( .NOT.notran .AND. .NOT.lsame( trans,
'T' ) .AND. .NOT.
621 $ lsame( trans,
'C' ) )
THEN
623 ELSE IF( n.LT.0 )
THEN
625 ELSE IF( nrhs.LT.0 )
THEN
627 ELSE IF( lda.LT.max( 1, n ) )
THEN
629 ELSE IF( ldaf.LT.max( 1, n ) )
THEN
631 ELSE IF( lsame( fact,
'F' ) .AND. .NOT.
632 $ ( rowequ .OR. colequ .OR. lsame( equed,
'N' ) ) )
THEN
639 rcmin = min( rcmin, r( j ) )
640 rcmax = max( rcmax, r( j ) )
642 IF( rcmin.LE.zero )
THEN
644 ELSE IF( n.GT.0 )
THEN
645 rowcnd = max( rcmin, smlnum ) / min( rcmax, bignum )
650 IF( colequ .AND. info.EQ.0 )
THEN
654 rcmin = min( rcmin, c( j ) )
655 rcmax = max( rcmax, c( j ) )
657 IF( rcmin.LE.zero )
THEN
659 ELSE IF( n.GT.0 )
THEN
660 colcnd = max( rcmin, smlnum ) / min( rcmax, bignum )
666 IF( ldb.LT.max( 1, n ) )
THEN
668 ELSE IF( ldx.LT.max( 1, n ) )
THEN
675 CALL xerbla(
'ZGESVXX', -info )
683 CALL zgeequb( n, n, a, lda, r, c, rowcnd, colcnd, amax,
685 IF( infequ.EQ.0 )
THEN
689 CALL zlaqge( n, n, a, lda, r, c, rowcnd, colcnd, amax,
691 rowequ = lsame( equed,
'R' ) .OR. lsame( equed,
'B' )
692 colequ = lsame( equed,
'C' ) .OR. lsame( equed,
'B' )
697 IF ( .NOT.rowequ )
THEN
702 IF ( .NOT.colequ )
THEN
712 IF( rowequ )
CALL zlascl2( n, nrhs, r, b, ldb )
714 IF( colequ )
CALL zlascl2( n, nrhs, c, b, ldb )
717 IF( nofact .OR. equil )
THEN
721 CALL zlacpy(
'Full', n, n, a, lda, af, ldaf )
722 CALL zgetrf( n, n, af, ldaf, ipiv, info )
732 rpvgrw = zla_gerpvgrw( n, info, a, lda, af, ldaf )
739 rpvgrw = zla_gerpvgrw( n, n, a, lda, af, ldaf )
743 CALL zlacpy(
'Full', n, nrhs, b, ldb, x, ldx )
744 CALL zgetrs( trans, n, nrhs, af, ldaf, ipiv, x, ldx, info )
749 CALL zgerfsx( trans, equed, n, nrhs, a, lda, af, ldaf,
750 $ ipiv, r, c, b, ldb, x, ldx, rcond, berr,
751 $ n_err_bnds, err_bnds_norm, err_bnds_comp, nparams, params,
752 $ work, rwork, info )
756 IF ( colequ .AND. notran )
THEN
757 CALL zlascl2 ( n, nrhs, c, x, ldx )
758 ELSE IF ( rowequ .AND. .NOT.notran )
THEN
759 CALL zlascl2 ( n, nrhs, r, x, ldx )
subroutine zgerfsx(trans, equed, n, nrhs, a, lda, af, ldaf, ipiv, r, c, b, ldb, x, ldx, rcond, berr, n_err_bnds, err_bnds_norm, err_bnds_comp, nparams, params, work, rwork, info)
ZGERFSX
subroutine zgesvxx(fact, trans, n, nrhs, a, lda, af, ldaf, ipiv, equed, r, c, b, ldb, x, ldx, rcond, rpvgrw, berr, n_err_bnds, err_bnds_norm, err_bnds_comp, nparams, params, work, rwork, info)
ZGESVXX computes the solution to system of linear equations A * X = B for GE matrices