Lots of trailing whitespaces in the files of Syd. Cleaning this. No big deal.
[platform/upstream/lapack.git] / SRC / zposv.f
1 *> \brief <b> ZPOSV computes the solution to system of linear equations A * X = B for PO 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 ZPOSV + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zposv.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zposv.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zposv.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE ZPOSV( UPLO, N, NRHS, A, LDA, B, LDB, INFO )
22 *
23 *       .. Scalar Arguments ..
24 *       CHARACTER          UPLO
25 *       INTEGER            INFO, LDA, LDB, N, NRHS
26 *       ..
27 *       .. Array Arguments ..
28 *       COMPLEX*16         A( LDA, * ), B( LDB, * )
29 *       ..
30 *
31 *
32 *> \par Purpose:
33 *  =============
34 *>
35 *> \verbatim
36 *>
37 *> ZPOSV 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 and X and B
40 *> 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] A
75 *> \verbatim
76 *>          A is COMPLEX*16 array, dimension (LDA,N)
77 *>          On entry, the Hermitian matrix A.  If UPLO = 'U', the leading
78 *>          N-by-N upper triangular part of A contains the upper
79 *>          triangular part of the matrix A, and the strictly lower
80 *>          triangular part of A is not referenced.  If UPLO = 'L', the
81 *>          leading N-by-N lower triangular part of A contains the lower
82 *>          triangular part of the matrix A, and the strictly upper
83 *>          triangular part of A is not referenced.
84 *>
85 *>          On exit, if INFO = 0, the factor U or L from the Cholesky
86 *>          factorization A = U**H *U or A = L*L**H.
87 *> \endverbatim
88 *>
89 *> \param[in] LDA
90 *> \verbatim
91 *>          LDA is INTEGER
92 *>          The leading dimension of the array A.  LDA >= max(1,N).
93 *> \endverbatim
94 *>
95 *> \param[in,out] B
96 *> \verbatim
97 *>          B is COMPLEX*16 array, dimension (LDB,NRHS)
98 *>          On entry, the N-by-NRHS right hand side matrix B.
99 *>          On exit, if INFO = 0, the N-by-NRHS solution matrix X.
100 *> \endverbatim
101 *>
102 *> \param[in] LDB
103 *> \verbatim
104 *>          LDB is INTEGER
105 *>          The leading dimension of the array B.  LDB >= max(1,N).
106 *> \endverbatim
107 *>
108 *> \param[out] INFO
109 *> \verbatim
110 *>          INFO is INTEGER
111 *>          = 0:  successful exit
112 *>          < 0:  if INFO = -i, the i-th argument had an illegal value
113 *>          > 0:  if INFO = i, the leading minor of order i of A is not
114 *>                positive definite, so the factorization could not be
115 *>                completed, and the solution has not been computed.
116 *> \endverbatim
117 *
118 *  Authors:
119 *  ========
120 *
121 *> \author Univ. of Tennessee
122 *> \author Univ. of California Berkeley
123 *> \author Univ. of Colorado Denver
124 *> \author NAG Ltd.
125 *
126 *> \date November 2011
127 *
128 *> \ingroup complex16POsolve
129 *
130 *  =====================================================================
131       SUBROUTINE ZPOSV( UPLO, N, NRHS, A, LDA, B, LDB, INFO )
132 *
133 *  -- LAPACK driver routine (version 3.4.0) --
134 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
135 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
136 *     November 2011
137 *
138 *     .. Scalar Arguments ..
139       CHARACTER          UPLO
140       INTEGER            INFO, LDA, LDB, N, NRHS
141 *     ..
142 *     .. Array Arguments ..
143       COMPLEX*16         A( LDA, * ), B( LDB, * )
144 *     ..
145 *
146 *  =====================================================================
147 *
148 *     .. External Functions ..
149       LOGICAL            LSAME
150       EXTERNAL           LSAME
151 *     ..
152 *     .. External Subroutines ..
153       EXTERNAL           XERBLA, ZPOTRF, ZPOTRS
154 *     ..
155 *     .. Intrinsic Functions ..
156       INTRINSIC          MAX
157 *     ..
158 *     .. Executable Statements ..
159 *
160 *     Test the input parameters.
161 *
162       INFO = 0
163       IF( .NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
164          INFO = -1
165       ELSE IF( N.LT.0 ) THEN
166          INFO = -2
167       ELSE IF( NRHS.LT.0 ) THEN
168          INFO = -3
169       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
170          INFO = -5
171       ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
172          INFO = -7
173       END IF
174       IF( INFO.NE.0 ) THEN
175          CALL XERBLA( 'ZPOSV ', -INFO )
176          RETURN
177       END IF
178 *
179 *     Compute the Cholesky factorization A = U**H *U or A = L*L**H.
180 *
181       CALL ZPOTRF( UPLO, N, A, LDA, INFO )
182       IF( INFO.EQ.0 ) THEN
183 *
184 *        Solve the system A*X = B, overwriting B with X.
185 *
186          CALL ZPOTRS( UPLO, N, NRHS, A, LDA, B, LDB, INFO )
187 *
188       END IF
189       RETURN
190 *
191 *     End of ZPOSV
192 *
193       END