File:  [local] / rpl / lapack / lapack / dpttrs.f
Revision 1.1: download - view: text, annotated - select for diffs - revision graph
Tue Jan 26 15:22:45 2010 UTC (14 years, 4 months ago) by bertrand
Branches: MAIN
CVS tags: HEAD
Initial revision

    1:       SUBROUTINE DPTTRS( N, NRHS, D, E, B, LDB, INFO )
    2: *
    3: *  -- LAPACK routine (version 3.2) --
    4: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
    5: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
    6: *     November 2006
    7: *
    8: *     .. Scalar Arguments ..
    9:       INTEGER            INFO, LDB, N, NRHS
   10: *     ..
   11: *     .. Array Arguments ..
   12:       DOUBLE PRECISION   B( LDB, * ), D( * ), E( * )
   13: *     ..
   14: *
   15: *  Purpose
   16: *  =======
   17: *
   18: *  DPTTRS solves a tridiagonal system of the form
   19: *     A * X = B
   20: *  using the L*D*L' factorization of A computed by DPTTRF.  D is a
   21: *  diagonal matrix specified in the vector D, L is a unit bidiagonal
   22: *  matrix whose subdiagonal is specified in the vector E, and X and B
   23: *  are N by NRHS matrices.
   24: *
   25: *  Arguments
   26: *  =========
   27: *
   28: *  N       (input) INTEGER
   29: *          The order of the tridiagonal matrix A.  N >= 0.
   30: *
   31: *  NRHS    (input) INTEGER
   32: *          The number of right hand sides, i.e., the number of columns
   33: *          of the matrix B.  NRHS >= 0.
   34: *
   35: *  D       (input) DOUBLE PRECISION array, dimension (N)
   36: *          The n diagonal elements of the diagonal matrix D from the
   37: *          L*D*L' factorization of A.
   38: *
   39: *  E       (input) DOUBLE PRECISION array, dimension (N-1)
   40: *          The (n-1) subdiagonal elements of the unit bidiagonal factor
   41: *          L from the L*D*L' factorization of A.  E can also be regarded
   42: *          as the superdiagonal of the unit bidiagonal factor U from the
   43: *          factorization A = U'*D*U.
   44: *
   45: *  B       (input/output) DOUBLE PRECISION array, dimension (LDB,NRHS)
   46: *          On entry, the right hand side vectors B for the system of
   47: *          linear equations.
   48: *          On exit, the solution vectors, X.
   49: *
   50: *  LDB     (input) INTEGER
   51: *          The leading dimension of the array B.  LDB >= max(1,N).
   52: *
   53: *  INFO    (output) INTEGER
   54: *          = 0: successful exit
   55: *          < 0: if INFO = -k, the k-th argument had an illegal value
   56: *
   57: *  =====================================================================
   58: *
   59: *     .. Local Scalars ..
   60:       INTEGER            J, JB, NB
   61: *     ..
   62: *     .. External Functions ..
   63:       INTEGER            ILAENV
   64:       EXTERNAL           ILAENV
   65: *     ..
   66: *     .. External Subroutines ..
   67:       EXTERNAL           DPTTS2, XERBLA
   68: *     ..
   69: *     .. Intrinsic Functions ..
   70:       INTRINSIC          MAX, MIN
   71: *     ..
   72: *     .. Executable Statements ..
   73: *
   74: *     Test the input arguments.
   75: *
   76:       INFO = 0
   77:       IF( N.LT.0 ) THEN
   78:          INFO = -1
   79:       ELSE IF( NRHS.LT.0 ) THEN
   80:          INFO = -2
   81:       ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
   82:          INFO = -6
   83:       END IF
   84:       IF( INFO.NE.0 ) THEN
   85:          CALL XERBLA( 'DPTTRS', -INFO )
   86:          RETURN
   87:       END IF
   88: *
   89: *     Quick return if possible
   90: *
   91:       IF( N.EQ.0 .OR. NRHS.EQ.0 )
   92:      $   RETURN
   93: *
   94: *     Determine the number of right-hand sides to solve at a time.
   95: *
   96:       IF( NRHS.EQ.1 ) THEN
   97:          NB = 1
   98:       ELSE
   99:          NB = MAX( 1, ILAENV( 1, 'DPTTRS', ' ', N, NRHS, -1, -1 ) )
  100:       END IF
  101: *
  102:       IF( NB.GE.NRHS ) THEN
  103:          CALL DPTTS2( N, NRHS, D, E, B, LDB )
  104:       ELSE
  105:          DO 10 J = 1, NRHS, NB
  106:             JB = MIN( NRHS-J+1, NB )
  107:             CALL DPTTS2( N, JB, D, E, B( 1, J ), LDB )
  108:    10    CONTINUE
  109:       END IF
  110: *
  111:       RETURN
  112: *
  113: *     End of DPTTRS
  114: *
  115:       END

CVSweb interface <joel.bertrand@systella.fr>