LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
cpstrf.f
Go to the documentation of this file.
1 *> \brief \b CPSTRF
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CPSTRF + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cpstrf.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cpstrf.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cpstrf.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE CPSTRF( UPLO, N, A, LDA, PIV, RANK, TOL, WORK, INFO )
22 *
23 * .. Scalar Arguments ..
24 * REAL TOL
25 * INTEGER INFO, LDA, N, RANK
26 * CHARACTER UPLO
27 * ..
28 * .. Array Arguments ..
29 * COMPLEX A( LDA, * )
30 * REAL WORK( 2*N )
31 * INTEGER PIV( N )
32 * ..
33 *
34 *
35 *> \par Purpose:
36 * =============
37 *>
38 *> \verbatim
39 *>
40 *> CPSTRF computes the Cholesky factorization with complete
41 *> pivoting of a complex Hermitian positive semidefinite matrix A.
42 *>
43 *> The factorization has the form
44 *> P**T * A * P = U**H * U , if UPLO = 'U',
45 *> P**T * A * P = L * L**H, if UPLO = 'L',
46 *> where U is an upper triangular matrix and L is lower triangular, and
47 *> P is stored as vector PIV.
48 *>
49 *> This algorithm does not attempt to check that A is positive
50 *> semidefinite. This version of the algorithm calls level 3 BLAS.
51 *> \endverbatim
52 *
53 * Arguments:
54 * ==========
55 *
56 *> \param[in] UPLO
57 *> \verbatim
58 *> UPLO is CHARACTER*1
59 *> Specifies whether the upper or lower triangular part of the
60 *> symmetric matrix A is stored.
61 *> = 'U': Upper triangular
62 *> = 'L': Lower triangular
63 *> \endverbatim
64 *>
65 *> \param[in] N
66 *> \verbatim
67 *> N is INTEGER
68 *> The order of the matrix A. N >= 0.
69 *> \endverbatim
70 *>
71 *> \param[in,out] A
72 *> \verbatim
73 *> A is COMPLEX array, dimension (LDA,N)
74 *> On entry, the symmetric matrix A. If UPLO = 'U', the leading
75 *> n by n upper triangular part of A contains the upper
76 *> triangular part of the matrix A, and the strictly lower
77 *> triangular part of A is not referenced. If UPLO = 'L', the
78 *> leading n by n lower triangular part of A contains the lower
79 *> triangular part of the matrix A, and the strictly upper
80 *> triangular part of A is not referenced.
81 *>
82 *> On exit, if INFO = 0, the factor U or L from the Cholesky
83 *> factorization as above.
84 *> \endverbatim
85 *>
86 *> \param[in] LDA
87 *> \verbatim
88 *> LDA is INTEGER
89 *> The leading dimension of the array A. LDA >= max(1,N).
90 *> \endverbatim
91 *>
92 *> \param[out] PIV
93 *> \verbatim
94 *> PIV is INTEGER array, dimension (N)
95 *> PIV is such that the nonzero entries are P( PIV(K), K ) = 1.
96 *> \endverbatim
97 *>
98 *> \param[out] RANK
99 *> \verbatim
100 *> RANK is INTEGER
101 *> The rank of A given by the number of steps the algorithm
102 *> completed.
103 *> \endverbatim
104 *>
105 *> \param[in] TOL
106 *> \verbatim
107 *> TOL is REAL
108 *> User defined tolerance. If TOL < 0, then N*U*MAX( A(K,K) )
109 *> will be used. The algorithm terminates at the (K-1)st step
110 *> if the pivot <= TOL.
111 *> \endverbatim
112 *>
113 *> \param[out] WORK
114 *> \verbatim
115 *> WORK is REAL array, dimension (2*N)
116 *> Work space.
117 *> \endverbatim
118 *>
119 *> \param[out] INFO
120 *> \verbatim
121 *> INFO is INTEGER
122 *> < 0: If INFO = -K, the K-th argument had an illegal value,
123 *> = 0: algorithm completed successfully, and
124 *> > 0: the matrix A is either rank deficient with computed rank
125 *> as returned in RANK, or is indefinite. See Section 7 of
126 *> LAPACK Working Note #161 for further information.
127 *> \endverbatim
128 *
129 * Authors:
130 * ========
131 *
132 *> \author Univ. of Tennessee
133 *> \author Univ. of California Berkeley
134 *> \author Univ. of Colorado Denver
135 *> \author NAG Ltd.
136 *
137 *> \date November 2011
138 *
139 *> \ingroup complexOTHERcomputational
140 *
141 * =====================================================================
142  SUBROUTINE cpstrf( UPLO, N, A, LDA, PIV, RANK, TOL, WORK, INFO )
143 *
144 * -- LAPACK computational routine (version 3.4.0) --
145 * -- LAPACK is a software package provided by Univ. of Tennessee, --
146 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
147 * November 2011
148 *
149 * .. Scalar Arguments ..
150  REAL tol
151  INTEGER info, lda, n, rank
152  CHARACTER uplo
153 * ..
154 * .. Array Arguments ..
155  COMPLEX a( lda, * )
156  REAL work( 2*n )
157  INTEGER piv( n )
158 * ..
159 *
160 * =====================================================================
161 *
162 * .. Parameters ..
163  REAL one, zero
164  parameter( one = 1.0e+0, zero = 0.0e+0 )
165  COMPLEX cone
166  parameter( cone = ( 1.0e+0, 0.0e+0 ) )
167 * ..
168 * .. Local Scalars ..
169  COMPLEX ctemp
170  REAL ajj, sstop, stemp
171  INTEGER i, itemp, j, jb, k, nb, pvt
172  LOGICAL upper
173 * ..
174 * .. External Functions ..
175  REAL slamch
176  INTEGER ilaenv
177  LOGICAL lsame, sisnan
178  EXTERNAL slamch, ilaenv, lsame, sisnan
179 * ..
180 * .. External Subroutines ..
181  EXTERNAL cgemv, cherk, clacgv, cpstf2, csscal, cswap,
182  $ xerbla
183 * ..
184 * .. Intrinsic Functions ..
185  INTRINSIC conjg, max, min, REAL, sqrt, maxloc
186 * ..
187 * .. Executable Statements ..
188 *
189 * Test the input parameters.
190 *
191  info = 0
192  upper = lsame( uplo, 'U' )
193  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
194  info = -1
195  ELSE IF( n.LT.0 ) THEN
196  info = -2
197  ELSE IF( lda.LT.max( 1, n ) ) THEN
198  info = -4
199  END IF
200  IF( info.NE.0 ) THEN
201  CALL xerbla( 'CPSTRF', -info )
202  return
203  END IF
204 *
205 * Quick return if possible
206 *
207  IF( n.EQ.0 )
208  $ return
209 *
210 * Get block size
211 *
212  nb = ilaenv( 1, 'CPOTRF', uplo, n, -1, -1, -1 )
213  IF( nb.LE.1 .OR. nb.GE.n ) THEN
214 *
215 * Use unblocked code
216 *
217  CALL cpstf2( uplo, n, a( 1, 1 ), lda, piv, rank, tol, work,
218  $ info )
219  go to 230
220 *
221  ELSE
222 *
223 * Initialize PIV
224 *
225  DO 100 i = 1, n
226  piv( i ) = i
227  100 continue
228 *
229 * Compute stopping value
230 *
231  DO 110 i = 1, n
232  work( i ) = REAL( A( I, I ) )
233  110 continue
234  pvt = maxloc( work( 1:n ), 1 )
235  ajj = REAL( A( PVT, PVT ) )
236  IF( ajj.EQ.zero.OR.sisnan( ajj ) ) THEN
237  rank = 0
238  info = 1
239  go to 230
240  END IF
241 *
242 * Compute stopping value if not supplied
243 *
244  IF( tol.LT.zero ) THEN
245  sstop = n * slamch( 'Epsilon' ) * ajj
246  ELSE
247  sstop = tol
248  END IF
249 *
250 *
251  IF( upper ) THEN
252 *
253 * Compute the Cholesky factorization P**T * A * P = U**H * U
254 *
255  DO 160 k = 1, n, nb
256 *
257 * Account for last block not being NB wide
258 *
259  jb = min( nb, n-k+1 )
260 *
261 * Set relevant part of first half of WORK to zero,
262 * holds dot products
263 *
264  DO 120 i = k, n
265  work( i ) = 0
266  120 continue
267 *
268  DO 150 j = k, k + jb - 1
269 *
270 * Find pivot, test for exit, else swap rows and columns
271 * Update dot products, compute possible pivots which are
272 * stored in the second half of WORK
273 *
274  DO 130 i = j, n
275 *
276  IF( j.GT.k ) THEN
277  work( i ) = work( i ) +
278  $ REAL( CONJG( A( J-1, I ) )*
279  $ a( j-1, i ) )
280  END IF
281  work( n+i ) = REAL( A( I, I ) ) - work( i )
282 *
283  130 continue
284 *
285  IF( j.GT.1 ) THEN
286  itemp = maxloc( work( (n+j):(2*n) ), 1 )
287  pvt = itemp + j - 1
288  ajj = work( n+pvt )
289  IF( ajj.LE.sstop.OR.sisnan( ajj ) ) THEN
290  a( j, j ) = ajj
291  go to 220
292  END IF
293  END IF
294 *
295  IF( j.NE.pvt ) THEN
296 *
297 * Pivot OK, so can now swap pivot rows and columns
298 *
299  a( pvt, pvt ) = a( j, j )
300  CALL cswap( j-1, a( 1, j ), 1, a( 1, pvt ), 1 )
301  IF( pvt.LT.n )
302  $ CALL cswap( n-pvt, a( j, pvt+1 ), lda,
303  $ a( pvt, pvt+1 ), lda )
304  DO 140 i = j + 1, pvt - 1
305  ctemp = conjg( a( j, i ) )
306  a( j, i ) = conjg( a( i, pvt ) )
307  a( i, pvt ) = ctemp
308  140 continue
309  a( j, pvt ) = conjg( a( j, pvt ) )
310 *
311 * Swap dot products and PIV
312 *
313  stemp = work( j )
314  work( j ) = work( pvt )
315  work( pvt ) = stemp
316  itemp = piv( pvt )
317  piv( pvt ) = piv( j )
318  piv( j ) = itemp
319  END IF
320 *
321  ajj = sqrt( ajj )
322  a( j, j ) = ajj
323 *
324 * Compute elements J+1:N of row J.
325 *
326  IF( j.LT.n ) THEN
327  CALL clacgv( j-1, a( 1, j ), 1 )
328  CALL cgemv( 'Trans', j-k, n-j, -cone, a( k, j+1 ),
329  $ lda, a( k, j ), 1, cone, a( j, j+1 ),
330  $ lda )
331  CALL clacgv( j-1, a( 1, j ), 1 )
332  CALL csscal( n-j, one / ajj, a( j, j+1 ), lda )
333  END IF
334 *
335  150 continue
336 *
337 * Update trailing matrix, J already incremented
338 *
339  IF( k+jb.LE.n ) THEN
340  CALL cherk( 'Upper', 'Conj Trans', n-j+1, jb, -one,
341  $ a( k, j ), lda, one, a( j, j ), lda )
342  END IF
343 *
344  160 continue
345 *
346  ELSE
347 *
348 * Compute the Cholesky factorization P**T * A * P = L * L**H
349 *
350  DO 210 k = 1, n, nb
351 *
352 * Account for last block not being NB wide
353 *
354  jb = min( nb, n-k+1 )
355 *
356 * Set relevant part of first half of WORK to zero,
357 * holds dot products
358 *
359  DO 170 i = k, n
360  work( i ) = 0
361  170 continue
362 *
363  DO 200 j = k, k + jb - 1
364 *
365 * Find pivot, test for exit, else swap rows and columns
366 * Update dot products, compute possible pivots which are
367 * stored in the second half of WORK
368 *
369  DO 180 i = j, n
370 *
371  IF( j.GT.k ) THEN
372  work( i ) = work( i ) +
373  $ REAL( CONJG( A( I, J-1 ) )*
374  $ a( i, j-1 ) )
375  END IF
376  work( n+i ) = REAL( A( I, I ) ) - work( i )
377 *
378  180 continue
379 *
380  IF( j.GT.1 ) THEN
381  itemp = maxloc( work( (n+j):(2*n) ), 1 )
382  pvt = itemp + j - 1
383  ajj = work( n+pvt )
384  IF( ajj.LE.sstop.OR.sisnan( ajj ) ) THEN
385  a( j, j ) = ajj
386  go to 220
387  END IF
388  END IF
389 *
390  IF( j.NE.pvt ) THEN
391 *
392 * Pivot OK, so can now swap pivot rows and columns
393 *
394  a( pvt, pvt ) = a( j, j )
395  CALL cswap( j-1, a( j, 1 ), lda, a( pvt, 1 ), lda )
396  IF( pvt.LT.n )
397  $ CALL cswap( n-pvt, a( pvt+1, j ), 1,
398  $ a( pvt+1, pvt ), 1 )
399  DO 190 i = j + 1, pvt - 1
400  ctemp = conjg( a( i, j ) )
401  a( i, j ) = conjg( a( pvt, i ) )
402  a( pvt, i ) = ctemp
403  190 continue
404  a( pvt, j ) = conjg( a( pvt, j ) )
405 *
406 * Swap dot products and PIV
407 *
408  stemp = work( j )
409  work( j ) = work( pvt )
410  work( pvt ) = stemp
411  itemp = piv( pvt )
412  piv( pvt ) = piv( j )
413  piv( j ) = itemp
414  END IF
415 *
416  ajj = sqrt( ajj )
417  a( j, j ) = ajj
418 *
419 * Compute elements J+1:N of column J.
420 *
421  IF( j.LT.n ) THEN
422  CALL clacgv( j-1, a( j, 1 ), lda )
423  CALL cgemv( 'No Trans', n-j, j-k, -cone,
424  $ a( j+1, k ), lda, a( j, k ), lda, cone,
425  $ a( j+1, j ), 1 )
426  CALL clacgv( j-1, a( j, 1 ), lda )
427  CALL csscal( n-j, one / ajj, a( j+1, j ), 1 )
428  END IF
429 *
430  200 continue
431 *
432 * Update trailing matrix, J already incremented
433 *
434  IF( k+jb.LE.n ) THEN
435  CALL cherk( 'Lower', 'No Trans', n-j+1, jb, -one,
436  $ a( j, k ), lda, one, a( j, j ), lda )
437  END IF
438 *
439  210 continue
440 *
441  END IF
442  END IF
443 *
444 * Ran to completion, A has full rank
445 *
446  rank = n
447 *
448  go to 230
449  220 continue
450 *
451 * Rank is the number of steps completed. Set INFO = 1 to signal
452 * that the factorization cannot be used to solve a system.
453 *
454  rank = j - 1
455  info = 1
456 *
457  230 continue
458  return
459 *
460 * End of CPSTRF
461 *
462  END