Previous: sgesvd Up: ../lapack-s.html Next: sgetf2


sgesvx


 NAME
      SGESVX - use the LU factorization to compute the solution to
      a real system of linear equations  A * X = B,

 SYNOPSIS
      SUBROUTINE SGESVX( FACT, TRANS, N, NRHS, A, LDA, AF, LDAF,
                         IPIV, EQUED, R, C, B, LDB, X, LDX, RCOND,
                         FERR, BERR, WORK, IWORK, INFO )

          CHARACTER      EQUED, FACT, TRANS

          INTEGER        INFO, LDA, LDAF, LDB, LDX, N, NRHS

          REAL           RCOND

          INTEGER        IPIV( * ), IWORK( * )

          REAL           A( LDA, * ), AF( LDAF, * ), B( LDB, * ),
                         BERR( * ), C( * ), FERR( * ), R( * ),
                         WORK( * ), X( LDX, * )

 PURPOSE
      SGESVX uses the LU factorization to compute the solution to
      a real system of linear equations
         A * X = B, where A is an N-by-N matrix and X and B are
      N-by-NRHS matrices.

      Error bounds on the solution and a condition estimate are
      also provided.

 DESCRIPTION
      The following steps are performed:

      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 = P * L * U,
         where P is a permutation matrix, L is a unit lower tri-
      angular
         matrix, and U is upper triangular.

      3. 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, steps 4-6 are skipped.

      4. The system of equations is solved for X using the fac-
      tored 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 FACT = 'E' and 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.

 ARGUMENTS
      FACT    (input) CHARACTER*1
              Specifies whether or not the factored form of the
              matrix A is supplied on entry, and if not, whether
              the matrix A should be equilibrated before it is
              factored.  = 'F':  On entry, AF and IPIV contain the
              factored form of A.  If EQUED is not 'N', the matrix
              A has been equilibrated with scaling factors given
              by R and C.  A, AF, and IPIV are not modified.  =
              'N':  The matrix A will be copied to AF and fac-
              tored.
              = 'E':  The matrix A will be equilibrated if neces-
              sary, then copied to AF and factored.

      TRANS   (input) CHARACTER*1
              Specifies the form of the system of equations:
              = 'N':  A * X = B     (No transpose)
              = 'T':  A**T * X = B  (Transpose)
              = 'C':  A**H * X = B  (Transpose)

      N       (input) INTEGER
              The number of linear equations, i.e., the order of
              the matrix A.  N >= 0.

      NRHS    (input) INTEGER
              The number of right-hand sides, i.e., the number of
              columns of the matrices B and X.  NRHS >= 0.

      A       (input/output) REAL array, dimension (LDA,N)
              On entry, the N-by-N matrix A.  If FACT = 'F' and
              EQUED is not 'N', then A must have been equilibrated
              by the scaling factors in R and/or C.  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 = 'R':  A := diag(R) * A
              EQUED = 'C':  A := A * diag(C)
              EQUED = 'B':  A := diag(R) * A * diag(C).

      LDA     (input) INTEGER
              The leading dimension of the array A.  LDA >=
              max(1,N).

      AF      (input or output) REAL array, dimension (LDAF,N)
              If FACT = 'F', then AF is an input argument and on
              entry contains the factors L and U from the factori-
              zation A = P*L*U as computed by SGETRF.  If EQUED
              .ne. 'N', then AF is the factored form of the
              equilibrated matrix A.

              If FACT = 'N', then AF is an output argument and on
              exit returns the factors L and U from the factoriza-
              tion A = P*L*U of the original matrix A.

              If FACT = 'E', then AF is an output argument and on
              exit returns the factors L and U from the factoriza-
              tion A = P*L*U of the equilibrated matrix A (see the
              description of A for the form of the equilibrated
              matrix).

      LDAF    (input) INTEGER
              The leading dimension of the array AF.  LDAF >=
              max(1,N).

      IPIV    (input or output) INTEGER array, dimension (N)
              If FACT = 'F', then IPIV is an input argument and on
              entry contains the pivot indices from the factoriza-
              tion A = P*L*U as computed by SGETRF; row i of the
              matrix was interchanged with row IPIV(i).

              If FACT = 'N', then IPIV is an output argument and
              on exit contains the pivot indices from the factori-
              zation A = P*L*U of the original matrix A.

              If FACT = 'E', then IPIV is an output argument and

              on exit contains the pivot indices from the factori-
              zation A = P*L*U of the equilibrated matrix A.

      EQUED   (input/output) CHARACTER*1
              Specifies the form of equilibration that was done.
              = 'N':  No equilibration (always true if FACT =
              'N').
              = 'R':  Row equilibration, i.e., A has been premul-
              tiplied by diag(R).  = 'C':  Column equilibration,
              i.e., A has been postmultiplied by diag(C).  = 'B':
              Both row and column equilibration, i.e., A has been
              replaced by diag(R) * A * diag(C).  EQUED is an
              input variable if FACT = 'F'; otherwise, it is an
              output variable.

      R       (input/output) REAL array, dimension (N)
              The row scale factors for A.  If EQUED = 'R' or 'B',
              A is multiplied on the left by diag(R); if EQUED =
              'N' or 'C', R is not accessed.  R is an input vari-
              able if FACT = 'F'; otherwise, R is an output vari-
              able.  If FACT = 'F' and EQUED = 'R' or 'B', each
              element of R must be positive.

      C       (input/output) REAL array, dimension (N)
              The column scale factors for A.  If EQUED = 'C' or
              'B', A is multiplied on the right by diag(C); if
              EQUED = 'N' or 'R', C is not accessed.  C is an
              input variable if FACT = 'F'; otherwise, C is an
              output variable.  If FACT = 'F' and EQUED = 'C' or
              'B', each element of C must be positive.

      B       (input/output) REAL array, dimension (LDB,NRHS)
              On entry, the N-by-NRHS right-hand side matrix B.
              On exit, if EQUED = 'N', B is not modified; if TRANS
              = 'N' and EQUED = 'R' or 'B', B is overwritten by
              diag(R)*B; if TRANS = 'T' or 'C' and EQUED = 'C' or
              'B', B is overwritten by diag(C)*B.

      LDB     (input) INTEGER
              The leading dimension of the array B.  LDB >=
              max(1,N).

      X       (output) REAL array, dimension (LDX,NRHS)
              If INFO = 0, the N-by-NRHS solution matrix X to the
              original system of equations.  Note that A and B are
              modified on exit if EQUED .ne. 'N', and the solution
              to the equilibrated system is inv(diag(C))*X if
              TRANS = 'N' and EQUED = 'C' or 'B', or
              inv(diag(R))*X if TRANS = 'T' or 'C' and EQUED = 'R'
              or 'B'.

      LDX     (input) INTEGER

              The leading dimension of the array X.  LDX >=
              max(1,N).

      RCOND   (output) REAL
              The estimate of the reciprocal condition number of
              the matrix A after equilibration (if done).  If
              RCOND is less than the machine precision (in partic-
              ular, if RCOND = 0), the matrix is singular to work-
              ing precision.  This condition is indicated by a
              return code of INFO > 0, and the solution and error
              bounds are not computed.

      FERR    (output) REAL array, dimension (NRHS)
              The estimated forward error bounds for each solution
              vector X(j) (the j-th column of the solution matrix
              X).  If XTRUE is the true solution, FERR(j) bounds
              the magnitude of the largest entry in (X(j) - XTRUE)
              divided by the magnitude of the largest entry in
              X(j).  The quality of the error bound depends on the
              quality of the estimate of norm(inv(A)) computed in
              the code; if the estimate of norm(inv(A)) is accu-
              rate, the error bound is guaranteed.

      BERR    (output) REAL array, dimension (NRHS)
              The componentwise relative backward error of each
              solution vector X(j) (i.e., the smallest relative
              change in any entry of A or B that makes X(j) an
              exact solution).

      WORK    (workspace) REAL array, dimension (4*N)

      IWORK   (workspace) INTEGER array, dimension (N)

      INFO    (output) INTEGER
              = 0:  successful exit
              < 0:  if INFO = -i, the i-th argument had an illegal
              value
              > 0:  if INFO = i, and i is
              <= N:  U(i,i) is exactly zero.  The factorization
              has been completed, but the factor U is exactly
              singular, so the solution and error bounds could not
              be computed.  = N+1: RCOND is less than machine pre-
              cision.  The factorization has been completed, but
              the matrix is singular to working precision, and the
              solution and error bounds have not been computed.