Annotation of rpl/lapack/lapack/dpftrs.f, revision 1.16

1.7       bertrand    1: *> \brief \b DPFTRS
1.1       bertrand    2: *
1.7       bertrand    3: *  =========== DOCUMENTATION ===========
1.1       bertrand    4: *
1.13      bertrand    5: * Online html documentation available at
                      6: *            http://www.netlib.org/lapack/explore-html/
1.1       bertrand    7: *
1.7       bertrand    8: *> \htmlonly
1.13      bertrand    9: *> Download DPFTRS + dependencies
                     10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dpftrs.f">
                     11: *> [TGZ]</a>
                     12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dpftrs.f">
                     13: *> [ZIP]</a>
                     14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dpftrs.f">
1.7       bertrand   15: *> [TXT]</a>
1.13      bertrand   16: *> \endhtmlonly
1.7       bertrand   17: *
                     18: *  Definition:
                     19: *  ===========
                     20: *
                     21: *       SUBROUTINE DPFTRS( TRANSR, UPLO, N, NRHS, A, B, LDB, INFO )
1.13      bertrand   22: *
1.7       bertrand   23: *       .. Scalar Arguments ..
                     24: *       CHARACTER          TRANSR, UPLO
                     25: *       INTEGER            INFO, LDB, N, NRHS
                     26: *       ..
                     27: *       .. Array Arguments ..
                     28: *       DOUBLE PRECISION   A( 0: * ), B( LDB, * )
                     29: *       ..
1.13      bertrand   30: *
1.7       bertrand   31: *
                     32: *> \par Purpose:
                     33: *  =============
                     34: *>
                     35: *> \verbatim
                     36: *>
                     37: *> DPFTRS solves a system of linear equations A*X = B with a symmetric
                     38: *> positive definite matrix A using the Cholesky factorization
                     39: *> A = U**T*U or A = L*L**T computed by DPFTRF.
                     40: *> \endverbatim
                     41: *
                     42: *  Arguments:
                     43: *  ==========
                     44: *
                     45: *> \param[in] TRANSR
                     46: *> \verbatim
                     47: *>          TRANSR is CHARACTER*1
                     48: *>          = 'N':  The Normal TRANSR of RFP A is stored;
                     49: *>          = 'T':  The Transpose TRANSR of RFP A is stored.
                     50: *> \endverbatim
                     51: *>
                     52: *> \param[in] UPLO
                     53: *> \verbatim
                     54: *>          UPLO is CHARACTER*1
                     55: *>          = 'U':  Upper triangle of RFP A is stored;
                     56: *>          = 'L':  Lower triangle of RFP A is stored.
                     57: *> \endverbatim
                     58: *>
                     59: *> \param[in] N
                     60: *> \verbatim
                     61: *>          N is INTEGER
                     62: *>          The order of the matrix A.  N >= 0.
                     63: *> \endverbatim
                     64: *>
                     65: *> \param[in] NRHS
                     66: *> \verbatim
                     67: *>          NRHS is INTEGER
                     68: *>          The number of right hand sides, i.e., the number of columns
                     69: *>          of the matrix B.  NRHS >= 0.
                     70: *> \endverbatim
                     71: *>
                     72: *> \param[in] A
                     73: *> \verbatim
                     74: *>          A is DOUBLE PRECISION array, dimension ( N*(N+1)/2 ).
                     75: *>          The triangular factor U or L from the Cholesky factorization
                     76: *>          of RFP A = U**T*U or RFP A = L*L**T, as computed by DPFTRF.
                     77: *>          See note below for more details about RFP A.
                     78: *> \endverbatim
                     79: *>
                     80: *> \param[in,out] B
                     81: *> \verbatim
                     82: *>          B is DOUBLE PRECISION array, dimension (LDB,NRHS)
                     83: *>          On entry, the right hand side matrix B.
                     84: *>          On exit, the solution matrix X.
                     85: *> \endverbatim
                     86: *>
                     87: *> \param[in] LDB
                     88: *> \verbatim
                     89: *>          LDB is INTEGER
                     90: *>          The leading dimension of the array B.  LDB >= max(1,N).
                     91: *> \endverbatim
                     92: *>
                     93: *> \param[out] INFO
                     94: *> \verbatim
                     95: *>          INFO is INTEGER
                     96: *>          = 0:  successful exit
                     97: *>          < 0:  if INFO = -i, the i-th argument had an illegal value
                     98: *> \endverbatim
                     99: *
                    100: *  Authors:
                    101: *  ========
                    102: *
