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