LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zpptrf.f
Go to the documentation of this file.
1*> \brief \b ZPPTRF
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZPPTRF + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zpptrf.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zpptrf.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpptrf.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZPPTRF( UPLO, N, AP, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, N
24* ..
25* .. Array Arguments ..
26* COMPLEX*16 AP( * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> ZPPTRF computes the Cholesky factorization of a complex Hermitian
36*> positive definite matrix A stored in packed format.
37*>
38*> The factorization has the form
39*> A = U**H * U, if UPLO = 'U', or
40*> A = L * L**H, if UPLO = 'L',
41*> where U is an upper triangular matrix and L is lower triangular.
42*> \endverbatim
43*
44* Arguments:
45* ==========
46*
47*> \param[in] UPLO
48*> \verbatim
49*> UPLO is CHARACTER*1
50*> = 'U': Upper triangle of A is stored;
51*> = 'L': Lower triangle of A is stored.
52*> \endverbatim
53*>
54*> \param[in] N
55*> \verbatim
56*> N is INTEGER
57*> The order of the matrix A. N >= 0.
58*> \endverbatim
59*>
60*> \param[in,out] AP
61*> \verbatim
62*> AP is COMPLEX*16 array, dimension (N*(N+1)/2)
63*> On entry, the upper or lower triangle of the Hermitian matrix
64*> A, packed columnwise in a linear array. The j-th column of A
65*> is stored in the array AP as follows:
66*> if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
67*> if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
68*> See below for further details.
69*>
70*> On exit, if INFO = 0, the triangular factor U or L from the
71*> Cholesky factorization A = U**H*U or A = L*L**H, in the same
72*> storage format as A.
73*> \endverbatim
74*>
75*> \param[out] INFO
76*> \verbatim
77*> INFO is INTEGER
78*> = 0: successful exit
79*> < 0: if INFO = -i, the i-th argument had an illegal value
80*> > 0: if INFO = i, the leading principal minor of order i
81*> is not positive, and the factorization could not be
82*> completed.
83*> \endverbatim
84*
85* Authors:
86* ========
87*
88*> \author Univ. of Tennessee
89*> \author Univ. of California Berkeley
90*> \author Univ. of Colorado Denver
91*> \author NAG Ltd.
92*
93*> \ingroup pptrf
94*
95*> \par Further Details:
96* =====================
97*>
98*> \verbatim
99*>
100*> The packed storage scheme is illustrated by the following example
101*> when N = 4, UPLO = 'U':
102*>
103*> Two-dimensional storage of the Hermitian matrix A:
104*>
105*> a11 a12 a13 a14
106*> a22 a23 a24
107*> a33 a34 (aij = conjg(aji))
108*> a44
109*>
110*> Packed storage of the upper triangle of A:
111*>
112*> AP = [ a11, a12, a22, a13, a23, a33, a14, a24, a34, a44 ]
113*> \endverbatim
114*>
115* =====================================================================
116 SUBROUTINE zpptrf( UPLO, N, AP, INFO )
117*
118* -- LAPACK computational routine --
119* -- LAPACK is a software package provided by Univ. of Tennessee, --
120* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
121*
122* .. Scalar Arguments ..
123 CHARACTER UPLO
124 INTEGER INFO, N
125* ..
126* .. Array Arguments ..
127 COMPLEX*16 AP( * )
128* ..
129*
130* =====================================================================
131*
132* .. Parameters ..
133 DOUBLE PRECISION ZERO, ONE
134 parameter( zero = 0.0d+0, one = 1.0d+0 )
135* ..
136* .. Local Scalars ..
137 LOGICAL UPPER
138 INTEGER J, JC, JJ
139 DOUBLE PRECISION AJJ
140* ..
141* .. External Functions ..
142 LOGICAL LSAME
143 COMPLEX*16 ZDOTC
144 EXTERNAL lsame, zdotc
145* ..
146* .. External Subroutines ..
147 EXTERNAL xerbla, zdscal, zhpr, ztpsv
148* ..
149* .. Intrinsic Functions ..
150 INTRINSIC dble, sqrt
151* ..
152* .. Executable Statements ..
153*
154* Test the input parameters.
155*
156 info = 0
157 upper = lsame( uplo, 'U' )
158 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
159 info = -1
160 ELSE IF( n.LT.0 ) THEN
161 info = -2
162 END IF
163 IF( info.NE.0 ) THEN
164 CALL xerbla( 'ZPPTRF', -info )
165 RETURN
166 END IF
167*
168* Quick return if possible
169*
170 IF( n.EQ.0 )
171 $ RETURN
172*
173 IF( upper ) THEN
174*
175* Compute the Cholesky factorization A = U**H * U.
176*
177 jj = 0
178 DO 10 j = 1, n
179 jc = jj + 1
180 jj = jj + j
181*
182* Compute elements 1:J-1 of column J.
183*
184 IF( j.GT.1 )
185 $ CALL ztpsv( 'Upper', 'Conjugate transpose',
186 $ 'Non-unit',
187 $ j-1, ap, ap( jc ), 1 )
188*
189* Compute U(J,J) and test for non-positive-definiteness.
190*
191 ajj = dble( ap( jj ) ) - dble( zdotc( j-1,
192 $ ap( jc ), 1, ap( jc ), 1 ) )
193 IF( ajj.LE.zero ) THEN
194 ap( jj ) = ajj
195 GO TO 30
196 END IF
197 ap( jj ) = sqrt( ajj )
198 10 CONTINUE
199 ELSE
200*
201* Compute the Cholesky factorization A = L * L**H.
202*
203 jj = 1
204 DO 20 j = 1, n
205*
206* Compute L(J,J) and test for non-positive-definiteness.
207*
208 ajj = dble( ap( jj ) )
209 IF( ajj.LE.zero ) THEN
210 ap( jj ) = ajj
211 GO TO 30
212 END IF
213 ajj = sqrt( ajj )
214 ap( jj ) = ajj
215*
216* Compute elements J+1:N of column J and update the trailing
217* submatrix.
218*
219 IF( j.LT.n ) THEN
220 CALL zdscal( n-j, one / ajj, ap( jj+1 ), 1 )
221 CALL zhpr( 'Lower', n-j, -one, ap( jj+1 ), 1,
222 $ ap( jj+n-j+1 ) )
223 jj = jj + n - j + 1
224 END IF
225 20 CONTINUE
226 END IF
227 GO TO 40
228*
229 30 CONTINUE
230 info = j
231*
232 40 CONTINUE
233 RETURN
234*
235* End of ZPPTRF
236*
237 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zhpr(uplo, n, alpha, x, incx, ap)
ZHPR
Definition zhpr.f:130
subroutine zpptrf(uplo, n, ap, info)
ZPPTRF
Definition zpptrf.f:117
subroutine zdscal(n, da, zx, incx)
ZDSCAL
Definition zdscal.f:78
subroutine ztpsv(uplo, trans, diag, n, ap, x, incx)
ZTPSV
Definition ztpsv.f:144