KTH framework for Nek5000 toolboxes; testing version  0.0.1
dsteqr.f
Go to the documentation of this file.
1  SUBROUTINE dsteqr( COMPZ, N, D, E, Z, LDZ, WORK, INFO )
2 *
3 * -- LAPACK routine (version 3.0) --
4 * Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
5 * Courant Institute, Argonne National Lab, and Rice University
6 * September 30, 1994
7 *
8 * .. Scalar Arguments ..
9  CHARACTER COMPZ
10  INTEGER INFO, LDZ, N
11 * ..
12 * .. Array Arguments ..
13  DOUBLE PRECISION D( * ), E( * ), WORK( * ), Z( LDZ, * )
14 * ..
15 *
16 * Purpose
17 * =======
18 *
19 * DSTEQR computes all eigenvalues and, optionally, eigenvectors of a
20 * symmetric tridiagonal matrix using the implicit QL or QR method.
21 * The eigenvectors of a full or band symmetric matrix can also be found
22 * if DSYTRD or DSPTRD or DSBTRD has been used to reduce this matrix to
23 * tridiagonal form.
24 *
25 * Arguments
26 * =========
27 *
28 * COMPZ (input) CHARACTER*1
29 * = 'N': Compute eigenvalues only.
30 * = 'V': Compute eigenvalues and eigenvectors of the original
31 * symmetric matrix. On entry, Z must contain the
32 * orthogonal matrix used to reduce the original matrix
33 * to tridiagonal form.
34 * = 'I': Compute eigenvalues and eigenvectors of the
35 * tridiagonal matrix. Z is initialized to the identity
36 * matrix.
37 *
38 * N (input) INTEGER
39 * The order of the matrix. N >= 0.
40 *
41 * D (input/output) DOUBLE PRECISION array, dimension (N)
42 * On entry, the diagonal elements of the tridiagonal matrix.
43 * On exit, if INFO = 0, the eigenvalues in ascending order.
44 *
45 * E (input/output) DOUBLE PRECISION array, dimension (N-1)
46 * On entry, the (n-1) subdiagonal elements of the tridiagonal
47 * matrix.
48 * On exit, E has been destroyed.
49 *
50 * Z (input/output) DOUBLE PRECISION array, dimension (LDZ, N)
51 * On entry, if COMPZ = 'V', then Z contains the orthogonal
52 * matrix used in the reduction to tridiagonal form.
53 * On exit, if INFO = 0, then if COMPZ = 'V', Z contains the
54 * orthonormal eigenvectors of the original symmetric matrix,
55 * and if COMPZ = 'I', Z contains the orthonormal eigenvectors
56 * of the symmetric tridiagonal matrix.
57 * If COMPZ = 'N', then Z is not referenced.
58 *
59 * LDZ (input) INTEGER
60 * The leading dimension of the array Z. LDZ >= 1, and if
61 * eigenvectors are desired, then LDZ >= max(1,N).
62 *
63 * WORK (workspace) DOUBLE PRECISION array, dimension (max(1,2*N-2))
64 * If COMPZ = 'N', then WORK is not referenced.
65 *
66 * INFO (output) INTEGER
67 * = 0: successful exit
68 * < 0: if INFO = -i, the i-th argument had an illegal value
69 * > 0: the algorithm has failed to find all the eigenvalues in
70 * a total of 30*N iterations; if INFO = i, then i
71 * elements of E have not converged to zero; on exit, D
72 * and E contain the elements of a symmetric tridiagonal
73 * matrix which is orthogonally similar to the original
74 * matrix.
75 *
76 * =====================================================================
77 *
78 * .. Parameters ..
79  DOUBLE PRECISION ZERO, ONE, TWO, THREE
80  parameter( zero = 0.0d0, one = 1.0d0, two = 2.0d0,
81  $ three = 3.0d0 )
82  INTEGER MAXIT
83  parameter( maxit = 30 )
84 * ..
85 * .. Local Scalars ..
86  INTEGER I, ICOMPZ, II, ISCALE, J, JTOT, K, L, L1, LEND,
87  $ LENDM1, LENDP1, LENDSV, LM1, LSV, M, MM, MM1,
88  $ NM1, NMAXIT
89  DOUBLE PRECISION ANORM, B, C, EPS, EPS2, F, G, P, R, RT1, RT2,
90  $ S, SAFMAX, SAFMIN, SSFMAX, SSFMIN, TST
91 * ..
92 * .. External Functions ..
93  LOGICAL LSAME
94  DOUBLE PRECISION DLAMCH, DLANST, DLAPY2
95  EXTERNAL lsame, dlamch, dlanst, dlapy2
96 * ..
97 * .. External Subroutines ..
98  EXTERNAL dlae2, dlaev2, dlartg, dlascl, dlaset, dlasr,
99  $ dlasrt, dswap, xerbla
100 * ..
101 * .. Intrinsic Functions ..
102  INTRINSIC abs, max, sign, sqrt
103 * ..
104 * .. Executable Statements ..
105 *
106 * Test the input parameters.
107 *
108  info = 0
109 *
110  IF( lsame( compz, 'N' ) ) THEN
111  icompz = 0
112  ELSE IF( lsame( compz, 'V' ) ) THEN
113  icompz = 1
114  ELSE IF( lsame( compz, 'I' ) ) THEN
115  icompz = 2
116  ELSE
117  icompz = -1
118  END IF
119  IF( icompz.LT.0 ) THEN
120  info = -1
121  ELSE IF( n.LT.0 ) THEN
122  info = -2
123  ELSE IF( ( ldz.LT.1 ) .OR. ( icompz.GT.0 .AND. ldz.LT.max( 1,
124  $ n ) ) ) THEN
125  info = -6
126  END IF
127  IF( info.NE.0 ) THEN
128  CALL xerbla( 'DSTEQR', -info )
129  RETURN
130  END IF
131 *
132 * Quick return if possible
133 *
134  IF( n.EQ.0 )
135  $ RETURN
136 *
137  IF( n.EQ.1 ) THEN
138  IF( icompz.EQ.2 )
139  $ z( 1, 1 ) = one
140  RETURN
141  END IF
142 *
143 * Determine the unit roundoff and over/underflow thresholds.
144 *
145  eps = dlamch( 'E' )
146  eps2 = eps**2
147  safmin = dlamch( 'S' )
148  safmax = one / safmin
149  ssfmax = sqrt( safmax ) / three
150  ssfmin = sqrt( safmin ) / eps2
151 *
152 * Compute the eigenvalues and eigenvectors of the tridiagonal
153 * matrix.
154 *
155  IF( icompz.EQ.2 )
156  $ CALL dlaset( 'Full', n, n, zero, one, z, ldz )
157 *
158  nmaxit = n*maxit
159  jtot = 0
160 *
161 * Determine where the matrix splits and choose QL or QR iteration
162 * for each block, according to whether top or bottom diagonal
163 * element is smaller.
164 *
165  l1 = 1
166  nm1 = n - 1
167 *
168  10 CONTINUE
169  IF( l1.GT.n )
170  $ GO TO 160
171  IF( l1.GT.1 )
172  $ e( l1-1 ) = zero
173  IF( l1.LE.nm1 ) THEN
174  DO 20 m = l1, nm1
175  tst = abs( e( m ) )
176  IF( tst.EQ.zero )
177  $ GO TO 30
178  IF( tst.LE.( sqrt( abs( d( m ) ) )*sqrt( abs( d( m+
179  $ 1 ) ) ) )*eps ) THEN
180  e( m ) = zero
181  GO TO 30
182  END IF
183  20 CONTINUE
184  END IF
185  m = n
186 *
187  30 CONTINUE
188  l = l1
189  lsv = l
190  lend = m
191  lendsv = lend
192  l1 = m + 1
193  IF( lend.EQ.l )
194  $ GO TO 10
195 *
196 * Scale submatrix in rows and columns L to LEND
197 *
198  anorm = dlanst( 'I', lend-l+1, d( l ), e( l ) )
199  iscale = 0
200  IF( anorm.EQ.zero )
201  $ GO TO 10
202  IF( anorm.GT.ssfmax ) THEN
203  iscale = 1
204  CALL dlascl( 'G', 0, 0, anorm, ssfmax, lend-l+1, 1, d( l ), n,
205  $ info )
206  CALL dlascl( 'G', 0, 0, anorm, ssfmax, lend-l, 1, e( l ), n,
207  $ info )
208  ELSE IF( anorm.LT.ssfmin ) THEN
209  iscale = 2
210  CALL dlascl( 'G', 0, 0, anorm, ssfmin, lend-l+1, 1, d( l ), n,
211  $ info )
212  CALL dlascl( 'G', 0, 0, anorm, ssfmin, lend-l, 1, e( l ), n,
213  $ info )
214  END IF
215 *
216 * Choose between QL and QR iteration
217 *
218  IF( abs( d( lend ) ).LT.abs( d( l ) ) ) THEN
219  lend = lsv
220  l = lendsv
221  END IF
222 *
223  IF( lend.GT.l ) THEN
224 *
225 * QL Iteration
226 *
227 * Look for small subdiagonal element.
228 *
229  40 CONTINUE
230  IF( l.NE.lend ) THEN
231  lendm1 = lend - 1
232  DO 50 m = l, lendm1
233  tst = abs( e( m ) )**2
234  IF( tst.LE.( eps2*abs( d( m ) ) )*abs( d( m+1 ) )+
235  $ safmin )GO TO 60
236  50 CONTINUE
237  END IF
238 *
239  m = lend
240 *
241  60 CONTINUE
242  IF( m.LT.lend )
243  $ e( m ) = zero
244  p = d( l )
245  IF( m.EQ.l )
246  $ GO TO 80
247 *
248 * If remaining matrix is 2-by-2, use DLAE2 or SLAEV2
249 * to compute its eigensystem.
250 *
251  IF( m.EQ.l+1 ) THEN
252  IF( icompz.GT.0 ) THEN
253  CALL dlaev2( d( l ), e( l ), d( l+1 ), rt1, rt2, c, s )
254  work( l ) = c
255  work( n-1+l ) = s
256  CALL dlasr( 'R', 'V', 'B', n, 2, work( l ),
257  $ work( n-1+l ), z( 1, l ), ldz )
258  ELSE
259  CALL dlae2( d( l ), e( l ), d( l+1 ), rt1, rt2 )
260  END IF
261  d( l ) = rt1
262  d( l+1 ) = rt2
263  e( l ) = zero
264  l = l + 2
265  IF( l.LE.lend )
266  $ GO TO 40
267  GO TO 140
268  END IF
269 *
270  IF( jtot.EQ.nmaxit )
271  $ GO TO 140
272  jtot = jtot + 1
273 *
274 * Form shift.
275 *
276  g = ( d( l+1 )-p ) / ( two*e( l ) )
277  r = dlapy2( g, one )
278  g = d( m ) - p + ( e( l ) / ( g+sign( r, g ) ) )
279 *
280  s = one
281  c = one
282  p = zero
283 *
284 * Inner loop
285 *
286  mm1 = m - 1
287  DO 70 i = mm1, l, -1
288  f = s*e( i )
289  b = c*e( i )
290  CALL dlartg( g, f, c, s, r )
291  IF( i.NE.m-1 )
292  $ e( i+1 ) = r
293  g = d( i+1 ) - p
294  r = ( d( i )-g )*s + two*c*b
295  p = s*r
296  d( i+1 ) = g + p
297  g = c*r - b
298 *
299 * If eigenvectors are desired, then save rotations.
300 *
301  IF( icompz.GT.0 ) THEN
302  work( i ) = c
303  work( n-1+i ) = -s
304  END IF
305 *
306  70 CONTINUE
307 *
308 * If eigenvectors are desired, then apply saved rotations.
309 *
310  IF( icompz.GT.0 ) THEN
311  mm = m - l + 1
312  CALL dlasr( 'R', 'V', 'B', n, mm, work( l ), work( n-1+l ),
313  $ z( 1, l ), ldz )
314  END IF
315 *
316  d( l ) = d( l ) - p
317  e( l ) = g
318  GO TO 40
319 *
320 * Eigenvalue found.
321 *
322  80 CONTINUE
323  d( l ) = p
324 *
325  l = l + 1
326  IF( l.LE.lend )
327  $ GO TO 40
328  GO TO 140
329 *
330  ELSE
331 *
332 * QR Iteration
333 *
334 * Look for small superdiagonal element.
335 *
336  90 CONTINUE
337  IF( l.NE.lend ) THEN
338  lendp1 = lend + 1
339  DO 100 m = l, lendp1, -1
340  tst = abs( e( m-1 ) )**2
341  IF( tst.LE.( eps2*abs( d( m ) ) )*abs( d( m-1 ) )+
342  $ safmin )GO TO 110
343  100 CONTINUE
344  END IF
345 *
346  m = lend
347 *
348  110 CONTINUE
349  IF( m.GT.lend )
350  $ e( m-1 ) = zero
351  p = d( l )
352  IF( m.EQ.l )
353  $ GO TO 130
354 *
355 * If remaining matrix is 2-by-2, use DLAE2 or SLAEV2
356 * to compute its eigensystem.
357 *
358  IF( m.EQ.l-1 ) THEN
359  IF( icompz.GT.0 ) THEN
360  CALL dlaev2( d( l-1 ), e( l-1 ), d( l ), rt1, rt2, c, s )
361  work( m ) = c
362  work( n-1+m ) = s
363  CALL dlasr( 'R', 'V', 'F', n, 2, work( m ),
364  $ work( n-1+m ), z( 1, l-1 ), ldz )
365  ELSE
366  CALL dlae2( d( l-1 ), e( l-1 ), d( l ), rt1, rt2 )
367  END IF
368  d( l-1 ) = rt1
369  d( l ) = rt2
370  e( l-1 ) = zero
371  l = l - 2
372  IF( l.GE.lend )
373  $ GO TO 90
374  GO TO 140
375  END IF
376 *
377  IF( jtot.EQ.nmaxit )
378  $ GO TO 140
379  jtot = jtot + 1
380 *
381 * Form shift.
382 *
383  g = ( d( l-1 )-p ) / ( two*e( l-1 ) )
384  r = dlapy2( g, one )
385  g = d( m ) - p + ( e( l-1 ) / ( g+sign( r, g ) ) )
386 *
387  s = one
388  c = one
389  p = zero
390 *
391 * Inner loop
392 *
393  lm1 = l - 1
394  DO 120 i = m, lm1
395  f = s*e( i )
396  b = c*e( i )
397  CALL dlartg( g, f, c, s, r )
398  IF( i.NE.m )
399  $ e( i-1 ) = r
400  g = d( i ) - p
401  r = ( d( i+1 )-g )*s + two*c*b
402  p = s*r
403  d( i ) = g + p
404  g = c*r - b
405 *
406 * If eigenvectors are desired, then save rotations.
407 *
408  IF( icompz.GT.0 ) THEN
409  work( i ) = c
410  work( n-1+i ) = s
411  END IF
412 *
413  120 CONTINUE
414 *
415 * If eigenvectors are desired, then apply saved rotations.
416 *
417  IF( icompz.GT.0 ) THEN
418  mm = l - m + 1
419  CALL dlasr( 'R', 'V', 'F', n, mm, work( m ), work( n-1+m ),
420  $ z( 1, m ), ldz )
421  END IF
422 *
423  d( l ) = d( l ) - p
424  e( lm1 ) = g
425  GO TO 90
426 *
427 * Eigenvalue found.
428 *
429  130 CONTINUE
430  d( l ) = p
431 *
432  l = l - 1
433  IF( l.GE.lend )
434  $ GO TO 90
435  GO TO 140
436 *
437  END IF
438 *
439 * Undo scaling if necessary
440 *
441  140 CONTINUE
442  IF( iscale.EQ.1 ) THEN
443  CALL dlascl( 'G', 0, 0, ssfmax, anorm, lendsv-lsv+1, 1,
444  $ d( lsv ), n, info )
445  CALL dlascl( 'G', 0, 0, ssfmax, anorm, lendsv-lsv, 1, e( lsv ),
446  $ n, info )
447  ELSE IF( iscale.EQ.2 ) THEN
448  CALL dlascl( 'G', 0, 0, ssfmin, anorm, lendsv-lsv+1, 1,
449  $ d( lsv ), n, info )
450  CALL dlascl( 'G', 0, 0, ssfmin, anorm, lendsv-lsv, 1, e( lsv ),
451  $ n, info )
452  END IF
453 *
454 * Check for no convergence to an eigenvalue after a total
455 * of N*MAXIT iterations.
456 *
457  IF( jtot.LT.nmaxit )
458  $ GO TO 10
459  DO 150 i = 1, n - 1
460  IF( e( i ).NE.zero )
461  $ info = info + 1
462  150 CONTINUE
463  GO TO 190
464 *
465 * Order eigenvalues and eigenvectors.
466 *
467  160 CONTINUE
468  IF( icompz.EQ.0 ) THEN
469 *
470 * Use Quick Sort
471 *
472  CALL dlasrt( 'I', n, d, info )
473 *
474  ELSE
475 *
476 * Use Selection Sort to minimize swaps of eigenvectors
477 *
478  DO 180 ii = 2, n
479  i = ii - 1
480  k = i
481  p = d( i )
482  DO 170 j = ii, n
483  IF( d( j ).LT.p ) THEN
484  k = j
485  p = d( j )
486  END IF
487  170 CONTINUE
488  IF( k.NE.i ) THEN
489  d( k ) = d( i )
490  d( i ) = p
491  CALL dswap( n, z( 1, i ), 1, z( 1, k ), 1 )
492  END IF
493  180 CONTINUE
494  END IF
495 *
496  190 CONTINUE
497  RETURN
498 *
499 * End of DSTEQR
500 *
501  END
subroutine dlae2(A, B, C, RT1, RT2)
Definition: dlae2.f:2
subroutine dlaev2(A, B, C, RT1, RT2, CS1, SN1)
Definition: dlaev2.f:2
subroutine dlartg(F, G, CS, SN, R)
Definition: dlartg.f:2
subroutine dlascl(TYPE, KL, KU, CFROM, CTO, M, N, A, LDA, INFO)
Definition: dlascl.f:2
subroutine dlaset(UPLO, M, N, ALPHA, BETA, A, LDA)
Definition: dlaset.f:2
subroutine dlasr(SIDE, PIVOT, DIRECT, M, N, C, S, A, LDA)
Definition: dlasr.f:2
subroutine dlasrt(ID, N, D, INFO)
Definition: dlasrt.f:2
subroutine dsteqr(COMPZ, N, D, E, Z, LDZ, WORK, INFO)
Definition: dsteqr.f:2
subroutine dswap(n, dx, incx, dy, incy)
Definition: dswap.f:2
subroutine xerbla(SRNAME, INFO)
Definition: xerbla.f:2