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

◆ cpotrf()

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

CPOTRF

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

Purpose:
 CPOTRF 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 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 106 of file cpotrf.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
124 COMPLEX CONE
125 parameter( one = 1.0e+0, cone = ( 1.0e+0, 0.0e+0 ) )
126* ..
127* .. Local Scalars ..
128 LOGICAL UPPER
129 INTEGER J, JB, NB
130* ..
131* .. External Functions ..
132 LOGICAL LSAME
133 INTEGER ILAENV
134 EXTERNAL lsame, ilaenv
135* ..
136* .. External Subroutines ..
137 EXTERNAL cgemm, cherk, cpotrf2, ctrsm, xerbla
138* ..
139* .. Intrinsic Functions ..
140 INTRINSIC max, min
141* ..
142* .. Executable Statements ..
143*
144* Test the input parameters.
145*
146 info = 0
147 upper = lsame( uplo, 'U' )
148 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
149 info = -1
150 ELSE IF( n.LT.0 ) THEN
151 info = -2
152 ELSE IF( lda.LT.max( 1, n ) ) THEN
153 info = -4
154 END IF
155 IF( info.NE.0 ) THEN
156 CALL xerbla( 'CPOTRF', -info )
157 RETURN
158 END IF
159*
160* Quick return if possible
161*
162 IF( n.EQ.0 )
163 $ RETURN
164*
165* Determine the block size for this environment.
166*
167 nb = ilaenv( 1, 'CPOTRF', uplo, n, -1, -1, -1 )
168 IF( nb.LE.1 .OR. nb.GE.n ) THEN
169*
170* Use unblocked code.
171*
172 CALL cpotrf2( uplo, n, a, lda, info )
173 ELSE
174*
175* Use blocked code.
176*
177 IF( upper ) THEN
178*
179* Compute the Cholesky factorization A = U**H *U.
180*
181 DO 10 j = 1, n, nb
182*
183* Update and factorize the current diagonal block and test
184* for non-positive-definiteness.
185*
186 jb = min( nb, n-j+1 )
187 CALL cherk( 'Upper', 'Conjugate transpose', jb, j-1,
188 $ -one, a( 1, j ), lda, one, a( j, j ), lda )
189 CALL cpotrf2( 'Upper', jb, a( j, j ), lda, info )
190 IF( info.NE.0 )
191 $ GO TO 30
192 IF( j+jb.LE.n ) THEN
193*
194* Compute the current block row.
195*
196 CALL cgemm( 'Conjugate transpose', 'No transpose', 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 ctrsm( '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 cherk( 'Lower', 'No transpose', jb, j-1, -one,
217 $ a( j, 1 ), lda, one, a( j, j ), lda )
218 CALL cpotrf2( '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 cgemm( '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 ctrsm( 'Right', 'Lower', 'Conjugate transpose',
230 $ 'Non-unit', n-j-jb+1, jb, cone, a( j, j ),
231 $ lda, a( j+jb, j ), lda )
232 END IF
233 20 CONTINUE
234 END IF
235 END IF
236 GO TO 40
237*
238 30 CONTINUE
239 info = info + j - 1
240*
241 40 CONTINUE
242 RETURN
243*
244* End of CPOTRF
245*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine cgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
CGEMM
Definition cgemm.f:188
subroutine cherk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)
CHERK
Definition cherk.f:173
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:162
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
recursive subroutine cpotrf2(uplo, n, a, lda, info)
CPOTRF2
Definition cpotrf2.f:106
subroutine ctrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
CTRSM
Definition ctrsm.f:180
Here is the call graph for this function:
Here is the caller graph for this function: