LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cposv.f
Go to the documentation of this file.
1*> \brief <b> CPOSV 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*> Download CPOSV + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cposv.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cposv.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cposv.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CPOSV( UPLO, N, NRHS, A, LDA, B, LDB, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, LDA, LDB, N, NRHS
24* ..
25* .. Array Arguments ..
26* COMPLEX A( LDA, * ), B( LDB, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> CPOSV computes the solution to a complex system of linear equations
36*> A * X = B,
37*> where A is an N-by-N Hermitian positive definite matrix and X and B
38*> are N-by-NRHS matrices.
39*>
40*> The Cholesky decomposition is used to factor A as
41*> A = U**H* U, if UPLO = 'U', or
42*> A = L * L**H, if UPLO = 'L',
43*> where U is an upper triangular matrix and L is a lower triangular
44*> matrix. The factored form of A is then used to solve the system of
45*> equations A * X = B.
46*> \endverbatim
47*
48* Arguments:
49* ==========
50*
51*> \param[in] UPLO
52*> \verbatim
53*> UPLO is CHARACTER*1
54*> = 'U': Upper triangle of A is stored;
55*> = 'L': Lower triangle of A is stored.
56*> \endverbatim
57*>
58*> \param[in] N
59*> \verbatim
60*> N is INTEGER
61*> The number of linear equations, i.e., the order of the
62*> matrix A. N >= 0.
63*> \endverbatim
64*>
65*> \param[in] NRHS
66*> \verbatim
67*> NRHS is INTEGER
68*> The number of right hand sides, i.e., the number of columns
69*> of the matrix B. NRHS >= 0.
70*> \endverbatim
71*>
72*> \param[in,out] A
73*> \verbatim
74*> A is COMPLEX array, dimension (LDA,N)
75*> On entry, the Hermitian matrix A. If UPLO = 'U', the leading
76*> N-by-N upper triangular part of A contains the upper
77*> triangular part of the matrix A, and the strictly lower
78*> triangular part of A is not referenced. If UPLO = 'L', the
79*> leading N-by-N lower triangular part of A contains the lower
80*> triangular part of the matrix A, and the strictly upper
81*> triangular part of A is not referenced.
82*>
83*> On exit, if INFO = 0, the factor U or L from the Cholesky
84*> factorization A = U**H*U or A = L*L**H.
85*> \endverbatim
86*>
87*> \param[in] LDA
88*> \verbatim
89*> LDA is INTEGER
90*> The leading dimension of the array A. LDA >= max(1,N).
91*> \endverbatim
92*>
93*> \param[in,out] B
94*> \verbatim
95*> B is COMPLEX array, dimension (LDB,NRHS)
96*> On entry, the N-by-NRHS right hand side matrix B.
97*> On exit, if INFO = 0, the N-by-NRHS solution matrix X.
98*> \endverbatim
99*>
100*> \param[in] LDB
101*> \verbatim
102*> LDB is INTEGER
103*> The leading dimension of the array B. LDB >= max(1,N).
104*> \endverbatim
105*>
106*> \param[out] INFO
107*> \verbatim
108*> INFO is INTEGER
109*> = 0: successful exit
110*> < 0: if INFO = -i, the i-th argument had an illegal value
111*> > 0: if INFO = i, the leading principal minor of order i
112*> of A is not positive, so the factorization could not
113*> be completed, and the solution has not been computed.
114*> \endverbatim
115*
116* Authors:
117* ========
118*
119*> \author Univ. of Tennessee
120*> \author Univ. of California Berkeley
121*> \author Univ. of Colorado Denver
122*> \author NAG Ltd.
123*
124*> \ingroup posv
125*
126* =====================================================================
127 SUBROUTINE cposv( UPLO, N, NRHS, A, LDA, B, LDB, INFO )
128*
129* -- LAPACK driver routine --
130* -- LAPACK is a software package provided by Univ. of Tennessee, --
131* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
132*
133* .. Scalar Arguments ..
134 CHARACTER UPLO
135 INTEGER INFO, LDA, LDB, N, NRHS
136* ..
137* .. Array Arguments ..
138 COMPLEX A( LDA, * ), B( LDB, * )
139* ..
140*
141* =====================================================================
142*
143* .. External Functions ..
144 LOGICAL LSAME
145 EXTERNAL lsame
146* ..
147* .. External Subroutines ..
148 EXTERNAL cpotrf, cpotrs, xerbla
149* ..
150* .. Intrinsic Functions ..
151 INTRINSIC max
152* ..
153* .. Executable Statements ..
154*
155* Test the input parameters.
156*
157 info = 0
158 IF( .NOT.lsame( uplo, 'U' ) .AND.
159 $ .NOT.lsame( uplo, 'L' ) ) THEN
160 info = -1
161 ELSE IF( n.LT.0 ) THEN
162 info = -2
163 ELSE IF( nrhs.LT.0 ) THEN
164 info = -3
165 ELSE IF( lda.LT.max( 1, n ) ) THEN
166 info = -5
167 ELSE IF( ldb.LT.max( 1, n ) ) THEN
168 info = -7
169 END IF
170 IF( info.NE.0 ) THEN
171 CALL xerbla( 'CPOSV ', -info )
172 RETURN
173 END IF
174*
175* Compute the Cholesky factorization A = U**H*U or A = L*L**H.
176*
177 CALL cpotrf( uplo, n, a, lda, info )
178 IF( info.EQ.0 ) THEN
179*
180* Solve the system A*X = B, overwriting B with X.
181*
182 CALL cpotrs( uplo, n, nrhs, a, lda, b, ldb, info )
183*
184 END IF
185 RETURN
186*
187* End of CPOSV
188*
189 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine cposv(uplo, n, nrhs, a, lda, b, ldb, info)
CPOSV computes the solution to system of linear equations A * X = B for PO matrices
Definition cposv.f:128
subroutine cpotrf(uplo, n, a, lda, info)
CPOTRF
Definition cpotrf.f:105
subroutine cpotrs(uplo, n, nrhs, a, lda, b, ldb, info)
CPOTRS
Definition cpotrs.f:108