1DGEESX(1) LAPACK driver routine (version 3.1) DGEESX(1)
2
3
4
6 DGEESX - for an N-by-N real nonsymmetric matrix A, the eigenvalues, the
7 real Schur form T, and, optionally, the matrix of Schur vectors Z
8
10 SUBROUTINE DGEESX( JOBVS, SORT, SELECT, SENSE, N, A, LDA, SDIM, WR, WI,
11 VS, LDVS, RCONDE, RCONDV, WORK, LWORK, IWORK,
12 LIWORK, BWORK, INFO )
13
14 CHARACTER JOBVS, SENSE, SORT
15
16 INTEGER INFO, LDA, LDVS, LIWORK, LWORK, N, SDIM
17
18 DOUBLE PRECISION RCONDE, RCONDV
19
20 LOGICAL BWORK( * )
21
22 INTEGER IWORK( * )
23
24 DOUBLE PRECISION A( LDA, * ), VS( LDVS, * ), WI( * ), WORK(
25 * ), WR( * )
26
27 LOGICAL SELECT
28
29 EXTERNAL SELECT
30
32 DGEESX computes for an N-by-N real nonsymmetric matrix A, the eigenval‐
33 ues, the real Schur form T, and, optionally, the matrix of Schur vec‐
34 tors Z. This gives the Schur factorization A = Z*T*(Z**T).
35
36 Optionally, it also orders the eigenvalues on the diagonal of the real
37 Schur form so that selected eigenvalues are at the top left; computes a
38 reciprocal condition number for the average of the selected eigenvalues
39 (RCONDE); and computes a reciprocal condition number for the right
40 invariant subspace corresponding to the selected eigenvalues (RCONDV).
41 The leading columns of Z form an orthonormal basis for this invariant
42 subspace.
43
44 For further explanation of the reciprocal condition numbers RCONDE and
45 RCONDV, see Section 4.10 of the LAPACK Users' Guide (where these quan‐
46 tities are called s and sep respectively).
47
48 A real matrix is in real Schur form if it is upper quasi-triangular
49 with 1-by-1 and 2-by-2 blocks. 2-by-2 blocks will be standardized in
50 the form
51 [ a b ]
52 [ c a ]
53
54 where b*c < 0. The eigenvalues of such a block are a +- sqrt(bc).
55
56
58 JOBVS (input) CHARACTER*1
59 = 'N': Schur vectors are not computed;
60 = 'V': Schur vectors are computed.
61
62 SORT (input) CHARACTER*1
63 Specifies whether or not to order the eigenvalues on the diago‐
64 nal of the Schur form. = 'N': Eigenvalues are not ordered;
65 = 'S': Eigenvalues are ordered (see SELECT).
66
67 SELECT (external procedure) LOGICAL FUNCTION of two DOUBLE PRECISION
68 arguments
69 SELECT must be declared EXTERNAL in the calling subroutine. If
70 SORT = 'S', SELECT is used to select eigenvalues to sort to the
71 top left of the Schur form. If SORT = 'N', SELECT is not ref‐
72 erenced. An eigenvalue WR(j)+sqrt(-1)*WI(j) is selected if
73 SELECT(WR(j),WI(j)) is true; i.e., if either one of a complex
74 conjugate pair of eigenvalues is selected, then both are. Note
75 that a selected complex eigenvalue may no longer satisfy
76 SELECT(WR(j),WI(j)) = .TRUE. after ordering, since ordering may
77 change the value of complex eigenvalues (especially if the ei‐
78 genvalue is ill-conditioned); in this case INFO may be set to
79 N+3 (see INFO below).
80
81 SENSE (input) CHARACTER*1
82 Determines which reciprocal condition numbers are computed. =
83 'N': None are computed;
84 = 'E': Computed for average of selected eigenvalues only;
85 = 'V': Computed for selected right invariant subspace only;
86 = 'B': Computed for both. If SENSE = 'E', 'V' or 'B', SORT
87 must equal 'S'.
88
89 N (input) INTEGER
90 The order of the matrix A. N >= 0.
91
92 A (input/output) DOUBLE PRECISION array, dimension (LDA, N)
93 On entry, the N-by-N matrix A. On exit, A is overwritten by
94 its real Schur form T.
95
96 LDA (input) INTEGER
97 The leading dimension of the array A. LDA >= max(1,N).
98
99 SDIM (output) INTEGER
100 If SORT = 'N', SDIM = 0. If SORT = 'S', SDIM = number of ei‐
101 genvalues (after sorting) for which SELECT is true. (Complex
102 conjugate pairs for which SELECT is true for either eigenvalue
103 count as 2.)
104
105 WR (output) DOUBLE PRECISION array, dimension (N)
106 WI (output) DOUBLE PRECISION array, dimension (N) WR and
107 WI contain the real and imaginary parts, respectively, of the
108 computed eigenvalues, in the same order that they appear on the
109 diagonal of the output Schur form T. Complex conjugate pairs
110 of eigenvalues appear consecutively with the eigenvalue having
111 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. If JOBVS = 'N', VS is not referenced.
116
117 LDVS (input) INTEGER
118 The leading dimension of the array VS. LDVS >= 1, and if JOBVS
119 = 'V', LDVS >= N.
120
121 RCONDE (output) DOUBLE PRECISION
122 If SENSE = 'E' or 'B', RCONDE contains the reciprocal condition
123 number for the average of the selected eigenvalues. Not refer‐
124 enced if SENSE = 'N' or 'V'.
125
126 RCONDV (output) DOUBLE PRECISION
127 If SENSE = 'V' or 'B', RCONDV contains the reciprocal condition
128 number for the selected right invariant subspace. Not refer‐
129 enced if SENSE = 'N' or 'E'.
130
131 WORK (workspace/output) DOUBLE PRECISION array, dimension
132 (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). Also,
137 if SENSE = 'E' or 'V' or 'B', LWORK >= N+2*SDIM*(N-SDIM), where
138 SDIM is the number of selected eigenvalues computed by this
139 routine. Note that N+2*SDIM*(N-SDIM) <= N+N*N/2. Note also
140 that an error is only returned if LWORK < max(1,3*N), but if
141 SENSE = 'E' or 'V' or 'B' this may not be large enough. For
142 good performance, LWORK must generally be larger.
143
144 If LWORK = -1, then a workspace query is assumed; the routine
145 only calculates upper bounds on the optimal sizes of the arrays
146 WORK and IWORK, returns these values as the first entries of
147 the WORK and IWORK arrays, and no error messages related to
148 LWORK or LIWORK are issued by XERBLA.
149
150 IWORK (workspace/output) INTEGER array, dimension (MAX(1,LIWORK))
151 On exit, if INFO = 0, IWORK(1) returns the optimal LIWORK.
152
153 LIWORK (input) INTEGER
154 The dimension of the array IWORK. LIWORK >= 1; if SENSE = 'V'
155 or 'B', LIWORK >= SDIM*(N-SDIM). Note that SDIM*(N-SDIM) <=
156 N*N/4. Note also that an error is only returned if LIWORK < 1,
157 but if SENSE = 'V' or 'B' this may not be large enough.
158
159 If LIWORK = -1, then a workspace query is assumed; the routine
160 only calculates upper bounds on the optimal sizes of the arrays
161 WORK and IWORK, returns these values as the first entries of
162 the WORK and IWORK arrays, and no error messages related to
163 LWORK or LIWORK are issued by XERBLA.
164
165 BWORK (workspace) LOGICAL array, dimension (N)
166 Not referenced if SORT = 'N'.
167
168 INFO (output) INTEGER
169 = 0: successful exit
170 < 0: if INFO = -i, the i-th argument had an illegal value.
171 > 0: if INFO = i, and i is
172 <= N: the QR algorithm failed to compute all the
173 eigenvalues; elements 1:ILO-1 and i+1:N of WR and WI contain
174 those eigenvalues which have converged; if JOBVS = 'V', VS con‐
175 tains the transformation which reduces A to its partially con‐
176 verged Schur form. = N+1: the eigenvalues could not be
177 reordered because some eigenvalues were too close to separate
178 (the problem is very ill-conditioned); = N+2: after reordering,
179 roundoff changed values of some complex eigenvalues so that
180 leading eigenvalues in the Schur form no longer satisfy
181 SELECT=.TRUE. This could also be caused by underflow due to
182 scaling.
183
184
185
186 LAPACK driver routine (version 3.N1o)vember 2006 DGEESX(1)