Previous: sgefa Up: ../plot79_s.html Next: sind


SGESL

       SUBROUTINE  SGESL (A,LDA,N,IPVT,B,JOB)
 C$    (Solve Linear System)
 C$
 C$    SGESL solves the real system
 C$
 C$    A * X = B  or  TRANS(A) * X = B
 C$
 C$    using the factors computed by SGECO or SGEFA.
 C$
 C$    On entry
 C$
 C$    A.........REAL(LDA, N)
 C$              The output from SGECO or SGEFA.
 C$
 C$    LDA.......INTEGER
 C$              The leading dimension of the array A.
 C$
 C$    N.........INTEGER
 C$              The order of the matrix A.
 C$
 C$    IPVT......INTEGER(N)
 C$              The pivot vector from SGECO or SGEFA.
 C$
 C$    B.........REAL(N)
 C$              The right hand side vector.
 C$
 C$    JOB.......INTEGER
 C$              = 0         to solve  A*X = B ,
 C$              = NONZERO   to solve  TRANS(A)*X = B  where
 C$                          TRANS(A)  is the transpose.
 C$
 C$    On return
 C$
 C$    B.........The solution vector X.
 C$
 C$    Error condition
 C$
 C$         A division  by zero  will occur  if the  input  factor
 C$         contains a  zero on  the diagonal.   Technically  this
 C$         indicates  singularity  but  it  is  often  caused  by
 C$         improper arguments  or improper  setting of  LDA.   It
 C$         will not occur if the subroutines are called correctly
 C$         and if SGECO has set RCOND  .GT. 0.0 or SGEFA has  set
 C$         INFO .EQ. 0 .
 C$
 C$    To compute  INVERSE(A) *  C  where C  is  a matrix  with  P
 C$    columns
 C$
 C$          CALL SGECO(A,LDA,N,IPVT,RCOND,Z)
 C$          IF (RCOND IS TOO SMALL) GO TO ...
 C$          DO 10 J = 1, P
 C$             CALL SGESL(A,LDA,N,IPVT,C(1,J),0)
 C$       10 CONTINUE
 C$
 C$    LINPACK.  This version dated 08/14/78 .
 C$    Cleve Moler, University of New Mexico, Argonne National Lab.
 C$
 C$    Subroutines and Functions
 C$
 C$    BLAS SAXPY,SDOT
 C$    (03-APR-82)