3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
11 * RECURSIVE SUBROUTINE ZPOTRF2( UPLO, N, A, LDA, INFO )
13 * .. Scalar Arguments ..
15 * INTEGER INFO, LDA, N
17 * .. Array Arguments ..
18 * COMPLEX*16 A( LDA, * )
27 *> ZPOTRF2 computes the Cholesky factorization of a real symmetric
28 *> positive definite matrix A using the recursive algorithm.
30 *> The factorization has the form
31 *> A = U**H * U, if UPLO = 'U', or
32 *> A = L * L**H, if UPLO = 'L',
33 *> where U is an upper triangular matrix and L is lower triangular.
35 *> This is the recursive version of the algorithm. It divides
36 *> the matrix into four submatrices:
38 *> [ A11 | A12 ] where A11 is n1 by n1 and A22 is n2 by n2
39 *> A = [ -----|----- ] with n1 = n/2
40 *> [ A21 | A22 ] n2 = n-n1
42 *> The subroutine calls itself to factor A11. Update and scale A21
43 *> or A12, update A22 then call itself to factor A22.
52 *> UPLO is CHARACTER*1
53 *> = 'U': Upper triangle of A is stored;
54 *> = 'L': Lower triangle of A is stored.
60 *> The order of the matrix A. N >= 0.
65 *> A is COMPLEX*16 array, dimension (LDA,N)
66 *> On entry, the symmetric matrix A. If UPLO = 'U', the leading
67 *> N-by-N upper triangular part of A contains the upper
68 *> triangular part of the matrix A, and the strictly lower
69 *> triangular part of A is not referenced. If UPLO = 'L', the
70 *> leading N-by-N lower triangular part of A contains the lower
71 *> triangular part of the matrix A, and the strictly upper
72 *> triangular part of A is not referenced.
74 *> On exit, if INFO = 0, the factor U or L from the Cholesky
75 *> factorization A = U**H*U or A = L*L**H.
81 *> The leading dimension of the array A. LDA >= max(1,N).
87 *> = 0: successful exit
88 *> < 0: if INFO = -i, the i-th argument had an illegal value
89 *> > 0: if INFO = i, the leading minor of order i is not
90 *> positive definite, and the factorization could not be
97 *> \author Univ. of Tennessee
98 *> \author Univ. of California Berkeley
99 *> \author Univ. of Colorado Denver
102 *> \date November 2015
104 *> \ingroup complex16POcomputational
106 * =====================================================================
107 RECURSIVE SUBROUTINE ZPOTRF2( UPLO, N, A, LDA, INFO )
109 * -- LAPACK computational routine (version 3.6.0) --
110 * -- LAPACK is a software package provided by Univ. of Tennessee, --
111 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
114 * .. Scalar Arguments ..
118 * .. Array Arguments ..
119 COMPLEX*16 A( LDA, * )
122 * =====================================================================
125 DOUBLE PRECISION ONE, ZERO
126 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
128 PARAMETER ( CONE = (1.0D+0, 0.0D+0) )
130 * .. Local Scalars ..
132 INTEGER N1, N2, IINFO
135 * .. External Functions ..
136 LOGICAL LSAME, DISNAN
137 EXTERNAL LSAME, DISNAN
139 * .. External Subroutines ..
140 EXTERNAL ZHERK, ZTRSM, XERBLA
142 * .. Intrinsic Functions ..
143 INTRINSIC MAX, DBLE, SQRT
145 * .. Executable Statements ..
147 * Test the input parameters
150 UPPER = LSAME( UPLO, 'U' )
151 IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
153 ELSE IF( N.LT.0 ) THEN
155 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
159 CALL XERBLA( 'ZPOTRF2', -INFO )
163 * Quick return if possible
172 * Test for non-positive-definiteness
174 AJJ = DBLE( A( 1, 1 ) )
175 IF( AJJ.LE.ZERO.OR.DISNAN( AJJ ) ) THEN
182 A( 1, 1 ) = SQRT( AJJ )
192 CALL ZPOTRF2( UPLO, N1, A( 1, 1 ), LDA, IINFO )
193 IF ( IINFO.NE.0 ) THEN
198 * Compute the Cholesky factorization A = U**H*U
202 * Update and scale A12
204 CALL ZTRSM( 'L', 'U', 'C', 'N', N1, N2, CONE,
205 $ A( 1, 1 ), LDA, A( 1, N1+1 ), LDA )
207 * Update and factor A22
209 CALL ZHERK( UPLO, 'C', N2, N1, -ONE, A( 1, N1+1 ), LDA,
210 $ ONE, A( N1+1, N1+1 ), LDA )
211 CALL ZPOTRF2( UPLO, N2, A( N1+1, N1+1 ), LDA, IINFO )
212 IF ( IINFO.NE.0 ) THEN
217 * Compute the Cholesky factorization A = L*L**H
221 * Update and scale A21
223 CALL ZTRSM( 'R', 'L', 'C', 'N', N2, N1, CONE,
224 $ A( 1, 1 ), LDA, A( N1+1, 1 ), LDA )
226 * Update and factor A22
228 CALL ZHERK( UPLO, 'N', N2, N1, -ONE, A( N1+1, 1 ), LDA,
229 $ ONE, A( N1+1, N1+1 ), LDA )
230 CALL ZPOTRF2( UPLO, N2, A( N1+1, N1+1 ), LDA, IINFO )
231 IF ( IINFO.NE.0 ) THEN