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

◆ zpotrf()

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

ZPOTRF

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

Purpose:
!>
!> ZPOTRF 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 block version of the algorithm, calling Level 3 BLAS.
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>          = 'U':  Upper triangle of A is stored;
!>          = 'L':  Lower triangle of A is stored.
!> 
[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 = -i, the i-th argument had an illegal value
!>          > 0:  if INFO = i, the leading principal minor of order i
!>                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 104 of file zpotrf.f.

105*
106* -- LAPACK computational routine --
107* -- LAPACK is a software package provided by Univ. of Tennessee, --
108* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
109*
110* .. Scalar Arguments ..
111 CHARACTER UPLO
112 INTEGER INFO, LDA, N
113* ..
114* .. Array Arguments ..
115 COMPLEX*16 A( LDA, * )
116* ..
117*
118* =====================================================================
119*
120* .. Parameters ..
121 DOUBLE PRECISION ONE
122 COMPLEX*16 CONE
123 parameter( one = 1.0d+0, cone = ( 1.0d+0, 0.0d+0 ) )
124* ..
125* .. Local Scalars ..
126 LOGICAL UPPER
127 INTEGER J, JB, NB
128* ..
129* .. External Functions ..
130 LOGICAL LSAME
131 INTEGER ILAENV
132 EXTERNAL lsame, ilaenv
133* ..
134* .. External Subroutines ..
135 EXTERNAL xerbla, zgemm, zherk, zpotrf2,
136 $ ztrsm
137* ..
138* .. Intrinsic Functions ..
139 INTRINSIC max, min
140* ..
141* .. Executable Statements ..
142*
143* Test the input parameters.
144*
145 info = 0
146 upper = lsame( uplo, 'U' )
147 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
148 info = -1
149 ELSE IF( n.LT.0 ) THEN
150 info = -2
151 ELSE IF( lda.LT.max( 1, n ) ) THEN
152 info = -4
153 END IF
154 IF( info.NE.0 ) THEN
155 CALL xerbla( 'ZPOTRF', -info )
156 RETURN
157 END IF
158*
159* Quick return if possible
160*
161 IF( n.EQ.0 )
162 $ RETURN
163*
164* Determine the block size for this environment.
165*
166 nb = ilaenv( 1, 'ZPOTRF', uplo, n, -1, -1, -1 )
167 IF( nb.LE.1 .OR. nb.GE.n ) THEN
168*
169* Use unblocked code.
170*
171 CALL zpotrf2( uplo, n, a, lda, info )
172 ELSE
173*
174* Use blocked code.
175*
176 IF( upper ) THEN
177*
178* Compute the Cholesky factorization A = U**H *U.
179*
180 DO 10 j = 1, n, nb
181*
182* Update and factorize the current diagonal block and test
183* for non-positive-definiteness.
184*
185 jb = min( nb, n-j+1 )
186 CALL zherk( 'Upper', 'Conjugate transpose', jb, j-1,
187 $ -one, a( 1, j ), lda, one, a( j, j ), lda )
188 CALL zpotrf2( 'Upper', jb, a( j, j ), lda, info )
189 IF( info.NE.0 )
190 $ GO TO 30
191 IF( j+jb.LE.n ) THEN
192*
193* Compute the current block row.
194*
195 CALL zgemm( 'Conjugate transpose', 'No transpose',
196 $ jb,
197 $ n-j-jb+1, j-1, -cone, a( 1, j ), lda,
198 $ a( 1, j+jb ), lda, cone, a( j, j+jb ),
199 $ lda )
200 CALL ztrsm( 'Left', 'Upper', 'Conjugate transpose',
201 $ 'Non-unit', jb, n-j-jb+1, cone, a( j, j ),
202 $ lda, a( j, j+jb ), lda )
203 END IF
204 10 CONTINUE
205*
206 ELSE
207*
208* Compute the Cholesky factorization A = L*L**H.
209*
210 DO 20 j = 1, n, nb
211*
212* Update and factorize the current diagonal block and test
213* for non-positive-definiteness.
214*
215 jb = min( nb, n-j+1 )
216 CALL zherk( 'Lower', 'No transpose', jb, j-1, -one,
217 $ a( j, 1 ), lda, one, a( j, j ), lda )
218 CALL zpotrf2( 'Lower', jb, a( j, j ), lda, info )
219 IF( info.NE.0 )
220 $ GO TO 30
221 IF( j+jb.LE.n ) THEN
222*
223* Compute the current block column.
224*
225 CALL zgemm( 'No transpose', 'Conjugate transpose',
226 $ n-j-jb+1, jb, j-1, -cone, a( j+jb, 1 ),
227 $ lda, a( j, 1 ), lda, cone, a( j+jb, j ),
228 $ lda )
229 CALL ztrsm( 'Right', 'Lower',
230 $ 'Conjugate transpose',
231 $ 'Non-unit', n-j-jb+1, jb, cone, a( j, j ),
232 $ lda, a( j+jb, j ), lda )
233 END IF
234 20 CONTINUE
235 END IF
236 END IF
237 GO TO 40
238*
239 30 CONTINUE
240 info = info + j - 1
241*
242 40 CONTINUE
243 RETURN
244*
245* End of ZPOTRF
246*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
ZGEMM
Definition zgemm.f:188
subroutine zherk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)
ZHERK
Definition zherk.f:173
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:160
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
recursive subroutine zpotrf2(uplo, n, a, lda, info)
ZPOTRF2
Definition zpotrf2.f:106
subroutine ztrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
ZTRSM
Definition ztrsm.f:180
Here is the call graph for this function:
Here is the caller graph for this function: