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