Lots of trailing whitespaces in the files of Syd. Cleaning this. No big deal.
[platform/upstream/lapack.git] / SRC / dlasyf_aasen.f
1 *> \brief \b DLASYF_AASEN
2 *
3 *  =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 *            http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download DLASYF_AASEN + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlasyf_aasen.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlasyf_aasen.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlasyf_aasen.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE DLASYF_AASEN( UPLO, J1, M, NB, A, LDA, IPIV,
22 *                                H, LDH, WORK, INFO )
23 *
24 *       .. Scalar Arguments ..
25 *       CHARACTER          UPLO
26 *       INTEGER            J1, M, NB, LDA, LDH, INFO
27 *       ..
28 *       .. Array Arguments ..
29 *       INTEGER            IPIV( * )
30 *       DOUBLE PRECISION   A( LDA, * ), H( LDH, * ), WORK( * )
31 *       ..
32 *
33 *
34 *> \par Purpose:
35 *  =============
36 *>
37 *> \verbatim
38 *>
39 *> DLATRF_AASEN factorizes a panel of a real symmetric matrix A using
40 *> the Aasen's algorithm. The panel consists of a set of NB rows of A
41 *> when UPLO is U, or a set of NB columns when UPLO is L.
42 *>
43 *> In order to factorize the panel, the Aasen's algorithm requires the
44 *> last row, or column, of the previous panel. The first row, or column,
45 *> of A is set to be the first row, or column, of an identity matrix,
46 *> which is used to factorize the first panel.
47 *>
48 *> The resulting J-th row of U, or J-th column of L, is stored in the
49 *> (J-1)-th row, or column, of A (without the unit diatonals), while
50 *> the diagonal and subdiagonal of A are overwritten by those of T.
51 *>
52 *> \endverbatim
53 *
54 *  Arguments:
55 *  ==========
56 *
57 *> \param[in] UPLO
58 *> \verbatim
59 *>          UPLO is CHARACTER*1
60 *>          = 'U':  Upper triangle of A is stored;
61 *>          = 'L':  Lower triangle of A is stored.
62 *> \endverbatim
63 *>
64 *> \param[in] J1
65 *> \verbatim
66 *>          J1 is INTEGER
67 *>          The location of the first row, or column, of the panel
68 *>          within the submatrix of A, passed to this routine, e.g.,
69 *>          when called by DSYTRF_AASEN, for the first panel, J1 is 1,
70 *>          while for the remaining panels, J1 is 2.
71 *> \endverbatim
72 *>
73 *> \param[in] M
74 *> \verbatim
75 *>          M is INTEGER
76 *>          The dimension of the submatrix. M >= 0.
77 *> \endverbatim
78 *>
79 *> \param[in] NB
80 *> \verbatim
81 *>          NB is INTEGER
82 *>          The dimension of the panel to be facotorized.
83 *> \endverbatim
84 *>
85 *> \param[in,out] A
86 *> \verbatim
87 *>          A is DOUBLE PRECISION array, dimension (LDA,M) for
88 *>          the first panel, while dimension (LDA,M+1) for the
89 *>          remaining panels.
90 *>
91 *>          On entry, A contains the last row, or column, of
92 *>          the previous panel, and the trailing submatrix of A
93 *>          to be factorized, except for the first panel, only
94 *>          the panel is passed.
95 *>
96 *>          On exit, the leading panel is factorized.
97 *> \endverbatim
98 *>
99 *> \param[in] LDA
100 *> \verbatim
101 *>          LDA is INTEGER
102 *>          The leading dimension of the array A.  LDA >= max(1,N).
103 *> \endverbatim
104 *>
105 *> \param[out] IPIV
106 *> \verbatim
107 *>          IPIV is INTEGER array, dimension (N)
108 *>          Details of the row and column interchanges,
109 *>          the row and column k were interchanged with the row and
110 *>          column IPIV(k).
111 *> \endverbatim
112 *>
113 *> \param[in,out] H
114 *> \verbatim
115 *>          H is DOUBLE PRECISION workspace, dimension (LDH,NB).
116 *>
117 *> \endverbatim
118 *>
119 *> \param[in] LDH
120 *> \verbatim
121 *>          LDH is INTEGER
122 *>          The leading dimension of the workspace H. LDH >= max(1,M).
123 *> \endverbatim
124 *>
125 *> \param[out] WORK
126 *> \verbatim
127 *>          WORK is DOUBLE PRECISION workspace, dimension (M).
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 November 2016
150 *
151 *> \ingroup doubleSYcomputational
152 *
153 *  @precisions fortran d -> s
154 *
155 *  =====================================================================
156       SUBROUTINE DLASYF_AASEN( UPLO, J1, M, NB, A, LDA, IPIV,
157      $                         H, LDH, WORK, INFO )
158 *
159 *  -- LAPACK computational routine (version 3.4.0) --
160 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
161 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
162 *     November 2016
163 *
164       IMPLICIT NONE
165 *
166 *     .. Scalar Arguments ..
167       CHARACTER          UPLO
168       INTEGER            M, NB, J1, LDA, LDH, INFO
169 *     ..
170 *     .. Array Arguments ..
171       INTEGER            IPIV( * )
172       DOUBLE PRECISION   A( LDA, * ), H( LDH, * ), WORK( * )
173 *     ..
174 *
175 *  =====================================================================
176 *     .. Parameters ..
177       DOUBLE PRECISION   ZERO, ONE
178       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
179 *
180 *     .. Local Scalars ..
181       INTEGER            J, K, K1, I1, I2
182       DOUBLE PRECISION   PIV, ALPHA
183 *     ..
184 *     .. External Functions ..
185       LOGICAL            LSAME
186       INTEGER            IDAMAX, ILAENV
187       EXTERNAL           LSAME, ILAENV, IDAMAX
188 *     ..
189 *     .. External Subroutines ..
190       EXTERNAL           XERBLA
191 *     ..
192 *     .. Intrinsic Functions ..
193       INTRINSIC          MAX
194 *     ..
195 *     .. Executable Statements ..
196 *
197       INFO = 0
198       J = 1
199 *
200 *     K1 is the first column of the panel to be factorized
201 *     i.e.,  K1 is 2 for the first block column, and 1 for the rest of the blocks
202 *
203       K1 = (2-J1)+1
204 *
205       IF( LSAME( UPLO, 'U' ) ) THEN
206 *
207 *        .....................................................
208 *        Factorize A as U**T*D*U using the upper triangle of A
209 *        .....................................................
210 *
211  10      CONTINUE
212          IF ( J.GT.MIN(M, NB) )
213      $      GO TO 20
214 *
215 *        K is the column to be factorized
216 *         when being called from DSYTRF_AASEN,
217 *         > for the first block column, J1 is 1, hence J1+J-1 is J,
218 *         > for the rest of the columns, J1 is 2, and J1+J-1 is J+1,
219 *
220          K = J1+J-1
221 *
222 *        H(J:N, J) := A(J, J:N) - H(J:N, 1:(J-1)) * L(J1:(J-1), J),
223 *         where H(J:N, J) has been initialized to be A(J, J:N)
224 *
225          IF( K.GT.2 ) THEN
226 *
227 *        K is the column to be factorized
228 *         > for the first block column, K is J, skipping the first two
229 *           columns
230 *         > for the rest of the columns, K is J+1, skipping only the
231 *           first column
232 *
233             CALL DGEMV( 'No transpose', M-J+1, J-K1,
234      $                 -ONE, H( J, K1 ), LDH,
235      $                       A( 1, J ), 1,
236      $                  ONE, H( J, J ), 1 )
237          END IF
238 *
239 *        Copy H(i:n, i) into WORK
240 *
241          CALL DCOPY( M-J+1, H( J, J ), 1, WORK( 1 ), 1 )
242 *
243          IF( J.GT.K1 ) THEN
244 *
245 *           Compute WORK := WORK - L(J-1, J:N) * T(J-1,J),
246 *            where A(J-1, J) stores T(J-1, J) and A(J-2, J:N) stores U(J-1, J:N)
247 *
248             ALPHA = -A( K-1, J )
249             CALL DAXPY( M-J+1, ALPHA, A( K-2, J ), LDA, WORK( 1 ), 1 )
250          END IF
251 *
252 *        Set A(J, J) = T(J, J)
253 *
254          A( K, J ) = WORK( 1 )
255 *
256          IF( J.LT.M ) THEN
257 *
258 *           Compute WORK(2:N) = T(J, J) L(J, (J+1):N)
259 *            where A(J, J) stores T(J, J) and A(J-1, (J+1):N) stores U(J, (J+1):N)
260 *
261             IF( (J1+J-1).GT.1 ) THEN
262                ALPHA = -A( K, J )
263                CALL DAXPY( M-J, ALPHA, A( K-1, J+1 ), LDA,
264      $                                 WORK( 2 ), 1 )
265             ENDIF
266 *
267 *           Find max(|WORK(2:n)|)
268 *
269             I2 = IDAMAX( M-J, WORK( 2 ), 1 ) + 1
270             PIV = WORK( I2 )
271 *
272 *           Apply symmetric pivot
273 *
274             IF( (I2.NE.2) .AND. (PIV.NE.0) ) THEN
275 *
276 *              Swap WORK(I1) and WORK(I2)
277 *
278                I1 = 2
279                WORK( I2 ) = WORK( I1 )
280                WORK( I1 ) = PIV
281 *
282 *              Swap A(I1, I1+1:N) with A(I1+1:N, I2)
283 *
284                I1 = I1+J-1
285                I2 = I2+J-1
286                CALL DSWAP( I2-I1-1, A( J1+I1-1, I1+1 ), LDA,
287      $                              A( J1+I1, I2 ), 1 )
288 *
289 *              Swap A(I1, I2+1:N) with A(I2, I2+1:N)
290 *
291                CALL DSWAP( M-I2, A( J1+I1-1, I2+1 ), LDA,
292      $                           A( J1+I2-1, I2+1 ), LDA )
293 *
294 *              Swap A(I1, I1) with A(I2,I2)
295 *
296                PIV = A( I1+J1-1, I1 )
297                A( J1+I1-1, I1 ) = A( J1+I2-1, I2 )
298                A( J1+I2-1, I2 ) = PIV
299 *
300 *              Swap H(I1, 1:J1) with H(I2, 1:J1)
301 *
302                CALL DSWAP( I1-1, H( I1, 1 ), LDH, H( I2, 1 ), LDH )
303                IPIV( I1 ) = I2
304 *
305                IF( I1.GT.(K1-1) ) THEN
306 *
307 *                 Swap L(1:I1-1, I1) with L(1:I1-1, I2),
308 *                  skipping the first column
309 *
310                   CALL DSWAP( I1-K1+1, A( 1, I1 ), 1,
311      $                                 A( 1, I2 ), 1 )
312                END IF
313             ELSE
314                IPIV( J+1 ) = J+1
315             ENDIF
316 *
317 *           Set A(J, J+1) = T(J, J+1)
318 *
319             A( K, J+1 ) = WORK( 2 )
320             IF( (A( K, J ).EQ.ZERO ) .AND.
321      $        ( (J.EQ.M) .OR. (A( K, J+1 ).EQ.ZERO))) THEN
322                 IF(INFO .EQ. 0) THEN
323                     INFO = J
324                 ENDIF
325             END IF
326 *
327             IF( J.LT.NB ) THEN
328 *
329 *              Copy A(J+1:N, J+1) into H(J:N, J),
330 *
331                CALL DCOPY( M-J, A( K+1, J+1 ), LDA,
332      $                          H( J+1, J+1 ), 1 )
333             END IF
334 *
335 *           Compute L(J+2, J+1) = WORK( 3:N ) / T(J, J+1),
336 *            where A(J, J+1) = T(J, J+1) and A(J+2:N, J) = L(J+2:N, J+1)
337 *
338             IF( A( K, J+1 ).NE.ZERO ) THEN
339                ALPHA = ONE / A( K, J+1 )
340                CALL DCOPY( M-J-1, WORK( 3 ), 1, A( K, J+2 ), LDA )
341                CALL DSCAL( M-J-1, ALPHA, A( K, J+2 ), LDA )
342             ELSE
343                CALL DLASET( 'Full', 1, M-J-1, ZERO, ZERO,
344      $                      A( K, J+2 ), LDA)
345             END IF
346          ELSE
347             IF( (A( K, J ).EQ.ZERO) .AND. (INFO.EQ.0) ) THEN
348                INFO = J
349             END IF
350          END IF
351          J = J + 1
352          GO TO 10
353  20      CONTINUE
354 *
355       ELSE
356 *
357 *        .....................................................
358 *        Factorize A as L*D*L**T using the lower triangle of A
359 *        .....................................................
360 *
361  30      CONTINUE
362          IF( J.GT.MIN( M, NB ) )
363      $      GO TO 40
364 *
365 *        K is the column to be factorized
366 *         when being called from DSYTRF_AASEN,
367 *         > for the first block column, J1 is 1, hence J1+J-1 is J,
368 *         > for the rest of the columns, J1 is 2, and J1+J-1 is J+1,
369 *
370          K = J1+J-1
371 *
372 *        H(J:N, J) := A(J:N, J) - H(J:N, 1:(J-1)) * L(J, J1:(J-1))^T,
373 *         where H(J:N, J) has been initialized to be A(J:N, J)
374 *
375          IF( K.GT.2 ) THEN
376 *
377 *        K is the column to be factorized
378 *         > for the first block column, K is J, skipping the first two
379 *           columns
380 *         > for the rest of the columns, K is J+1, skipping only the
381 *           first column
382 *
383             CALL DGEMV( 'No transpose', M-J+1, J-K1,
384      $                 -ONE, H( J, K1 ), LDH,
385      $                       A( J, 1 ), LDA,
386      $                  ONE, H( J, J ), 1 )
387          END IF
388 *
389 *        Copy H(J:N, J) into WORK
390 *
391          CALL DCOPY( M-J+1, H( J, J ), 1, WORK( 1 ), 1 )
392 *
393          IF( J.GT.K1 ) THEN
394 *
395 *           Compute WORK := WORK - L(J:N, J-1) * T(J-1,J),
396 *            where A(J-1, J) = T(J-1, J) and A(J, J-2) = L(J, J-1)
397 *
398             ALPHA = -A( J, K-1 )
399             CALL DAXPY( M-J+1, ALPHA, A( J, K-2 ), 1, WORK( 1 ), 1 )
400          END IF
401 *
402 *        Set A(J, J) = T(J, J)
403 *
404          A( J, K ) = WORK( 1 )
405 *
406          IF( J.LT.M ) THEN
407 *
408 *           Compute WORK(2:N) = T(J, J) L((J+1):N, J)
409 *            where A(J, J) = T(J, J) and A((J+1):N, J-1) = L((J+1):N, J)
410 *
411             IF( (J1+J-1).GT.1 ) THEN
412                ALPHA = -A( J, K )
413                CALL DAXPY( M-J, ALPHA, A( J+1, K-1 ), 1,
414      $                                 WORK( 2 ), 1 )
415             ENDIF
416 *
417 *           Find max(|WORK(2:n)|)
418 *
419             I2 = IDAMAX( M-J, WORK( 2 ), 1 ) + 1
420             PIV = WORK( I2 )
421 *
422 *           Apply symmetric pivot
423 *
424             IF( (I2.NE.2) .AND. (PIV.NE.0) ) THEN
425 *
426 *              Swap WORK(I1) and WORK(I2)
427 *
428                I1 = 2
429                WORK( I2 ) = WORK( I1 )
430                WORK( I1 ) = PIV
431 *
432 *              Swap A(I1+1:N, I1) with A(I2, I1+1:N)
433 *
434                I1 = I1+J-1
435                I2 = I2+J-1
436                CALL DSWAP( I2-I1-1, A( I1+1, J1+I1-1 ), 1,
437      $                              A( I2, J1+I1 ), LDA )
438 *
439 *              Swap A(I2+1:N, I1) with A(I2+1:N, I2)
440 *
441                CALL DSWAP( M-I2, A( I2+1, J1+I1-1 ), 1,
442      $                           A( I2+1, J1+I2-1 ), 1 )
443 *
444 *              Swap A(I1, I1) with A(I2, I2)
445 *
446                PIV = A( I1, J1+I1-1 )
447                A( I1, J1+I1-1 ) = A( I2, J1+I2-1 )
448                A( I2, J1+I2-1 ) = PIV
449 *
450 *              Swap H(I1, I1:J1) with H(I2, I2:J1)
451 *
452                CALL DSWAP( I1-1, H( I1, 1 ), LDH, H( I2, 1 ), LDH )
453                IPIV( I1 ) = I2
454 *
455                IF( I1.GT.(K1-1) ) THEN
456 *
457 *                 Swap L(1:I1-1, I1) with L(1:I1-1, I2),
458 *                  skipping the first column
459 *
460                   CALL DSWAP( I1-K1+1, A( I1, 1 ), LDA,
461      $                                 A( I2, 1 ), LDA )
462                END IF
463             ELSE
464                IPIV( J+1 ) = J+1
465             ENDIF
466 *
467 *           Set A(J+1, J) = T(J+1, J)
468 *
469             A( J+1, K ) = WORK( 2 )
470             IF( (A( J, K ).EQ.ZERO) .AND.
471      $        ( (J.EQ.M) .OR. (A( J+1, K ).EQ.ZERO)) ) THEN
472                 IF (INFO .EQ. 0)
473      $              INFO = J
474             END IF
475 *
476             IF( J.LT.NB ) THEN
477 *
478 *              Copy A(J+1:N, J+1) into H(J+1:N, J),
479 *
480                CALL DCOPY( M-J, A( J+1, K+1 ), 1,
481      $                          H( J+1, J+1 ), 1 )
482             END IF
483 *
484 *           Compute L(J+2, J+1) = WORK( 3:N ) / T(J, J+1),
485 *            where A(J, J+1) = T(J, J+1) and A(J+2:N, J) = L(J+2:N, J+1)
486 *
487             IF( A( J+1, K ).NE.ZERO ) THEN
488                ALPHA = ONE / A( J+1, K )
489                CALL DCOPY( M-J-1, WORK( 3 ), 1, A( J+2, K ), 1 )
490                CALL DSCAL( M-J-1, ALPHA, A( J+2, K ), 1 )
491             ELSE
492                CALL DLASET( 'Full', M-J-1, 1, ZERO, ZERO,
493      $                      A( J+2, K ), LDA )
494             END IF
495          ELSE
496             IF( (A( J, K ).EQ.ZERO) .AND. (INFO.EQ.0) ) THEN
497                INFO = J
498             END IF
499          END IF
500          J = J + 1
501          GO TO 30
502  40      CONTINUE
503       END IF
504       RETURN
505 *
506 *     End of DLASYF_AASEN
507 *
508       END