12321ad37e10a495fc1f4e5c884b34151387c50d
[platform/upstream/lapack.git] / SRC / spstf2.f
1 *> \brief \b SPSTF2 computes the Cholesky factorization with complete pivoting of a real symmetric positive semidefinite matrix.
2 *
3 *  =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at 
6 *            http://www.netlib.org/lapack/explore-html/ 
7 *
8 *> \htmlonly
9 *> Download SPSTF2 + dependencies 
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/spstf2.f"> 
11 *> [TGZ]</a> 
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/spstf2.f"> 
13 *> [ZIP]</a> 
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/spstf2.f"> 
15 *> [TXT]</a>
16 *> \endhtmlonly 
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE SPSTF2( 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 *       REAL               A( LDA, * ), WORK( 2*N )
30 *       INTEGER            PIV( N )
31 *       ..
32 *  
33 *
34 *> \par Purpose:
35 *  =============
36 *>
37 *> \verbatim
38 *>
39 *> SPSTF2 computes the Cholesky factorization with complete
40 *> pivoting of a real symmetric positive semidefinite matrix A.
41 *>
42 *> The factorization has the form
43 *>    P**T * A * P = U**T * U ,  if UPLO = 'U',
44 *>    P**T * A * P = L  * L**T,  if UPLO = 'L',
45 *> where U is an upper triangular matrix and L is lower triangular, and
46 *> P is stored as vector PIV.
47 *>
48 *> This algorithm does not attempt to check that A is positive
49 *> semidefinite. This version of the algorithm calls level 2 BLAS.
50 *> \endverbatim
51 *
52 *  Arguments:
53 *  ==========
54 *
55 *> \param[in] UPLO
56 *> \verbatim
57 *>          UPLO is CHARACTER*1
58 *>          Specifies whether the upper or lower triangular part of the
59 *>          symmetric matrix A is stored.
60 *>          = 'U':  Upper triangular
61 *>          = 'L':  Lower triangular
62 *> \endverbatim
63 *>
64 *> \param[in] N
65 *> \verbatim
66 *>          N is INTEGER
67 *>          The order of the matrix A.  N >= 0.
68 *> \endverbatim
69 *>
70 *> \param[in,out] A
71 *> \verbatim
72 *>          A is REAL array, dimension (LDA,N)
73 *>          On entry, the symmetric matrix A.  If UPLO = 'U', the leading
74 *>          n by n upper triangular part of A contains the upper
75 *>          triangular part of the matrix A, and the strictly lower
76 *>          triangular part of A is not referenced.  If UPLO = 'L', the
77 *>          leading n by n lower triangular part of A contains the lower
78 *>          triangular part of the matrix A, and the strictly upper
79 *>          triangular part of A is not referenced.
80 *>
81 *>          On exit, if INFO = 0, the factor U or L from the Cholesky
82 *>          factorization as above.
83 *> \endverbatim
84 *>
85 *> \param[out] PIV
86 *> \verbatim
87 *>          PIV is INTEGER array, dimension (N)
88 *>          PIV is such that the nonzero entries are P( PIV(K), K ) = 1.
89 *> \endverbatim
90 *>
91 *> \param[out] RANK
92 *> \verbatim
93 *>          RANK is INTEGER
94 *>          The rank of A given by the number of steps the algorithm
95 *>          completed.
96 *> \endverbatim
97 *>
98 *> \param[in] TOL
99 *> \verbatim
100 *>          TOL is REAL
101 *>          User defined tolerance. If TOL < 0, then N*U*MAX( A( K,K ) )
102 *>          will be used. The algorithm terminates at the (K-1)st step
103 *>          if the pivot <= TOL.
104 *> \endverbatim
105 *>
106 *> \param[in] LDA
107 *> \verbatim
108 *>          LDA is INTEGER
109 *>          The leading dimension of the array A.  LDA >= max(1,N).
110 *> \endverbatim
111 *>
112 *> \param[out] WORK
113 *> \verbatim
114 *>          WORK is REAL array, dimension (2*N)
115 *>          Work space.
116 *> \endverbatim
117 *>
118 *> \param[out] INFO
119 *> \verbatim
120 *>          INFO is INTEGER
121 *>          < 0: If INFO = -K, the K-th argument had an illegal value,
122 *>          = 0: algorithm completed successfully, and
123 *>          > 0: the matrix A is either rank deficient with computed rank
124 *>               as returned in RANK, or is not positive semidefinite. See
125 *>               Section 7 of LAPACK Working Note #161 for further
126 *>               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 2015
138 *
139 *> \ingroup realOTHERcomputational
140 *
141 *  =====================================================================
142       SUBROUTINE SPSTF2( UPLO, N, A, LDA, PIV, RANK, TOL, WORK, INFO )
143 *
144 *  -- LAPACK computational routine (version 3.6.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 2015
148 *
149 *     .. Scalar Arguments ..
150       REAL               TOL
151       INTEGER            INFO, LDA, N, RANK
152       CHARACTER          UPLO
153 *     ..
154 *     .. Array Arguments ..
155       REAL               A( LDA, * ), WORK( 2*N )
156       INTEGER            PIV( N )
157 *     ..
158 *
159 *  =====================================================================
160 *
161 *     .. Parameters ..
162       REAL               ONE, ZERO
163       PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
164 *     ..
165 *     .. Local Scalars ..
166       REAL               AJJ, SSTOP, STEMP
167       INTEGER            I, ITEMP, J, PVT
168       LOGICAL            UPPER
169 *     ..
170 *     .. External Functions ..
171       REAL               SLAMCH
172       LOGICAL            LSAME, SISNAN
173       EXTERNAL           SLAMCH, LSAME, SISNAN
174 *     ..
175 *     .. External Subroutines ..
176       EXTERNAL           SGEMV, SSCAL, SSWAP, XERBLA
177 *     ..
178 *     .. Intrinsic Functions ..
179       INTRINSIC          MAX, SQRT, MAXLOC
180 *     ..
181 *     .. Executable Statements ..
182 *
183 *     Test the input parameters
184 *
185       INFO = 0
186       UPPER = LSAME( UPLO, 'U' )
187       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
188          INFO = -1
189       ELSE IF( N.LT.0 ) THEN
190          INFO = -2
191       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
192          INFO = -4
193       END IF
194       IF( INFO.NE.0 ) THEN
195          CALL XERBLA( 'SPSTF2', -INFO )
196          RETURN
197       END IF
198 *
199 *     Quick return if possible
200 *
201       IF( N.EQ.0 )
202      $   RETURN
203 *
204 *     Initialize PIV
205 *
206       DO 100 I = 1, N
207          PIV( I ) = I
208   100 CONTINUE
209 *
210 *     Compute stopping value
211 *
212       PVT = 1
213       AJJ = A( PVT, PVT )
214       DO I = 2, N
215          IF( A( I, I ).GT.AJJ ) THEN
216             PVT = I
217             AJJ = A( PVT, PVT )
218          END IF
219       END DO
220       IF( AJJ.LE.ZERO.OR.SISNAN( AJJ ) ) THEN
221          RANK = 0
222          INFO = 1
223          GO TO 170
224       END IF
225 *
226 *     Compute stopping value if not supplied
227 *
228       IF( TOL.LT.ZERO ) THEN
229          SSTOP = N * SLAMCH( 'Epsilon' ) * AJJ
230       ELSE
231          SSTOP = TOL
232       END IF
233 *
234 *     Set first half of WORK to zero, holds dot products
235 *
236       DO 110 I = 1, N
237          WORK( I ) = 0
238   110 CONTINUE
239 *
240       IF( UPPER ) THEN
241 *
242 *        Compute the Cholesky factorization P**T * A * P = U**T * U
243 *
244          DO 130 J = 1, N
245 *
246 *        Find pivot, test for exit, else swap rows and columns
247 *        Update dot products, compute possible pivots which are
248 *        stored in the second half of WORK
249 *
250             DO 120 I = J, N
251 *
252                IF( J.GT.1 ) THEN
253                   WORK( I ) = WORK( I ) + A( J-1, I )**2
254                END IF
255                WORK( N+I ) = A( I, I ) - WORK( I )
256 *
257   120       CONTINUE
258 *
259             IF( J.GT.1 ) THEN
260                ITEMP = MAXLOC( WORK( (N+J):(2*N) ), 1 )
261                PVT = ITEMP + J - 1
262                AJJ = WORK( N+PVT )
263                IF( AJJ.LE.SSTOP.OR.SISNAN( AJJ ) ) THEN
264                   A( J, J ) = AJJ
265                   GO TO 160
266                END IF
267             END IF
268 *
269             IF( J.NE.PVT ) THEN
270 *
271 *              Pivot OK, so can now swap pivot rows and columns
272 *
273                A( PVT, PVT ) = A( J, J )
274                CALL SSWAP( J-1, A( 1, J ), 1, A( 1, PVT ), 1 )
275                IF( PVT.LT.N )
276      $            CALL SSWAP( N-PVT, A( J, PVT+1 ), LDA,
277      $                        A( PVT, PVT+1 ), LDA )
278                CALL SSWAP( PVT-J-1, A( J, J+1 ), LDA, A( J+1, PVT ), 1 )
279 *
280 *              Swap dot products and PIV
281 *
282                STEMP = WORK( J )
283                WORK( J ) = WORK( PVT )
284                WORK( PVT ) = STEMP
285                ITEMP = PIV( PVT )
286                PIV( PVT ) = PIV( J )
287                PIV( J ) = ITEMP
288             END IF
289 *
290             AJJ = SQRT( AJJ )
291             A( J, J ) = AJJ
292 *
293 *           Compute elements J+1:N of row J
294 *
295             IF( J.LT.N ) THEN
296                CALL SGEMV( 'Trans', J-1, N-J, -ONE, A( 1, J+1 ), LDA,
297      $                     A( 1, J ), 1, ONE, A( J, J+1 ), LDA )
298                CALL SSCAL( N-J, ONE / AJJ, A( J, J+1 ), LDA )
299             END IF
300 *
301   130    CONTINUE
302 *
303       ELSE
304 *
305 *        Compute the Cholesky factorization P**T * A * P = L * L**T
306 *
307          DO 150 J = 1, N
308 *
309 *        Find pivot, test for exit, else swap rows and columns
310 *        Update dot products, compute possible pivots which are
311 *        stored in the second half of WORK
312 *
313             DO 140 I = J, N
314 *
315                IF( J.GT.1 ) THEN
316                   WORK( I ) = WORK( I ) + A( I, J-1 )**2
317                END IF
318                WORK( N+I ) = A( I, I ) - WORK( I )
319 *
320   140       CONTINUE
321 *
322             IF( J.GT.1 ) THEN
323                ITEMP = MAXLOC( WORK( (N+J):(2*N) ), 1 )
324                PVT = ITEMP + J - 1
325                AJJ = WORK( N+PVT )
326                IF( AJJ.LE.SSTOP.OR.SISNAN( AJJ ) ) THEN
327                   A( J, J ) = AJJ
328                   GO TO 160
329                END IF
330             END IF
331 *
332             IF( J.NE.PVT ) THEN
333 *
334 *              Pivot OK, so can now swap pivot rows and columns
335 *
336                A( PVT, PVT ) = A( J, J )
337                CALL SSWAP( J-1, A( J, 1 ), LDA, A( PVT, 1 ), LDA )
338                IF( PVT.LT.N )
339      $            CALL SSWAP( N-PVT, A( PVT+1, J ), 1, A( PVT+1, PVT ),
340      $                        1 )
341                CALL SSWAP( PVT-J-1, A( J+1, J ), 1, A( PVT, J+1 ), LDA )
342 *
343 *              Swap dot products and PIV
344 *
345                STEMP = WORK( J )
346                WORK( J ) = WORK( PVT )
347                WORK( PVT ) = STEMP
348                ITEMP = PIV( PVT )
349                PIV( PVT ) = PIV( J )
350                PIV( J ) = ITEMP
351             END IF
352 *
353             AJJ = SQRT( AJJ )
354             A( J, J ) = AJJ
355 *
356 *           Compute elements J+1:N of column J
357 *
358             IF( J.LT.N ) THEN
359                CALL SGEMV( 'No Trans', N-J, J-1, -ONE, A( J+1, 1 ), LDA,
360      $                     A( J, 1 ), LDA, ONE, A( J+1, J ), 1 )
361                CALL SSCAL( N-J, ONE / AJJ, A( J+1, J ), 1 )
362             END IF
363 *
364   150    CONTINUE
365 *
366       END IF
367 *
368 *     Ran to completion, A has full rank
369 *
370       RANK = N
371 *
372       GO TO 170
373   160 CONTINUE
374 *
375 *     Rank is number of steps completed.  Set INFO = 1 to signal
376 *     that the factorization cannot be used to solve a system.
377 *
378       RANK = J - 1
379       INFO = 1
380 *
381   170 CONTINUE
382       RETURN
383 *
384 *     End of SPSTF2
385 *
386       END