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