1SGEESX(1) LAPACK driver routine (version 3.1) SGEESX(1)
2
3
4
6 SGEESX - 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 SGEESX( 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 REAL RCONDE, RCONDV
19
20 LOGICAL BWORK( * )
21
22 INTEGER IWORK( * )
23
24 REAL A( LDA, * ), VS( LDVS, * ), WI( * ), WORK( * ), WR(
25 * )
26
27 LOGICAL SELECT
28
29 EXTERNAL SELECT
30
32 SGEESX 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 REAL arguments
68 SELECT must be declared EXTERNAL in the calling subroutine. If
69 SORT = 'S', SELECT is used to select eigenvalues to sort to the
70 top left of the Schur form. If SORT = 'N', SELECT is not ref‐
71 erenced. 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 complex
73 conjugate pair of eigenvalues is selected, then both are. Note
74 that a selected complex eigenvalue may no longer satisfy
75 SELECT(WR(j),WI(j)) = .TRUE. after ordering, since ordering may
76 change the value of complex eigenvalues (especially if the ei‐
77 genvalue is ill-conditioned); in this case INFO may be set to
78 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. If SENSE = 'E', 'V' or 'B', SORT
86 must equal 'S'.
87
88 N (input) INTEGER
89 The order of the matrix A. N >= 0.
90
91 A (input/output) REAL array, dimension (LDA, N)
92 On entry, the N-by-N matrix A. On exit, A is overwritten by
93 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. If SORT = 'S', SDIM = number of ei‐
100 genvalues (after sorting) for which SELECT is true. (Complex
101 conjugate pairs for which SELECT is true for either eigenvalue
102 count as 2.)
103
104 WR (output) REAL array, dimension (N)
105 WI (output) REAL array, dimension (N) WR and WI contain
106 the real and imaginary parts, respectively, of the computed ei‐
107 genvalues, in the same order that they appear on the diagonal
108 of the output Schur form T. Complex conjugate pairs of eigen‐
109 values appear consecutively with the eigenvalue having the pos‐
110 itive imaginary part first.
111
112 VS (output) REAL array, dimension (LDVS,N)
113 If JOBVS = 'V', VS contains the orthogonal matrix Z of Schur
114 vectors. If JOBVS = 'N', VS is not referenced.
115
116 LDVS (input) INTEGER
117 The leading dimension of the array VS. LDVS >= 1, and if JOBVS
118 = 'V', LDVS >= N.
119
120 RCONDE (output) REAL
121 If SENSE = 'E' or 'B', RCONDE contains the reciprocal condition
122 number for the average of the selected eigenvalues. Not refer‐
123 enced if SENSE = 'N' or 'V'.
124
125 RCONDV (output) REAL
126 If SENSE = 'V' or 'B', RCONDV contains the reciprocal condition
127 number for the selected right invariant subspace. Not refer‐
128 enced if SENSE = 'N' or 'E'.
129
130 WORK (workspace/output) REAL array, dimension (MAX(1,LWORK))
131 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
132
133 LWORK (input) INTEGER
134 The dimension of the array WORK. LWORK >= max(1,3*N). Also,
135 if SENSE = 'E' or 'V' or 'B', LWORK >= N+2*SDIM*(N-SDIM), where
136 SDIM is the number of selected eigenvalues computed by this
137 routine. Note that N+2*SDIM*(N-SDIM) <= N+N*N/2. Note also
138 that an error is only returned if LWORK < max(1,3*N), but if
139 SENSE = 'E' or 'V' or 'B' this may not be large enough. For
140 good performance, LWORK must generally be larger.
141
142 If LWORK = -1, then a workspace query is assumed; the routine
143 only calculates upper bounds on the optimal sizes of the arrays
144 WORK and IWORK, returns these values as the first entries of
145 the WORK and IWORK arrays, and no error messages related to
146 LWORK or LIWORK are issued by XERBLA.
147
148 IWORK (workspace/output) INTEGER array, dimension (MAX(1,LIWORK))
149 On exit, if INFO = 0, IWORK(1) returns the optimal LIWORK.
150
151 LIWORK (input) INTEGER
152 The dimension of the array IWORK. LIWORK >= 1; if SENSE = 'V'
153 or 'B', LIWORK >= SDIM*(N-SDIM). Note that SDIM*(N-SDIM) <=
154 N*N/4. Note also that an error is only returned if LIWORK < 1,
155 but if SENSE = 'V' or 'B' this may not be large enough.
156
157 If LIWORK = -1, then a workspace query is assumed; the routine
158 only calculates upper bounds on the optimal sizes of the arrays
159 WORK and IWORK, returns these values as the first entries of
160 the WORK and IWORK arrays, and no error messages related to
161 LWORK or LIWORK are issued by XERBLA.
162
163 BWORK (workspace) LOGICAL array, dimension (N)
164 Not referenced if SORT = 'N'.
165
166 INFO (output) INTEGER
167 = 0: successful exit
168 < 0: if INFO = -i, the i-th argument had an illegal value.
169 > 0: if INFO = i, and i is
170 <= N: the QR algorithm failed to compute all the
171 eigenvalues; elements 1:ILO-1 and i+1:N of WR and WI contain
172 those eigenvalues which have converged; if JOBVS = 'V', VS con‐
173 tains the transformation which reduces A to its partially con‐
174 verged Schur form. = N+1: the eigenvalues could not be
175 reordered because some eigenvalues were too close to separate
176 (the problem is very ill-conditioned); = N+2: after reordering,
177 roundoff changed values of some complex eigenvalues so that
178 leading eigenvalues in the Schur form no longer satisfy
179 SELECT=.TRUE. This could also be caused by underflow due to
180 scaling.
181
182
183
184 LAPACK driver routine (version 3.N1o)vember 2006 SGEESX(1)