LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cpotf2.f
Go to the documentation of this file.
1*> \brief \b CPOTF2 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 CPOTF2 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cpotf2.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cpotf2.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cpotf2.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CPOTF2( UPLO, N, A, LDA, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, LDA, N
24* ..
25* .. Array Arguments ..
26* COMPLEX A( LDA, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> CPOTF2 computes the Cholesky factorization of a complex Hermitian
36*> positive definite matrix A.
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*>
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*> Hermitian 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 COMPLEX array, dimension (LDA,N)
67*> On entry, the Hermitian 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**H *U or A = L*L**H.
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 cpotf2( 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 COMPLEX A( LDA, * )
118* ..
119*
120* =====================================================================
121*
122* .. Parameters ..
123 REAL ONE, ZERO
124 parameter( one = 1.0e+0, zero = 0.0e+0 )
125 COMPLEX CONE
126 parameter( cone = ( 1.0e+0, 0.0e+0 ) )
127* ..
128* .. Local Scalars ..
129 LOGICAL UPPER
130 INTEGER J
131 REAL AJJ
132* ..
133* .. External Functions ..
134 LOGICAL LSAME, SISNAN
135 COMPLEX CDOTC
136 EXTERNAL lsame, cdotc, sisnan
137* ..
138* .. External Subroutines ..
139 EXTERNAL cgemv, clacgv, csscal, xerbla
140* ..
141* .. Intrinsic Functions ..
142 INTRINSIC max, real, sqrt
143* ..
144* .. Executable Statements ..
145*
146* Test the input parameters.
147*
148 info = 0
149 upper = lsame( uplo, 'U' )
150 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
151 info = -1
152 ELSE IF( n.LT.0 ) THEN
153 info = -2
154 ELSE IF( lda.LT.max( 1, n ) ) THEN
155 info = -4
156 END IF
157 IF( info.NE.0 ) THEN
158 CALL xerbla( 'CPOTF2', -info )
159 RETURN
160 END IF
161*
162* Quick return if possible
163*
164 IF( n.EQ.0 )
165 $ RETURN
166*
167 IF( upper ) THEN
168*
169* Compute the Cholesky factorization A = U**H *U.
170*
171 DO 10 j = 1, n
172*
173* Compute U(J,J) and test for non-positive-definiteness.
174*
175 ajj = real( real( a( j, j ) ) - cdotc( j-1, a( 1, j ), 1,
176 $ a( 1, j ), 1 ) )
177 IF( ajj.LE.zero.OR.sisnan( ajj ) ) THEN
178 a( j, j ) = ajj
179 GO TO 30
180 END IF
181 ajj = sqrt( ajj )
182 a( j, j ) = ajj
183*
184* Compute elements J+1:N of row J.
185*
186 IF( j.LT.n ) THEN
187 CALL clacgv( j-1, a( 1, j ), 1 )
188 CALL cgemv( 'Transpose', j-1, n-j, -cone, a( 1, j+1 ),
189 $ lda, a( 1, j ), 1, cone, a( j, j+1 ), lda )
190 CALL clacgv( j-1, a( 1, j ), 1 )
191 CALL csscal( n-j, one / ajj, a( j, j+1 ), lda )
192 END IF
193 10 CONTINUE
194 ELSE
195*
196* Compute the Cholesky factorization A = L*L**H.
197*
198 DO 20 j = 1, n
199*
200* Compute L(J,J) and test for non-positive-definiteness.
201*
202 ajj = real( real( a( j, j ) ) - cdotc( j-1, a( j, 1 ),
203 $ lda,
204 $ a( j, 1 ), lda ) )
205 IF( ajj.LE.zero.OR.sisnan( ajj ) ) THEN
206 a( j, j ) = ajj
207 GO TO 30
208 END IF
209 ajj = sqrt( ajj )
210 a( j, j ) = ajj
211*
212* Compute elements J+1:N of column J.
213*
214 IF( j.LT.n ) THEN
215 CALL clacgv( j-1, a( j, 1 ), lda )
216 CALL cgemv( 'No transpose', n-j, j-1, -cone, a( j+1,
217 $ 1 ),
218 $ lda, a( j, 1 ), lda, cone, a( j+1, j ), 1 )
219 CALL clacgv( j-1, a( j, 1 ), lda )
220 CALL csscal( n-j, one / ajj, a( j+1, j ), 1 )
221 END IF
222 20 CONTINUE
223 END IF
224 GO TO 40
225*
226 30 CONTINUE
227 info = j
228*
229 40 CONTINUE
230 RETURN
231*
232* End of CPOTF2
233*
234 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine cgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
CGEMV
Definition cgemv.f:160
subroutine clacgv(n, x, incx)
CLACGV conjugates a complex vector.
Definition clacgv.f:72
subroutine cpotf2(uplo, n, a, lda, info)
CPOTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite matrix (unblock...
Definition cpotf2.f:107
subroutine csscal(n, sa, cx, incx)
CSSCAL
Definition csscal.f:78