LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cpftrs.f
Go to the documentation of this file.
1*> \brief \b CPFTRS
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download CPFTRS + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cpftrs.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cpftrs.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cpftrs.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CPFTRS( TRANSR, UPLO, N, NRHS, A, B, LDB, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER TRANSR, UPLO
23* INTEGER INFO, LDB, N, NRHS
24* ..
25* .. Array Arguments ..
26* COMPLEX A( 0: * ), B( LDB, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> CPFTRS solves a system of linear equations A*X = B with a Hermitian
36*> positive definite matrix A using the Cholesky factorization
37*> A = U**H*U or A = L*L**H computed by CPFTRF.
38*> \endverbatim
39*
40* Arguments:
41* ==========
42*
43*> \param[in] TRANSR
44*> \verbatim
45*> TRANSR is CHARACTER*1
46*> = 'N': The Normal TRANSR of RFP A is stored;
47*> = 'C': The Conjugate-transpose TRANSR of RFP A is stored.
48*> \endverbatim
49*>
50*> \param[in] UPLO
51*> \verbatim
52*> UPLO is CHARACTER*1
53*> = 'U': Upper triangle of RFP A is stored;
54*> = 'L': Lower triangle of RFP A is stored.
55*> \endverbatim
56*>
57*> \param[in] N
58*> \verbatim
59*> N is INTEGER
60*> The order of the matrix A. N >= 0.
61*> \endverbatim
62*>
63*> \param[in] NRHS
64*> \verbatim
65*> NRHS is INTEGER
66*> The number of right hand sides, i.e., the number of columns
67*> of the matrix B. NRHS >= 0.
68*> \endverbatim
69*>
70*> \param[in] A
71*> \verbatim
72*> A is COMPLEX array, dimension ( N*(N+1)/2 );
73*> The triangular factor U or L from the Cholesky factorization
74*> of RFP A = U**H*U or RFP A = L*L**H, as computed by CPFTRF.
75*> See note below for more details about RFP A.
76*> \endverbatim
77*>
78*> \param[in,out] B
79*> \verbatim
80*> B is COMPLEX array, dimension (LDB,NRHS)
81*> On entry, the right hand side matrix B.
82*> On exit, the solution matrix X.
83*> \endverbatim
84*>
85*> \param[in] LDB
86*> \verbatim
87*> LDB is INTEGER
88*> The leading dimension of the array B. LDB >= max(1,N).
89*> \endverbatim
90*>
91*> \param[out] INFO
92*> \verbatim
93*> INFO is INTEGER
94*> = 0: successful exit
95*> < 0: if INFO = -i, the i-th argument had an illegal value
96*> \endverbatim
97*
98* Authors:
99* ========
100*
101*> \author Univ. of Tennessee
102*> \author Univ. of California Berkeley
103*> \author Univ. of Colorado Denver
104*> \author NAG Ltd.
105*
106*> \ingroup pftrs
107*
108*> \par Further Details:
109* =====================
110*>
111*> \verbatim
112*>
113*> We first consider Standard Packed Format when N is even.
114*> We give an example where N = 6.
115*>
116*> AP is Upper AP is Lower
117*>
118*> 00 01 02 03 04 05 00
119*> 11 12 13 14 15 10 11
120*> 22 23 24 25 20 21 22
121*> 33 34 35 30 31 32 33
122*> 44 45 40 41 42 43 44
123*> 55 50 51 52 53 54 55
124*>
125*>
126*> Let TRANSR = 'N'. RFP holds AP as follows:
127*> For UPLO = 'U' the upper trapezoid A(0:5,0:2) consists of the last
128*> three columns of AP upper. The lower triangle A(4:6,0:2) consists of
129*> conjugate-transpose of the first three columns of AP upper.
130*> For UPLO = 'L' the lower trapezoid A(1:6,0:2) consists of the first
131*> three columns of AP lower. The upper triangle A(0:2,0:2) consists of
132*> conjugate-transpose of the last three columns of AP lower.
133*> To denote conjugate we place -- above the element. This covers the
134*> case N even and TRANSR = 'N'.
135*>
136*> RFP A RFP A
137*>
138*> -- -- --
139*> 03 04 05 33 43 53
140*> -- --
141*> 13 14 15 00 44 54
142*> --
143*> 23 24 25 10 11 55
144*>
145*> 33 34 35 20 21 22
146*> --
147*> 00 44 45 30 31 32
148*> -- --
149*> 01 11 55 40 41 42
150*> -- -- --
151*> 02 12 22 50 51 52
152*>
153*> Now let TRANSR = 'C'. RFP A in both UPLO cases is just the conjugate-
154*> transpose of RFP A above. One therefore gets:
155*>
156*>
157*> RFP A RFP A
158*>
159*> -- -- -- -- -- -- -- -- -- --
160*> 03 13 23 33 00 01 02 33 00 10 20 30 40 50
161*> -- -- -- -- -- -- -- -- -- --
162*> 04 14 24 34 44 11 12 43 44 11 21 31 41 51
163*> -- -- -- -- -- -- -- -- -- --
164*> 05 15 25 35 45 55 22 53 54 55 22 32 42 52
165*>
166*>
167*> We next consider Standard Packed Format when N is odd.
168*> We give an example where N = 5.
169*>
170*> AP is Upper AP is Lower
171*>
172*> 00 01 02 03 04 00
173*> 11 12 13 14 10 11
174*> 22 23 24 20 21 22
175*> 33 34 30 31 32 33
176*> 44 40 41 42 43 44
177*>
178*>
179*> Let TRANSR = 'N'. RFP holds AP as follows:
180*> For UPLO = 'U' the upper trapezoid A(0:4,0:2) consists of the last
181*> three columns of AP upper. The lower triangle A(3:4,0:1) consists of
182*> conjugate-transpose of the first two columns of AP upper.
183*> For UPLO = 'L' the lower trapezoid A(0:4,0:2) consists of the first
184*> three columns of AP lower. The upper triangle A(0:1,1:2) consists of
185*> conjugate-transpose of the last two columns of AP lower.
186*> To denote conjugate we place -- above the element. This covers the
187*> case N odd and TRANSR = 'N'.
188*>
189*> RFP A RFP A
190*>
191*> -- --
192*> 02 03 04 00 33 43
193*> --
194*> 12 13 14 10 11 44
195*>
196*> 22 23 24 20 21 22
197*> --
198*> 00 33 34 30 31 32
199*> -- --
200*> 01 11 44 40 41 42
201*>
202*> Now let TRANSR = 'C'. RFP A in both UPLO cases is just the conjugate-
203*> transpose of RFP A above. One therefore gets:
204*>
205*>
206*> RFP A RFP A
207*>
208*> -- -- -- -- -- -- -- -- --
209*> 02 12 22 00 01 00 10 20 30 40 50
210*> -- -- -- -- -- -- -- -- --
211*> 03 13 23 33 11 33 11 21 31 41 51
212*> -- -- -- -- -- -- -- -- --
213*> 04 14 24 34 44 43 44 22 32 42 52
214*> \endverbatim
215*>
216* =====================================================================
217 SUBROUTINE cpftrs( TRANSR, UPLO, N, NRHS, A, B, LDB, INFO )
218*
219* -- LAPACK computational routine --
220* -- LAPACK is a software package provided by Univ. of Tennessee, --
221* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
222*
223* .. Scalar Arguments ..
224 CHARACTER TRANSR, UPLO
225 INTEGER INFO, LDB, N, NRHS
226* ..
227* .. Array Arguments ..
228 COMPLEX A( 0: * ), B( LDB, * )
229* ..
230*
231* =====================================================================
232*
233* .. Parameters ..
234 COMPLEX CONE
235 parameter( cone = ( 1.0e+0, 0.0e+0 ) )
236* ..
237* .. Local Scalars ..
238 LOGICAL LOWER, NORMALTRANSR
239* ..
240* .. External Functions ..
241 LOGICAL LSAME
242 EXTERNAL lsame
243* ..
244* .. External Subroutines ..
245 EXTERNAL xerbla, ctfsm
246* ..
247* .. Intrinsic Functions ..
248 INTRINSIC max
249* ..
250* .. Executable Statements ..
251*
252* Test the input parameters.
253*
254 info = 0
255 normaltransr = lsame( transr, 'N' )
256 lower = lsame( uplo, 'L' )
257 IF( .NOT.normaltransr .AND. .NOT.lsame( transr, 'C' ) ) THEN
258 info = -1
259 ELSE IF( .NOT.lower .AND. .NOT.lsame( uplo, 'U' ) ) THEN
260 info = -2
261 ELSE IF( n.LT.0 ) THEN
262 info = -3
263 ELSE IF( nrhs.LT.0 ) THEN
264 info = -4
265 ELSE IF( ldb.LT.max( 1, n ) ) THEN
266 info = -7
267 END IF
268 IF( info.NE.0 ) THEN
269 CALL xerbla( 'CPFTRS', -info )
270 RETURN
271 END IF
272*
273* Quick return if possible
274*
275 IF( n.EQ.0 .OR. nrhs.EQ.0 )
276 $ RETURN
277*
278* start execution: there are two triangular solves
279*
280 IF( lower ) THEN
281 CALL ctfsm( transr, 'L', uplo, 'N', 'N', n, nrhs, cone, a,
282 $ b,
283 $ ldb )
284 CALL ctfsm( transr, 'L', uplo, 'C', 'N', n, nrhs, cone, a,
285 $ b,
286 $ ldb )
287 ELSE
288 CALL ctfsm( transr, 'L', uplo, 'C', 'N', n, nrhs, cone, a,
289 $ b,
290 $ ldb )
291 CALL ctfsm( transr, 'L', uplo, 'N', 'N', n, nrhs, cone, a,
292 $ b,
293 $ ldb )
294 END IF
295*
296 RETURN
297*
298* End of CPFTRS
299*
300 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine cpftrs(transr, uplo, n, nrhs, a, b, ldb, info)
CPFTRS
Definition cpftrs.f:218
subroutine ctfsm(transr, side, uplo, trans, diag, m, n, alpha, a, b, ldb)
CTFSM solves a matrix equation (one operand is a triangular matrix in RFP format).
Definition ctfsm.f:298