1       SUBROUTINE ZPOSV( UPLO, N, NRHS, A, LDA, B, LDB, INFO )
  2 *
  3 *  -- LAPACK driver routine (version 3.3.1) --
  4 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  5 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  6 *  -- April 2011                                                      --
  7 *
  8 *     .. Scalar Arguments ..
  9       CHARACTER          UPLO
 10       INTEGER            INFO, LDA, LDB, N, NRHS
 11 *     ..
 12 *     .. Array Arguments ..
 13       COMPLEX*16         A( LDA, * ), B( LDB, * )
 14 *     ..
 15 *
 16 *  Purpose
 17 *  =======
 18 *
 19 *  ZPOSV computes the solution to a complex system of linear equations
 20 *     A * X = B,
 21 *  where A is an N-by-N Hermitian positive definite matrix and X and B
 22 *  are N-by-NRHS matrices.
 23 *
 24 *  The Cholesky decomposition is used to factor A as
 25 *     A = U**H* U,  if UPLO = 'U', or
 26 *     A = L * L**H,  if UPLO = 'L',
 27 *  where U is an upper triangular matrix and  L is a lower triangular
 28 *  matrix.  The factored form of A is then used to solve the system of
 29 *  equations A * X = B.
 30 *
 31 *  Arguments
 32 *  =========
 33 *
 34 *  UPLO    (input) CHARACTER*1
 35 *          = 'U':  Upper triangle of A is stored;
 36 *          = 'L':  Lower triangle of A is stored.
 37 *
 38 *  N       (input) INTEGER
 39 *          The number of linear equations, i.e., the order of the
 40 *          matrix A.  N >= 0.
 41 *
 42 *  NRHS    (input) INTEGER
 43 *          The number of right hand sides, i.e., the number of columns
 44 *          of the matrix B.  NRHS >= 0.
 45 *
 46 *  A       (input/output) COMPLEX*16 array, dimension (LDA,N)
 47 *          On entry, the Hermitian matrix A.  If UPLO = 'U', the leading
 48 *          N-by-N upper triangular part of A contains the upper
 49 *          triangular part of the matrix A, and the strictly lower
 50 *          triangular part of A is not referenced.  If UPLO = 'L', the
 51 *          leading N-by-N lower triangular part of A contains the lower
 52 *          triangular part of the matrix A, and the strictly upper
 53 *          triangular part of A is not referenced.
 54 *
 55 *          On exit, if INFO = 0, the factor U or L from the Cholesky
 56 *          factorization A = U**H *U or A = L*L**H.
 57 *
 58 *  LDA     (input) INTEGER
 59 *          The leading dimension of the array A.  LDA >= max(1,N).
 60 *
 61 *  B       (input/output) COMPLEX*16 array, dimension (LDB,NRHS)
 62 *          On entry, the N-by-NRHS right hand side matrix B.
 63 *          On exit, if INFO = 0, the N-by-NRHS solution matrix X.
 64 *
 65 *  LDB     (input) INTEGER
 66 *          The leading dimension of the array B.  LDB >= max(1,N).
 67 *
 68 *  INFO    (output) INTEGER
 69 *          = 0:  successful exit
 70 *          < 0:  if INFO = -i, the i-th argument had an illegal value
 71 *          > 0:  if INFO = i, the leading minor of order i of A is not
 72 *                positive definite, so the factorization could not be
 73 *                completed, and the solution has not been computed.
 74 *
 75 *  =====================================================================
 76 *
 77 *     .. External Functions ..
 78       LOGICAL            LSAME
 79       EXTERNAL           LSAME
 80 *     ..
 81 *     .. External Subroutines ..
 82       EXTERNAL           XERBLA, ZPOTRF, ZPOTRS
 83 *     ..
 84 *     .. Intrinsic Functions ..
 85       INTRINSIC          MAX
 86 *     ..
 87 *     .. Executable Statements ..
 88 *
 89 *     Test the input parameters.
 90 *
 91       INFO = 0
 92       IF.NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
 93          INFO = -1
 94       ELSE IF( N.LT.0 ) THEN
 95          INFO = -2
 96       ELSE IF( NRHS.LT.0 ) THEN
 97          INFO = -3
 98       ELSE IF( LDA.LT.MAX1, N ) ) THEN
 99          INFO = -5
100       ELSE IF( LDB.LT.MAX1, N ) ) THEN
101          INFO = -7
102       END IF
103       IF( INFO.NE.0 ) THEN
104          CALL XERBLA( 'ZPOSV '-INFO )
105          RETURN
106       END IF
107 *
108 *     Compute the Cholesky factorization A = U**H *U or A = L*L**H.
109 *
110       CALL ZPOTRF( UPLO, N, A, LDA, INFO )
111       IF( INFO.EQ.0 ) THEN
112 *
113 *        Solve the system A*X = B, overwriting B with X.
114 *
115          CALL ZPOTRS( UPLO, N, NRHS, A, LDA, B, LDB, INFO )
116 *
117       END IF
118       RETURN
119 *
120 *     End of ZPOSV
121 *
122       END