1ZGEESX(1) LAPACK driver routine (version 3.1) ZGEESX(1)
2
3
4
6 ZGEESX - for an N-by-N complex nonsymmetric matrix A, the eigenvalues,
7 the Schur form T, and, optionally, the matrix of Schur vectors Z
8
10 SUBROUTINE ZGEESX( JOBVS, SORT, SELECT, SENSE, N, A, LDA, SDIM, W, VS,
11 LDVS, RCONDE, RCONDV, WORK, LWORK, RWORK, BWORK,
12 INFO )
13
14 CHARACTER JOBVS, SENSE, SORT
15
16 INTEGER INFO, LDA, LDVS, LWORK, N, SDIM
17
18 DOUBLE PRECISION RCONDE, RCONDV
19
20 LOGICAL BWORK( * )
21
22 DOUBLE PRECISION RWORK( * )
23
24 COMPLEX*16 A( LDA, * ), VS( LDVS, * ), W( * ), WORK( * )
25
26 LOGICAL SELECT
27
28 EXTERNAL SELECT
29
31 ZGEESX computes for an N-by-N complex nonsymmetric matrix A, the eigen‐
32 values, the Schur form T, and, optionally, the matrix of Schur vectors
33 Z. This gives the Schur factorization A = Z*T*(Z**H).
34
35 Optionally, it also orders the eigenvalues on the diagonal of the Schur
36 form so that selected eigenvalues are at the top left; computes a
37 reciprocal condition number for the average of the selected eigenvalues
38 (RCONDE); and computes a reciprocal condition number for the right
39 invariant subspace corresponding to the selected eigenvalues (RCONDV).
40 The leading columns of Z form an orthonormal basis for this invariant
41 subspace.
42
43 For further explanation of the reciprocal condition numbers RCONDE and
44 RCONDV, see Section 4.10 of the LAPACK Users' Guide (where these quan‐
45 tities are called s and sep respectively).
46
47 A complex matrix is in Schur form if it is upper triangular.
48
49
51 JOBVS (input) CHARACTER*1
52 = 'N': Schur vectors are not computed;
53 = 'V': Schur vectors are computed.
54
55 SORT (input) CHARACTER*1
56 Specifies whether or not to order the eigenvalues on the diago‐
57 nal of the Schur form. = 'N': Eigenvalues are not ordered;
58 = 'S': Eigenvalues are ordered (see SELECT).
59
60 SELECT (external procedure) LOGICAL FUNCTION of one COMPLEX*16 argu‐
61 ment
62 SELECT must be declared EXTERNAL in the calling subroutine. If
63 SORT = 'S', SELECT is used to select eigenvalues to order to
64 the top left of the Schur form. If SORT = 'N', SELECT is not
65 referenced. An eigenvalue W(j) is selected if SELECT(W(j)) is
66 true.
67
68 SENSE (input) CHARACTER*1
69 Determines which reciprocal condition numbers are computed. =
70 'N': None are computed;
71 = 'E': Computed for average of selected eigenvalues only;
72 = 'V': Computed for selected right invariant subspace only;
73 = 'B': Computed for both. If SENSE = 'E', 'V' or 'B', SORT
74 must equal 'S'.
75
76 N (input) INTEGER
77 The order of the matrix A. N >= 0.
78
79 A (input/output) COMPLEX*16 array, dimension (LDA, N)
80 On entry, the N-by-N matrix A. On exit, A is overwritten by
81 its Schur form T.
82
83 LDA (input) INTEGER
84 The leading dimension of the array A. LDA >= max(1,N).
85
86 SDIM (output) INTEGER
87 If SORT = 'N', SDIM = 0. If SORT = 'S', SDIM = number of ei‐
88 genvalues for which SELECT is true.
89
90 W (output) COMPLEX*16 array, dimension (N)
91 W contains the computed eigenvalues, in the same order that
92 they appear on the diagonal of the output Schur form T.
93
94 VS (output) COMPLEX*16 array, dimension (LDVS,N)
95 If JOBVS = 'V', VS contains the unitary matrix Z of Schur vec‐
96 tors. If JOBVS = 'N', VS is not referenced.
97
98 LDVS (input) INTEGER
99 The leading dimension of the array VS. LDVS >= 1, and if JOBVS
100 = 'V', LDVS >= N.
101
102 RCONDE (output) DOUBLE PRECISION
103 If SENSE = 'E' or 'B', RCONDE contains the reciprocal condition
104 number for the average of the selected eigenvalues. Not refer‐
105 enced if SENSE = 'N' or 'V'.
106
107 RCONDV (output) DOUBLE PRECISION
108 If SENSE = 'V' or 'B', RCONDV contains the reciprocal condition
109 number for the selected right invariant subspace. Not refer‐
110 enced if SENSE = 'N' or 'E'.
111
112 WORK (workspace/output) COMPLEX*16 array, dimension (MAX(1,LWORK))
113 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
114
115 LWORK (input) INTEGER
116 The dimension of the array WORK. LWORK >= max(1,2*N). Also,
117 if SENSE = 'E' or 'V' or 'B', LWORK >= 2*SDIM*(N-SDIM), where
118 SDIM is the number of selected eigenvalues computed by this
119 routine. Note that 2*SDIM*(N-SDIM) <= N*N/2. Note also that an
120 error is only returned if LWORK < max(1,2*N), but if SENSE =
121 'E' or 'V' or 'B' this may not be large enough. For good per‐
122 formance, LWORK must generally be larger.
123
124 If LWORK = -1, then a workspace query is assumed; the routine
125 only calculates upper bound on the optimal size of the array
126 WORK, returns this value as the first entry of the WORK array,
127 and no error message related to LWORK is issued by XERBLA.
128
129 RWORK (workspace) DOUBLE PRECISION array, dimension (N)
130
131 BWORK (workspace) LOGICAL array, dimension (N)
132 Not referenced if SORT = 'N'.
133
134 INFO (output) INTEGER
135 = 0: successful exit
136 < 0: if INFO = -i, the i-th argument had an illegal value.
137 > 0: if INFO = i, and i is
138 <= N: the QR algorithm failed to compute all the
139 eigenvalues; elements 1:ILO-1 and i+1:N of W contain those ei‐
140 genvalues which have converged; if JOBVS = 'V', VS contains the
141 transformation which reduces A to its partially converged Schur
142 form. = N+1: the eigenvalues could not be reordered because
143 some eigenvalues were too close to separate (the problem is
144 very ill-conditioned); = N+2: after reordering, roundoff
145 changed values of some complex eigenvalues so that leading ei‐
146 genvalues in the Schur form no longer satisfy SELECT=.TRUE.
147 This could also be caused by underflow due to scaling.
148
149
150
151 LAPACK driver routine (version 3.N1o)vember 2006 ZGEESX(1)