1*> \brief <b> CPPSV computes the solution to system of linear equations A * X = B for OTHER matrices</b>
2*
3*  =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6*            http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download CPPSV + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cppsv.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cppsv.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cppsv.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18*  Definition:
19*  ===========
20*
21*       SUBROUTINE CPPSV( UPLO, N, NRHS, AP, B, LDB, INFO )
22*
23*       .. Scalar Arguments ..
24*       CHARACTER          UPLO
25*       INTEGER            INFO, LDB, N, NRHS
26*       ..
27*       .. Array Arguments ..
28*       COMPLEX            AP( * ), B( LDB, * )
29*       ..
30*
31*
32*> \par Purpose:
33*  =============
34*>
35*> \verbatim
36*>
37*> CPPSV computes the solution to a complex system of linear equations
38*>    A * X = B,
39*> where A is an N-by-N Hermitian positive definite matrix stored in
40*> packed format and X and B are N-by-NRHS matrices.
41*>
42*> The Cholesky decomposition is used to factor A as
43*>    A = U**H * U,  if UPLO = 'U', or
44*>    A = L * L**H,  if UPLO = 'L',
45*> where U is an upper triangular matrix and L is a lower triangular
46*> matrix.  The factored form of A is then used to solve the system of
47*> equations A * X = B.
48*> \endverbatim
49*
50*  Arguments:
51*  ==========
52*
53*> \param[in] UPLO
54*> \verbatim
55*>          UPLO is CHARACTER*1
56*>          = 'U':  Upper triangle of A is stored;
57*>          = 'L':  Lower triangle of A is stored.
58*> \endverbatim
59*>
60*> \param[in] N
61*> \verbatim
62*>          N is INTEGER
63*>          The number of linear equations, i.e., the order of the
64*>          matrix A.  N >= 0.
65*> \endverbatim
66*>
67*> \param[in] NRHS
68*> \verbatim
69*>          NRHS is INTEGER
70*>          The number of right hand sides, i.e., the number of columns
71*>          of the matrix B.  NRHS >= 0.
72*> \endverbatim
73*>
74*> \param[in,out] AP
75*> \verbatim
76*>          AP is COMPLEX array, dimension (N*(N+1)/2)
77*>          On entry, the upper or lower triangle of the Hermitian matrix
78*>          A, packed columnwise in a linear array.  The j-th column of A
79*>          is stored in the array AP as follows:
80*>          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
81*>          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
82*>          See below for further details.
83*>
84*>          On exit, if INFO = 0, the factor U or L from the Cholesky
85*>          factorization A = U**H*U or A = L*L**H, in the same storage
86*>          format as A.
87*> \endverbatim
88*>
89*> \param[in,out] B
90*> \verbatim
91*>          B is COMPLEX array, dimension (LDB,NRHS)
92*>          On entry, the N-by-NRHS right hand side matrix B.
93*>          On exit, if INFO = 0, the N-by-NRHS solution matrix X.
94*> \endverbatim
95*>
96*> \param[in] LDB
97*> \verbatim
98*>          LDB is INTEGER
99*>          The leading dimension of the array B.  LDB >= max(1,N).
100*> \endverbatim
101*>
102*> \param[out] INFO
103*> \verbatim
104*>          INFO is INTEGER
105*>          = 0:  successful exit
106*>          < 0:  if INFO = -i, the i-th argument had an illegal value
107*>          > 0:  if INFO = i, the leading minor of order i of A is not
108*>                positive definite, so the factorization could not be
109*>                completed, and the solution has not been computed.
110*> \endverbatim
111*
112*  Authors:
113*  ========
114*
115*> \author Univ. of Tennessee
116*> \author Univ. of California Berkeley
117*> \author Univ. of Colorado Denver
118*> \author NAG Ltd.
119*
120*> \ingroup complexOTHERsolve
121*
122*> \par Further Details:
123*  =====================
124*>
125*> \verbatim
126*>
127*>  The packed storage scheme is illustrated by the following example
128*>  when N = 4, UPLO = 'U':
129*>
130*>  Two-dimensional storage of the Hermitian matrix A:
131*>
132*>     a11 a12 a13 a14
133*>         a22 a23 a24
134*>             a33 a34     (aij = conjg(aji))
135*>                 a44
136*>
137*>  Packed storage of the upper triangle of A:
138*>
139*>  AP = [ a11, a12, a22, a13, a23, a33, a14, a24, a34, a44 ]
140*> \endverbatim
141*>
142*  =====================================================================
143      SUBROUTINE CPPSV( UPLO, N, NRHS, AP, B, LDB, INFO )
144*
145*  -- LAPACK driver routine --
146*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
147*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
148*
149*     .. Scalar Arguments ..
150      CHARACTER          UPLO
151      INTEGER            INFO, LDB, N, NRHS
152*     ..
153*     .. Array Arguments ..
154      COMPLEX            AP( * ), B( LDB, * )
155*     ..
156*
157*  =====================================================================
158*
159*     .. External Functions ..
160      LOGICAL            LSAME
161      EXTERNAL           LSAME
162*     ..
163*     .. External Subroutines ..
164      EXTERNAL           CPPTRF, CPPTRS, XERBLA
165*     ..
166*     .. Intrinsic Functions ..
167      INTRINSIC          MAX
168*     ..
169*     .. Executable Statements ..
170*
171*     Test the input parameters.
172*
173      INFO = 0
174      IF( .NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
175         INFO = -1
176      ELSE IF( N.LT.0 ) THEN
177         INFO = -2
178      ELSE IF( NRHS.LT.0 ) THEN
179         INFO = -3
180      ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
181         INFO = -6
182      END IF
183      IF( INFO.NE.0 ) THEN
184         CALL XERBLA( 'CPPSV ', -INFO )
185         RETURN
186      END IF
187*
188*     Compute the Cholesky factorization A = U**H *U or A = L*L**H.
189*
190      CALL CPPTRF( UPLO, N, AP, INFO )
191      IF( INFO.EQ.0 ) THEN
192*
193*        Solve the system A*X = B, overwriting B with X.
194*
195         CALL CPPTRS( UPLO, N, NRHS, AP, B, LDB, INFO )
196*
197      END IF
198      RETURN
199*
200*     End of CPPSV
201*
202      END
203