2329
|
1 SUBROUTINE ZHSEQR( JOB, COMPZ, N, ILO, IHI, H, LDH, W, Z, LDZ, |
|
2 $ WORK, LWORK, INFO ) |
|
3 * |
7034
|
4 * -- LAPACK driver routine (version 3.1) -- |
|
5 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd.. |
|
6 * November 2006 |
2329
|
7 * |
|
8 * .. Scalar Arguments .. |
7034
|
9 INTEGER IHI, ILO, INFO, LDH, LDZ, LWORK, N |
2329
|
10 CHARACTER COMPZ, JOB |
|
11 * .. |
|
12 * .. Array Arguments .. |
|
13 COMPLEX*16 H( LDH, * ), W( * ), WORK( * ), Z( LDZ, * ) |
|
14 * .. |
7034
|
15 * Purpose |
|
16 * ======= |
2329
|
17 * |
7034
|
18 * ZHSEQR computes the eigenvalues of a Hessenberg matrix H |
|
19 * and, optionally, the matrices T and Z from the Schur decomposition |
|
20 * H = Z T Z**H, where T is an upper triangular matrix (the |
|
21 * Schur form), and Z is the unitary matrix of Schur vectors. |
|
22 * |
|
23 * Optionally Z may be postmultiplied into an input unitary |
|
24 * matrix Q so that this routine can give the Schur factorization |
|
25 * of a matrix A which has been reduced to the Hessenberg form H |
|
26 * by the unitary matrix Q: A = Q*H*Q**H = (QZ)*H*(QZ)**H. |
2329
|
27 * |
7034
|
28 * Arguments |
|
29 * ========= |
|
30 * |
|
31 * JOB (input) CHARACTER*1 |
|
32 * = 'E': compute eigenvalues only; |
|
33 * = 'S': compute eigenvalues and the Schur form T. |
|
34 * |
|
35 * COMPZ (input) CHARACTER*1 |
|
36 * = 'N': no Schur vectors are computed; |
|
37 * = 'I': Z is initialized to the unit matrix and the matrix Z |
|
38 * of Schur vectors of H is returned; |
|
39 * = 'V': Z must contain an unitary matrix Q on entry, and |
|
40 * the product Q*Z is returned. |
2329
|
41 * |
7034
|
42 * N (input) INTEGER |
|
43 * The order of the matrix H. N .GE. 0. |
|
44 * |
|
45 * ILO (input) INTEGER |
|
46 * IHI (input) INTEGER |
|
47 * It is assumed that H is already upper triangular in rows |
|
48 * and columns 1:ILO-1 and IHI+1:N. ILO and IHI are normally |
|
49 * set by a previous call to ZGEBAL, and then passed to ZGEHRD |
|
50 * when the matrix output by ZGEBAL is reduced to Hessenberg |
|
51 * form. Otherwise ILO and IHI should be set to 1 and N |
|
52 * respectively. If N.GT.0, then 1.LE.ILO.LE.IHI.LE.N. |
|
53 * If N = 0, then ILO = 1 and IHI = 0. |
2329
|
54 * |
7034
|
55 * H (input/output) COMPLEX*16 array, dimension (LDH,N) |
|
56 * On entry, the upper Hessenberg matrix H. |
|
57 * On exit, if INFO = 0 and JOB = 'S', H contains the upper |
|
58 * triangular matrix T from the Schur decomposition (the |
|
59 * Schur form). If INFO = 0 and JOB = 'E', the contents of |
|
60 * H are unspecified on exit. (The output value of H when |
|
61 * INFO.GT.0 is given under the description of INFO below.) |
2329
|
62 * |
7034
|
63 * Unlike earlier versions of ZHSEQR, this subroutine may |
|
64 * explicitly H(i,j) = 0 for i.GT.j and j = 1, 2, ... ILO-1 |
|
65 * or j = IHI+1, IHI+2, ... N. |
|
66 * |
|
67 * LDH (input) INTEGER |
|
68 * The leading dimension of the array H. LDH .GE. max(1,N). |
2329
|
69 * |
7034
|
70 * W (output) COMPLEX*16 array, dimension (N) |
|
71 * The computed eigenvalues. If JOB = 'S', the eigenvalues are |
|
72 * stored in the same order as on the diagonal of the Schur |
|
73 * form returned in H, with W(i) = H(i,i). |
2329
|
74 * |
7034
|
75 * Z (input/output) COMPLEX*16 array, dimension (LDZ,N) |
|
76 * If COMPZ = 'N', Z is not referenced. |
|
77 * If COMPZ = 'I', on entry Z need not be set and on exit, |
|
78 * if INFO = 0, Z contains the unitary matrix Z of the Schur |
|
79 * vectors of H. If COMPZ = 'V', on entry Z must contain an |
|
80 * N-by-N matrix Q, which is assumed to be equal to the unit |
|
81 * matrix except for the submatrix Z(ILO:IHI,ILO:IHI). On exit, |
|
82 * if INFO = 0, Z contains Q*Z. |
|
83 * Normally Q is the unitary matrix generated by ZUNGHR |
|
84 * after the call to ZGEHRD which formed the Hessenberg matrix |
|
85 * H. (The output value of Z when INFO.GT.0 is given under |
|
86 * the description of INFO below.) |
|
87 * |
|
88 * LDZ (input) INTEGER |
|
89 * The leading dimension of the array Z. if COMPZ = 'I' or |
|
90 * COMPZ = 'V', then LDZ.GE.MAX(1,N). Otherwize, LDZ.GE.1. |
|
91 * |
|
92 * WORK (workspace/output) COMPLEX*16 array, dimension (LWORK) |
|
93 * On exit, if INFO = 0, WORK(1) returns an estimate of |
|
94 * the optimal value for LWORK. |
2329
|
95 * |
7034
|
96 * LWORK (input) INTEGER |
|
97 * The dimension of the array WORK. LWORK .GE. max(1,N) |
|
98 * is sufficient, but LWORK typically as large as 6*N may |
|
99 * be required for optimal performance. A workspace query |
|
100 * to determine the optimal workspace size is recommended. |
|
101 * |
|
102 * If LWORK = -1, then ZHSEQR does a workspace query. |
|
103 * In this case, ZHSEQR checks the input parameters and |
|
104 * estimates the optimal workspace size for the given |
|
105 * values of N, ILO and IHI. The estimate is returned |
|
106 * in WORK(1). No error message related to LWORK is |
|
107 * issued by XERBLA. Neither H nor Z are accessed. |
|
108 * |
2329
|
109 * |
7034
|
110 * INFO (output) INTEGER |
|
111 * = 0: successful exit |
|
112 * .LT. 0: if INFO = -i, the i-th argument had an illegal |
|
113 * value |
|
114 * .GT. 0: if INFO = i, ZHSEQR failed to compute all of |
|
115 * the eigenvalues. Elements 1:ilo-1 and i+1:n of WR |
|
116 * and WI contain those eigenvalues which have been |
|
117 * successfully computed. (Failures are rare.) |
2329
|
118 * |
7034
|
119 * If INFO .GT. 0 and JOB = 'E', then on exit, the |
|
120 * remaining unconverged eigenvalues are the eigen- |
|
121 * values of the upper Hessenberg matrix rows and |
|
122 * columns ILO through INFO of the final, output |
|
123 * value of H. |
|
124 * |
|
125 * If INFO .GT. 0 and JOB = 'S', then on exit |
2329
|
126 * |
7034
|
127 * (*) (initial value of H)*U = U*(final value of H) |
|
128 * |
|
129 * where U is a unitary matrix. The final |
|
130 * value of H is upper Hessenberg and triangular in |
|
131 * rows and columns INFO+1 through IHI. |
|
132 * |
|
133 * If INFO .GT. 0 and COMPZ = 'V', then on exit |
|
134 * |
|
135 * (final value of Z) = (initial value of Z)*U |
|
136 * |
|
137 * where U is the unitary matrix in (*) (regard- |
|
138 * less of the value of JOB.) |
|
139 * |
|
140 * If INFO .GT. 0 and COMPZ = 'I', then on exit |
|
141 * (final value of Z) = U |
|
142 * where U is the unitary matrix in (*) (regard- |
|
143 * less of the value of JOB.) |
|
144 * |
|
145 * If INFO .GT. 0 and COMPZ = 'N', then Z is not |
|
146 * accessed. |
2329
|
147 * |
7034
|
148 * ================================================================ |
|
149 * Default values supplied by |
|
150 * ILAENV(ISPEC,'ZHSEQR',JOB(:1)//COMPZ(:1),N,ILO,IHI,LWORK). |
|
151 * It is suggested that these defaults be adjusted in order |
|
152 * to attain best performance in each particular |
|
153 * computational environment. |
|
154 * |
|
155 * ISPEC=1: The ZLAHQR vs ZLAQR0 crossover point. |
|
156 * Default: 75. (Must be at least 11.) |
2329
|
157 * |
7034
|
158 * ISPEC=2: Recommended deflation window size. |
|
159 * This depends on ILO, IHI and NS. NS is the |
|
160 * number of simultaneous shifts returned |
|
161 * by ILAENV(ISPEC=4). (See ISPEC=4 below.) |
|
162 * The default for (IHI-ILO+1).LE.500 is NS. |
|
163 * The default for (IHI-ILO+1).GT.500 is 3*NS/2. |
2329
|
164 * |
7034
|
165 * ISPEC=3: Nibble crossover point. (See ILAENV for |
|
166 * details.) Default: 14% of deflation window |
|
167 * size. |
2329
|
168 * |
7034
|
169 * ISPEC=4: Number of simultaneous shifts, NS, in |
|
170 * a multi-shift QR iteration. |
|
171 * |
|
172 * If IHI-ILO+1 is ... |
|
173 * |
|
174 * greater than ...but less ... the |
|
175 * or equal to ... than default is |
3333
|
176 * |
7034
|
177 * 1 30 NS - 2(+) |
|
178 * 30 60 NS - 4(+) |
|
179 * 60 150 NS = 10(+) |
|
180 * 150 590 NS = ** |
|
181 * 590 3000 NS = 64 |
|
182 * 3000 6000 NS = 128 |
|
183 * 6000 infinity NS = 256 |
|
184 * |
|
185 * (+) By default some or all matrices of this order |
|
186 * are passed to the implicit double shift routine |
|
187 * ZLAHQR and NS is ignored. See ISPEC=1 above |
|
188 * and comments in IPARM for details. |
|
189 * |
|
190 * The asterisks (**) indicate an ad-hoc |
|
191 * function of N increasing from 10 to 64. |
|
192 * |
|
193 * ISPEC=5: Select structured matrix multiply. |
|
194 * (See ILAENV for details.) Default: 3. |
|
195 * |
|
196 * ================================================================ |
|
197 * Based on contributions by |
|
198 * Karen Braman and Ralph Byers, Department of Mathematics, |
|
199 * University of Kansas, USA |
|
200 * |
|
201 * ================================================================ |
|
202 * References: |
|
203 * K. Braman, R. Byers and R. Mathias, The Multi-Shift QR |
|
204 * Algorithm Part I: Maintaining Well Focused Shifts, and Level 3 |
|
205 * Performance, SIAM Journal of Matrix Analysis, volume 23, pages |
|
206 * 929--947, 2002. |
2329
|
207 * |
7034
|
208 * K. Braman, R. Byers and R. Mathias, The Multi-Shift QR |
|
209 * Algorithm Part II: Aggressive Early Deflation, SIAM Journal |
|
210 * of Matrix Analysis, volume 23, pages 948--973, 2002. |
2329
|
211 * |
7034
|
212 * ================================================================ |
|
213 * .. Parameters .. |
|
214 * |
|
215 * ==== Matrices of order NTINY or smaller must be processed by |
|
216 * . ZLAHQR because of insufficient subdiagonal scratch space. |
|
217 * . (This is a hard limit.) ==== |
2329
|
218 * |
7034
|
219 * ==== NL allocates some local workspace to help small matrices |
|
220 * . through a rare ZLAHQR failure. NL .GT. NTINY = 11 is |
|
221 * . required and NL .LE. NMIN = ILAENV(ISPEC=1,...) is recom- |
|
222 * . mended. (The default value of NMIN is 75.) Using NL = 49 |
|
223 * . allows up to six simultaneous shifts and a 16-by-16 |
|
224 * . deflation window. ==== |
|
225 * |
|
226 INTEGER NTINY |
|
227 PARAMETER ( NTINY = 11 ) |
|
228 INTEGER NL |
|
229 PARAMETER ( NL = 49 ) |
2329
|
230 COMPLEX*16 ZERO, ONE |
7034
|
231 PARAMETER ( ZERO = ( 0.0d0, 0.0d0 ), |
|
232 $ ONE = ( 1.0d0, 0.0d0 ) ) |
|
233 DOUBLE PRECISION RZERO |
|
234 PARAMETER ( RZERO = 0.0d0 ) |
|
235 * .. |
|
236 * .. Local Arrays .. |
|
237 COMPLEX*16 HL( NL, NL ), WORKL( NL ) |
2329
|
238 * .. |
|
239 * .. Local Scalars .. |
7034
|
240 INTEGER KBOT, NMIN |
3333
|
241 LOGICAL INITZ, LQUERY, WANTT, WANTZ |
2329
|
242 * .. |
|
243 * .. External Functions .. |
7034
|
244 INTEGER ILAENV |
2329
|
245 LOGICAL LSAME |
7034
|
246 EXTERNAL ILAENV, LSAME |
2329
|
247 * .. |
|
248 * .. External Subroutines .. |
7034
|
249 EXTERNAL XERBLA, ZCOPY, ZLACPY, ZLAHQR, ZLAQR0, ZLASET |
2329
|
250 * .. |
|
251 * .. Intrinsic Functions .. |
7034
|
252 INTRINSIC DBLE, DCMPLX, MAX, MIN |
2329
|
253 * .. |
|
254 * .. Executable Statements .. |
|
255 * |
7034
|
256 * ==== Decode and check the input parameters. ==== |
2329
|
257 * |
|
258 WANTT = LSAME( JOB, 'S' ) |
|
259 INITZ = LSAME( COMPZ, 'I' ) |
|
260 WANTZ = INITZ .OR. LSAME( COMPZ, 'V' ) |
7034
|
261 WORK( 1 ) = DCMPLX( DBLE( MAX( 1, N ) ), RZERO ) |
|
262 LQUERY = LWORK.EQ.-1 |
2329
|
263 * |
|
264 INFO = 0 |
|
265 IF( .NOT.LSAME( JOB, 'E' ) .AND. .NOT.WANTT ) THEN |
|
266 INFO = -1 |
|
267 ELSE IF( .NOT.LSAME( COMPZ, 'N' ) .AND. .NOT.WANTZ ) THEN |
|
268 INFO = -2 |
|
269 ELSE IF( N.LT.0 ) THEN |
|
270 INFO = -3 |
|
271 ELSE IF( ILO.LT.1 .OR. ILO.GT.MAX( 1, N ) ) THEN |
|
272 INFO = -4 |
|
273 ELSE IF( IHI.LT.MIN( ILO, N ) .OR. IHI.GT.N ) THEN |
|
274 INFO = -5 |
|
275 ELSE IF( LDH.LT.MAX( 1, N ) ) THEN |
|
276 INFO = -7 |
7034
|
277 ELSE IF( LDZ.LT.1 .OR. ( WANTZ .AND. LDZ.LT.MAX( 1, N ) ) ) THEN |
2329
|
278 INFO = -10 |
3333
|
279 ELSE IF( LWORK.LT.MAX( 1, N ) .AND. .NOT.LQUERY ) THEN |
|
280 INFO = -12 |
2329
|
281 END IF |
7034
|
282 * |
2329
|
283 IF( INFO.NE.0 ) THEN |
7034
|
284 * |
|
285 * ==== Quick return in case of invalid argument. ==== |
|
286 * |
2329
|
287 CALL XERBLA( 'ZHSEQR', -INFO ) |
|
288 RETURN |
|
289 * |
7034
|
290 ELSE IF( N.EQ.0 ) THEN |
2329
|
291 * |
7034
|
292 * ==== Quick return in case N = 0; nothing to do. ==== |
2329
|
293 * |
|
294 RETURN |
|
295 * |
7034
|
296 ELSE IF( LQUERY ) THEN |
|
297 * |
|
298 * ==== Quick return in case of a workspace query ==== |
2329
|
299 * |
7034
|
300 CALL ZLAQR0( WANTT, WANTZ, N, ILO, IHI, H, LDH, W, ILO, IHI, Z, |
|
301 $ LDZ, WORK, LWORK, INFO ) |
|
302 * ==== Ensure reported workspace size is backward-compatible with |
|
303 * . previous LAPACK versions. ==== |
|
304 WORK( 1 ) = DCMPLX( MAX( DBLE( WORK( 1 ) ), DBLE( MAX( 1, |
|
305 $ N ) ) ), RZERO ) |
|
306 RETURN |
2329
|
307 * |
7034
|
308 ELSE |
2329
|
309 * |
7034
|
310 * ==== copy eigenvalues isolated by ZGEBAL ==== |
2329
|
311 * |
7034
|
312 IF( ILO.GT.1 ) |
|
313 $ CALL ZCOPY( ILO-1, H, LDH+1, W, 1 ) |
|
314 IF( IHI.LT.N ) |
|
315 $ CALL ZCOPY( N-IHI, H( IHI+1, IHI+1 ), LDH+1, W( IHI+1 ), 1 ) |
2329
|
316 * |
7034
|
317 * ==== Initialize Z, if requested ==== |
2329
|
318 * |
7034
|
319 IF( INITZ ) |
|
320 $ CALL ZLASET( 'A', N, N, ZERO, ONE, Z, LDZ ) |
2329
|
321 * |
7034
|
322 * ==== Quick return if possible ==== |
2329
|
323 * |
7034
|
324 IF( ILO.EQ.IHI ) THEN |
|
325 W( ILO ) = H( ILO, ILO ) |
|
326 RETURN |
2329
|
327 END IF |
|
328 * |
7034
|
329 * ==== ZLAHQR/ZLAQR0 crossover point ==== |
2329
|
330 * |
7034
|
331 NMIN = ILAENV( 1, 'ZHSEQR', JOB( : 1 ) // COMPZ( : 1 ), N, ILO, |
|
332 $ IHI, LWORK ) |
|
333 NMIN = MAX( NTINY, NMIN ) |
2329
|
334 * |
7034
|
335 * ==== ZLAQR0 for big matrices; ZLAHQR for small ones ==== |
2329
|
336 * |
7034
|
337 IF( N.GT.NMIN ) THEN |
|
338 CALL ZLAQR0( WANTT, WANTZ, N, ILO, IHI, H, LDH, W, ILO, IHI, |
|
339 $ Z, LDZ, WORK, LWORK, INFO ) |
2329
|
340 ELSE |
|
341 * |
7034
|
342 * ==== Small matrix ==== |
|
343 * |
|
344 CALL ZLAHQR( WANTT, WANTZ, N, ILO, IHI, H, LDH, W, ILO, IHI, |
|
345 $ Z, LDZ, INFO ) |
|
346 * |
|
347 IF( INFO.GT.0 ) THEN |
|
348 * |
|
349 * ==== A rare ZLAHQR failure! ZLAQR0 sometimes succeeds |
|
350 * . when ZLAHQR fails. ==== |
|
351 * |
|
352 KBOT = INFO |
|
353 * |
|
354 IF( N.GE.NL ) THEN |
|
355 * |
|
356 * ==== Larger matrices have enough subdiagonal scratch |
|
357 * . space to call ZLAQR0 directly. ==== |
2329
|
358 * |
7034
|
359 CALL ZLAQR0( WANTT, WANTZ, N, ILO, KBOT, H, LDH, W, |
|
360 $ ILO, IHI, Z, LDZ, WORK, LWORK, INFO ) |
|
361 * |
|
362 ELSE |
|
363 * |
|
364 * ==== Tiny matrices don't have enough subdiagonal |
|
365 * . scratch space to benefit from ZLAQR0. Hence, |
|
366 * . tiny matrices must be copied into a larger |
|
367 * . array before calling ZLAQR0. ==== |
2329
|
368 * |
7034
|
369 CALL ZLACPY( 'A', N, N, H, LDH, HL, NL ) |
|
370 HL( N+1, N ) = ZERO |
|
371 CALL ZLASET( 'A', NL, NL-N, ZERO, ZERO, HL( 1, N+1 ), |
|
372 $ NL ) |
|
373 CALL ZLAQR0( WANTT, WANTZ, NL, ILO, KBOT, HL, NL, W, |
|
374 $ ILO, IHI, Z, LDZ, WORKL, NL, INFO ) |
|
375 IF( WANTT .OR. INFO.NE.0 ) |
|
376 $ CALL ZLACPY( 'A', N, N, HL, NL, H, LDH ) |
|
377 END IF |
2329
|
378 END IF |
|
379 END IF |
|
380 * |
7034
|
381 * ==== Clear out the trash, if necessary. ==== |
2329
|
382 * |
7034
|
383 IF( ( WANTT .OR. INFO.NE.0 ) .AND. N.GT.2 ) |
|
384 $ CALL ZLASET( 'L', N-2, N-2, ZERO, ZERO, H( 3, 1 ), LDH ) |
2329
|
385 * |
7034
|
386 * ==== Ensure reported workspace size is backward-compatible with |
|
387 * . previous LAPACK versions. ==== |
2329
|
388 * |
7034
|
389 WORK( 1 ) = DCMPLX( MAX( DBLE( MAX( 1, N ) ), |
|
390 $ DBLE( WORK( 1 ) ) ), RZERO ) |
|
391 END IF |
2329
|
392 * |
7034
|
393 * ==== End of ZHSEQR ==== |
2329
|
394 * |
|
395 END |