LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zpotrf.f
Go to the documentation of this file.
1 C> \brief \b ZPOTRF VARIANT: right looking block version of the algorithm, calling Level 3 BLAS.
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE ZPOTRF ( UPLO, N, A, LDA, INFO )
12 *
13 * .. Scalar Arguments ..
14 * CHARACTER UPLO
15 * INTEGER INFO, LDA, N
16 * ..
17 * .. Array Arguments ..
18 * COMPLEX*16 A( LDA, * )
19 * ..
20 *
21 * Purpose
22 * =======
23 *
24 C>\details \b Purpose:
25 C>\verbatim
26 C>
27 C> ZPOTRF computes the Cholesky factorization of a real Hermitian
28 C> positive definite matrix A.
29 C>
30 C> The factorization has the form
31 C> A = U**H * U, if UPLO = 'U', or
32 C> A = L * L**H, if UPLO = 'L',
33 C> where U is an upper triangular matrix and L is lower triangular.
34 C>
35 C> This is the right looking block version of the algorithm, calling Level 3 BLAS.
36 C>
37 C>\endverbatim
38 *
39 * Arguments:
40 * ==========
41 *
42 C> \param[in] UPLO
43 C> \verbatim
44 C> UPLO is CHARACTER*1
45 C> = 'U': Upper triangle of A is stored;
46 C> = 'L': Lower triangle of A is stored.
47 C> \endverbatim
48 C>
49 C> \param[in] N
50 C> \verbatim
51 C> N is INTEGER
52 C> The order of the matrix A. N >= 0.
53 C> \endverbatim
54 C>
55 C> \param[in,out] A
56 C> \verbatim
57 C> A is COMPLEX*16 array, dimension (LDA,N)
58 C> On entry, the Hermitian matrix A. If UPLO = 'U', the leading
59 C> N-by-N upper triangular part of A contains the upper
60 C> triangular part of the matrix A, and the strictly lower
61 C> triangular part of A is not referenced. If UPLO = 'L', the
62 C> leading N-by-N lower triangular part of A contains the lower
63 C> triangular part of the matrix A, and the strictly upper
64 C> triangular part of A is not referenced.
65 C> \endverbatim
66 C> \verbatim
67 C> On exit, if INFO = 0, the factor U or L from the Cholesky
68 C> factorization A = U**H*U or A = L*L**H.
69 C> \endverbatim
70 C>
71 C> \param[in] LDA
72 C> \verbatim
73 C> LDA is INTEGER
74 C> The leading dimension of the array A. LDA >= max(1,N).
75 C> \endverbatim
76 C>
77 C> \param[out] INFO
78 C> \verbatim
79 C> INFO is INTEGER
80 C> = 0: successful exit
81 C> < 0: if INFO = -i, the i-th argument had an illegal value
82 C> > 0: if INFO = i, the leading minor of order i is not
83 C> positive definite, and the factorization could not be
84 C> completed.
85 C> \endverbatim
86 C>
87 *
88 * Authors:
89 * ========
90 *
91 C> \author Univ. of Tennessee
92 C> \author Univ. of California Berkeley
93 C> \author Univ. of Colorado Denver
94 C> \author NAG Ltd.
95 *
96 C> \date November 2011
97 *
98 C> \ingroup variantsPOcomputational
99 *
100 * =====================================================================
101  SUBROUTINE zpotrf ( UPLO, N, A, LDA, INFO )
102 *
103 * -- LAPACK computational routine (version 3.1) --
104 * -- LAPACK is a software package provided by Univ. of Tennessee, --
105 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
106 * November 2011
107 *
108 * .. Scalar Arguments ..
109  CHARACTER uplo
110  INTEGER info, lda, n
111 * ..
112 * .. Array Arguments ..
113  COMPLEX*16 a( lda, * )
114 * ..
115 *
116 * =====================================================================
117 *
118 * .. Parameters ..
119  DOUBLE PRECISION one
120  COMPLEX*16 cone
121  parameter( one = 1.0d+0, cone = ( 1.0d+0, 0.0d+0 ) )
122 * ..
123 * .. Local Scalars ..
124  LOGICAL upper
125  INTEGER j, jb, nb
126 * ..
127 * .. External Functions ..
128  LOGICAL lsame
129  INTEGER ilaenv
130  EXTERNAL lsame, ilaenv
131 * ..
132 * .. External Subroutines ..
133  EXTERNAL zgemm, zpotf2, zherk, ztrsm, xerbla
134 * ..
135 * .. Intrinsic Functions ..
136  INTRINSIC max, min
137 * ..
138 * .. Executable Statements ..
139 *
140 * Test the input parameters.
141 *
142  info = 0
143  upper = lsame( uplo, 'U' )
144  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
145  info = -1
146  ELSE IF( n.LT.0 ) THEN
147  info = -2
148  ELSE IF( lda.LT.max( 1, n ) ) THEN
149  info = -4
150  END IF
151  IF( info.NE.0 ) THEN
152  CALL xerbla( 'ZPOTRF', -info )
153  return
154  END IF
155 *
156 * Quick return if possible
157 *
158  IF( n.EQ.0 )
159  $ return
160 *
161 * Determine the block size for this environment.
162 *
163  nb = ilaenv( 1, 'ZPOTRF', uplo, n, -1, -1, -1 )
164  IF( nb.LE.1 .OR. nb.GE.n ) THEN
165 *
166 * Use unblocked code.
167 *
168  CALL zpotf2( uplo, n, a, lda, info )
169  ELSE
170 *
171 * Use blocked code.
172 *
173  IF( upper ) THEN
174 *
175 * Compute the Cholesky factorization A = U'*U.
176 *
177  DO 10 j = 1, n, nb
178 *
179 * Update and factorize the current diagonal block and test
180 * for non-positive-definiteness.
181 *
182  jb = min( nb, n-j+1 )
183 
184  CALL zpotf2( 'Upper', jb, a( j, j ), lda, info )
185 
186  IF( info.NE.0 )
187  $ go to 30
188 
189  IF( j+jb.LE.n ) THEN
190 *
191 * Updating the trailing submatrix.
192 *
193  CALL ztrsm( 'Left', 'Upper', 'Conjugate Transpose',
194  $ 'Non-unit', jb, n-j-jb+1, cone, a( j, j ),
195  $ lda, a( j, j+jb ), lda )
196  CALL zherk( 'Upper', 'Conjugate transpose', n-j-jb+1,
197  $ jb, -one, a( j, j+jb ), lda,
198  $ one, a( j+jb, j+jb ), lda )
199  END IF
200  10 continue
201 *
202  ELSE
203 *
204 * Compute the Cholesky factorization A = L*L'.
205 *
206  DO 20 j = 1, n, nb
207 *
208 * Update and factorize the current diagonal block and test
209 * for non-positive-definiteness.
210 *
211  jb = min( nb, n-j+1 )
212 
213  CALL zpotf2( 'Lower', jb, a( j, j ), lda, info )
214 
215  IF( info.NE.0 )
216  $ go to 30
217 
218  IF( j+jb.LE.n ) THEN
219 *
220 * Updating the trailing submatrix.
221 *
222  CALL ztrsm( 'Right', 'Lower', 'Conjugate Transpose',
223  $ 'Non-unit', n-j-jb+1, jb, cone, a( j, j ),
224  $ lda, a( j+jb, j ), lda )
225 
226  CALL zherk( 'Lower', 'No Transpose', n-j-jb+1, jb,
227  $ -one, a( j+jb, j ), lda,
228  $ one, a( j+jb, j+jb ), lda )
229  END IF
230  20 continue
231  END IF
232  END IF
233  go to 40
234 *
235  30 continue
236  info = info + j - 1
237 *
238  40 continue
239  return
240 *
241 * End of ZPOTRF
242 *
243  END