1.13      bertrand  103: *> \author Univ. of Tennessee
                    104: *> \author Univ. of California Berkeley
                    105: *> \author Univ. of Colorado Denver
                    106: *> \author NAG Ltd.
1.7       bertrand  107: *
                    108: *> \ingroup doubleOTHERcomputational
                    109: *
                    110: *> \par Further Details:
                    111: *  =====================
                    112: *>
                    113: *> \verbatim
                    114: *>
                    115: *>  We first consider Rectangular Full Packed (RFP) Format when N is
                    116: *>  even. We give an example where N = 6.
                    117: *>
                    118: *>      AP is Upper             AP is Lower
                    119: *>
                    120: *>   00 01 02 03 04 05       00
                    121: *>      11 12 13 14 15       10 11
                    122: *>         22 23 24 25       20 21 22
                    123: *>            33 34 35       30 31 32 33
                    124: *>               44 45       40 41 42 43 44
                    125: *>                  55       50 51 52 53 54 55
                    126: *>
                    127: *>
                    128: *>  Let TRANSR = 'N'. RFP holds AP as follows:
                    129: *>  For UPLO = 'U' the upper trapezoid A(0:5,0:2) consists of the last
                    130: *>  three columns of AP upper. The lower triangle A(4:6,0:2) consists of
                    131: *>  the transpose of the first three columns of AP upper.
                    132: *>  For UPLO = 'L' the lower trapezoid A(1:6,0:2) consists of the first
                    133: *>  three columns of AP lower. The upper triangle A(0:2,0:2) consists of
                    134: *>  the transpose of the last three columns of AP lower.
                    135: *>  This covers the case N even and TRANSR = 'N'.
                    136: *>
                    137: *>         RFP A                   RFP A
                    138: *>
                    139: *>        03 04 05                33 43 53
                    140: *>        13 14 15                00 44 54
                    141: *>        23 24 25                10 11 55
                    142: *>        33 34 35                20 21 22
                    143: *>        00 44 45                30 31 32
                    144: *>        01 11 55                40 41 42
                    145: *>        02 12 22                50 51 52
                    146: *>
                    147: *>  Now let TRANSR = 'T'. RFP A in both UPLO cases is just the
                    148: *>  transpose of RFP A above. One therefore gets:
                    149: *>
                    150: *>
                    151: *>           RFP A                   RFP A
                    152: *>
                    153: *>     03 13 23 33 00 01 02    33 00 10 20 30 40 50
                    154: *>     04 14 24 34 44 11 12    43 44 11 21 31 41 51
                    155: *>     05 15 25 35 45 55 22    53 54 55 22 32 42 52
                    156: *>
                    157: *>
                    158: *>  We then consider Rectangular Full Packed (RFP) Format when N is
                    159: *>  odd. We give an example where N = 5.
                    160: *>
                    161: *>     AP is Upper                 AP is Lower
                    162: *>
                    163: *>   00 01 02 03 04              00
                    164: *>      11 12 13 14              10 11
                    165: *>         22 23 24              20 21 22
                    166: *>            33 34              30 31 32 33
                    167: *>               44              40 41 42 43 44
                    168: *>
                    169: *>
                    170: *>  Let TRANSR = 'N'. RFP holds AP as follows:
                    171: *>  For UPLO = 'U' the upper trapezoid A(0:4,0:2) consists of the last
                    172: *>  three columns of AP upper. The lower triangle A(3:4,0:1) consists of
                    173: *>  the transpose of the first two columns of AP upper.
                    174: *>  For UPLO = 'L' the lower trapezoid A(0:4,0:2) consists of the first
                    175: *>  three columns of AP lower. The upper triangle A(0:1,1:2) consists of
                    176: *>  the transpose of the last two columns of AP lower.
                    177: *>  This covers the case N odd and TRANSR = 'N'.
                    178: *>
                    179: *>         RFP A                   RFP A
                    180: *>
                    181: *>        02 03 04                00 33 43
                    182: *>        12 13 14                10 11 44
                    183: *>        22 23 24                20 21 22
                    184: *>        00 33 34                30 31 32
                    185: *>        01 11 44                40 41 42
                    186: *>
                    187: *>  Now let TRANSR = 'T'. RFP A in both UPLO cases is just the
                    188: *>  transpose of RFP A above. One therefore gets:
                    189: *>
                    190: *>           RFP A                   RFP A
                    191: *>
                    192: *>     02 12 22 00 01             00 10 20 30 40 50
                    193: *>     03 13 23 33 11             33 11 21 31 41 51
                    194: *>     04 14 24 34 44             43 44 22 32 42 52
                    195: *> \endverbatim
                    196: *>
                    197: *  =====================================================================
                    198:       SUBROUTINE DPFTRS( TRANSR, UPLO, N, NRHS, A, B, LDB, INFO )
                    199: *
