Previous: sgtsv Up: ../lapack-s.html Next: sgttrf
 NAME
      SGTSVX - use the LU factorization to compute the solution to
      a real system of linear equations A * X = B or A**T * X = B,
 SYNOPSIS
      SUBROUTINE SGTSVX( FACT, TRANS, N, NRHS, DL, D, DU, DLF, DF,
                         DUF, DU2, IPIV, B, LDB, X, LDX, RCOND,
                         FERR, BERR, WORK, IWORK, INFO )
          CHARACTER      FACT, TRANS
          INTEGER        INFO, LDB, LDX, N, NRHS
          REAL           RCOND
          INTEGER        IPIV( * ), IWORK( * )
          REAL           B( LDB, * ), BERR( * ), D( * ), DF( * ),
                         DL( * ), DLF( * ), DU( * ), DU2( * ),
                         DUF( * ), FERR( * ), WORK( * ), X( LDX, *
                         )
 PURPOSE
      SGTSVX uses the LU factorization to compute the solution to
      a real system of linear equations A * X = B or A**T * X = B,
      where A is a tridiagonal matrix of order N 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 = 'N', the LU decomposition is used to factor the
      matrix A
         as A = L * U, where L is a product of permutation and
      unit lower
         bidiagonal matrices and U is upper triangular with
      nonzeros in
         only the main diagonal and first two superdiagonals.
      2. 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 3 and 4 are skipped.
      3. The system of equations is solved for X using the fac-
      tored form
         of A.
      4. Iterative refinement is applied to improve the computed
      solution
         matrix and calculate error bounds and backward error
      estimates
         for it.
 ARGUMENTS
      FACT    (input) CHARACTER*1
              Specifies whether or not the factored form of A has
              been supplied on entry.  = 'F':  DLF, DF, DUF, DU2,
              and IPIV contain the factored form of A; DL, D, DU,
              DLF, DF, DUF, DU2 and IPIV will not be modified.  =
              'N':  The matrix will be copied to DLF, DF, and DUF
              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  (Conjugate transpose = Tran-
              spose)
      N       (input) INTEGER
              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 matrix B.  NRHS >= 0.
      DL      (input) REAL array, dimension (N-1)
              The (n-1) subdiagonal elements of A.
      D       (input) REAL array, dimension (N)
              The n diagonal elements of A.
      DU      (input) REAL array, dimension (N-1)
              The (n-1) superdiagonal elements of A.
      DLF     (input or output) REAL array, dimension (N-1)
              If FACT = 'F', then DLF is an input argument and on
              entry contains the (n-1) multipliers that define the
              matrix L from the LU factorization of A as computed
              by SGTTRF.
              If FACT = 'N', then DLF is an output argument and on
              exit contains the (n-1) multipliers that define the
              matrix L from the LU factorization of A.
      DF      (input or output) REAL array, dimension (N)
              If FACT = 'F', then DF is an input argument and on
              entry contains the n diagonal elements of the upper
              triangular matrix U from the LU factorization of A.
              If FACT = 'N', then DF is an output argument and on
              exit contains the n diagonal elements of the upper
              triangular matrix U from the LU factorization of A.
      DUF     (input or output) REAL array, dimension (N-1)
              If FACT = 'F', then DUF is an input argument and on
              entry contains the (n-1) elements of the first
              superdiagonal of U.
              If FACT = 'N', then DUF is an output argument and on
              exit contains the (n-1) elements of the first super-
              diagonal of U.
      DU2     (input or output) REAL array, dimension (N-2)
              If FACT = 'F', then DU2 is an input argument and on
              entry contains the (n-2) elements of the second
              superdiagonal of U.
              If FACT = 'N', then DU2 is an output argument and on
              exit contains the (n-2) elements of the second
              superdiagonal of U.
      IPIV    (input) INTEGER array, dimension (N)
              If FACT = 'F', then IPIV is an input argument and on
              entry contains the pivot indices from the LU factor-
              ization of A as computed by SGTTRF.
              If FACT = 'N', then IPIV is an output argument and
              on exit contains the pivot indices from the LU fac-
              torization of A; row i of the matrix was inter-
              changed with row IPIV(i).  IPIV(i) will always be
              either i or i+1; IPIV(i) = i indicates a row inter-
              change was not required.
      B       (input) REAL array, dimension (LDB,NRHS)
              The N-by-NRHS right hand side matrix 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.
      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.  If RCOND is less than the machine
              precision (in particular, if RCOND = 0), the matrix
              is singular to working 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 bound 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 (3*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 not been completed unless i = N, but the factor
              U is exactly singular, so the solution and error
              bounds could not be computed.  = N+1:  RCOND is less
              than machine precision.  The factorization has been
              completed, but the matrix is singular to working
              precision, and the solution and error bounds have
              not been computed.