LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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 minor of order k is not
               positive definite, and the factorization could not be
               completed.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
September 2012

Definition at line 111 of file zpotf2.f.

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

Here is the call graph for this function:

Here is the caller graph for this function: