001:       SUBROUTINE ZPOTRS( UPLO, N, NRHS, A, LDA, B, LDB, INFO )
002: *
003: *  -- LAPACK routine (version 3.2) --
004: *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
005: *     November 2006
006: *
007: *     .. Scalar Arguments ..
008:       CHARACTER          UPLO
009:       INTEGER            INFO, LDA, LDB, N, NRHS
010: *     ..
011: *     .. Array Arguments ..
012:       COMPLEX*16         A( LDA, * ), B( LDB, * )
013: *     ..
014: *
015: *  Purpose
016: *  =======
017: *
018: *  ZPOTRS solves a system of linear equations A*X = B with a Hermitian
019: *  positive definite matrix A using the Cholesky factorization
020: *  A = U**H*U or A = L*L**H computed by ZPOTRF.
021: *
022: *  Arguments
023: *  =========
024: *
025: *  UPLO    (input) CHARACTER*1
026: *          = 'U':  Upper triangle of A is stored;
027: *          = 'L':  Lower triangle of A is stored.
028: *
029: *  N       (input) INTEGER
030: *          The order of the matrix A.  N >= 0.
031: *
032: *  NRHS    (input) INTEGER
033: *          The number of right hand sides, i.e., the number of columns
034: *          of the matrix B.  NRHS >= 0.
035: *
036: *  A       (input) COMPLEX*16 array, dimension (LDA,N)
037: *          The triangular factor U or L from the Cholesky factorization
038: *          A = U**H*U or A = L*L**H, as computed by ZPOTRF.
039: *
040: *  LDA     (input) INTEGER
041: *          The leading dimension of the array A.  LDA >= max(1,N).
042: *
043: *  B       (input/output) COMPLEX*16 array, dimension (LDB,NRHS)
044: *          On entry, the right hand side matrix B.
045: *          On exit, the solution matrix X.
046: *
047: *  LDB     (input) INTEGER
048: *          The leading dimension of the array B.  LDB >= max(1,N).
049: *
050: *  INFO    (output) INTEGER
051: *          = 0:  successful exit
052: *          < 0:  if INFO = -i, the i-th argument had an illegal value
053: *
054: *  =====================================================================
055: *
056: *     .. Parameters ..
057:       COMPLEX*16         ONE
058:       PARAMETER          ( ONE = ( 1.0D+0, 0.0D+0 ) )
059: *     ..
060: *     .. Local Scalars ..
061:       LOGICAL            UPPER
062: *     ..
063: *     .. External Functions ..
064:       LOGICAL            LSAME
065:       EXTERNAL           LSAME
066: *     ..
067: *     .. External Subroutines ..
068:       EXTERNAL           XERBLA, ZTRSM
069: *     ..
070: *     .. Intrinsic Functions ..
071:       INTRINSIC          MAX
072: *     ..
073: *     .. Executable Statements ..
074: *
075: *     Test the input parameters.
076: *
077:       INFO = 0
078:       UPPER = LSAME( UPLO, 'U' )
079:       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
080:          INFO = -1
081:       ELSE IF( N.LT.0 ) THEN
082:          INFO = -2
083:       ELSE IF( NRHS.LT.0 ) THEN
084:          INFO = -3
085:       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
086:          INFO = -5
087:       ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
088:          INFO = -7
089:       END IF
090:       IF( INFO.NE.0 ) THEN
091:          CALL XERBLA( 'ZPOTRS', -INFO )
092:          RETURN
093:       END IF
094: *
095: *     Quick return if possible
096: *
097:       IF( N.EQ.0 .OR. NRHS.EQ.0 )
098:      $   RETURN
099: *
100:       IF( UPPER ) THEN
101: *
102: *        Solve A*X = B where A = U'*U.
103: *
104: *        Solve U'*X = B, overwriting B with X.
105: *
106:          CALL ZTRSM( 'Left', 'Upper', 'Conjugate transpose', 'Non-unit',
107:      $               N, NRHS, ONE, A, LDA, B, LDB )
108: *
109: *        Solve U*X = B, overwriting B with X.
110: *
111:          CALL ZTRSM( 'Left', 'Upper', 'No transpose', 'Non-unit', N,
112:      $               NRHS, ONE, A, LDA, B, LDB )
113:       ELSE
114: *
115: *        Solve A*X = B where A = L*L'.
116: *
117: *        Solve L*X = B, overwriting B with X.
118: *
119:          CALL ZTRSM( 'Left', 'Lower', 'No transpose', 'Non-unit', N,
120:      $               NRHS, ONE, A, LDA, B, LDB )
121: *
122: *        Solve L'*X = B, overwriting B with X.
123: *
124:          CALL ZTRSM( 'Left', 'Lower', 'Conjugate transpose', 'Non-unit',
125:      $               N, NRHS, ONE, A, LDA, B, LDB )
126:       END IF
127: *
128:       RETURN
129: *
130: *     End of ZPOTRS
131: *
132:       END
133: