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

◆ zpotf2()

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

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

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

Purpose:
 ZPOTF2 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*16 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 108 of file zpotf2.f.

109*
110* -- LAPACK computational routine --
111* -- LAPACK is a software package provided by Univ. of Tennessee, --
112* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
113*
114* .. Scalar Arguments ..
115 CHARACTER UPLO
116 INTEGER INFO, LDA, N
117* ..
118* .. Array Arguments ..
119 COMPLEX*16 A( LDA, * )
120* ..
121*
122* =====================================================================
123*
124* .. Parameters ..
125 DOUBLE PRECISION ONE, ZERO
126 parameter( one = 1.0d+0, zero = 0.0d+0 )
127 COMPLEX*16 CONE
128 parameter( cone = ( 1.0d+0, 0.0d+0 ) )
129* ..
130* .. Local Scalars ..
131 LOGICAL UPPER
132 INTEGER J
133 DOUBLE PRECISION AJJ
134* ..
135* .. External Functions ..
136 LOGICAL LSAME, DISNAN
137 COMPLEX*16 ZDOTC
138 EXTERNAL lsame, zdotc, disnan
139* ..
140* .. External Subroutines ..
141 EXTERNAL xerbla, zdscal, zgemv, zlacgv
142* ..
143* .. Intrinsic Functions ..
144 INTRINSIC dble, max, sqrt
145* ..
146* .. Executable Statements ..
147*
148* Test the input parameters.
149*
150 info = 0
151 upper = lsame( uplo, 'U' )
152 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
153 info = -1
154 ELSE IF( n.LT.0 ) THEN
155 info = -2
156 ELSE IF( lda.LT.max( 1, n ) ) THEN
157 info = -4
158 END IF
159 IF( info.NE.0 ) THEN
160 CALL xerbla( 'ZPOTF2', -info )
161 RETURN
162 END IF
163*
164* Quick return if possible
165*
166 IF( n.EQ.0 )
167 $ RETURN
168*
169 IF( upper ) THEN
170*
171* Compute the Cholesky factorization A = U**H *U.
172*
173 DO 10 j = 1, n
174*
175* Compute U(J,J) and test for non-positive-definiteness.
176*
177 ajj = dble( a( j, j ) ) - dble( zdotc( j-1, a( 1, j ), 1,
178 $ a( 1, j ), 1 ) )
179 IF( ajj.LE.zero.OR.disnan( ajj ) ) THEN
180 a( j, j ) = ajj
181 GO TO 30
182 END IF
183 ajj = sqrt( ajj )
184 a( j, j ) = ajj
185*
186* Compute elements J+1:N of row J.
187*
188 IF( j.LT.n ) THEN
189 CALL zlacgv( j-1, a( 1, j ), 1 )
190 CALL zgemv( 'Transpose', j-1, n-j, -cone, a( 1, j+1 ),
191 $ lda, a( 1, j ), 1, cone, a( j, j+1 ), lda )
192 CALL zlacgv( j-1, a( 1, j ), 1 )
193 CALL zdscal( n-j, one / ajj, a( j, j+1 ), lda )
194 END IF
195 10 CONTINUE
196 ELSE
197*
198* Compute the Cholesky factorization A = L*L**H.
199*
200 DO 20 j = 1, n
201*
202* Compute L(J,J) and test for non-positive-definiteness.
203*
204 ajj = dble( a( j, j ) ) - dble( zdotc( j-1, a( j, 1 ), lda,
205 $ a( j, 1 ), lda ) )
206 IF( ajj.LE.zero.OR.disnan( ajj ) ) THEN
207 a( j, j ) = ajj
208 GO TO 30
209 END IF
210 ajj = sqrt( ajj )
211 a( j, j ) = ajj
212*
213* Compute elements J+1:N of column J.
214*
215 IF( j.LT.n ) THEN
216 CALL zlacgv( j-1, a( j, 1 ), lda )
217 CALL zgemv( 'No transpose', n-j, j-1, -cone, a( j+1, 1 ),
218 $ lda, a( j, 1 ), lda, cone, a( j+1, j ), 1 )
219 CALL zlacgv( j-1, a( j, 1 ), lda )
220 CALL zdscal( 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 ZPOTF2
233*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
complex *16 function zdotc(n, zx, incx, zy, incy)
ZDOTC
Definition zdotc.f:83
subroutine zgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
ZGEMV
Definition zgemv.f:160
logical function disnan(din)
DISNAN tests input for NaN.
Definition disnan.f:59
subroutine zlacgv(n, x, incx)
ZLACGV conjugates a complex vector.
Definition zlacgv.f:74
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine zdscal(n, da, zx, incx)
ZDSCAL
Definition zdscal.f:78
Here is the call graph for this function:
Here is the caller graph for this function: