LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dpftrf.f
Go to the documentation of this file.
1*> \brief \b DPFTRF
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DPFTRF + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dpftrf.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dpftrf.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dpftrf.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DPFTRF( TRANSR, UPLO, N, A, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER TRANSR, UPLO
23* INTEGER N, INFO
24* ..
25* .. Array Arguments ..
26* DOUBLE PRECISION A( 0: * )
27*
28*
29*> \par Purpose:
30* =============
31*>
32*> \verbatim
33*>
34*> DPFTRF computes the Cholesky factorization of a real symmetric
35*> positive definite matrix A.
36*>
37*> The factorization has the form
38*> A = U**T * U, if UPLO = 'U', or
39*> A = L * L**T, if UPLO = 'L',
40*> where U is an upper triangular matrix and L is lower triangular.
41*>
42*> This is the block version of the algorithm, calling Level 3 BLAS.
43*> \endverbatim
44*
45* Arguments:
46* ==========
47*
48*> \param[in] TRANSR
49*> \verbatim
50*> TRANSR is CHARACTER*1
51*> = 'N': The Normal TRANSR of RFP A is stored;
52*> = 'T': The Transpose TRANSR of RFP A is stored.
53*> \endverbatim
54*>
55*> \param[in] UPLO
56*> \verbatim
57*> UPLO is CHARACTER*1
58*> = 'U': Upper triangle of RFP A is stored;
59*> = 'L': Lower triangle of RFP A is stored.
60*> \endverbatim
61*>
62*> \param[in] N
63*> \verbatim
64*> N is INTEGER
65*> The order of the matrix A. N >= 0.
66*> \endverbatim
67*>
68*> \param[in,out] A
69*> \verbatim
70*> A is DOUBLE PRECISION array, dimension ( N*(N+1)/2 );
71*> On entry, the symmetric matrix A in RFP format. RFP format is
72*> described by TRANSR, UPLO, and N as follows: If TRANSR = 'N'
73*> then RFP A is (0:N,0:k-1) when N is even; k=N/2. RFP A is
74*> (0:N-1,0:k) when N is odd; k=N/2. IF TRANSR = 'T' then RFP is
75*> the transpose of RFP A as defined when
76*> TRANSR = 'N'. The contents of RFP A are defined by UPLO as
77*> follows: If UPLO = 'U' the RFP A contains the NT elements of
78*> upper packed A. If UPLO = 'L' the RFP A contains the elements
79*> of lower packed A. The LDA of RFP A is (N+1)/2 when TRANSR =
80*> 'T'. When TRANSR is 'N' the LDA is N+1 when N is even and N
81*> is odd. See the Note below for more details.
82*>
83*> On exit, if INFO = 0, the factor U or L from the Cholesky
84*> factorization RFP A = U**T*U or RFP A = L*L**T.
85*> \endverbatim
86*>
87*> \param[out] INFO
88*> \verbatim
89*> INFO is INTEGER
90*> = 0: successful exit
91*> < 0: if INFO = -i, the i-th argument had an illegal value
92*> > 0: if INFO = i, the leading principal minor of order i
93*> is not positive, and the factorization could not be
94*> completed.
95*> \endverbatim
96*
97* Authors:
98* ========
99*
100*> \author Univ. of Tennessee
101*> \author Univ. of California Berkeley
102*> \author Univ. of Colorado Denver
103*> \author NAG Ltd.
104*
105*> \ingroup pftrf
106*
107*> \par Further Details:
108* =====================
109*>
110*> \verbatim
111*>
112*> We first consider Rectangular Full Packed (RFP) Format when N is
113*> even. We give an example where N = 6.
114*>
115*> AP is Upper AP is Lower
116*>
117*> 00 01 02 03 04 05 00
118*> 11 12 13 14 15 10 11
119*> 22 23 24 25 20 21 22
120*> 33 34 35 30 31 32 33
121*> 44 45 40 41 42 43 44
122*> 55 50 51 52 53 54 55
123*>
124*>
125*> Let TRANSR = 'N'. RFP holds AP as follows:
126*> For UPLO = 'U' the upper trapezoid A(0:5,0:2) consists of the last
127*> three columns of AP upper. The lower triangle A(4:6,0:2) consists of
128*> the transpose of the first three columns of AP upper.
129*> For UPLO = 'L' the lower trapezoid A(1:6,0:2) consists of the first
130*> three columns of AP lower. The upper triangle A(0:2,0:2) consists of
131*> the transpose of the last three columns of AP lower.
132*> This covers the case N even and TRANSR = 'N'.
133*>
134*> RFP A RFP A
135*>
136*> 03 04 05 33 43 53
137*> 13 14 15 00 44 54
138*> 23 24 25 10 11 55
139*> 33 34 35 20 21 22
140*> 00 44 45 30 31 32
141*> 01 11 55 40 41 42
142*> 02 12 22 50 51 52
143*>
144*> Now let TRANSR = 'T'. RFP A in both UPLO cases is just the
145*> transpose of RFP A above. One therefore gets:
146*>
147*>
148*> RFP A RFP A
149*>
150*> 03 13 23 33 00 01 02 33 00 10 20 30 40 50
151*> 04 14 24 34 44 11 12 43 44 11 21 31 41 51
152*> 05 15 25 35 45 55 22 53 54 55 22 32 42 52
153*>
154*>
155*> We then consider Rectangular Full Packed (RFP) Format when N is
156*> odd. We give an example where N = 5.
157*>
158*> AP is Upper AP is Lower
159*>
160*> 00 01 02 03 04 00
161*> 11 12 13 14 10 11
162*> 22 23 24 20 21 22
163*> 33 34 30 31 32 33
164*> 44 40 41 42 43 44
165*>
166*>
167*> Let TRANSR = 'N'. RFP holds AP as follows:
168*> For UPLO = 'U' the upper trapezoid A(0:4,0:2) consists of the last
169*> three columns of AP upper. The lower triangle A(3:4,0:1) consists of
170*> the transpose of the first two columns of AP upper.
171*> For UPLO = 'L' the lower trapezoid A(0:4,0:2) consists of the first
172*> three columns of AP lower. The upper triangle A(0:1,1:2) consists of
173*> the transpose of the last two columns of AP lower.
174*> This covers the case N odd and TRANSR = 'N'.
175*>
176*> RFP A RFP A
177*>
178*> 02 03 04 00 33 43
179*> 12 13 14 10 11 44
180*> 22 23 24 20 21 22
181*> 00 33 34 30 31 32
182*> 01 11 44 40 41 42
183*>
184*> Now let TRANSR = 'T'. RFP A in both UPLO cases is just the
185*> transpose of RFP A above. One therefore gets:
186*>
187*> RFP A RFP A
188*>
189*> 02 12 22 00 01 00 10 20 30 40 50
190*> 03 13 23 33 11 33 11 21 31 41 51
191*> 04 14 24 34 44 43 44 22 32 42 52
192*> \endverbatim
193*>
194* =====================================================================
195 SUBROUTINE dpftrf( TRANSR, UPLO, N, A, INFO )
196*
197* -- LAPACK computational routine --
198* -- LAPACK is a software package provided by Univ. of Tennessee, --
199* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
200*
201* .. Scalar Arguments ..
202 CHARACTER TRANSR, UPLO
203 INTEGER N, INFO
204* ..
205* .. Array Arguments ..
206 DOUBLE PRECISION A( 0: * )
207*
208* =====================================================================
209*
210* .. Parameters ..
211 DOUBLE PRECISION ONE
212 parameter( one = 1.0d+0 )
213* ..
214* .. Local Scalars ..
215 LOGICAL LOWER, NISODD, NORMALTRANSR
216 INTEGER N1, N2, K
217* ..
218* .. External Functions ..
219 LOGICAL LSAME
220 EXTERNAL lsame
221* ..
222* .. External Subroutines ..
223 EXTERNAL xerbla, dsyrk, dpotrf, dtrsm
224* ..
225* .. Intrinsic Functions ..
226 INTRINSIC mod
227* ..
228* .. Executable Statements ..
229*
230* Test the input parameters.
231*
232 info = 0
233 normaltransr = lsame( transr, 'N' )
234 lower = lsame( uplo, 'L' )
235 IF( .NOT.normaltransr .AND. .NOT.lsame( transr, 'T' ) ) THEN
236 info = -1
237 ELSE IF( .NOT.lower .AND. .NOT.lsame( uplo, 'U' ) ) THEN
238 info = -2
239 ELSE IF( n.LT.0 ) THEN
240 info = -3
241 END IF
242 IF( info.NE.0 ) THEN
243 CALL xerbla( 'DPFTRF', -info )
244 RETURN
245 END IF
246*
247* Quick return if possible
248*
249 IF( n.EQ.0 )
250 $ RETURN
251*
252* If N is odd, set NISODD = .TRUE.
253* If N is even, set K = N/2 and NISODD = .FALSE.
254*
255 IF( mod( n, 2 ).EQ.0 ) THEN
256 k = n / 2
257 nisodd = .false.
258 ELSE
259 nisodd = .true.
260 END IF
261*
262* Set N1 and N2 depending on LOWER
263*
264 IF( lower ) THEN
265 n2 = n / 2
266 n1 = n - n2
267 ELSE
268 n1 = n / 2
269 n2 = n - n1
270 END IF
271*
272* start execution: there are eight cases
273*
274 IF( nisodd ) THEN
275*
276* N is odd
277*
278 IF( normaltransr ) THEN
279*
280* N is odd and TRANSR = 'N'
281*
282 IF( lower ) THEN
283*
284* SRPA for LOWER, NORMAL and N is odd ( a(0:n-1,0:n1-1) )
285* T1 -> a(0,0), T2 -> a(0,1), S -> a(n1,0)
286* T1 -> a(0), T2 -> a(n), S -> a(n1)
287*
288 CALL dpotrf( 'L', n1, a( 0 ), n, info )
289 IF( info.GT.0 )
290 $ RETURN
291 CALL dtrsm( 'R', 'L', 'T', 'N', n2, n1, one, a( 0 ),
292 $ n,
293 $ a( n1 ), n )
294 CALL dsyrk( 'U', 'N', n2, n1, -one, a( n1 ), n, one,
295 $ a( n ), n )
296 CALL dpotrf( 'U', n2, a( n ), n, info )
297 IF( info.GT.0 )
298 $ info = info + n1
299*
300 ELSE
301*
302* SRPA for UPPER, NORMAL and N is odd ( a(0:n-1,0:n2-1)
303* T1 -> a(n1+1,0), T2 -> a(n1,0), S -> a(0,0)
304* T1 -> a(n2), T2 -> a(n1), S -> a(0)
305*
306 CALL dpotrf( 'L', n1, a( n2 ), n, info )
307 IF( info.GT.0 )
308 $ RETURN
309 CALL dtrsm( 'L', 'L', 'N', 'N', n1, n2, one, a( n2 ),
310 $ n,
311 $ a( 0 ), n )
312 CALL dsyrk( 'U', 'T', n2, n1, -one, a( 0 ), n, one,
313 $ a( n1 ), n )
314 CALL dpotrf( 'U', n2, a( n1 ), n, info )
315 IF( info.GT.0 )
316 $ info = info + n1
317*
318 END IF
319*
320 ELSE
321*
322* N is odd and TRANSR = 'T'
323*
324 IF( lower ) THEN
325*
326* SRPA for LOWER, TRANSPOSE and N is odd
327* T1 -> A(0,0) , T2 -> A(1,0) , S -> A(0,n1)
328* T1 -> a(0+0) , T2 -> a(1+0) , S -> a(0+n1*n1); lda=n1
329*
330 CALL dpotrf( 'U', n1, a( 0 ), n1, info )
331 IF( info.GT.0 )
332 $ RETURN
333 CALL dtrsm( 'L', 'U', 'T', 'N', n1, n2, one, a( 0 ),
334 $ n1,
335 $ a( n1*n1 ), n1 )
336 CALL dsyrk( 'L', 'T', n2, n1, -one, a( n1*n1 ), n1,
337 $ one,
338 $ a( 1 ), n1 )
339 CALL dpotrf( 'L', n2, a( 1 ), n1, info )
340 IF( info.GT.0 )
341 $ info = info + n1
342*
343 ELSE
344*
345* SRPA for UPPER, TRANSPOSE and N is odd
346* T1 -> A(0,n1+1), T2 -> A(0,n1), S -> A(0,0)
347* T1 -> a(n2*n2), T2 -> a(n1*n2), S -> a(0); lda = n2
348*
349 CALL dpotrf( 'U', n1, a( n2*n2 ), n2, info )
350 IF( info.GT.0 )
351 $ RETURN
352 CALL dtrsm( 'R', 'U', 'N', 'N', n2, n1, one,
353 $ a( n2*n2 ),
354 $ n2, a( 0 ), n2 )
355 CALL dsyrk( 'L', 'N', n2, n1, -one, a( 0 ), n2, one,
356 $ a( n1*n2 ), n2 )
357 CALL dpotrf( 'L', n2, a( n1*n2 ), n2, info )
358 IF( info.GT.0 )
359 $ info = info + n1
360*
361 END IF
362*
363 END IF
364*
365 ELSE
366*
367* N is even
368*
369 IF( normaltransr ) THEN
370*
371* N is even and TRANSR = 'N'
372*
373 IF( lower ) THEN
374*
375* SRPA for LOWER, NORMAL, and N is even ( a(0:n,0:k-1) )
376* T1 -> a(1,0), T2 -> a(0,0), S -> a(k+1,0)
377* T1 -> a(1), T2 -> a(0), S -> a(k+1)
378*
379 CALL dpotrf( 'L', k, a( 1 ), n+1, info )
380 IF( info.GT.0 )
381 $ RETURN
382 CALL dtrsm( 'R', 'L', 'T', 'N', k, k, one, a( 1 ),
383 $ n+1,
384 $ a( k+1 ), n+1 )
385 CALL dsyrk( 'U', 'N', k, k, -one, a( k+1 ), n+1, one,
386 $ a( 0 ), n+1 )
387 CALL dpotrf( 'U', k, a( 0 ), n+1, info )
388 IF( info.GT.0 )
389 $ info = info + k
390*
391 ELSE
392*
393* SRPA for UPPER, NORMAL, and N is even ( a(0:n,0:k-1) )
394* T1 -> a(k+1,0) , T2 -> a(k,0), S -> a(0,0)
395* T1 -> a(k+1), T2 -> a(k), S -> a(0)
396*
397 CALL dpotrf( 'L', k, a( k+1 ), n+1, info )
398 IF( info.GT.0 )
399 $ RETURN
400 CALL dtrsm( 'L', 'L', 'N', 'N', k, k, one, a( k+1 ),
401 $ n+1, a( 0 ), n+1 )
402 CALL dsyrk( 'U', 'T', k, k, -one, a( 0 ), n+1, one,
403 $ a( k ), n+1 )
404 CALL dpotrf( 'U', k, a( k ), n+1, info )
405 IF( info.GT.0 )
406 $ info = info + k
407*
408 END IF
409*
410 ELSE
411*
412* N is even and TRANSR = 'T'
413*
414 IF( lower ) THEN
415*
416* SRPA for LOWER, TRANSPOSE and N is even (see paper)
417* T1 -> B(0,1), T2 -> B(0,0), S -> B(0,k+1)
418* T1 -> a(0+k), T2 -> a(0+0), S -> a(0+k*(k+1)); lda=k
419*
420 CALL dpotrf( 'U', k, a( 0+k ), k, info )
421 IF( info.GT.0 )
422 $ RETURN
423 CALL dtrsm( 'L', 'U', 'T', 'N', k, k, one, a( k ), n1,
424 $ a( k*( k+1 ) ), k )
425 CALL dsyrk( 'L', 'T', k, k, -one, a( k*( k+1 ) ), k,
426 $ one,
427 $ a( 0 ), k )
428 CALL dpotrf( 'L', k, a( 0 ), k, info )
429 IF( info.GT.0 )
430 $ info = info + k
431*
432 ELSE
433*
434* SRPA for UPPER, TRANSPOSE and N is even (see paper)
435* T1 -> B(0,k+1), T2 -> B(0,k), S -> B(0,0)
436* T1 -> a(0+k*(k+1)), T2 -> a(0+k*k), S -> a(0+0)); lda=k
437*
438 CALL dpotrf( 'U', k, a( k*( k+1 ) ), k, info )
439 IF( info.GT.0 )
440 $ RETURN
441 CALL dtrsm( 'R', 'U', 'N', 'N', k, k, one,
442 $ a( k*( k+1 ) ), k, a( 0 ), k )
443 CALL dsyrk( 'L', 'N', k, k, -one, a( 0 ), k, one,
444 $ a( k*k ), k )
445 CALL dpotrf( 'L', k, a( k*k ), k, info )
446 IF( info.GT.0 )
447 $ info = info + k
448*
449 END IF
450*
451 END IF
452*
453 END IF
454*
455 RETURN
456*
457* End of DPFTRF
458*
459 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dsyrk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)
DSYRK
Definition dsyrk.f:169
subroutine dpftrf(transr, uplo, n, a, info)
DPFTRF
Definition dpftrf.f:196
subroutine dpotrf(uplo, n, a, lda, info)
DPOTRF
Definition dpotrf.f:105
subroutine dtrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
DTRSM
Definition dtrsm.f:181