LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
csytf2.f
Go to the documentation of this file.
1 *> \brief \b CSYTF2 computes the factorization of a real symmetric indefinite matrix, using the diagonal pivoting method (unblocked algorithm).
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CSYTF2 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/csytf2.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/csytf2.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/csytf2.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE CSYTF2( UPLO, N, A, LDA, IPIV, INFO )
22 *
23 * .. Scalar Arguments ..
24 * CHARACTER UPLO
25 * INTEGER INFO, LDA, N
26 * ..
27 * .. Array Arguments ..
28 * INTEGER IPIV( * )
29 * COMPLEX A( LDA, * )
30 * ..
31 *
32 *
33 *> \par Purpose:
34 * =============
35 *>
36 *> \verbatim
37 *>
38 *> CSYTF2 computes the factorization of a complex symmetric matrix A
39 *> using the Bunch-Kaufman diagonal pivoting method:
40 *>
41 *> A = U*D*U**T or A = L*D*L**T
42 *>
43 *> where U (or L) is a product of permutation and unit upper (lower)
44 *> triangular matrices, U**T is the transpose of U, and D is symmetric and
45 *> block diagonal with 1-by-1 and 2-by-2 diagonal blocks.
46 *>
47 *> This is the unblocked version of the algorithm, calling Level 2 BLAS.
48 *> \endverbatim
49 *
50 * Arguments:
51 * ==========
52 *
53 *> \param[in] UPLO
54 *> \verbatim
55 *> UPLO is CHARACTER*1
56 *> Specifies whether the upper or lower triangular part of the
57 *> symmetric matrix A is stored:
58 *> = 'U': Upper triangular
59 *> = 'L': Lower triangular
60 *> \endverbatim
61 *>
62 *> \param[in] N
63 *> \verbatim
64 *> N is INTEGER
65 *> The order of the matrix A. N >= 0.
66 *> \endverbatim
67 *>
68 *> \param[in,out] A
69 *> \verbatim
70 *> A is COMPLEX array, dimension (LDA,N)
71 *> On entry, the symmetric matrix A. If UPLO = 'U', the leading
72 *> n-by-n upper triangular part of A contains the upper
73 *> triangular part of the matrix A, and the strictly lower
74 *> triangular part of A is not referenced. If UPLO = 'L', the
75 *> leading n-by-n lower triangular part of A contains the lower
76 *> triangular part of the matrix A, and the strictly upper
77 *> triangular part of A is not referenced.
78 *>
79 *> On exit, the block diagonal matrix D and the multipliers used
80 *> to obtain the factor U or L (see below for further details).
81 *> \endverbatim
82 *>
83 *> \param[in] LDA
84 *> \verbatim
85 *> LDA is INTEGER
86 *> The leading dimension of the array A. LDA >= max(1,N).
87 *> \endverbatim
88 *>
89 *> \param[out] IPIV
90 *> \verbatim
91 *> IPIV is INTEGER array, dimension (N)
92 *> Details of the interchanges and the block structure of D.
93 *> If IPIV(k) > 0, then rows and columns k and IPIV(k) were
94 *> interchanged and D(k,k) is a 1-by-1 diagonal block.
95 *> If UPLO = 'U' and IPIV(k) = IPIV(k-1) < 0, then rows and
96 *> columns k-1 and -IPIV(k) were interchanged and D(k-1:k,k-1:k)
97 *> is a 2-by-2 diagonal block. If UPLO = 'L' and IPIV(k) =
98 *> IPIV(k+1) < 0, then rows and columns k+1 and -IPIV(k) were
99 *> interchanged and D(k:k+1,k:k+1) is a 2-by-2 diagonal block.
100 *> \endverbatim
101 *>
102 *> \param[out] INFO
103 *> \verbatim
104 *> INFO is INTEGER
105 *> = 0: successful exit
106 *> < 0: if INFO = -k, the k-th argument had an illegal value
107 *> > 0: if INFO = k, D(k,k) is exactly zero. The factorization
108 *> has been completed, but the block diagonal matrix D is
109 *> exactly singular, and division by zero will occur if it
110 *> is used to solve a system of equations.
111 *> \endverbatim
112 *
113 * Authors:
114 * ========
115 *
116 *> \author Univ. of Tennessee
117 *> \author Univ. of California Berkeley
118 *> \author Univ. of Colorado Denver
119 *> \author NAG Ltd.
120 *
121 *> \date September 2012
122 *
123 *> \ingroup complexSYcomputational
124 *
125 *> \par Further Details:
126 * =====================
127 *>
128 *> \verbatim
129 *>
130 *> If UPLO = 'U', then A = U*D*U**T, where
131 *> U = P(n)*U(n)* ... *P(k)U(k)* ...,
132 *> i.e., U is a product of terms P(k)*U(k), where k decreases from n to
133 *> 1 in steps of 1 or 2, and D is a block diagonal matrix with 1-by-1
134 *> and 2-by-2 diagonal blocks D(k). P(k) is a permutation matrix as
135 *> defined by IPIV(k), and U(k) is a unit upper triangular matrix, such
136 *> that if the diagonal block D(k) is of order s (s = 1 or 2), then
137 *>
138 *> ( I v 0 ) k-s
139 *> U(k) = ( 0 I 0 ) s
140 *> ( 0 0 I ) n-k
141 *> k-s s n-k
142 *>
143 *> If s = 1, D(k) overwrites A(k,k), and v overwrites A(1:k-1,k).
144 *> If s = 2, the upper triangle of D(k) overwrites A(k-1,k-1), A(k-1,k),
145 *> and A(k,k), and v overwrites A(1:k-2,k-1:k).
146 *>
147 *> If UPLO = 'L', then A = L*D*L**T, where
148 *> L = P(1)*L(1)* ... *P(k)*L(k)* ...,
149 *> i.e., L is a product of terms P(k)*L(k), where k increases from 1 to
150 *> n in steps of 1 or 2, and D is a block diagonal matrix with 1-by-1
151 *> and 2-by-2 diagonal blocks D(k). P(k) is a permutation matrix as
152 *> defined by IPIV(k), and L(k) is a unit lower triangular matrix, such
153 *> that if the diagonal block D(k) is of order s (s = 1 or 2), then
154 *>
155 *> ( I 0 0 ) k-1
156 *> L(k) = ( 0 I 0 ) s
157 *> ( 0 v I ) n-k-s+1
158 *> k-1 s n-k-s+1
159 *>
160 *> If s = 1, D(k) overwrites A(k,k), and v overwrites A(k+1:n,k).
161 *> If s = 2, the lower triangle of D(k) overwrites A(k,k), A(k+1,k),
162 *> and A(k+1,k+1), and v overwrites A(k+2:n,k:k+1).
163 *> \endverbatim
164 *
165 *> \par Contributors:
166 * ==================
167 *>
168 *> \verbatim
169 *>
170 *> 09-29-06 - patch from
171 *> Bobby Cheng, MathWorks
172 *>
173 *> Replace l.209 and l.377
174 *> IF( MAX( ABSAKK, COLMAX ).EQ.ZERO ) THEN
175 *> by
176 *> IF( (MAX( ABSAKK, COLMAX ).EQ.ZERO) .OR. SISNAN(ABSAKK) ) THEN
177 *>
178 *> 1-96 - Based on modifications by J. Lewis, Boeing Computer Services
179 *> Company
180 *> \endverbatim
181 *
182 * =====================================================================
183  SUBROUTINE csytf2( UPLO, N, A, LDA, IPIV, INFO )
184 *
185 * -- LAPACK computational routine (version 3.4.2) --
186 * -- LAPACK is a software package provided by Univ. of Tennessee, --
187 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
188 * September 2012
189 *
190 * .. Scalar Arguments ..
191  CHARACTER uplo
192  INTEGER info, lda, n
193 * ..
194 * .. Array Arguments ..
195  INTEGER ipiv( * )
196  COMPLEX a( lda, * )
197 * ..
198 *
199 * =====================================================================
200 *
201 * .. Parameters ..
202  REAL zero, one
203  parameter( zero = 0.0e+0, one = 1.0e+0 )
204  REAL eight, sevten
205  parameter( eight = 8.0e+0, sevten = 17.0e+0 )
206  COMPLEX cone
207  parameter( cone = ( 1.0e+0, 0.0e+0 ) )
208 * ..
209 * .. Local Scalars ..
210  LOGICAL upper
211  INTEGER i, imax, j, jmax, k, kk, kp, kstep
212  REAL absakk, alpha, colmax, rowmax
213  COMPLEX d11, d12, d21, d22, r1, t, wk, wkm1, wkp1, z
214 * ..
215 * .. External Functions ..
216  LOGICAL lsame, sisnan
217  INTEGER icamax
218  EXTERNAL lsame, icamax, sisnan
219 * ..
220 * .. External Subroutines ..
221  EXTERNAL cscal, cswap, csyr, xerbla
222 * ..
223 * .. Intrinsic Functions ..
224  INTRINSIC abs, aimag, max, REAL, sqrt
225 * ..
226 * .. Statement Functions ..
227  REAL cabs1
228 * ..
229 * .. Statement Function definitions ..
230  cabs1( z ) = abs( REAL( Z ) ) + abs( aimag( z ) )
231 * ..
232 * .. Executable Statements ..
233 *
234 * Test the input parameters.
235 *
236  info = 0
237  upper = lsame( uplo, 'U' )
238  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
239  info = -1
240  ELSE IF( n.LT.0 ) THEN
241  info = -2
242  ELSE IF( lda.LT.max( 1, n ) ) THEN
243  info = -4
244  END IF
245  IF( info.NE.0 ) THEN
246  CALL xerbla( 'CSYTF2', -info )
247  return
248  END IF
249 *
250 * Initialize ALPHA for use in choosing pivot block size.
251 *
252  alpha = ( one+sqrt( sevten ) ) / eight
253 *
254  IF( upper ) THEN
255 *
256 * Factorize A as U*D*U**T using the upper triangle of A
257 *
258 * K is the main loop index, decreasing from N to 1 in steps of
259 * 1 or 2
260 *
261  k = n
262  10 continue
263 *
264 * If K < 1, exit from loop
265 *
266  IF( k.LT.1 )
267  $ go to 70
268  kstep = 1
269 *
270 * Determine rows and columns to be interchanged and whether
271 * a 1-by-1 or 2-by-2 pivot block will be used
272 *
273  absakk = cabs1( a( k, k ) )
274 *
275 * IMAX is the row-index of the largest off-diagonal element in
276 * column K, and COLMAX is its absolute value
277 *
278  IF( k.GT.1 ) THEN
279  imax = icamax( k-1, a( 1, k ), 1 )
280  colmax = cabs1( a( imax, k ) )
281  ELSE
282  colmax = zero
283  END IF
284 *
285  IF( max( absakk, colmax ).EQ.zero .OR. sisnan(absakk) ) THEN
286 *
287 * Column K is zero or NaN: set INFO and continue
288 *
289  IF( info.EQ.0 )
290  $ info = k
291  kp = k
292  ELSE
293  IF( absakk.GE.alpha*colmax ) THEN
294 *
295 * no interchange, use 1-by-1 pivot block
296 *
297  kp = k
298  ELSE
299 *
300 * JMAX is the column-index of the largest off-diagonal
301 * element in row IMAX, and ROWMAX is its absolute value
302 *
303  jmax = imax + icamax( k-imax, a( imax, imax+1 ), lda )
304  rowmax = cabs1( a( imax, jmax ) )
305  IF( imax.GT.1 ) THEN
306  jmax = icamax( imax-1, a( 1, imax ), 1 )
307  rowmax = max( rowmax, cabs1( a( jmax, imax ) ) )
308  END IF
309 *
310  IF( absakk.GE.alpha*colmax*( colmax / rowmax ) ) THEN
311 *
312 * no interchange, use 1-by-1 pivot block
313 *
314  kp = k
315  ELSE IF( cabs1( a( imax, imax ) ).GE.alpha*rowmax ) THEN
316 *
317 * interchange rows and columns K and IMAX, use 1-by-1
318 * pivot block
319 *
320  kp = imax
321  ELSE
322 *
323 * interchange rows and columns K-1 and IMAX, use 2-by-2
324 * pivot block
325 *
326  kp = imax
327  kstep = 2
328  END IF
329  END IF
330 *
331  kk = k - kstep + 1
332  IF( kp.NE.kk ) THEN
333 *
334 * Interchange rows and columns KK and KP in the leading
335 * submatrix A(1:k,1:k)
336 *
337  CALL cswap( kp-1, a( 1, kk ), 1, a( 1, kp ), 1 )
338  CALL cswap( kk-kp-1, a( kp+1, kk ), 1, a( kp, kp+1 ),
339  $ lda )
340  t = a( kk, kk )
341  a( kk, kk ) = a( kp, kp )
342  a( kp, kp ) = t
343  IF( kstep.EQ.2 ) THEN
344  t = a( k-1, k )
345  a( k-1, k ) = a( kp, k )
346  a( kp, k ) = t
347  END IF
348  END IF
349 *
350 * Update the leading submatrix
351 *
352  IF( kstep.EQ.1 ) THEN
353 *
354 * 1-by-1 pivot block D(k): column k now holds
355 *
356 * W(k) = U(k)*D(k)
357 *
358 * where U(k) is the k-th column of U
359 *
360 * Perform a rank-1 update of A(1:k-1,1:k-1) as
361 *
362 * A := A - U(k)*D(k)*U(k)**T = A - W(k)*1/D(k)*W(k)**T
363 *
364  r1 = cone / a( k, k )
365  CALL csyr( uplo, k-1, -r1, a( 1, k ), 1, a, lda )
366 *
367 * Store U(k) in column k
368 *
369  CALL cscal( k-1, r1, a( 1, k ), 1 )
370  ELSE
371 *
372 * 2-by-2 pivot block D(k): columns k and k-1 now hold
373 *
374 * ( W(k-1) W(k) ) = ( U(k-1) U(k) )*D(k)
375 *
376 * where U(k) and U(k-1) are the k-th and (k-1)-th columns
377 * of U
378 *
379 * Perform a rank-2 update of A(1:k-2,1:k-2) as
380 *
381 * A := A - ( U(k-1) U(k) )*D(k)*( U(k-1) U(k) )**T
382 * = A - ( W(k-1) W(k) )*inv(D(k))*( W(k-1) W(k) )**T
383 *
384  IF( k.GT.2 ) THEN
385 *
386  d12 = a( k-1, k )
387  d22 = a( k-1, k-1 ) / d12
388  d11 = a( k, k ) / d12
389  t = cone / ( d11*d22-cone )
390  d12 = t / d12
391 *
392  DO 30 j = k - 2, 1, -1
393  wkm1 = d12*( d11*a( j, k-1 )-a( j, k ) )
394  wk = d12*( d22*a( j, k )-a( j, k-1 ) )
395  DO 20 i = j, 1, -1
396  a( i, j ) = a( i, j ) - a( i, k )*wk -
397  $ a( i, k-1 )*wkm1
398  20 continue
399  a( j, k ) = wk
400  a( j, k-1 ) = wkm1
401  30 continue
402 *
403  END IF
404 *
405  END IF
406  END IF
407 *
408 * Store details of the interchanges in IPIV
409 *
410  IF( kstep.EQ.1 ) THEN
411  ipiv( k ) = kp
412  ELSE
413  ipiv( k ) = -kp
414  ipiv( k-1 ) = -kp
415  END IF
416 *
417 * Decrease K and return to the start of the main loop
418 *
419  k = k - kstep
420  go to 10
421 *
422  ELSE
423 *
424 * Factorize A as L*D*L**T using the lower triangle of A
425 *
426 * K is the main loop index, increasing from 1 to N in steps of
427 * 1 or 2
428 *
429  k = 1
430  40 continue
431 *
432 * If K > N, exit from loop
433 *
434  IF( k.GT.n )
435  $ go to 70
436  kstep = 1
437 *
438 * Determine rows and columns to be interchanged and whether
439 * a 1-by-1 or 2-by-2 pivot block will be used
440 *
441  absakk = cabs1( a( k, k ) )
442 *
443 * IMAX is the row-index of the largest off-diagonal element in
444 * column K, and COLMAX is its absolute value
445 *
446  IF( k.LT.n ) THEN
447  imax = k + icamax( n-k, a( k+1, k ), 1 )
448  colmax = cabs1( a( imax, k ) )
449  ELSE
450  colmax = zero
451  END IF
452 *
453  IF( max( absakk, colmax ).EQ.zero .OR. sisnan(absakk) ) THEN
454 *
455 * Column K is zero or NaN: set INFO and continue
456 *
457  IF( info.EQ.0 )
458  $ info = k
459  kp = k
460  ELSE
461  IF( absakk.GE.alpha*colmax ) THEN
462 *
463 * no interchange, use 1-by-1 pivot block
464 *
465  kp = k
466  ELSE
467 *
468 * JMAX is the column-index of the largest off-diagonal
469 * element in row IMAX, and ROWMAX is its absolute value
470 *
471  jmax = k - 1 + icamax( imax-k, a( imax, k ), lda )
472  rowmax = cabs1( a( imax, jmax ) )
473  IF( imax.LT.n ) THEN
474  jmax = imax + icamax( n-imax, a( imax+1, imax ), 1 )
475  rowmax = max( rowmax, cabs1( a( jmax, imax ) ) )
476  END IF
477 *
478  IF( absakk.GE.alpha*colmax*( colmax / rowmax ) ) THEN
479 *
480 * no interchange, use 1-by-1 pivot block
481 *
482  kp = k
483  ELSE IF( cabs1( a( imax, imax ) ).GE.alpha*rowmax ) THEN
484 *
485 * interchange rows and columns K and IMAX, use 1-by-1
486 * pivot block
487 *
488  kp = imax
489  ELSE
490 *
491 * interchange rows and columns K+1 and IMAX, use 2-by-2
492 * pivot block
493 *
494  kp = imax
495  kstep = 2
496  END IF
497  END IF
498 *
499  kk = k + kstep - 1
500  IF( kp.NE.kk ) THEN
501 *
502 * Interchange rows and columns KK and KP in the trailing
503 * submatrix A(k:n,k:n)
504 *
505  IF( kp.LT.n )
506  $ CALL cswap( n-kp, a( kp+1, kk ), 1, a( kp+1, kp ), 1 )
507  CALL cswap( kp-kk-1, a( kk+1, kk ), 1, a( kp, kk+1 ),
508  $ lda )
509  t = a( kk, kk )
510  a( kk, kk ) = a( kp, kp )
511  a( kp, kp ) = t
512  IF( kstep.EQ.2 ) THEN
513  t = a( k+1, k )
514  a( k+1, k ) = a( kp, k )
515  a( kp, k ) = t
516  END IF
517  END IF
518 *
519 * Update the trailing submatrix
520 *
521  IF( kstep.EQ.1 ) THEN
522 *
523 * 1-by-1 pivot block D(k): column k now holds
524 *
525 * W(k) = L(k)*D(k)
526 *
527 * where L(k) is the k-th column of L
528 *
529  IF( k.LT.n ) THEN
530 *
531 * Perform a rank-1 update of A(k+1:n,k+1:n) as
532 *
533 * A := A - L(k)*D(k)*L(k)**T = A - W(k)*(1/D(k))*W(k)**T
534 *
535  r1 = cone / a( k, k )
536  CALL csyr( uplo, n-k, -r1, a( k+1, k ), 1,
537  $ a( k+1, k+1 ), lda )
538 *
539 * Store L(k) in column K
540 *
541  CALL cscal( n-k, r1, a( k+1, k ), 1 )
542  END IF
543  ELSE
544 *
545 * 2-by-2 pivot block D(k)
546 *
547  IF( k.LT.n-1 ) THEN
548 *
549 * Perform a rank-2 update of A(k+2:n,k+2:n) as
550 *
551 * A := A - ( L(k) L(k+1) )*D(k)*( L(k) L(k+1) )**T
552 * = A - ( W(k) W(k+1) )*inv(D(k))*( W(k) W(k+1) )**T
553 *
554 * where L(k) and L(k+1) are the k-th and (k+1)-th
555 * columns of L
556 *
557  d21 = a( k+1, k )
558  d11 = a( k+1, k+1 ) / d21
559  d22 = a( k, k ) / d21
560  t = cone / ( d11*d22-cone )
561  d21 = t / d21
562 *
563  DO 60 j = k + 2, n
564  wk = d21*( d11*a( j, k )-a( j, k+1 ) )
565  wkp1 = d21*( d22*a( j, k+1 )-a( j, k ) )
566  DO 50 i = j, n
567  a( i, j ) = a( i, j ) - a( i, k )*wk -
568  $ a( i, k+1 )*wkp1
569  50 continue
570  a( j, k ) = wk
571  a( j, k+1 ) = wkp1
572  60 continue
573  END IF
574  END IF
575  END IF
576 *
577 * Store details of the interchanges in IPIV
578 *
579  IF( kstep.EQ.1 ) THEN
580  ipiv( k ) = kp
581  ELSE
582  ipiv( k ) = -kp
583  ipiv( k+1 ) = -kp
584  END IF
585 *
586 * Increase K and return to the start of the main loop
587 *
588  k = k + kstep
589  go to 40
590 *
591  END IF
592 *
593  70 continue
594  return
595 *
596 * End of CSYTF2
597 *
598  END