1 SUBROUTINE ZPPTRF
( UPLO
, N
, AP
, INFO
)
3 * -- LAPACK routine
(version
3.1) --
4 * Univ
. of Tennessee
, Univ
. of California Berkeley and NAG Ltd
..
7 * .. Scalar Arguments
..
11 * .. Array Arguments
..
18 * ZPPTRF computes the Cholesky factorization of a
complex Hermitian
19 * positive definite matrix A stored in packed
format.
21 * The factorization has the form
22 * A
= U**H
* U
, if UPLO
= 'U', or
23 * A
= L
* L**H
, if UPLO
= 'L',
24 * where U is an upper triangular matrix and L is lower triangular
.
29 * UPLO
(input
) CHARACTER*1
30 * = 'U': Upper triangle of A is stored
;
31 * = 'L': Lower triangle of A is stored
.
34 * The order of the matrix A
. N
>= 0.
36 * AP
(input
/output
) COMPLEX*16 array
, dimension (N*
(N
+1)/2)
37 * On entry
, the upper or lower triangle of the Hermitian matrix
38 * A
, packed columnwise in a linear array
. The j
-th column of A
39 * is stored in the array AP as follows
:
40 * if UPLO
= 'U', AP
(i
+ (j
-1)*j
/2) = A
(i
,j
) for 1<=i
<=j
;
41 * if UPLO
= 'L', AP
(i
+ (j
-1)*(2n
-j
)/2) = A
(i
,j
) for j
<=i
<=n
.
42 * See below
for further details
.
44 * On exit
, if INFO
= 0, the triangular factor U or L from the
45 * Cholesky factorization A
= U**H*U or A
= L*L**H
, in the same
46 * storage
format as A
.
48 * INFO
(output
) INTEGER
49 * = 0: successful exit
50 * < 0: if INFO
= -i
, the i
-th argument had an illegal value
51 * > 0: if INFO
= i
, the leading minor of order i is not
52 * positive definite
, and the factorization could not be
58 * The packed storage scheme is illustrated by the following example
59 * when N
= 4, UPLO
= 'U':
61 * Two
-dimensional storage of the Hermitian matrix A
:
65 * a33 a34
(aij
= conjg
(aji
))
68 * Packed storage of the upper triangle of A
:
70 * AP
= [ a11
, a12
, a22
, a13
, a23
, a33
, a14
, a24
, a34
, a44
]
72 * =====================================================================
75 DOUBLE PRECISION ZERO
, ONE
76 PARAMETER ( ZERO
= 0.0D
+0, ONE
= 1.0D
+0 )
83 * .. External Functions
..
88 * .. External Subroutines
..
89 EXTERNAL XERBLA
, ZDSCAL
, ZHPR
, ZTPSV
91 * .. Intrinsic Functions
..
94 * .. Executable Statements
..
96 * Test the input parameters
.
99 UPPER
= LSAME
( UPLO
, 'U' )
100 IF( .NOT
.UPPER
.AND
. .NOT
.LSAME
( UPLO
, 'L' ) ) THEN
102 ELSE IF( N
.LT
.0 ) THEN
106 CALL XERBLA
( 'ZPPTRF', -INFO
)
110 * Quick
return if possible
117 * Compute the Cholesky factorization A
= U
'*U.
124 * Compute elements 1:J-1 of column J.
127 $ CALL ZTPSV( 'Upper
', 'Conjugate transpose
', 'Non
-unit
',
128 $ J-1, AP, AP( JC ), 1 )
130 * Compute U(J,J) and test for non-positive-definiteness.
132 AJJ = DBLE( AP( JJ ) ) - ZDOTC( J-1, AP( JC ), 1, AP( JC ),
134 IF( AJJ.LE.ZERO ) THEN
138 AP( JJ ) = SQRT( AJJ )
142 * Compute the Cholesky factorization A = L*L'.
147 * Compute L
(J
,J
) and test
for non
-positive
-definiteness
.
149 AJJ
= DBLE
( AP
( JJ
) )
150 IF( AJJ
.LE
.ZERO
) THEN
157 * Compute elements J
+1:N of column J and update the trailing
161 CALL ZDSCAL
( N
-J
, ONE
/ AJJ
, AP
( JJ
+1 ), 1 )
162 CALL ZHPR
( 'Lower', N
-J
, -ONE
, AP
( JJ
+1 ), 1,