File:  [local] / rpl / lapack / lapack / dgttrs.f
Revision 1.19: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:38:52 2023 UTC (8 months, 3 weeks ago) by bertrand
Branches: MAIN
CVS tags: rpl-4_1_35, rpl-4_1_34, HEAD
Première mise à jour de lapack et blas.

    1: *> \brief \b DGTTRS
    2: *
    3: *  =========== DOCUMENTATION ===========
    4: *
    5: * Online html documentation available at
    6: *            http://www.netlib.org/lapack/explore-html/
    7: *
    8: *> \htmlonly
    9: *> Download DGTTRS + dependencies
   10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dgttrs.f">
   11: *> [TGZ]</a>
   12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dgttrs.f">
   13: *> [ZIP]</a>
   14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgttrs.f">
   15: *> [TXT]</a>
   16: *> \endhtmlonly
   17: *
   18: *  Definition:
   19: *  ===========
   20: *
   21: *       SUBROUTINE DGTTRS( TRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB,
   22: *                          INFO )
   23: *
   24: *       .. Scalar Arguments ..
   25: *       CHARACTER          TRANS
   26: *       INTEGER            INFO, LDB, N, NRHS
   27: *       ..
   28: *       .. Array Arguments ..
   29: *       INTEGER            IPIV( * )
   30: *       DOUBLE PRECISION   B( LDB, * ), D( * ), DL( * ), DU( * ), DU2( * )
   31: *       ..
   32: *
   33: *
   34: *> \par Purpose:
   35: *  =============
   36: *>
   37: *> \verbatim
   38: *>
   39: *> DGTTRS solves one of the systems of equations
   40: *>    A*X = B  or  A**T*X = B,
   41: *> with a tridiagonal matrix A using the LU factorization computed
   42: *> by DGTTRF.
   43: *> \endverbatim
   44: *
   45: *  Arguments:
   46: *  ==========
   47: *
   48: *> \param[in] TRANS
   49: *> \verbatim
   50: *>          TRANS is CHARACTER*1
   51: *>          Specifies the form of the system of equations.
   52: *>          = 'N':  A * X = B  (No transpose)
   53: *>          = 'T':  A**T* X = B  (Transpose)
   54: *>          = 'C':  A**T* X = B  (Conjugate transpose = Transpose)
   55: *> \endverbatim
   56: *>
   57: *> \param[in] N
   58: *> \verbatim
   59: *>          N is INTEGER
   60: *>          The order of the matrix A.
   61: *> \endverbatim
   62: *>
   63: *> \param[in] NRHS
   64: *> \verbatim
   65: *>          NRHS is INTEGER
   66: *>          The number of right hand sides, i.e., the number of columns
   67: *>          of the matrix B.  NRHS >= 0.
   68: *> \endverbatim
   69: *>
   70: *> \param[in] DL
   71: *> \verbatim
   72: *>          DL is DOUBLE PRECISION array, dimension (N-1)
   73: *>          The (n-1) multipliers that define the matrix L from the
   74: *>          LU factorization of A.
   75: *> \endverbatim
   76: *>
   77: *> \param[in] D
   78: *> \verbatim
   79: *>          D is DOUBLE PRECISION array, dimension (N)
   80: *>          The n diagonal elements of the upper triangular matrix U from
   81: *>          the LU factorization of A.
   82: *> \endverbatim
   83: *>
   84: *> \param[in] DU
   85: *> \verbatim
   86: *>          DU is DOUBLE PRECISION array, dimension (N-1)
   87: *>          The (n-1) elements of the first super-diagonal of U.
   88: *> \endverbatim
   89: *>
   90: *> \param[in] DU2
   91: *> \verbatim
   92: *>          DU2 is DOUBLE PRECISION array, dimension (N-2)
   93: *>          The (n-2) elements of the second super-diagonal of U.
   94: *> \endverbatim
   95: *>
   96: *> \param[in] IPIV
   97: *> \verbatim
   98: *>          IPIV is INTEGER array, dimension (N)
   99: *>          The pivot indices; for 1 <= i <= n, row i of the matrix was
  100: *>          interchanged with row IPIV(i).  IPIV(i) will always be either
  101: *>          i or i+1; IPIV(i) = i indicates a row interchange was not
  102: *>          required.
  103: *> \endverbatim
  104: *>
  105: *> \param[in,out] B
  106: *> \verbatim
  107: *>          B is DOUBLE PRECISION array, dimension (LDB,NRHS)
  108: *>          On entry, the matrix of right hand side vectors B.
  109: *>          On exit, B is overwritten by the solution vectors X.
  110: *> \endverbatim
  111: *>
  112: *> \param[in] LDB
  113: *> \verbatim
  114: *>          LDB is INTEGER
  115: *>          The leading dimension of the array B.  LDB >= max(1,N).
  116: *> \endverbatim
  117: *>
  118: *> \param[out] INFO
  119: *> \verbatim
  120: *>          INFO is INTEGER
  121: *>          = 0:  successful exit
  122: *>          < 0:  if INFO = -i, the i-th argument had an illegal value
  123: *> \endverbatim
  124: *
  125: *  Authors:
  126: *  ========
  127: *
  128: *> \author Univ. of Tennessee
  129: *> \author Univ. of California Berkeley
  130: *> \author Univ. of Colorado Denver
  131: *> \author NAG Ltd.
  132: *
  133: *> \ingroup doubleGTcomputational
  134: *
  135: *  =====================================================================
  136:       SUBROUTINE DGTTRS( TRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB,
  137:      $                   INFO )
  138: *
  139: *  -- LAPACK computational routine --
  140: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  141: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  142: *
  143: *     .. Scalar Arguments ..
  144:       CHARACTER          TRANS
  145:       INTEGER            INFO, LDB, N, NRHS
  146: *     ..
  147: *     .. Array Arguments ..
  148:       INTEGER            IPIV( * )
  149:       DOUBLE PRECISION   B( LDB, * ), D( * ), DL( * ), DU( * ), DU2( * )
  150: *     ..
  151: *
  152: *  =====================================================================
  153: *
  154: *     .. Local Scalars ..
  155:       LOGICAL            NOTRAN
  156:       INTEGER            ITRANS, J, JB, NB
  157: *     ..
  158: *     .. External Functions ..
  159:       INTEGER            ILAENV
  160:       EXTERNAL           ILAENV
  161: *     ..
  162: *     .. External Subroutines ..
  163:       EXTERNAL           DGTTS2, XERBLA
  164: *     ..
  165: *     .. Intrinsic Functions ..
  166:       INTRINSIC          MAX, MIN
  167: *     ..
  168: *     .. Executable Statements ..
  169: *
  170:       INFO = 0
  171:       NOTRAN = ( TRANS.EQ.'N' .OR. TRANS.EQ.'n' )
  172:       IF( .NOT.NOTRAN .AND. .NOT.( TRANS.EQ.'T' .OR. TRANS.EQ.
  173:      $    't' ) .AND. .NOT.( TRANS.EQ.'C' .OR. TRANS.EQ.'c' ) ) THEN
  174:          INFO = -1
  175:       ELSE IF( N.LT.0 ) THEN
  176:          INFO = -2
  177:       ELSE IF( NRHS.LT.0 ) THEN
  178:          INFO = -3
  179:       ELSE IF( LDB.LT.MAX( N, 1 ) ) THEN
  180:          INFO = -10
  181:       END IF
  182:       IF( INFO.NE.0 ) THEN
  183:          CALL XERBLA( 'DGTTRS', -INFO )
  184:          RETURN
  185:       END IF
  186: *
  187: *     Quick return if possible
  188: *
  189:       IF( N.EQ.0 .OR. NRHS.EQ.0 )
  190:      $   RETURN
  191: *
  192: *     Decode TRANS
  193: *
  194:       IF( NOTRAN ) THEN
  195:          ITRANS = 0
  196:       ELSE
  197:          ITRANS = 1
  198:       END IF
  199: *
  200: *     Determine the number of right-hand sides to solve at a time.
  201: *
  202:       IF( NRHS.EQ.1 ) THEN
  203:          NB = 1
  204:       ELSE
  205:          NB = MAX( 1, ILAENV( 1, 'DGTTRS', TRANS, N, NRHS, -1, -1 ) )
  206:       END IF
  207: *
  208:       IF( NB.GE.NRHS ) THEN
  209:          CALL DGTTS2( ITRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB )
  210:       ELSE
  211:          DO 10 J = 1, NRHS, NB
  212:             JB = MIN( NRHS-J+1, NB )
  213:             CALL DGTTS2( ITRANS, N, JB, DL, D, DU, DU2, IPIV, B( 1, J ),
  214:      $                   LDB )
  215:    10    CONTINUE
  216:       END IF
  217: *
  218: *     End of DGTTRS
  219: *
  220:       END

CVSweb interface <joel.bertrand@systella.fr>