ENH: Improving the travis dashboard name
[platform/upstream/lapack.git] / SRC / ssytrf_rook.f
1 *> \brief \b SSYTRF_ROOK
2 *
3 *  =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 *            http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SSYTRF_ROOK + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ssytrf_rook.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ssytrf_rook.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ssytrf_rook.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE SSYTRF_ROOK( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO )
22 *
23 *       .. Scalar Arguments ..
24 *       CHARACTER          UPLO
25 *       INTEGER            INFO, LDA, LWORK, N
26 *       ..
27 *       .. Array Arguments ..
28 *       INTEGER            IPIV( * )
29 *       REAL               A( LDA, * ), WORK( * )
30 *       ..
31 *
32 *
33 *> \par Purpose:
34 *  =============
35 *>
36 *> \verbatim
37 *>
38 *> SSYTRF_ROOK computes the factorization of a real symmetric matrix A
39 *> using the bounded Bunch-Kaufman ("rook") diagonal pivoting method.
40 *> The form of the factorization is
41 *>
42 *>    A = U*D*U**T  or  A = L*D*L**T
43 *>
44 *> where U (or L) is a product of permutation and unit upper (lower)
45 *> triangular matrices, and D is symmetric and block diagonal with
46 *> 1-by-1 and 2-by-2 diagonal blocks.
47 *>
48 *> This is the blocked version of the algorithm, calling Level 3 BLAS.
49 *> \endverbatim
50 *
51 *  Arguments:
52 *  ==========
53 *
54 *> \param[in] UPLO
55 *> \verbatim
56 *>          UPLO is CHARACTER*1
57 *>          = 'U':  Upper triangle of A is stored;
58 *>          = 'L':  Lower triangle of A is stored.
59 *> \endverbatim
60 *>
61 *> \param[in] N
62 *> \verbatim
63 *>          N is INTEGER
64 *>          The order of the matrix A.  N >= 0.
65 *> \endverbatim
66 *>
67 *> \param[in,out] A
68 *> \verbatim
69 *>          A is REAL array, dimension (LDA,N)
70 *>          On entry, the symmetric matrix A.  If UPLO = 'U', the leading
71 *>          N-by-N upper triangular part of A contains the upper
72 *>          triangular part of the matrix A, and the strictly lower
73 *>          triangular part of A is not referenced.  If UPLO = 'L', the
74 *>          leading N-by-N lower triangular part of A contains the lower
75 *>          triangular part of the matrix A, and the strictly upper
76 *>          triangular part of A is not referenced.
77 *>
78 *>          On exit, the block diagonal matrix D and the multipliers used
79 *>          to obtain the factor U or L (see below for further details).
80 *> \endverbatim
81 *>
82 *> \param[in] LDA
83 *> \verbatim
84 *>          LDA is INTEGER
85 *>          The leading dimension of the array A.  LDA >= max(1,N).
86 *> \endverbatim
87 *>
88 *> \param[out] IPIV
89 *> \verbatim
90 *>          IPIV is INTEGER array, dimension (N)
91 *>          Details of the interchanges and the block structure of D.
92 *>
93 *>          If UPLO = 'U':
94 *>               If IPIV(k) > 0, then rows and columns k and IPIV(k)
95 *>               were interchanged and D(k,k) is a 1-by-1 diagonal block.
96 *>
97 *>               If IPIV(k) < 0 and IPIV(k-1) < 0, then rows and
98 *>               columns k and -IPIV(k) were interchanged and rows and
99 *>               columns k-1 and -IPIV(k-1) were inerchaged,
100 *>               D(k-1:k,k-1:k) is a 2-by-2 diagonal block.
101 *>
102 *>          If UPLO = 'L':
103 *>               If IPIV(k) > 0, then rows and columns k and IPIV(k)
104 *>               were interchanged and D(k,k) is a 1-by-1 diagonal block.
105 *>
106 *>               If IPIV(k) < 0 and IPIV(k+1) < 0, then rows and
107 *>               columns k and -IPIV(k) were interchanged and rows and
108 *>               columns k+1 and -IPIV(k+1) were inerchaged,
109 *>               D(k:k+1,k:k+1) is a 2-by-2 diagonal block.
110 *> \endverbatim
111 *>
112 *> \param[out] WORK
113 *> \verbatim
114 *>          WORK is REAL array, dimension (MAX(1,LWORK)).
115 *>          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
116 *> \endverbatim
117 *>
118 *> \param[in] LWORK
119 *> \verbatim
120 *>          LWORK is INTEGER
121 *>          The length of WORK.  LWORK >=1.  For best performance
122 *>          LWORK >= N*NB, where NB is the block size returned by ILAENV.
123 *>
124 *>          If LWORK = -1, then a workspace query is assumed; the routine
125 *>          only calculates the optimal size of the WORK array, returns
126 *>          this value as the first entry of the WORK array, and no error
127 *>          message related to LWORK is issued by XERBLA.
128 *> \endverbatim
129 *>
130 *> \param[out] INFO
131 *> \verbatim
132 *>          INFO is INTEGER
133 *>          = 0:  successful exit
134 *>          < 0:  if INFO = -i, the i-th argument had an illegal value
135 *>          > 0:  if INFO = i, D(i,i) is exactly zero.  The factorization
136 *>                has been completed, but the block diagonal matrix D is
137 *>                exactly singular, and division by zero will occur if it
138 *>                is used to solve a system of equations.
139 *> \endverbatim
140 *
141 *  Authors:
142 *  ========
143 *
144 *> \author Univ. of Tennessee
145 *> \author Univ. of California Berkeley
146 *> \author Univ. of Colorado Denver
147 *> \author NAG Ltd.
148 *
149 *> \date June 2016
150 *
151 *> \ingroup realSYcomputational
152 *
153 *> \par Further Details:
154 *  =====================
155 *>
156 *> \verbatim
157 *>
158 *>  If UPLO = 'U', then A = U*D*U**T, where
159 *>     U = P(n)*U(n)* ... *P(k)U(k)* ...,
160 *>  i.e., U is a product of terms P(k)*U(k), where k decreases from n to
161 *>  1 in steps of 1 or 2, and D is a block diagonal matrix with 1-by-1
162 *>  and 2-by-2 diagonal blocks D(k).  P(k) is a permutation matrix as
163 *>  defined by IPIV(k), and U(k) is a unit upper triangular matrix, such
164 *>  that if the diagonal block D(k) is of order s (s = 1 or 2), then
165 *>
166 *>             (   I    v    0   )   k-s
167 *>     U(k) =  (   0    I    0   )   s
168 *>             (   0    0    I   )   n-k
169 *>                k-s   s   n-k
170 *>
171 *>  If s = 1, D(k) overwrites A(k,k), and v overwrites A(1:k-1,k).
172 *>  If s = 2, the upper triangle of D(k) overwrites A(k-1,k-1), A(k-1,k),
173 *>  and A(k,k), and v overwrites A(1:k-2,k-1:k).
174 *>
175 *>  If UPLO = 'L', then A = L*D*L**T, where
176 *>     L = P(1)*L(1)* ... *P(k)*L(k)* ...,
177 *>  i.e., L is a product of terms P(k)*L(k), where k increases from 1 to
178 *>  n in steps of 1 or 2, and D is a block diagonal matrix with 1-by-1
179 *>  and 2-by-2 diagonal blocks D(k).  P(k) is a permutation matrix as
180 *>  defined by IPIV(k), and L(k) is a unit lower triangular matrix, such
181 *>  that if the diagonal block D(k) is of order s (s = 1 or 2), then
182 *>
183 *>             (   I    0     0   )  k-1
184 *>     L(k) =  (   0    I     0   )  s
185 *>             (   0    v     I   )  n-k-s+1
186 *>                k-1   s  n-k-s+1
187 *>
188 *>  If s = 1, D(k) overwrites A(k,k), and v overwrites A(k+1:n,k).
189 *>  If s = 2, the lower triangle of D(k) overwrites A(k,k), A(k+1,k),
190 *>  and A(k+1,k+1), and v overwrites A(k+2:n,k:k+1).
191 *> \endverbatim
192 *
193 *> \par Contributors:
194 *  ==================
195 *>
196 *> \verbatim
197 *>
198 *>   June 2016, Igor Kozachenko,
199 *>                  Computer Science Division,
200 *>                  University of California, Berkeley
201 *>
202 *>  September 2007, Sven Hammarling, Nicholas J. Higham, Craig Lucas,
203 *>                  School of Mathematics,
204 *>                  University of Manchester
205 *>
206 *> \endverbatim
207 *
208 *  =====================================================================
209       SUBROUTINE SSYTRF_ROOK( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO )
210 *
211 *  -- LAPACK computational routine (version 3.6.1) --
212 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
213 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
214 *     June 2016
215 *
216 *     .. Scalar Arguments ..
217       CHARACTER          UPLO
218       INTEGER            INFO, LDA, LWORK, N
219 *     ..
220 *     .. Array Arguments ..
221       INTEGER            IPIV( * )
222       REAL               A( LDA, * ), WORK( * )
223 *     ..
224 *
225 *  =====================================================================
226 *
227 *     .. Local Scalars ..
228       LOGICAL            LQUERY, UPPER
229       INTEGER            IINFO, IWS, J, K, KB, LDWORK, LWKOPT, NB, NBMIN
230 *     ..
231 *     .. External Functions ..
232       LOGICAL            LSAME
233       INTEGER            ILAENV
234       EXTERNAL           LSAME, ILAENV
235 *     ..
236 *     .. External Subroutines ..
237       EXTERNAL           SLASYF_ROOK, SSYTF2_ROOK, XERBLA
238 *     ..
239 *     .. Intrinsic Functions ..
240       INTRINSIC          MAX
241 *     ..
242 *     .. Executable Statements ..
243 *
244 *     Test the input parameters.
245 *
246       INFO = 0
247       UPPER = LSAME( UPLO, 'U' )
248       LQUERY = ( LWORK.EQ.-1 )
249       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
250          INFO = -1
251       ELSE IF( N.LT.0 ) THEN
252          INFO = -2
253       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
254          INFO = -4
255       ELSE IF( LWORK.LT.1 .AND. .NOT.LQUERY ) THEN
256          INFO = -7
257       END IF
258 *
259       IF( INFO.EQ.0 ) THEN
260 *
261 *        Determine the block size
262 *
263          NB = ILAENV( 1, 'SSYTRF_ROOK', UPLO, N, -1, -1, -1 )
264          LWKOPT = MAX( 1, N*NB )
265          WORK( 1 ) = LWKOPT
266       END IF
267 *
268       IF( INFO.NE.0 ) THEN
269          CALL XERBLA( 'SSYTRF_ROOK', -INFO )
270          RETURN
271       ELSE IF( LQUERY ) THEN
272          RETURN
273       END IF
274 *
275       NBMIN = 2
276       LDWORK = N
277       IF( NB.GT.1 .AND. NB.LT.N ) THEN
278          IWS = LDWORK*NB
279          IF( LWORK.LT.IWS ) THEN
280             NB = MAX( LWORK / LDWORK, 1 )
281             NBMIN = MAX( 2, ILAENV( 2, 'SSYTRF_ROOK',
282      $                              UPLO, N, -1, -1, -1 ) )
283          END IF
284       ELSE
285          IWS = 1
286       END IF
287       IF( NB.LT.NBMIN )
288      $   NB = N
289 *
290       IF( UPPER ) THEN
291 *
292 *        Factorize A as U*D*U**T using the upper triangle of A
293 *
294 *        K is the main loop index, decreasing from N to 1 in steps of
295 *        KB, where KB is the number of columns factorized by SLASYF_ROOK;
296 *        KB is either NB or NB-1, or K for the last block
297 *
298          K = N
299    10    CONTINUE
300 *
301 *        If K < 1, exit from loop
302 *
303          IF( K.LT.1 )
304      $      GO TO 40
305 *
306          IF( K.GT.NB ) THEN
307 *
308 *           Factorize columns k-kb+1:k of A and use blocked code to
309 *           update columns 1:k-kb
310 *
311             CALL SLASYF_ROOK( UPLO, K, NB, KB, A, LDA,
312      $                        IPIV, WORK, LDWORK, IINFO )
313          ELSE
314 *
315 *           Use unblocked code to factorize columns 1:k of A
316 *
317             CALL SSYTF2_ROOK( UPLO, K, A, LDA, IPIV, IINFO )
318             KB = K
319          END IF
320 *
321 *        Set INFO on the first occurrence of a zero pivot
322 *
323          IF( INFO.EQ.0 .AND. IINFO.GT.0 )
324      $      INFO = IINFO
325 *
326 *        No need to adjust IPIV
327 *
328 *        Decrease K and return to the start of the main loop
329 *
330          K = K - KB
331          GO TO 10
332 *
333       ELSE
334 *
335 *        Factorize A as L*D*L**T using the lower triangle of A
336 *
337 *        K is the main loop index, increasing from 1 to N in steps of
338 *        KB, where KB is the number of columns factorized by SLASYF_ROOK;
339 *        KB is either NB or NB-1, or N-K+1 for the last block
340 *
341          K = 1
342    20    CONTINUE
343 *
344 *        If K > N, exit from loop
345 *
346          IF( K.GT.N )
347      $      GO TO 40
348 *
349          IF( K.LE.N-NB ) THEN
350 *
351 *           Factorize columns k:k+kb-1 of A and use blocked code to
352 *           update columns k+kb:n
353 *
354             CALL SLASYF_ROOK( UPLO, N-K+1, NB, KB, A( K, K ), LDA,
355      $                        IPIV( K ), WORK, LDWORK, IINFO )
356          ELSE
357 *
358 *           Use unblocked code to factorize columns k:n of A
359 *
360             CALL SSYTF2_ROOK( UPLO, N-K+1, A( K, K ), LDA, IPIV( K ),
361      $                   IINFO )
362             KB = N - K + 1
363          END IF
364 *
365 *        Set INFO on the first occurrence of a zero pivot
366 *
367          IF( INFO.EQ.0 .AND. IINFO.GT.0 )
368      $      INFO = IINFO + K - 1
369 *
370 *        Adjust IPIV
371 *
372          DO 30 J = K, K + KB - 1
373             IF( IPIV( J ).GT.0 ) THEN
374                IPIV( J ) = IPIV( J ) + K - 1
375             ELSE
376                IPIV( J ) = IPIV( J ) - K + 1
377             END IF
378    30    CONTINUE
379 *
380 *        Increase K and return to the start of the main loop
381 *
382          K = K + KB
383          GO TO 20
384 *
385       END IF
386 *
387    40 CONTINUE
388       WORK( 1 ) = LWKOPT
389       RETURN
390 *
391 *     End of SSYTRF_ROOK
392 *
393       END