1 SUBROUTINE DGEESX( JOBVS, SORT, SELECT, SENSE, N, A, LDA, SDIM,
2 $ WR, WI, VS, LDVS, RCONDE, RCONDV, WORK, LWORK,
3 $ IWORK, LIWORK, BWORK, INFO )
4 *
5 * -- LAPACK driver routine (version 3.2.2) --
6 * -- LAPACK is a software package provided by Univ. of Tennessee, --
7 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
8 * June 2010
9 *
10 * .. Scalar Arguments ..
11 CHARACTER JOBVS, SENSE, SORT
12 INTEGER INFO, LDA, LDVS, LIWORK, LWORK, N, SDIM
13 DOUBLE PRECISION RCONDE, RCONDV
14 * ..
15 * .. Array Arguments ..
16 LOGICAL BWORK( * )
17 INTEGER IWORK( * )
18 DOUBLE PRECISION A( LDA, * ), VS( LDVS, * ), WI( * ), WORK( * ),
19 $ WR( * )
20 * ..
21 * .. Function Arguments ..
22 LOGICAL SELECT
23 EXTERNAL SELECT
24 * ..
25 *
26 * Purpose
27 * =======
28 *
29 * DGEESX computes for an N-by-N real nonsymmetric matrix A, the
30 * eigenvalues, the real Schur form T, and, optionally, the matrix of
31 * Schur vectors Z. This gives the Schur factorization A = Z*T*(Z**T).
32 *
33 * Optionally, it also orders the eigenvalues on the diagonal of the
34 * real Schur form so that selected eigenvalues are at the top left;
35 * computes a reciprocal condition number for the average of the
36 * selected eigenvalues (RCONDE); and computes a reciprocal condition
37 * number for the right invariant subspace corresponding to the
38 * selected eigenvalues (RCONDV). The leading columns of Z form an
39 * orthonormal basis for this invariant subspace.
40 *
41 * For further explanation of the reciprocal condition numbers RCONDE
42 * and RCONDV, see Section 4.10 of the LAPACK Users' Guide (where
43 * these quantities are called s and sep respectively).
44 *
45 * A real matrix is in real Schur form if it is upper quasi-triangular
46 * with 1-by-1 and 2-by-2 blocks. 2-by-2 blocks will be standardized in
47 * the form
48 * [ a b ]
49 * [ c a ]
50 *
51 * where b*c < 0. The eigenvalues of such a block are a +- sqrt(bc).
52 *
53 * Arguments
54 * =========
55 *
56 * JOBVS (input) CHARACTER*1
57 * = 'N': Schur vectors are not computed;
58 * = 'V': Schur vectors are computed.
59 *
60 * SORT (input) CHARACTER*1
61 * Specifies whether or not to order the eigenvalues on the
62 * diagonal of the Schur form.
63 * = 'N': Eigenvalues are not ordered;
64 * = 'S': Eigenvalues are ordered (see SELECT).
65 *
66 * SELECT (external procedure) LOGICAL FUNCTION of two DOUBLE PRECISION arguments
67 * SELECT must be declared EXTERNAL in the calling subroutine.
68 * If SORT = 'S', SELECT is used to select eigenvalues to sort
69 * to the top left of the Schur form.
70 * If SORT = 'N', SELECT is not referenced.
71 * An eigenvalue WR(j)+sqrt(-1)*WI(j) is selected if
72 * SELECT(WR(j),WI(j)) is true; i.e., if either one of a
73 * complex conjugate pair of eigenvalues is selected, then both
74 * are. Note that a selected complex eigenvalue may no longer
75 * satisfy SELECT(WR(j),WI(j)) = .TRUE. after ordering, since
76 * ordering may change the value of complex eigenvalues
77 * (especially if the eigenvalue is ill-conditioned); in this
78 * case INFO may be set to N+3 (see INFO below).
79 *
80 * SENSE (input) CHARACTER*1
81 * Determines which reciprocal condition numbers are computed.
82 * = 'N': None are computed;
83 * = 'E': Computed for average of selected eigenvalues only;
84 * = 'V': Computed for selected right invariant subspace only;
85 * = 'B': Computed for both.
86 * If SENSE = 'E', 'V' or 'B', SORT must equal 'S'.
87 *
88 * N (input) INTEGER
89 * The order of the matrix A. N >= 0.
90 *
91 * A (input/output) DOUBLE PRECISION array, dimension (LDA, N)
92 * On entry, the N-by-N matrix A.
93 * On exit, A is overwritten by its real Schur form T.
94 *
95 * LDA (input) INTEGER
96 * The leading dimension of the array A. LDA >= max(1,N).
97 *
98 * SDIM (output) INTEGER
99 * If SORT = 'N', SDIM = 0.
100 * If SORT = 'S', SDIM = number of eigenvalues (after sorting)
101 * for which SELECT is true. (Complex conjugate
102 * pairs for which SELECT is true for either
103 * eigenvalue count as 2.)
104 *
105 * WR (output) DOUBLE PRECISION array, dimension (N)
106 * WI (output) DOUBLE PRECISION array, dimension (N)
107 * WR and WI contain the real and imaginary parts, respectively,
108 * of the computed eigenvalues, in the same order that they
109 * appear on the diagonal of the output Schur form T. Complex
110 * conjugate pairs of eigenvalues appear consecutively with the
111 * eigenvalue having the positive imaginary part first.
112 *
113 * VS (output) DOUBLE PRECISION array, dimension (LDVS,N)
114 * If JOBVS = 'V', VS contains the orthogonal matrix Z of Schur
115 * vectors.
116 * If JOBVS = 'N', VS is not referenced.
117 *
118 * LDVS (input) INTEGER
119 * The leading dimension of the array VS. LDVS >= 1, and if
120 * JOBVS = 'V', LDVS >= N.
121 *
122 * RCONDE (output) DOUBLE PRECISION
123 * If SENSE = 'E' or 'B', RCONDE contains the reciprocal
124 * condition number for the average of the selected eigenvalues.
125 * Not referenced if SENSE = 'N' or 'V'.
126 *
127 * RCONDV (output) DOUBLE PRECISION
128 * If SENSE = 'V' or 'B', RCONDV contains the reciprocal
129 * condition number for the selected right invariant subspace.
130 * Not referenced if SENSE = 'N' or 'E'.
131 *
132 * WORK (workspace/output) DOUBLE PRECISION array, dimension (MAX(1,LWORK))
133 * On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
134 *
135 * LWORK (input) INTEGER
136 * The dimension of the array WORK. LWORK >= max(1,3*N).
137 * Also, if SENSE = 'E' or 'V' or 'B',
138 * LWORK >= N+2*SDIM*(N-SDIM), where SDIM is the number of
139 * selected eigenvalues computed by this routine. Note that
140 * N+2*SDIM*(N-SDIM) <= N+N*N/2. Note also that an error is only
141 * returned if LWORK < max(1,3*N), but if SENSE = 'E' or 'V' or
142 * 'B' this may not be large enough.
143 * For good performance, LWORK must generally be larger.
144 *
145 * If LWORK = -1, then a workspace query is assumed; the routine
146 * only calculates upper bounds on the optimal sizes of the
147 * arrays WORK and IWORK, returns these values as the first
148 * entries of the WORK and IWORK arrays, and no error messages
149 * related to LWORK or LIWORK are issued by XERBLA.
150 *
151 * IWORK (workspace/output) INTEGER array, dimension (MAX(1,LIWORK))
152 * On exit, if INFO = 0, IWORK(1) returns the optimal LIWORK.
153 *
154 * LIWORK (input) INTEGER
155 * The dimension of the array IWORK.
156 * LIWORK >= 1; if SENSE = 'V' or 'B', LIWORK >= SDIM*(N-SDIM).
157 * Note that SDIM*(N-SDIM) <= N*N/4. Note also that an error is
158 * only returned if LIWORK < 1, but if SENSE = 'V' or 'B' this
159 * may not be large enough.
160 *
161 * If LIWORK = -1, then a workspace query is assumed; the
162 * routine only calculates upper bounds on the optimal sizes of
163 * the arrays WORK and IWORK, returns these values as the first
164 * entries of the WORK and IWORK arrays, and no error messages
165 * related to LWORK or LIWORK are issued by XERBLA.
166 *
167 * BWORK (workspace) LOGICAL array, dimension (N)
168 * Not referenced if SORT = 'N'.
169 *
170 * INFO (output) INTEGER
171 * = 0: successful exit
172 * < 0: if INFO = -i, the i-th argument had an illegal value.
173 * > 0: if INFO = i, and i is
174 * <= N: the QR algorithm failed to compute all the
175 * eigenvalues; elements 1:ILO-1 and i+1:N of WR and WI
176 * contain those eigenvalues which have converged; if
177 * JOBVS = 'V', VS contains the transformation which
178 * reduces A to its partially converged Schur form.
179 * = N+1: the eigenvalues could not be reordered because some
180 * eigenvalues were too close to separate (the problem
181 * is very ill-conditioned);
182 * = N+2: after reordering, roundoff changed values of some
183 * complex eigenvalues so that leading eigenvalues in
184 * the Schur form no longer satisfy SELECT=.TRUE. This
185 * could also be caused by underflow due to scaling.
186 *
187 * =====================================================================
188 *
189 * .. Parameters ..
190 DOUBLE PRECISION ZERO, ONE
191 PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0 )
192 * ..
193 * .. Local Scalars ..
194 LOGICAL CURSL, LASTSL, LQUERY, LST2SL, SCALEA, WANTSB,
195 $ WANTSE, WANTSN, WANTST, WANTSV, WANTVS
196 INTEGER HSWORK, I, I1, I2, IBAL, ICOND, IERR, IEVAL,
197 $ IHI, ILO, INXT, IP, ITAU, IWRK, LIWRK, LWRK,
198 $ MAXWRK, MINWRK
199 DOUBLE PRECISION ANRM, BIGNUM, CSCALE, EPS, SMLNUM
200 * ..
201 * .. Local Arrays ..
202 DOUBLE PRECISION DUM( 1 )
203 * ..
204 * .. External Subroutines ..
205 EXTERNAL DCOPY, DGEBAK, DGEBAL, DGEHRD, DHSEQR, DLACPY,
206 $ DLASCL, DORGHR, DSWAP, DTRSEN, XERBLA
207 * ..
208 * .. External Functions ..
209 LOGICAL LSAME
210 INTEGER ILAENV
211 DOUBLE PRECISION DLAMCH, DLANGE
212 EXTERNAL LSAME, ILAENV, DLABAD, DLAMCH, DLANGE
213 * ..
214 * .. Intrinsic Functions ..
215 INTRINSIC MAX, SQRT
216 * ..
217 * .. Executable Statements ..
218 *
219 * Test the input arguments
220 *
221 INFO = 0
222 WANTVS = LSAME( JOBVS, 'V' )
223 WANTST = LSAME( SORT, 'S' )
224 WANTSN = LSAME( SENSE, 'N' )
225 WANTSE = LSAME( SENSE, 'E' )
226 WANTSV = LSAME( SENSE, 'V' )
227 WANTSB = LSAME( SENSE, 'B' )
228 LQUERY = ( LWORK.EQ.-1 .OR. LIWORK.EQ.-1 )
229 *
230 IF( ( .NOT.WANTVS ) .AND. ( .NOT.LSAME( JOBVS, 'N' ) ) ) THEN
231 INFO = -1
232 ELSE IF( ( .NOT.WANTST ) .AND. ( .NOT.LSAME( SORT, 'N' ) ) ) THEN
233 INFO = -2
234 ELSE IF( .NOT.( WANTSN .OR. WANTSE .OR. WANTSV .OR. WANTSB ) .OR.
235 $ ( .NOT.WANTST .AND. .NOT.WANTSN ) ) THEN
236 INFO = -4
237 ELSE IF( N.LT.0 ) THEN
238 INFO = -5
239 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
240 INFO = -7
241 ELSE IF( LDVS.LT.1 .OR. ( WANTVS .AND. LDVS.LT.N ) ) THEN
242 INFO = -12
243 END IF
244 *
245 * Compute workspace
246 * (Note: Comments in the code beginning "RWorkspace:" describe the
247 * minimal amount of real workspace needed at that point in the
248 * code, as well as the preferred amount for good performance.
249 * IWorkspace refers to integer workspace.
250 * NB refers to the optimal block size for the immediately
251 * following subroutine, as returned by ILAENV.
252 * HSWORK refers to the workspace preferred by DHSEQR, as
253 * calculated below. HSWORK is computed assuming ILO=1 and IHI=N,
254 * the worst case.
255 * If SENSE = 'E', 'V' or 'B', then the amount of workspace needed
256 * depends on SDIM, which is computed by the routine DTRSEN later
257 * in the code.)
258 *
259 IF( INFO.EQ.0 ) THEN
260 LIWRK = 1
261 IF( N.EQ.0 ) THEN
262 MINWRK = 1
263 LWRK = 1
264 ELSE
265 MAXWRK = 2*N + N*ILAENV( 1, 'DGEHRD', ' ', N, 1, N, 0 )
266 MINWRK = 3*N
267 *
268 CALL DHSEQR( 'S', JOBVS, N, 1, N, A, LDA, WR, WI, VS, LDVS,
269 $ WORK, -1, IEVAL )
270 HSWORK = WORK( 1 )
271 *
272 IF( .NOT.WANTVS ) THEN
273 MAXWRK = MAX( MAXWRK, N + HSWORK )
274 ELSE
275 MAXWRK = MAX( MAXWRK, 2*N + ( N - 1 )*ILAENV( 1,
276 $ 'DORGHR', ' ', N, 1, N, -1 ) )
277 MAXWRK = MAX( MAXWRK, N + HSWORK )
278 END IF
279 LWRK = MAXWRK
280 IF( .NOT.WANTSN )
281 $ LWRK = MAX( LWRK, N + ( N*N )/2 )
282 IF( WANTSV .OR. WANTSB )
283 $ LIWRK = ( N*N )/4
284 END IF
285 IWORK( 1 ) = LIWRK
286 WORK( 1 ) = LWRK
287 *
288 IF( LWORK.LT.MINWRK .AND. .NOT.LQUERY ) THEN
289 INFO = -16
290 ELSE IF( LIWORK.LT.1 .AND. .NOT.LQUERY ) THEN
291 INFO = -18
292 END IF
293 END IF
294 *
295 IF( INFO.NE.0 ) THEN
296 CALL XERBLA( 'DGEESX', -INFO )
297 RETURN
298 ELSE IF( LQUERY ) THEN
299 RETURN
300 END IF
301 *
302 * Quick return if possible
303 *
304 IF( N.EQ.0 ) THEN
305 SDIM = 0
306 RETURN
307 END IF
308 *
309 * Get machine constants
310 *
311 EPS = DLAMCH( 'P' )
312 SMLNUM = DLAMCH( 'S' )
313 BIGNUM = ONE / SMLNUM
314 CALL DLABAD( SMLNUM, BIGNUM )
315 SMLNUM = SQRT( SMLNUM ) / EPS
316 BIGNUM = ONE / SMLNUM
317 *
318 * Scale A if max element outside range [SMLNUM,BIGNUM]
319 *
320 ANRM = DLANGE( 'M', N, N, A, LDA, DUM )
321 SCALEA = .FALSE.
322 IF( ANRM.GT.ZERO .AND. ANRM.LT.SMLNUM ) THEN
323 SCALEA = .TRUE.
324 CSCALE = SMLNUM
325 ELSE IF( ANRM.GT.BIGNUM ) THEN
326 SCALEA = .TRUE.
327 CSCALE = BIGNUM
328 END IF
329 IF( SCALEA )
330 $ CALL DLASCL( 'G', 0, 0, ANRM, CSCALE, N, N, A, LDA, IERR )
331 *
332 * Permute the matrix to make it more nearly triangular
333 * (RWorkspace: need N)
334 *
335 IBAL = 1
336 CALL DGEBAL( 'P', N, A, LDA, ILO, IHI, WORK( IBAL ), IERR )
337 *
338 * Reduce to upper Hessenberg form
339 * (RWorkspace: need 3*N, prefer 2*N+N*NB)
340 *
341 ITAU = N + IBAL
342 IWRK = N + ITAU
343 CALL DGEHRD( N, ILO, IHI, A, LDA, WORK( ITAU ), WORK( IWRK ),
344 $ LWORK-IWRK+1, IERR )
345 *
346 IF( WANTVS ) THEN
347 *
348 * Copy Householder vectors to VS
349 *
350 CALL DLACPY( 'L', N, N, A, LDA, VS, LDVS )
351 *
352 * Generate orthogonal matrix in VS
353 * (RWorkspace: need 3*N-1, prefer 2*N+(N-1)*NB)
354 *
355 CALL DORGHR( N, ILO, IHI, VS, LDVS, WORK( ITAU ), WORK( IWRK ),
356 $ LWORK-IWRK+1, IERR )
357 END IF
358 *
359 SDIM = 0
360 *
361 * Perform QR iteration, accumulating Schur vectors in VS if desired
362 * (RWorkspace: need N+1, prefer N+HSWORK (see comments) )
363 *
364 IWRK = ITAU
365 CALL DHSEQR( 'S', JOBVS, N, ILO, IHI, A, LDA, WR, WI, VS, LDVS,
366 $ WORK( IWRK ), LWORK-IWRK+1, IEVAL )
367 IF( IEVAL.GT.0 )
368 $ INFO = IEVAL
369 *
370 * Sort eigenvalues if desired
371 *
372 IF( WANTST .AND. INFO.EQ.0 ) THEN
373 IF( SCALEA ) THEN
374 CALL DLASCL( 'G', 0, 0, CSCALE, ANRM, N, 1, WR, N, IERR )
375 CALL DLASCL( 'G', 0, 0, CSCALE, ANRM, N, 1, WI, N, IERR )
376 END IF
377 DO 10 I = 1, N
378 BWORK( I ) = SELECT( WR( I ), WI( I ) )
379 10 CONTINUE
380 *
381 * Reorder eigenvalues, transform Schur vectors, and compute
382 * reciprocal condition numbers
383 * (RWorkspace: if SENSE is not 'N', need N+2*SDIM*(N-SDIM)
384 * otherwise, need N )
385 * (IWorkspace: if SENSE is 'V' or 'B', need SDIM*(N-SDIM)
386 * otherwise, need 0 )
387 *
388 CALL DTRSEN( SENSE, JOBVS, BWORK, N, A, LDA, VS, LDVS, WR, WI,
389 $ SDIM, RCONDE, RCONDV, WORK( IWRK ), LWORK-IWRK+1,
390 $ IWORK, LIWORK, ICOND )
391 IF( .NOT.WANTSN )
392 $ MAXWRK = MAX( MAXWRK, N+2*SDIM*( N-SDIM ) )
393 IF( ICOND.EQ.-15 ) THEN
394 *
395 * Not enough real workspace
396 *
397 INFO = -16
398 ELSE IF( ICOND.EQ.-17 ) THEN
399 *
400 * Not enough integer workspace
401 *
402 INFO = -18
403 ELSE IF( ICOND.GT.0 ) THEN
404 *
405 * DTRSEN failed to reorder or to restore standard Schur form
406 *
407 INFO = ICOND + N
408 END IF
409 END IF
410 *
411 IF( WANTVS ) THEN
412 *
413 * Undo balancing
414 * (RWorkspace: need N)
415 *
416 CALL DGEBAK( 'P', 'R', N, ILO, IHI, WORK( IBAL ), N, VS, LDVS,
417 $ IERR )
418 END IF
419 *
420 IF( SCALEA ) THEN
421 *
422 * Undo scaling for the Schur form of A
423 *
424 CALL DLASCL( 'H', 0, 0, CSCALE, ANRM, N, N, A, LDA, IERR )
425 CALL DCOPY( N, A, LDA+1, WR, 1 )
426 IF( ( WANTSV .OR. WANTSB ) .AND. INFO.EQ.0 ) THEN
427 DUM( 1 ) = RCONDV
428 CALL DLASCL( 'G', 0, 0, CSCALE, ANRM, 1, 1, DUM, 1, IERR )
429 RCONDV = DUM( 1 )
430 END IF
431 IF( CSCALE.EQ.SMLNUM ) THEN
432 *
433 * If scaling back towards underflow, adjust WI if an
434 * offdiagonal element of a 2-by-2 block in the Schur form
435 * underflows.
436 *
437 IF( IEVAL.GT.0 ) THEN
438 I1 = IEVAL + 1
439 I2 = IHI - 1
440 CALL DLASCL( 'G', 0, 0, CSCALE, ANRM, ILO-1, 1, WI, N,
441 $ IERR )
442 ELSE IF( WANTST ) THEN
443 I1 = 1
444 I2 = N - 1
445 ELSE
446 I1 = ILO
447 I2 = IHI - 1
448 END IF
449 INXT = I1 - 1
450 DO 20 I = I1, I2
451 IF( I.LT.INXT )
452 $ GO TO 20
453 IF( WI( I ).EQ.ZERO ) THEN
454 INXT = I + 1
455 ELSE
456 IF( A( I+1, I ).EQ.ZERO ) THEN
457 WI( I ) = ZERO
458 WI( I+1 ) = ZERO
459 ELSE IF( A( I+1, I ).NE.ZERO .AND. A( I, I+1 ).EQ.
460 $ ZERO ) THEN
461 WI( I ) = ZERO
462 WI( I+1 ) = ZERO
463 IF( I.GT.1 )
464 $ CALL DSWAP( I-1, A( 1, I ), 1, A( 1, I+1 ), 1 )
465 IF( N.GT.I+1 )
466 $ CALL DSWAP( N-I-1, A( I, I+2 ), LDA,
467 $ A( I+1, I+2 ), LDA )
468 CALL DSWAP( N, VS( 1, I ), 1, VS( 1, I+1 ), 1 )
469 A( I, I+1 ) = A( I+1, I )
470 A( I+1, I ) = ZERO
471 END IF
472 INXT = I + 2
473 END IF
474 20 CONTINUE
475 END IF
476 CALL DLASCL( 'G', 0, 0, CSCALE, ANRM, N-IEVAL, 1,
477 $ WI( IEVAL+1 ), MAX( N-IEVAL, 1 ), IERR )
478 END IF
479 *
480 IF( WANTST .AND. INFO.EQ.0 ) THEN
481 *
482 * Check if reordering successful
483 *
484 LASTSL = .TRUE.
485 LST2SL = .TRUE.
486 SDIM = 0
487 IP = 0
488 DO 30 I = 1, N
489 CURSL = SELECT( WR( I ), WI( I ) )
490 IF( WI( I ).EQ.ZERO ) THEN
491 IF( CURSL )
492 $ SDIM = SDIM + 1
493 IP = 0
494 IF( CURSL .AND. .NOT.LASTSL )
495 $ INFO = N + 2
496 ELSE
497 IF( IP.EQ.1 ) THEN
498 *
499 * Last eigenvalue of conjugate pair
500 *
501 CURSL = CURSL .OR. LASTSL
502 LASTSL = CURSL
503 IF( CURSL )
504 $ SDIM = SDIM + 2
505 IP = -1
506 IF( CURSL .AND. .NOT.LST2SL )
507 $ INFO = N + 2
508 ELSE
509 *
510 * First eigenvalue of conjugate pair
511 *
512 IP = 1
513 END IF
514 END IF
515 LST2SL = LASTSL
516 LASTSL = CURSL
517 30 CONTINUE
518 END IF
519 *
520 WORK( 1 ) = MAXWRK
521 IF( WANTSV .OR. WANTSB ) THEN
522 IWORK( 1 ) = MAX( 1, SDIM*( N-SDIM ) )
523 ELSE
524 IWORK( 1 ) = 1
525 END IF
526 *
527 RETURN
528 *
529 * End of DGEESX
530 *
531 END
2 $ WR, WI, VS, LDVS, RCONDE, RCONDV, WORK, LWORK,
3 $ IWORK, LIWORK, BWORK, INFO )
4 *
5 * -- LAPACK driver routine (version 3.2.2) --
6 * -- LAPACK is a software package provided by Univ. of Tennessee, --
7 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
8 * June 2010
9 *
10 * .. Scalar Arguments ..
11 CHARACTER JOBVS, SENSE, SORT
12 INTEGER INFO, LDA, LDVS, LIWORK, LWORK, N, SDIM
13 DOUBLE PRECISION RCONDE, RCONDV
14 * ..
15 * .. Array Arguments ..
16 LOGICAL BWORK( * )
17 INTEGER IWORK( * )
18 DOUBLE PRECISION A( LDA, * ), VS( LDVS, * ), WI( * ), WORK( * ),
19 $ WR( * )
20 * ..
21 * .. Function Arguments ..
22 LOGICAL SELECT
23 EXTERNAL SELECT
24 * ..
25 *
26 * Purpose
27 * =======
28 *
29 * DGEESX computes for an N-by-N real nonsymmetric matrix A, the
30 * eigenvalues, the real Schur form T, and, optionally, the matrix of
31 * Schur vectors Z. This gives the Schur factorization A = Z*T*(Z**T).
32 *
33 * Optionally, it also orders the eigenvalues on the diagonal of the
34 * real Schur form so that selected eigenvalues are at the top left;
35 * computes a reciprocal condition number for the average of the
36 * selected eigenvalues (RCONDE); and computes a reciprocal condition
37 * number for the right invariant subspace corresponding to the
38 * selected eigenvalues (RCONDV). The leading columns of Z form an
39 * orthonormal basis for this invariant subspace.
40 *
41 * For further explanation of the reciprocal condition numbers RCONDE
42 * and RCONDV, see Section 4.10 of the LAPACK Users' Guide (where
43 * these quantities are called s and sep respectively).
44 *
45 * A real matrix is in real Schur form if it is upper quasi-triangular
46 * with 1-by-1 and 2-by-2 blocks. 2-by-2 blocks will be standardized in
47 * the form
48 * [ a b ]
49 * [ c a ]
50 *
51 * where b*c < 0. The eigenvalues of such a block are a +- sqrt(bc).
52 *
53 * Arguments
54 * =========
55 *
56 * JOBVS (input) CHARACTER*1
57 * = 'N': Schur vectors are not computed;
58 * = 'V': Schur vectors are computed.
59 *
60 * SORT (input) CHARACTER*1
61 * Specifies whether or not to order the eigenvalues on the
62 * diagonal of the Schur form.
63 * = 'N': Eigenvalues are not ordered;
64 * = 'S': Eigenvalues are ordered (see SELECT).
65 *
66 * SELECT (external procedure) LOGICAL FUNCTION of two DOUBLE PRECISION arguments
67 * SELECT must be declared EXTERNAL in the calling subroutine.
68 * If SORT = 'S', SELECT is used to select eigenvalues to sort
69 * to the top left of the Schur form.
70 * If SORT = 'N', SELECT is not referenced.
71 * An eigenvalue WR(j)+sqrt(-1)*WI(j) is selected if
72 * SELECT(WR(j),WI(j)) is true; i.e., if either one of a
73 * complex conjugate pair of eigenvalues is selected, then both
74 * are. Note that a selected complex eigenvalue may no longer
75 * satisfy SELECT(WR(j),WI(j)) = .TRUE. after ordering, since
76 * ordering may change the value of complex eigenvalues
77 * (especially if the eigenvalue is ill-conditioned); in this
78 * case INFO may be set to N+3 (see INFO below).
79 *
80 * SENSE (input) CHARACTER*1
81 * Determines which reciprocal condition numbers are computed.
82 * = 'N': None are computed;
83 * = 'E': Computed for average of selected eigenvalues only;
84 * = 'V': Computed for selected right invariant subspace only;
85 * = 'B': Computed for both.
86 * If SENSE = 'E', 'V' or 'B', SORT must equal 'S'.
87 *
88 * N (input) INTEGER
89 * The order of the matrix A. N >= 0.
90 *
91 * A (input/output) DOUBLE PRECISION array, dimension (LDA, N)
92 * On entry, the N-by-N matrix A.
93 * On exit, A is overwritten by its real Schur form T.
94 *
95 * LDA (input) INTEGER
96 * The leading dimension of the array A. LDA >= max(1,N).
97 *
98 * SDIM (output) INTEGER
99 * If SORT = 'N', SDIM = 0.
100 * If SORT = 'S', SDIM = number of eigenvalues (after sorting)
101 * for which SELECT is true. (Complex conjugate
102 * pairs for which SELECT is true for either
103 * eigenvalue count as 2.)
104 *
105 * WR (output) DOUBLE PRECISION array, dimension (N)
106 * WI (output) DOUBLE PRECISION array, dimension (N)
107 * WR and WI contain the real and imaginary parts, respectively,
108 * of the computed eigenvalues, in the same order that they
109 * appear on the diagonal of the output Schur form T. Complex
110 * conjugate pairs of eigenvalues appear consecutively with the
111 * eigenvalue having the positive imaginary part first.
112 *
113 * VS (output) DOUBLE PRECISION array, dimension (LDVS,N)
114 * If JOBVS = 'V', VS contains the orthogonal matrix Z of Schur
115 * vectors.
116 * If JOBVS = 'N', VS is not referenced.
117 *
118 * LDVS (input) INTEGER
119 * The leading dimension of the array VS. LDVS >= 1, and if
120 * JOBVS = 'V', LDVS >= N.
121 *
122 * RCONDE (output) DOUBLE PRECISION
123 * If SENSE = 'E' or 'B', RCONDE contains the reciprocal
124 * condition number for the average of the selected eigenvalues.
125 * Not referenced if SENSE = 'N' or 'V'.
126 *
127 * RCONDV (output) DOUBLE PRECISION
128 * If SENSE = 'V' or 'B', RCONDV contains the reciprocal
129 * condition number for the selected right invariant subspace.
130 * Not referenced if SENSE = 'N' or 'E'.
131 *
132 * WORK (workspace/output) DOUBLE PRECISION array, dimension (MAX(1,LWORK))
133 * On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
134 *
135 * LWORK (input) INTEGER
136 * The dimension of the array WORK. LWORK >= max(1,3*N).
137 * Also, if SENSE = 'E' or 'V' or 'B',
138 * LWORK >= N+2*SDIM*(N-SDIM), where SDIM is the number of
139 * selected eigenvalues computed by this routine. Note that
140 * N+2*SDIM*(N-SDIM) <= N+N*N/2. Note also that an error is only
141 * returned if LWORK < max(1,3*N), but if SENSE = 'E' or 'V' or
142 * 'B' this may not be large enough.
143 * For good performance, LWORK must generally be larger.
144 *
145 * If LWORK = -1, then a workspace query is assumed; the routine
146 * only calculates upper bounds on the optimal sizes of the
147 * arrays WORK and IWORK, returns these values as the first
148 * entries of the WORK and IWORK arrays, and no error messages
149 * related to LWORK or LIWORK are issued by XERBLA.
150 *
151 * IWORK (workspace/output) INTEGER array, dimension (MAX(1,LIWORK))
152 * On exit, if INFO = 0, IWORK(1) returns the optimal LIWORK.
153 *
154 * LIWORK (input) INTEGER
155 * The dimension of the array IWORK.
156 * LIWORK >= 1; if SENSE = 'V' or 'B', LIWORK >= SDIM*(N-SDIM).
157 * Note that SDIM*(N-SDIM) <= N*N/4. Note also that an error is
158 * only returned if LIWORK < 1, but if SENSE = 'V' or 'B' this
159 * may not be large enough.
160 *
161 * If LIWORK = -1, then a workspace query is assumed; the
162 * routine only calculates upper bounds on the optimal sizes of
163 * the arrays WORK and IWORK, returns these values as the first
164 * entries of the WORK and IWORK arrays, and no error messages
165 * related to LWORK or LIWORK are issued by XERBLA.
166 *
167 * BWORK (workspace) LOGICAL array, dimension (N)
168 * Not referenced if SORT = 'N'.
169 *
170 * INFO (output) INTEGER
171 * = 0: successful exit
172 * < 0: if INFO = -i, the i-th argument had an illegal value.
173 * > 0: if INFO = i, and i is
174 * <= N: the QR algorithm failed to compute all the
175 * eigenvalues; elements 1:ILO-1 and i+1:N of WR and WI
176 * contain those eigenvalues which have converged; if
177 * JOBVS = 'V', VS contains the transformation which
178 * reduces A to its partially converged Schur form.
179 * = N+1: the eigenvalues could not be reordered because some
180 * eigenvalues were too close to separate (the problem
181 * is very ill-conditioned);
182 * = N+2: after reordering, roundoff changed values of some
183 * complex eigenvalues so that leading eigenvalues in
184 * the Schur form no longer satisfy SELECT=.TRUE. This
185 * could also be caused by underflow due to scaling.
186 *
187 * =====================================================================
188 *
189 * .. Parameters ..
190 DOUBLE PRECISION ZERO, ONE
191 PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0 )
192 * ..
193 * .. Local Scalars ..
194 LOGICAL CURSL, LASTSL, LQUERY, LST2SL, SCALEA, WANTSB,
195 $ WANTSE, WANTSN, WANTST, WANTSV, WANTVS
196 INTEGER HSWORK, I, I1, I2, IBAL, ICOND, IERR, IEVAL,
197 $ IHI, ILO, INXT, IP, ITAU, IWRK, LIWRK, LWRK,
198 $ MAXWRK, MINWRK
199 DOUBLE PRECISION ANRM, BIGNUM, CSCALE, EPS, SMLNUM
200 * ..
201 * .. Local Arrays ..
202 DOUBLE PRECISION DUM( 1 )
203 * ..
204 * .. External Subroutines ..
205 EXTERNAL DCOPY, DGEBAK, DGEBAL, DGEHRD, DHSEQR, DLACPY,
206 $ DLASCL, DORGHR, DSWAP, DTRSEN, XERBLA
207 * ..
208 * .. External Functions ..
209 LOGICAL LSAME
210 INTEGER ILAENV
211 DOUBLE PRECISION DLAMCH, DLANGE
212 EXTERNAL LSAME, ILAENV, DLABAD, DLAMCH, DLANGE
213 * ..
214 * .. Intrinsic Functions ..
215 INTRINSIC MAX, SQRT
216 * ..
217 * .. Executable Statements ..
218 *
219 * Test the input arguments
220 *
221 INFO = 0
222 WANTVS = LSAME( JOBVS, 'V' )
223 WANTST = LSAME( SORT, 'S' )
224 WANTSN = LSAME( SENSE, 'N' )
225 WANTSE = LSAME( SENSE, 'E' )
226 WANTSV = LSAME( SENSE, 'V' )
227 WANTSB = LSAME( SENSE, 'B' )
228 LQUERY = ( LWORK.EQ.-1 .OR. LIWORK.EQ.-1 )
229 *
230 IF( ( .NOT.WANTVS ) .AND. ( .NOT.LSAME( JOBVS, 'N' ) ) ) THEN
231 INFO = -1
232 ELSE IF( ( .NOT.WANTST ) .AND. ( .NOT.LSAME( SORT, 'N' ) ) ) THEN
233 INFO = -2
234 ELSE IF( .NOT.( WANTSN .OR. WANTSE .OR. WANTSV .OR. WANTSB ) .OR.
235 $ ( .NOT.WANTST .AND. .NOT.WANTSN ) ) THEN
236 INFO = -4
237 ELSE IF( N.LT.0 ) THEN
238 INFO = -5
239 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
240 INFO = -7
241 ELSE IF( LDVS.LT.1 .OR. ( WANTVS .AND. LDVS.LT.N ) ) THEN
242 INFO = -12
243 END IF
244 *
245 * Compute workspace
246 * (Note: Comments in the code beginning "RWorkspace:" describe the
247 * minimal amount of real workspace needed at that point in the
248 * code, as well as the preferred amount for good performance.
249 * IWorkspace refers to integer workspace.
250 * NB refers to the optimal block size for the immediately
251 * following subroutine, as returned by ILAENV.
252 * HSWORK refers to the workspace preferred by DHSEQR, as
253 * calculated below. HSWORK is computed assuming ILO=1 and IHI=N,
254 * the worst case.
255 * If SENSE = 'E', 'V' or 'B', then the amount of workspace needed
256 * depends on SDIM, which is computed by the routine DTRSEN later
257 * in the code.)
258 *
259 IF( INFO.EQ.0 ) THEN
260 LIWRK = 1
261 IF( N.EQ.0 ) THEN
262 MINWRK = 1
263 LWRK = 1
264 ELSE
265 MAXWRK = 2*N + N*ILAENV( 1, 'DGEHRD', ' ', N, 1, N, 0 )
266 MINWRK = 3*N
267 *
268 CALL DHSEQR( 'S', JOBVS, N, 1, N, A, LDA, WR, WI, VS, LDVS,
269 $ WORK, -1, IEVAL )
270 HSWORK = WORK( 1 )
271 *
272 IF( .NOT.WANTVS ) THEN
273 MAXWRK = MAX( MAXWRK, N + HSWORK )
274 ELSE
275 MAXWRK = MAX( MAXWRK, 2*N + ( N - 1 )*ILAENV( 1,
276 $ 'DORGHR', ' ', N, 1, N, -1 ) )
277 MAXWRK = MAX( MAXWRK, N + HSWORK )
278 END IF
279 LWRK = MAXWRK
280 IF( .NOT.WANTSN )
281 $ LWRK = MAX( LWRK, N + ( N*N )/2 )
282 IF( WANTSV .OR. WANTSB )
283 $ LIWRK = ( N*N )/4
284 END IF
285 IWORK( 1 ) = LIWRK
286 WORK( 1 ) = LWRK
287 *
288 IF( LWORK.LT.MINWRK .AND. .NOT.LQUERY ) THEN
289 INFO = -16
290 ELSE IF( LIWORK.LT.1 .AND. .NOT.LQUERY ) THEN
291 INFO = -18
292 END IF
293 END IF
294 *
295 IF( INFO.NE.0 ) THEN
296 CALL XERBLA( 'DGEESX', -INFO )
297 RETURN
298 ELSE IF( LQUERY ) THEN
299 RETURN
300 END IF
301 *
302 * Quick return if possible
303 *
304 IF( N.EQ.0 ) THEN
305 SDIM = 0
306 RETURN
307 END IF
308 *
309 * Get machine constants
310 *
311 EPS = DLAMCH( 'P' )
312 SMLNUM = DLAMCH( 'S' )
313 BIGNUM = ONE / SMLNUM
314 CALL DLABAD( SMLNUM, BIGNUM )
315 SMLNUM = SQRT( SMLNUM ) / EPS
316 BIGNUM = ONE / SMLNUM
317 *
318 * Scale A if max element outside range [SMLNUM,BIGNUM]
319 *
320 ANRM = DLANGE( 'M', N, N, A, LDA, DUM )
321 SCALEA = .FALSE.
322 IF( ANRM.GT.ZERO .AND. ANRM.LT.SMLNUM ) THEN
323 SCALEA = .TRUE.
324 CSCALE = SMLNUM
325 ELSE IF( ANRM.GT.BIGNUM ) THEN
326 SCALEA = .TRUE.
327 CSCALE = BIGNUM
328 END IF
329 IF( SCALEA )
330 $ CALL DLASCL( 'G', 0, 0, ANRM, CSCALE, N, N, A, LDA, IERR )
331 *
332 * Permute the matrix to make it more nearly triangular
333 * (RWorkspace: need N)
334 *
335 IBAL = 1
336 CALL DGEBAL( 'P', N, A, LDA, ILO, IHI, WORK( IBAL ), IERR )
337 *
338 * Reduce to upper Hessenberg form
339 * (RWorkspace: need 3*N, prefer 2*N+N*NB)
340 *
341 ITAU = N + IBAL
342 IWRK = N + ITAU
343 CALL DGEHRD( N, ILO, IHI, A, LDA, WORK( ITAU ), WORK( IWRK ),
344 $ LWORK-IWRK+1, IERR )
345 *
346 IF( WANTVS ) THEN
347 *
348 * Copy Householder vectors to VS
349 *
350 CALL DLACPY( 'L', N, N, A, LDA, VS, LDVS )
351 *
352 * Generate orthogonal matrix in VS
353 * (RWorkspace: need 3*N-1, prefer 2*N+(N-1)*NB)
354 *
355 CALL DORGHR( N, ILO, IHI, VS, LDVS, WORK( ITAU ), WORK( IWRK ),
356 $ LWORK-IWRK+1, IERR )
357 END IF
358 *
359 SDIM = 0
360 *
361 * Perform QR iteration, accumulating Schur vectors in VS if desired
362 * (RWorkspace: need N+1, prefer N+HSWORK (see comments) )
363 *
364 IWRK = ITAU
365 CALL DHSEQR( 'S', JOBVS, N, ILO, IHI, A, LDA, WR, WI, VS, LDVS,
366 $ WORK( IWRK ), LWORK-IWRK+1, IEVAL )
367 IF( IEVAL.GT.0 )
368 $ INFO = IEVAL
369 *
370 * Sort eigenvalues if desired
371 *
372 IF( WANTST .AND. INFO.EQ.0 ) THEN
373 IF( SCALEA ) THEN
374 CALL DLASCL( 'G', 0, 0, CSCALE, ANRM, N, 1, WR, N, IERR )
375 CALL DLASCL( 'G', 0, 0, CSCALE, ANRM, N, 1, WI, N, IERR )
376 END IF
377 DO 10 I = 1, N
378 BWORK( I ) = SELECT( WR( I ), WI( I ) )
379 10 CONTINUE
380 *
381 * Reorder eigenvalues, transform Schur vectors, and compute
382 * reciprocal condition numbers
383 * (RWorkspace: if SENSE is not 'N', need N+2*SDIM*(N-SDIM)
384 * otherwise, need N )
385 * (IWorkspace: if SENSE is 'V' or 'B', need SDIM*(N-SDIM)
386 * otherwise, need 0 )
387 *
388 CALL DTRSEN( SENSE, JOBVS, BWORK, N, A, LDA, VS, LDVS, WR, WI,
389 $ SDIM, RCONDE, RCONDV, WORK( IWRK ), LWORK-IWRK+1,
390 $ IWORK, LIWORK, ICOND )
391 IF( .NOT.WANTSN )
392 $ MAXWRK = MAX( MAXWRK, N+2*SDIM*( N-SDIM ) )
393 IF( ICOND.EQ.-15 ) THEN
394 *
395 * Not enough real workspace
396 *
397 INFO = -16
398 ELSE IF( ICOND.EQ.-17 ) THEN
399 *
400 * Not enough integer workspace
401 *
402 INFO = -18
403 ELSE IF( ICOND.GT.0 ) THEN
404 *
405 * DTRSEN failed to reorder or to restore standard Schur form
406 *
407 INFO = ICOND + N
408 END IF
409 END IF
410 *
411 IF( WANTVS ) THEN
412 *
413 * Undo balancing
414 * (RWorkspace: need N)
415 *
416 CALL DGEBAK( 'P', 'R', N, ILO, IHI, WORK( IBAL ), N, VS, LDVS,
417 $ IERR )
418 END IF
419 *
420 IF( SCALEA ) THEN
421 *
422 * Undo scaling for the Schur form of A
423 *
424 CALL DLASCL( 'H', 0, 0, CSCALE, ANRM, N, N, A, LDA, IERR )
425 CALL DCOPY( N, A, LDA+1, WR, 1 )
426 IF( ( WANTSV .OR. WANTSB ) .AND. INFO.EQ.0 ) THEN
427 DUM( 1 ) = RCONDV
428 CALL DLASCL( 'G', 0, 0, CSCALE, ANRM, 1, 1, DUM, 1, IERR )
429 RCONDV = DUM( 1 )
430 END IF
431 IF( CSCALE.EQ.SMLNUM ) THEN
432 *
433 * If scaling back towards underflow, adjust WI if an
434 * offdiagonal element of a 2-by-2 block in the Schur form
435 * underflows.
436 *
437 IF( IEVAL.GT.0 ) THEN
438 I1 = IEVAL + 1
439 I2 = IHI - 1
440 CALL DLASCL( 'G', 0, 0, CSCALE, ANRM, ILO-1, 1, WI, N,
441 $ IERR )
442 ELSE IF( WANTST ) THEN
443 I1 = 1
444 I2 = N - 1
445 ELSE
446 I1 = ILO
447 I2 = IHI - 1
448 END IF
449 INXT = I1 - 1
450 DO 20 I = I1, I2
451 IF( I.LT.INXT )
452 $ GO TO 20
453 IF( WI( I ).EQ.ZERO ) THEN
454 INXT = I + 1
455 ELSE
456 IF( A( I+1, I ).EQ.ZERO ) THEN
457 WI( I ) = ZERO
458 WI( I+1 ) = ZERO
459 ELSE IF( A( I+1, I ).NE.ZERO .AND. A( I, I+1 ).EQ.
460 $ ZERO ) THEN
461 WI( I ) = ZERO
462 WI( I+1 ) = ZERO
463 IF( I.GT.1 )
464 $ CALL DSWAP( I-1, A( 1, I ), 1, A( 1, I+1 ), 1 )
465 IF( N.GT.I+1 )
466 $ CALL DSWAP( N-I-1, A( I, I+2 ), LDA,
467 $ A( I+1, I+2 ), LDA )
468 CALL DSWAP( N, VS( 1, I ), 1, VS( 1, I+1 ), 1 )
469 A( I, I+1 ) = A( I+1, I )
470 A( I+1, I ) = ZERO
471 END IF
472 INXT = I + 2
473 END IF
474 20 CONTINUE
475 END IF
476 CALL DLASCL( 'G', 0, 0, CSCALE, ANRM, N-IEVAL, 1,
477 $ WI( IEVAL+1 ), MAX( N-IEVAL, 1 ), IERR )
478 END IF
479 *
480 IF( WANTST .AND. INFO.EQ.0 ) THEN
481 *
482 * Check if reordering successful
483 *
484 LASTSL = .TRUE.
485 LST2SL = .TRUE.
486 SDIM = 0
487 IP = 0
488 DO 30 I = 1, N
489 CURSL = SELECT( WR( I ), WI( I ) )
490 IF( WI( I ).EQ.ZERO ) THEN
491 IF( CURSL )
492 $ SDIM = SDIM + 1
493 IP = 0
494 IF( CURSL .AND. .NOT.LASTSL )
495 $ INFO = N + 2
496 ELSE
497 IF( IP.EQ.1 ) THEN
498 *
499 * Last eigenvalue of conjugate pair
500 *
501 CURSL = CURSL .OR. LASTSL
502 LASTSL = CURSL
503 IF( CURSL )
504 $ SDIM = SDIM + 2
505 IP = -1
506 IF( CURSL .AND. .NOT.LST2SL )
507 $ INFO = N + 2
508 ELSE
509 *
510 * First eigenvalue of conjugate pair
511 *
512 IP = 1
513 END IF
514 END IF
515 LST2SL = LASTSL
516 LASTSL = CURSL
517 30 CONTINUE
518 END IF
519 *
520 WORK( 1 ) = MAXWRK
521 IF( WANTSV .OR. WANTSB ) THEN
522 IWORK( 1 ) = MAX( 1, SDIM*( N-SDIM ) )
523 ELSE
524 IWORK( 1 ) = 1
525 END IF
526 *
527 RETURN
528 *
529 * End of DGEESX
530 *
531 END