SUBROUTINE ZGBSVX( FACT, TRANSA, N, NSUB, NSUPER, NRHS, A, LDA, AF, * LDAF, IPIVOT, EQUED, ROWSC, COLSC, B, LDB, X, LDX, RCOND, FERR, * BERR, WORK, WORK2, INFO) CHARACTER * 1 FACT, TRANSA, EQUED DOUBLE COMPLEX A(LDA,*), AF(LDAF,*), B(LDB,*), X(LDX,*), WORK(*) INTEGER N, NSUB, NSUPER, NRHS, LDA, LDAF, LDB, LDX, INFO INTEGER IPIVOT(*) DOUBLE PRECISION RCOND DOUBLE PRECISION ROWSC(*), COLSC(*), FERR(*), BERR(*), WORK2(*) SUBROUTINE ZGBSVX_64( FACT, TRANSA, N, NSUB, NSUPER, NRHS, A, LDA, * AF, LDAF, IPIVOT, EQUED, ROWSC, COLSC, B, LDB, X, LDX, RCOND, * FERR, BERR, WORK, WORK2, INFO) CHARACTER * 1 FACT, TRANSA, EQUED DOUBLE COMPLEX A(LDA,*), AF(LDAF,*), B(LDB,*), X(LDX,*), WORK(*) INTEGER*8 N, NSUB, NSUPER, NRHS, LDA, LDAF, LDB, LDX, INFO INTEGER*8 IPIVOT(*) DOUBLE PRECISION RCOND DOUBLE PRECISION ROWSC(*), COLSC(*), FERR(*), BERR(*), WORK2(*)
SUBROUTINE GBSVX( FACT, [TRANSA], [N], NSUB, NSUPER, [NRHS], A, [LDA], * AF, [LDAF], IPIVOT, EQUED, ROWSC, COLSC, B, [LDB], X, [LDX], * RCOND, FERR, BERR, [WORK], [WORK2], [INFO]) CHARACTER(LEN=1) :: FACT, TRANSA, EQUED COMPLEX(8), DIMENSION(:) :: WORK COMPLEX(8), DIMENSION(:,:) :: A, AF, B, X INTEGER :: N, NSUB, NSUPER, NRHS, LDA, LDAF, LDB, LDX, INFO INTEGER, DIMENSION(:) :: IPIVOT REAL(8) :: RCOND REAL(8), DIMENSION(:) :: ROWSC, COLSC, FERR, BERR, WORK2 SUBROUTINE GBSVX_64( FACT, [TRANSA], [N], NSUB, NSUPER, [NRHS], A, * [LDA], AF, [LDAF], IPIVOT, EQUED, ROWSC, COLSC, B, [LDB], X, [LDX], * RCOND, FERR, BERR, [WORK], [WORK2], [INFO]) CHARACTER(LEN=1) :: FACT, TRANSA, EQUED COMPLEX(8), DIMENSION(:) :: WORK COMPLEX(8), DIMENSION(:,:) :: A, AF, B, X INTEGER(8) :: N, NSUB, NSUPER, NRHS, LDA, LDAF, LDB, LDX, INFO INTEGER(8), DIMENSION(:) :: IPIVOT REAL(8) :: RCOND REAL(8), DIMENSION(:) :: ROWSC, COLSC, FERR, BERR, WORK2
void zgbsvx(char fact, char transa, int n, int nsub, int nsuper, int nrhs, doublecomplex *a, int lda, doublecomplex *af, int ldaf, int *ipivot, char equed, double *rowsc, double *colsc, doublecomplex *b, int ldb, doublecomplex *x, int ldx, double *rcond, double *ferr, double *berr, int *info);
void zgbsvx_64(char fact, char transa, long n, long nsub, long nsuper, long nrhs, doublecomplex *a, long lda, doublecomplex *af, long ldaf, long *ipivot, char equed, double *rowsc, double *colsc, doublecomplex *b, long ldb, doublecomplex *x, long ldx, double *rcond, double *ferr, double *berr, long *info);
Error bounds on the solution and a condition estimate are also provided.
The following steps are performed by this subroutine:
1. If FACT = 'E', real scaling factors are computed to equilibrate the system:
TRANS = 'N': diag(R)*A*diag(C) *inv(diag(C))*X = diag(R)*B
TRANS = 'T': (diag(R)*A*diag(C))**T *inv(diag(R))*X = diag(C)*B
TRANS = 'C': (diag(R)*A*diag(C))**H *inv(diag(R))*X = diag(C)*B
Whether or not the system will be equilibrated depends on the
scaling of the matrix A, but if equilibration is used, A is
overwritten by diag(R)*A*diag(C) and B by diag(R)*B (if TRANS='N')
or diag(C)*B (if TRANS = 'T' or 'C').
2. If FACT = 'N' or 'E', the LU decomposition is used to factor the matrix A (after equilibration if FACT = 'E') as
A = L * U,
where L is a product of permutation and unit lower triangular
matrices with KL subdiagonals, and U is upper triangular with
KL+KU superdiagonals.
3. If some U(i,i)=0, so that U is exactly singular, then the routine returns with INFO = i. Otherwise, the factored form of A is used to estimate the condition number of the matrix A. If the reciprocal of the condition number is less than machine precision, INFO = N+1 is returned as a warning, but the routine still goes on to solve for X and compute error bounds as described below.
4. The system of equations is solved for X using the factored form of A.
5. Iterative refinement is applied to improve the computed solution matrix and calculate error bounds and backward error estimates for it.
6. If equilibration was used, the matrix X is premultiplied by diag(C) (if TRANS = 'N') or diag(R) (if TRANS = 'T' or 'C') so that it solves the original system before equilibration.
If FACT = 'F' and EQUED is not 'N', then A must have been equilibrated by the scaling factors in ROWSC and/or COLSC. A is not modified if FACT = 'F' or 'N', or if FACT = 'E' and EQUED = 'N' on exit.
On exit, if EQUED .ne. 'N', A is scaled as follows: EQUED = 'ROWSC': A := diag(ROWSC) * A
EQUED = 'COLSC': A := A * diag(COLSC)
EQUED = 'B': A := diag(ROWSC) * A * diag(COLSC).
If FACT = 'N', then AF is an output argument and on exit returns details of the LU factorization of A.
If FACT = 'E', then AF is an output argument and on exit returns details of the LU factorization of the equilibrated matrix A (see the description of A for the form of the equilibrated matrix).
If FACT = 'N', then IPIVOT is an output argument and on exit contains the pivot indices from the factorization A = L*U of the original matrix A.
If FACT = 'E', then IPIVOT is an output argument and on exit contains the pivot indices from the factorization A = L*U of the equilibrated matrix A.