1.16    ! bertrand  200: *  -- LAPACK computational routine --
1.1       bertrand  201: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
                    202: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
                    203: *
                    204: *     .. Scalar Arguments ..
                    205:       CHARACTER          TRANSR, UPLO
                    206:       INTEGER            INFO, LDB, N, NRHS
                    207: *     ..
                    208: *     .. Array Arguments ..
                    209:       DOUBLE PRECISION   A( 0: * ), B( LDB, * )
                    210: *     ..
                    211: *
                    212: *  =====================================================================
                    213: *
                    214: *     .. Parameters ..
                    215:       DOUBLE PRECISION   ONE
                    216:       PARAMETER          ( ONE = 1.0D+0 )
                    217: *     ..
                    218: *     .. Local Scalars ..
                    219:       LOGICAL            LOWER, NORMALTRANSR
                    220: *     ..
                    221: *     .. External Functions ..
                    222:       LOGICAL            LSAME
                    223:       EXTERNAL           LSAME
                    224: *     ..
                    225: *     .. External Subroutines ..
                    226:       EXTERNAL           XERBLA, DTFSM
                    227: *     ..
                    228: *     .. Intrinsic Functions ..
                    229:       INTRINSIC          MAX
                    230: *     ..
                    231: *     .. Executable Statements ..
                    232: *
                    233: *     Test the input parameters.
                    234: *
                    235:       INFO = 0
                    236:       NORMALTRANSR = LSAME( TRANSR, 'N' )
                    237:       LOWER = LSAME( UPLO, 'L' )
                    238:       IF( .NOT.NORMALTRANSR .AND. .NOT.LSAME( TRANSR, 'T' ) ) THEN
                    239:          INFO = -1
                    240:       ELSE IF( .NOT.LOWER .AND. .NOT.LSAME( UPLO, 'U' ) ) THEN
                    241:          INFO = -2
                    242:       ELSE IF( N.LT.0 ) THEN
                    243:          INFO = -3
                    244:       ELSE IF( NRHS.LT.0 ) THEN
                    245:          INFO = -4
                    246:       ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
                    247:          INFO = -7
                    248:       END IF
                    249:       IF( INFO.NE.0 ) THEN
                    250:          CALL XERBLA( 'DPFTRS', -INFO )
                    251:          RETURN
                    252:       END IF
                    253: *
                    254: *     Quick return if possible
                    255: *
                    256:       IF( N.EQ.0 .OR. NRHS.EQ.0 )
1.6       bertrand  257:      $   RETURN
1.1       bertrand  258: *
                    259: *     start execution: there are two triangular solves
                    260: *
                    261:       IF( LOWER ) THEN
                    262:          CALL DTFSM( TRANSR, 'L', UPLO, 'N', 'N', N, NRHS, ONE, A, B,
1.6       bertrand  263:      $               LDB )
1.1       bertrand  264:          CALL DTFSM( TRANSR, 'L', UPLO, 'T', 'N', N, NRHS, ONE, A, B,
1.6       bertrand  265:      $               LDB )
1.1       bertrand  266:       ELSE
                    267:          CALL DTFSM( TRANSR, 'L', UPLO, 'T', 'N', N, NRHS, ONE, A, B,
1.6       bertrand  268:      $               LDB )
1.1       bertrand  269:          CALL DTFSM( TRANSR, 'L', UPLO, 'N', 'N', N, NRHS, ONE, A, B,
1.6       bertrand  270:      $               LDB )
1.1       bertrand  271:       END IF
                    272: *
                    273:       RETURN
                    274: *
                    275: *     End of DPFTRS
                    276: *
                    277:       END

CVSweb interface <joel.bertrand@systella.fr>