LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Modules Pages
dpotf2.f
Go to the documentation of this file.
1*> \brief \b DPOTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite matrix (unblocked algorithm).
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DPOTF2 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dpotf2.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dpotf2.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dpotf2.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DPOTF2( UPLO, N, A, LDA, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, LDA, N
24* ..
25* .. Array Arguments ..
26* DOUBLE PRECISION A( LDA, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> DPOTF2 computes the Cholesky factorization of a real symmetric
36*> positive definite matrix A.
37*>
38*> The factorization has the form
39*> A = U**T * U , if UPLO = 'U', or
40*> A = L * L**T, if UPLO = 'L',
41*> where U is an upper triangular matrix and L is lower triangular.
42*>
43*> This is the unblocked version of the algorithm, calling Level 2 BLAS.
44*> \endverbatim
45*
46* Arguments:
47* ==========
48*
49*> \param[in] UPLO
50*> \verbatim
51*> UPLO is CHARACTER*1
52*> Specifies whether the upper or lower triangular part of the
53*> symmetric matrix A is stored.
54*> = 'U': Upper triangular
55*> = 'L': Lower triangular
56*> \endverbatim
57*>
58*> \param[in] N
59*> \verbatim
60*> N is INTEGER
61*> The order of the matrix A. N >= 0.
62*> \endverbatim
63*>
64*> \param[in,out] A
65*> \verbatim
66*> A is DOUBLE PRECISION array, dimension (LDA,N)
67*> On entry, the symmetric matrix A. If UPLO = 'U', the leading
68*> n by n upper triangular part of A contains the upper
69*> triangular part of the matrix A, and the strictly lower
70*> triangular part of A is not referenced. If UPLO = 'L', the
71*> leading n by n lower triangular part of A contains the lower
72*> triangular part of the matrix A, and the strictly upper
73*> triangular part of A is not referenced.
74*>
75*> On exit, if INFO = 0, the factor U or L from the Cholesky
76*> factorization A = U**T *U or A = L*L**T.
77*> \endverbatim
78*>
79*> \param[in] LDA
80*> \verbatim
81*> LDA is INTEGER
82*> The leading dimension of the array A. LDA >= max(1,N).
83*> \endverbatim
84*>
85*> \param[out] INFO
86*> \verbatim
87*> INFO is INTEGER
88*> = 0: successful exit
89*> < 0: if INFO = -k, the k-th argument had an illegal value
90*> > 0: if INFO = k, the leading principal minor of order k
91*> is not positive, and the factorization could not be
92*> completed.
93*> \endverbatim
94*
95* Authors:
96* ========
97*
98*> \author Univ. of Tennessee
99*> \author Univ. of California Berkeley
100*> \author Univ. of Colorado Denver
101*> \author NAG Ltd.
102*
103*> \ingroup potf2
104*
105* =====================================================================
106 SUBROUTINE dpotf2( UPLO, N, A, LDA, INFO )
107*
108* -- LAPACK computational routine --
109* -- LAPACK is a software package provided by Univ. of Tennessee, --
110* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
111*
112* .. Scalar Arguments ..
113 CHARACTER UPLO
114 INTEGER INFO, LDA, N
115* ..
116* .. Array Arguments ..
117 DOUBLE PRECISION A( LDA, * )
118* ..
119*
120* =====================================================================
121*
122* .. Parameters ..
123 DOUBLE PRECISION ONE, ZERO
124 parameter( one = 1.0d+0, zero = 0.0d+0 )
125* ..
126* .. Local Scalars ..
127 LOGICAL UPPER
128 INTEGER J
129 DOUBLE PRECISION AJJ
130* ..
131* .. External Functions ..
132 LOGICAL LSAME, DISNAN
133 DOUBLE PRECISION DDOT
134 EXTERNAL lsame, ddot, disnan
135* ..
136* .. External Subroutines ..
137 EXTERNAL dgemv, dscal, xerbla
138* ..
139* .. Intrinsic Functions ..
140 INTRINSIC max, sqrt
141* ..
142* .. Executable Statements ..
143*
144* Test the input parameters.
145*
146 info = 0
147 upper = lsame( uplo, 'U' )
148 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
149 info = -1
150 ELSE IF( n.LT.0 ) THEN
151 info = -2
152 ELSE IF( lda.LT.max( 1, n ) ) THEN
153 info = -4
154 END IF
155 IF( info.NE.0 ) THEN
156 CALL xerbla( 'DPOTF2', -info )
157 RETURN
158 END IF
159*
160* Quick return if possible
161*
162 IF( n.EQ.0 )
163 $ RETURN
164*
165 IF( upper ) THEN
166*
167* Compute the Cholesky factorization A = U**T *U.
168*
169 DO 10 j = 1, n
170*
171* Compute U(J,J) and test for non-positive-definiteness.
172*
173 ajj = a( j, j ) - ddot( j-1, a( 1, j ), 1, a( 1, j ), 1 )
174 IF( ajj.LE.zero.OR.disnan( ajj ) ) THEN
175 a( j, j ) = ajj
176 GO TO 30
177 END IF
178 ajj = sqrt( ajj )
179 a( j, j ) = ajj
180*
181* Compute elements J+1:N of row J.
182*
183 IF( j.LT.n ) THEN
184 CALL dgemv( 'Transpose', j-1, n-j, -one, a( 1, j+1 ),
185 $ lda, a( 1, j ), 1, one, a( j, j+1 ), lda )
186 CALL dscal( n-j, one / ajj, a( j, j+1 ), lda )
187 END IF
188 10 CONTINUE
189 ELSE
190*
191* Compute the Cholesky factorization A = L*L**T.
192*
193 DO 20 j = 1, n
194*
195* Compute L(J,J) and test for non-positive-definiteness.
196*
197 ajj = a( j, j ) - ddot( j-1, a( j, 1 ), lda, a( j, 1 ),
198 $ lda )
199 IF( ajj.LE.zero.OR.disnan( ajj ) ) THEN
200 a( j, j ) = ajj
201 GO TO 30
202 END IF
203 ajj = sqrt( ajj )
204 a( j, j ) = ajj
205*
206* Compute elements J+1:N of column J.
207*
208 IF( j.LT.n ) THEN
209 CALL dgemv( 'No transpose', n-j, j-1, -one, a( j+1,
210 $ 1 ),
211 $ lda, a( j, 1 ), lda, one, a( j+1, j ), 1 )
212 CALL dscal( n-j, one / ajj, a( j+1, j ), 1 )
213 END IF
214 20 CONTINUE
215 END IF
216 GO TO 40
217*
218 30 CONTINUE
219 info = j
220*
221 40 CONTINUE
222 RETURN
223*
224* End of DPOTF2
225*
226 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
DGEMV
Definition dgemv.f:158
subroutine dpotf2(uplo, n, a, lda, info)
DPOTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite matrix (unblock...
Definition dpotf2.f:107
subroutine dscal(n, da, dx, incx)
DSCAL
Definition dscal.f:79