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