LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ cpotf2()

subroutine cpotf2 ( character uplo,
integer n,
complex, dimension( lda, * ) a,
integer lda,
integer info )

CPOTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite matrix (unblocked algorithm).

Download CPOTF2 + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> CPOTF2 computes the Cholesky factorization of a complex Hermitian
!> positive definite matrix A.
!>
!> The factorization has the form
!>    A = U**H * U ,  if UPLO = 'U', or
!>    A = L  * L**H,  if UPLO = 'L',
!> where U is an upper triangular matrix and L is lower triangular.
!>
!> This is the unblocked version of the algorithm, calling Level 2 BLAS.
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>          Specifies whether the upper or lower triangular part of the
!>          Hermitian matrix A is stored.
!>          = 'U':  Upper triangular
!>          = 'L':  Lower triangular
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix A.  N >= 0.
!> 
[in,out]A
!>          A is COMPLEX array, dimension (LDA,N)
!>          On entry, the Hermitian matrix A.  If UPLO = 'U', the leading
!>          n by n upper triangular part of A contains the upper
!>          triangular part of the matrix A, and the strictly lower
!>          triangular part of A is not referenced.  If UPLO = 'L', the
!>          leading n by n lower triangular part of A contains the lower
!>          triangular part of the matrix A, and the strictly upper
!>          triangular part of A is not referenced.
!>
!>          On exit, if INFO = 0, the factor U or L from the Cholesky
!>          factorization A = U**H *U  or A = L*L**H.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A.  LDA >= max(1,N).
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0: successful exit
!>          < 0: if INFO = -k, the k-th argument had an illegal value
!>          > 0: if INFO = k, the leading principal minor of order k
!>               is not positive, and the factorization could not be
!>               completed.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 106 of file cpotf2.f.

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*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
complex function cdotc(n, cx, incx, cy, incy)
CDOTC
Definition cdotc.f:83
subroutine cgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
CGEMV
Definition cgemv.f:160
logical function sisnan(sin)
SISNAN tests input for NaN.
Definition sisnan.f:57
subroutine clacgv(n, x, incx)
CLACGV conjugates a complex vector.
Definition clacgv.f:72
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine csscal(n, sa, cx, incx)
CSSCAL
Definition csscal.f:78
Here is the call graph for this function:
Here is the caller graph for this function: