1       SUBROUTINE ZPPSV( UPLO, N, NRHS, AP, 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, LDB, N, NRHS
 11 *     ..
 12 *     .. Array Arguments ..
 13       COMPLEX*16         AP( * ), B( LDB, * )
 14 *     ..
 15 *
 16 *  Purpose
 17 *  =======
 18 *
 19 *  ZPPSV 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 stored in
 22 *  packed format and X and B 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 *  AP      (input/output) COMPLEX*16 array, dimension (N*(N+1)/2)
 47 *          On entry, the upper or lower triangle of the Hermitian matrix
 48 *          A, packed columnwise in a linear array.  The j-th column of A
 49 *          is stored in the array AP as follows:
 50 *          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
 51 *          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
 52 *          See below for further details.
 53 *
 54 *          On exit, if INFO = 0, the factor U or L from the Cholesky
 55 *          factorization A = U**H*U or A = L*L**H, in the same storage
 56 *          format as A.
 57 *
 58 *  B       (input/output) COMPLEX*16 array, dimension (LDB,NRHS)
 59 *          On entry, the N-by-NRHS right hand side matrix B.
 60 *          On exit, if INFO = 0, the N-by-NRHS solution matrix X.
 61 *
 62 *  LDB     (input) INTEGER
 63 *          The leading dimension of the array B.  LDB >= max(1,N).
 64 *
 65 *  INFO    (output) INTEGER
 66 *          = 0:  successful exit
 67 *          < 0:  if INFO = -i, the i-th argument had an illegal value
 68 *          > 0:  if INFO = i, the leading minor of order i of A is not
 69 *                positive definite, so the factorization could not be
 70 *                completed, and the solution has not been computed.
 71 *
 72 *  Further Details
 73 *  ===============
 74 *
 75 *  The packed storage scheme is illustrated by the following example
 76 *  when N = 4, UPLO = 'U':
 77 *
 78 *  Two-dimensional storage of the Hermitian matrix A:
 79 *
 80 *     a11 a12 a13 a14
 81 *         a22 a23 a24
 82 *             a33 a34     (aij = conjg(aji))
 83 *                 a44
 84 *
 85 *  Packed storage of the upper triangle of A:
 86 *
 87 *  AP = [ a11, a12, a22, a13, a23, a33, a14, a24, a34, a44 ]
 88 *
 89 *  =====================================================================
 90 *
 91 *     .. External Functions ..
 92       LOGICAL            LSAME
 93       EXTERNAL           LSAME
 94 *     ..
 95 *     .. External Subroutines ..
 96       EXTERNAL           XERBLA, ZPPTRF, ZPPTRS
 97 *     ..
 98 *     .. Intrinsic Functions ..
 99       INTRINSIC          MAX
100 *     ..
101 *     .. Executable Statements ..
102 *
103 *     Test the input parameters.
104 *
105       INFO = 0
106       IF.NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
107          INFO = -1
108       ELSE IF( N.LT.0 ) THEN
109          INFO = -2
110       ELSE IF( NRHS.LT.0 ) THEN
111          INFO = -3
112       ELSE IF( LDB.LT.MAX1, N ) ) THEN
113          INFO = -6
114       END IF
115       IF( INFO.NE.0 ) THEN
116          CALL XERBLA( 'ZPPSV '-INFO )
117          RETURN
118       END IF
119 *
120 *     Compute the Cholesky factorization A = U**H *U or A = L*L**H.
121 *
122       CALL ZPPTRF( UPLO, N, AP, INFO )
123       IF( INFO.EQ.0 ) THEN
124 *
125 *        Solve the system A*X = B, overwriting B with X.
126 *
127          CALL ZPPTRS( UPLO, N, NRHS, AP, B, LDB, INFO )
128 *
129       END IF
130       RETURN
131 *
132 *     End of ZPPSV
133 *
134       END