LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
slaed8.f
Go to the documentation of this file.
1 *> \brief \b SLAED8 used by sstedc. Merges eigenvalues and deflates secular equation. Used when the original matrix is dense.
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SLAED8 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slaed8.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slaed8.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slaed8.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE SLAED8( ICOMPQ, K, N, QSIZ, D, Q, LDQ, INDXQ, RHO,
22 * CUTPNT, Z, DLAMDA, Q2, LDQ2, W, PERM, GIVPTR,
23 * GIVCOL, GIVNUM, INDXP, INDX, INFO )
24 *
25 * .. Scalar Arguments ..
26 * INTEGER CUTPNT, GIVPTR, ICOMPQ, INFO, K, LDQ, LDQ2, N,
27 * $ QSIZ
28 * REAL RHO
29 * ..
30 * .. Array Arguments ..
31 * INTEGER GIVCOL( 2, * ), INDX( * ), INDXP( * ),
32 * $ INDXQ( * ), PERM( * )
33 * REAL D( * ), DLAMDA( * ), GIVNUM( 2, * ),
34 * $ Q( LDQ, * ), Q2( LDQ2, * ), W( * ), Z( * )
35 * ..
36 *
37 *
38 *> \par Purpose:
39 * =============
40 *>
41 *> \verbatim
42 *>
43 *> SLAED8 merges the two sets of eigenvalues together into a single
44 *> sorted set. Then it tries to deflate the size of the problem.
45 *> There are two ways in which deflation can occur: when two or more
46 *> eigenvalues are close together or if there is a tiny element in the
47 *> Z vector. For each such occurrence the order of the related secular
48 *> equation problem is reduced by one.
49 *> \endverbatim
50 *
51 * Arguments:
52 * ==========
53 *
54 *> \param[in] ICOMPQ
55 *> \verbatim
56 *> ICOMPQ is INTEGER
57 *> = 0: Compute eigenvalues only.
58 *> = 1: Compute eigenvectors of original dense symmetric matrix
59 *> also. On entry, Q contains the orthogonal matrix used
60 *> to reduce the original matrix to tridiagonal form.
61 *> \endverbatim
62 *>
63 *> \param[out] K
64 *> \verbatim
65 *> K is INTEGER
66 *> The number of non-deflated eigenvalues, and the order of the
67 *> related secular equation.
68 *> \endverbatim
69 *>
70 *> \param[in] N
71 *> \verbatim
72 *> N is INTEGER
73 *> The dimension of the symmetric tridiagonal matrix. N >= 0.
74 *> \endverbatim
75 *>
76 *> \param[in] QSIZ
77 *> \verbatim
78 *> QSIZ is INTEGER
79 *> The dimension of the orthogonal matrix used to reduce
80 *> the full matrix to tridiagonal form. QSIZ >= N if ICOMPQ = 1.
81 *> \endverbatim
82 *>
83 *> \param[in,out] D
84 *> \verbatim
85 *> D is REAL array, dimension (N)
86 *> On entry, the eigenvalues of the two submatrices to be
87 *> combined. On exit, the trailing (N-K) updated eigenvalues
88 *> (those which were deflated) sorted into increasing order.
89 *> \endverbatim
90 *>
91 *> \param[in,out] Q
92 *> \verbatim
93 *> Q is REAL array, dimension (LDQ,N)
94 *> If ICOMPQ = 0, Q is not referenced. Otherwise,
95 *> on entry, Q contains the eigenvectors of the partially solved
96 *> system which has been previously updated in matrix
97 *> multiplies with other partially solved eigensystems.
98 *> On exit, Q contains the trailing (N-K) updated eigenvectors
99 *> (those which were deflated) in its last N-K columns.
100 *> \endverbatim
101 *>
102 *> \param[in] LDQ
103 *> \verbatim
104 *> LDQ is INTEGER
105 *> The leading dimension of the array Q. LDQ >= max(1,N).
106 *> \endverbatim
107 *>
108 *> \param[in] INDXQ
109 *> \verbatim
110 *> INDXQ is INTEGER array, dimension (N)
111 *> The permutation which separately sorts the two sub-problems
112 *> in D into ascending order. Note that elements in the second
113 *> half of this permutation must first have CUTPNT added to
114 *> their values in order to be accurate.
115 *> \endverbatim
116 *>
117 *> \param[in,out] RHO
118 *> \verbatim
119 *> RHO is REAL
120 *> On entry, the off-diagonal element associated with the rank-1
121 *> cut which originally split the two submatrices which are now
122 *> being recombined.
123 *> On exit, RHO has been modified to the value required by
124 *> SLAED3.
125 *> \endverbatim
126 *>
127 *> \param[in] CUTPNT
128 *> \verbatim
129 *> CUTPNT is INTEGER
130 *> The location of the last eigenvalue in the leading
131 *> sub-matrix. min(1,N) <= CUTPNT <= N.
132 *> \endverbatim
133 *>
134 *> \param[in] Z
135 *> \verbatim
136 *> Z is REAL array, dimension (N)
137 *> On entry, Z contains the updating vector (the last row of
138 *> the first sub-eigenvector matrix and the first row of the
139 *> second sub-eigenvector matrix).
140 *> On exit, the contents of Z are destroyed by the updating
141 *> process.
142 *> \endverbatim
143 *>
144 *> \param[out] DLAMDA
145 *> \verbatim
146 *> DLAMDA is REAL array, dimension (N)
147 *> A copy of the first K eigenvalues which will be used by
148 *> SLAED3 to form the secular equation.
149 *> \endverbatim
150 *>
151 *> \param[out] Q2
152 *> \verbatim
153 *> Q2 is REAL array, dimension (LDQ2,N)
154 *> If ICOMPQ = 0, Q2 is not referenced. Otherwise,
155 *> a copy of the first K eigenvectors which will be used by
156 *> SLAED7 in a matrix multiply (SGEMM) to update the new
157 *> eigenvectors.
158 *> \endverbatim
159 *>
160 *> \param[in] LDQ2
161 *> \verbatim
162 *> LDQ2 is INTEGER
163 *> The leading dimension of the array Q2. LDQ2 >= max(1,N).
164 *> \endverbatim
165 *>
166 *> \param[out] W
167 *> \verbatim
168 *> W is REAL array, dimension (N)
169 *> The first k values of the final deflation-altered z-vector and
170 *> will be passed to SLAED3.
171 *> \endverbatim
172 *>
173 *> \param[out] PERM
174 *> \verbatim
175 *> PERM is INTEGER array, dimension (N)
176 *> The permutations (from deflation and sorting) to be applied
177 *> to each eigenblock.
178 *> \endverbatim
179 *>
180 *> \param[out] GIVPTR
181 *> \verbatim
182 *> GIVPTR is INTEGER
183 *> The number of Givens rotations which took place in this
184 *> subproblem.
185 *> \endverbatim
186 *>
187 *> \param[out] GIVCOL
188 *> \verbatim
189 *> GIVCOL is INTEGER array, dimension (2, N)
190 *> Each pair of numbers indicates a pair of columns to take place
191 *> in a Givens rotation.
192 *> \endverbatim
193 *>
194 *> \param[out] GIVNUM
195 *> \verbatim
196 *> GIVNUM is REAL array, dimension (2, N)
197 *> Each number indicates the S value to be used in the
198 *> corresponding Givens rotation.
199 *> \endverbatim
200 *>
201 *> \param[out] INDXP
202 *> \verbatim
203 *> INDXP is INTEGER array, dimension (N)
204 *> The permutation used to place deflated values of D at the end
205 *> of the array. INDXP(1:K) points to the nondeflated D-values
206 *> and INDXP(K+1:N) points to the deflated eigenvalues.
207 *> \endverbatim
208 *>
209 *> \param[out] INDX
210 *> \verbatim
211 *> INDX is INTEGER array, dimension (N)
212 *> The permutation used to sort the contents of D into ascending
213 *> order.
214 *> \endverbatim
215 *>
216 *> \param[out] INFO
217 *> \verbatim
218 *> INFO is INTEGER
219 *> = 0: successful exit.
220 *> < 0: if INFO = -i, the i-th argument had an illegal value.
221 *> \endverbatim
222 *
223 * Authors:
224 * ========
225 *
226 *> \author Univ. of Tennessee
227 *> \author Univ. of California Berkeley
228 *> \author Univ. of Colorado Denver
229 *> \author NAG Ltd.
230 *
231 *> \date September 2012
232 *
233 *> \ingroup auxOTHERcomputational
234 *
235 *> \par Contributors:
236 * ==================
237 *>
238 *> Jeff Rutter, Computer Science Division, University of California
239 *> at Berkeley, USA
240 *
241 * =====================================================================
242  SUBROUTINE slaed8( ICOMPQ, K, N, QSIZ, D, Q, LDQ, INDXQ, RHO,
243  $ cutpnt, z, dlamda, q2, ldq2, w, perm, givptr,
244  $ givcol, givnum, indxp, indx, info )
245 *
246 * -- LAPACK computational routine (version 3.4.2) --
247 * -- LAPACK is a software package provided by Univ. of Tennessee, --
248 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
249 * September 2012
250 *
251 * .. Scalar Arguments ..
252  INTEGER cutpnt, givptr, icompq, info, k, ldq, ldq2, n,
253  $ qsiz
254  REAL rho
255 * ..
256 * .. Array Arguments ..
257  INTEGER givcol( 2, * ), indx( * ), indxp( * ),
258  $ indxq( * ), perm( * )
259  REAL d( * ), dlamda( * ), givnum( 2, * ),
260  $ q( ldq, * ), q2( ldq2, * ), w( * ), z( * )
261 * ..
262 *
263 * =====================================================================
264 *
265 * .. Parameters ..
266  REAL mone, zero, one, two, eight
267  parameter( mone = -1.0e0, zero = 0.0e0, one = 1.0e0,
268  $ two = 2.0e0, eight = 8.0e0 )
269 * ..
270 * .. Local Scalars ..
271 *
272  INTEGER i, imax, j, jlam, jmax, jp, k2, n1, n1p1, n2
273  REAL c, eps, s, t, tau, tol
274 * ..
275 * .. External Functions ..
276  INTEGER isamax
277  REAL slamch, slapy2
278  EXTERNAL isamax, slamch, slapy2
279 * ..
280 * .. External Subroutines ..
281  EXTERNAL scopy, slacpy, slamrg, srot, sscal, xerbla
282 * ..
283 * .. Intrinsic Functions ..
284  INTRINSIC abs, max, min, sqrt
285 * ..
286 * .. Executable Statements ..
287 *
288 * Test the input parameters.
289 *
290  info = 0
291 *
292  IF( icompq.LT.0 .OR. icompq.GT.1 ) THEN
293  info = -1
294  ELSE IF( n.LT.0 ) THEN
295  info = -3
296  ELSE IF( icompq.EQ.1 .AND. qsiz.LT.n ) THEN
297  info = -4
298  ELSE IF( ldq.LT.max( 1, n ) ) THEN
299  info = -7
300  ELSE IF( cutpnt.LT.min( 1, n ) .OR. cutpnt.GT.n ) THEN
301  info = -10
302  ELSE IF( ldq2.LT.max( 1, n ) ) THEN
303  info = -14
304  END IF
305  IF( info.NE.0 ) THEN
306  CALL xerbla( 'SLAED8', -info )
307  return
308  END IF
309 *
310 * Need to initialize GIVPTR to O here in case of quick exit
311 * to prevent an unspecified code behavior (usually sigfault)
312 * when IWORK array on entry to *stedc is not zeroed
313 * (or at least some IWORK entries which used in *laed7 for GIVPTR).
314 *
315  givptr = 0
316 *
317 * Quick return if possible
318 *
319  IF( n.EQ.0 )
320  $ return
321 *
322  n1 = cutpnt
323  n2 = n - n1
324  n1p1 = n1 + 1
325 *
326  IF( rho.LT.zero ) THEN
327  CALL sscal( n2, mone, z( n1p1 ), 1 )
328  END IF
329 *
330 * Normalize z so that norm(z) = 1
331 *
332  t = one / sqrt( two )
333  DO 10 j = 1, n
334  indx( j ) = j
335  10 continue
336  CALL sscal( n, t, z, 1 )
337  rho = abs( two*rho )
338 *
339 * Sort the eigenvalues into increasing order
340 *
341  DO 20 i = cutpnt + 1, n
342  indxq( i ) = indxq( i ) + cutpnt
343  20 continue
344  DO 30 i = 1, n
345  dlamda( i ) = d( indxq( i ) )
346  w( i ) = z( indxq( i ) )
347  30 continue
348  i = 1
349  j = cutpnt + 1
350  CALL slamrg( n1, n2, dlamda, 1, 1, indx )
351  DO 40 i = 1, n
352  d( i ) = dlamda( indx( i ) )
353  z( i ) = w( indx( i ) )
354  40 continue
355 *
356 * Calculate the allowable deflation tolerence
357 *
358  imax = isamax( n, z, 1 )
359  jmax = isamax( n, d, 1 )
360  eps = slamch( 'Epsilon' )
361  tol = eight*eps*abs( d( jmax ) )
362 *
363 * If the rank-1 modifier is small enough, no more needs to be done
364 * except to reorganize Q so that its columns correspond with the
365 * elements in D.
366 *
367  IF( rho*abs( z( imax ) ).LE.tol ) THEN
368  k = 0
369  IF( icompq.EQ.0 ) THEN
370  DO 50 j = 1, n
371  perm( j ) = indxq( indx( j ) )
372  50 continue
373  ELSE
374  DO 60 j = 1, n
375  perm( j ) = indxq( indx( j ) )
376  CALL scopy( qsiz, q( 1, perm( j ) ), 1, q2( 1, j ), 1 )
377  60 continue
378  CALL slacpy( 'A', qsiz, n, q2( 1, 1 ), ldq2, q( 1, 1 ),
379  $ ldq )
380  END IF
381  return
382  END IF
383 *
384 * If there are multiple eigenvalues then the problem deflates. Here
385 * the number of equal eigenvalues are found. As each equal
386 * eigenvalue is found, an elementary reflector is computed to rotate
387 * the corresponding eigensubspace so that the corresponding
388 * components of Z are zero in this new basis.
389 *
390  k = 0
391  k2 = n + 1
392  DO 70 j = 1, n
393  IF( rho*abs( z( j ) ).LE.tol ) THEN
394 *
395 * Deflate due to small z component.
396 *
397  k2 = k2 - 1
398  indxp( k2 ) = j
399  IF( j.EQ.n )
400  $ go to 110
401  ELSE
402  jlam = j
403  go to 80
404  END IF
405  70 continue
406  80 continue
407  j = j + 1
408  IF( j.GT.n )
409  $ go to 100
410  IF( rho*abs( z( j ) ).LE.tol ) THEN
411 *
412 * Deflate due to small z component.
413 *
414  k2 = k2 - 1
415  indxp( k2 ) = j
416  ELSE
417 *
418 * Check if eigenvalues are close enough to allow deflation.
419 *
420  s = z( jlam )
421  c = z( j )
422 *
423 * Find sqrt(a**2+b**2) without overflow or
424 * destructive underflow.
425 *
426  tau = slapy2( c, s )
427  t = d( j ) - d( jlam )
428  c = c / tau
429  s = -s / tau
430  IF( abs( t*c*s ).LE.tol ) THEN
431 *
432 * Deflation is possible.
433 *
434  z( j ) = tau
435  z( jlam ) = zero
436 *
437 * Record the appropriate Givens rotation
438 *
439  givptr = givptr + 1
440  givcol( 1, givptr ) = indxq( indx( jlam ) )
441  givcol( 2, givptr ) = indxq( indx( j ) )
442  givnum( 1, givptr ) = c
443  givnum( 2, givptr ) = s
444  IF( icompq.EQ.1 ) THEN
445  CALL srot( qsiz, q( 1, indxq( indx( jlam ) ) ), 1,
446  $ q( 1, indxq( indx( j ) ) ), 1, c, s )
447  END IF
448  t = d( jlam )*c*c + d( j )*s*s
449  d( j ) = d( jlam )*s*s + d( j )*c*c
450  d( jlam ) = t
451  k2 = k2 - 1
452  i = 1
453  90 continue
454  IF( k2+i.LE.n ) THEN
455  IF( d( jlam ).LT.d( indxp( k2+i ) ) ) THEN
456  indxp( k2+i-1 ) = indxp( k2+i )
457  indxp( k2+i ) = jlam
458  i = i + 1
459  go to 90
460  ELSE
461  indxp( k2+i-1 ) = jlam
462  END IF
463  ELSE
464  indxp( k2+i-1 ) = jlam
465  END IF
466  jlam = j
467  ELSE
468  k = k + 1
469  w( k ) = z( jlam )
470  dlamda( k ) = d( jlam )
471  indxp( k ) = jlam
472  jlam = j
473  END IF
474  END IF
475  go to 80
476  100 continue
477 *
478 * Record the last eigenvalue.
479 *
480  k = k + 1
481  w( k ) = z( jlam )
482  dlamda( k ) = d( jlam )
483  indxp( k ) = jlam
484 *
485  110 continue
486 *
487 * Sort the eigenvalues and corresponding eigenvectors into DLAMDA
488 * and Q2 respectively. The eigenvalues/vectors which were not
489 * deflated go into the first K slots of DLAMDA and Q2 respectively,
490 * while those which were deflated go into the last N - K slots.
491 *
492  IF( icompq.EQ.0 ) THEN
493  DO 120 j = 1, n
494  jp = indxp( j )
495  dlamda( j ) = d( jp )
496  perm( j ) = indxq( indx( jp ) )
497  120 continue
498  ELSE
499  DO 130 j = 1, n
500  jp = indxp( j )
501  dlamda( j ) = d( jp )
502  perm( j ) = indxq( indx( jp ) )
503  CALL scopy( qsiz, q( 1, perm( j ) ), 1, q2( 1, j ), 1 )
504  130 continue
505  END IF
506 *
507 * The deflated eigenvalues and their corresponding vectors go back
508 * into the last N - K slots of D and Q respectively.
509 *
510  IF( k.LT.n ) THEN
511  IF( icompq.EQ.0 ) THEN
512  CALL scopy( n-k, dlamda( k+1 ), 1, d( k+1 ), 1 )
513  ELSE
514  CALL scopy( n-k, dlamda( k+1 ), 1, d( k+1 ), 1 )
515  CALL slacpy( 'A', qsiz, n-k, q2( 1, k+1 ), ldq2,
516  $ q( 1, k+1 ), ldq )
517  END IF
518  END IF
519 *
520  return
521 *
522 * End of SLAED8
523 *
524  END