1STGEVC(1) LAPACK routine (version 3.1) STGEVC(1)
2
3
4
6 STGEVC - some or all of the right and/or left eigenvectors of a pair of
7 real matrices (S,P), where S is a quasi-triangular matrix and P is
8 upper triangular
9
11 SUBROUTINE STGEVC( SIDE, HOWMNY, SELECT, N, S, LDS, P, LDP, VL, LDVL,
12 VR, LDVR, MM, M, WORK, INFO )
13
14 CHARACTER HOWMNY, SIDE
15
16 INTEGER INFO, LDP, LDS, LDVL, LDVR, M, MM, N
17
18 LOGICAL SELECT( * )
19
20 REAL P( LDP, * ), S( LDS, * ), VL( LDVL, * ), VR( LDVR, *
21 ), WORK( * )
22
24 STGEVC computes some or all of the right and/or left eigenvectors of a
25 pair of real matrices (S,P), where S is a quasi-triangular matrix and P
26 is upper triangular. Matrix pairs of this type are produced by the
27 generalized Schur factorization of a matrix pair (A,B):
28
29 A = Q*S*Z**T, B = Q*P*Z**T
30
31 as computed by SGGHRD + SHGEQZ.
32
33 The right eigenvector x and the left eigenvector y of (S,P) correspond‐
34 ing to an eigenvalue w are defined by:
35
36 S*x = w*P*x, (y**H)*S = w*(y**H)*P,
37
38 where y**H denotes the conjugate tranpose of y.
39 The eigenvalues are not input to this routine, but are computed
40 directly from the diagonal blocks of S and P.
41
42 This routine returns the matrices X and/or Y of right and left eigen‐
43 vectors of (S,P), or the products Z*X and/or Q*Y,
44 where Z and Q are input matrices.
45 If Q and Z are the orthogonal factors from the generalized Schur fac‐
46 torization of a matrix pair (A,B), then Z*X and Q*Y
47 are the matrices of right and left eigenvectors of (A,B).
48
49
51 SIDE (input) CHARACTER*1
52 = 'R': compute right eigenvectors only;
53 = 'L': compute left eigenvectors only;
54 = 'B': compute both right and left eigenvectors.
55
56 HOWMNY (input) CHARACTER*1
57 = 'A': compute all right and/or left eigenvectors;
58 = 'B': compute all right and/or left eigenvectors, backtrans‐
59 formed by the matrices in VR and/or VL; = 'S': compute selected
60 right and/or left eigenvectors, specified by the logical array
61 SELECT.
62
63 SELECT (input) LOGICAL array, dimension (N)
64 If HOWMNY='S', SELECT specifies the eigenvectors to be com‐
65 puted. If w(j) is a real eigenvalue, the corresponding real
66 eigenvector is computed if SELECT(j) is .TRUE.. If w(j) and
67 w(j+1) are the real and imaginary parts of a complex eigenval‐
68 ue, the corresponding complex eigenvector is computed if either
69 SELECT(j) or SELECT(j+1) is .TRUE., and on exit SELECT(j) is
70 set to .TRUE. and SELECT(j+1) is set to .FALSE.. Not refer‐
71 enced if HOWMNY = 'A' or 'B'.
72
73 N (input) INTEGER
74 The order of the matrices S and P. N >= 0.
75
76 S (input) REAL array, dimension (LDS,N)
77 The upper quasi-triangular matrix S from a generalized Schur
78 factorization, as computed by SHGEQZ.
79
80 LDS (input) INTEGER
81 The leading dimension of array S. LDS >= max(1,N).
82
83 P (input) REAL array, dimension (LDP,N)
84 The upper triangular matrix P from a generalized Schur factor‐
85 ization, as computed by SHGEQZ. 2-by-2 diagonal blocks of P
86 corresponding to 2-by-2 blocks of S must be in positive diago‐
87 nal form.
88
89 LDP (input) INTEGER
90 The leading dimension of array P. LDP >= max(1,N).
91
92 VL (input/output) REAL array, dimension (LDVL,MM)
93 On entry, if SIDE = 'L' or 'B' and HOWMNY = 'B', VL must con‐
94 tain an N-by-N matrix Q (usually the orthogonal matrix Q of
95 left Schur vectors returned by SHGEQZ). On exit, if SIDE = 'L'
96 or 'B', VL contains: if HOWMNY = 'A', the matrix Y of left
97 eigenvectors of (S,P); if HOWMNY = 'B', the matrix Q*Y; if
98 HOWMNY = 'S', the left eigenvectors of (S,P) specified by
99 SELECT, stored consecutively in the columns of VL, in the same
100 order as their eigenvalues.
101
102 A complex eigenvector corresponding to a complex eigenvalue is
103 stored in two consecutive columns, the first holding the real
104 part, and the second the imaginary part.
105
106 Not referenced if SIDE = 'R'.
107
108 LDVL (input) INTEGER
109 The leading dimension of array VL. LDVL >= 1, and if SIDE =
110 'L' or 'B', LDVL >= N.
111
112 VR (input/output) REAL array, dimension (LDVR,MM)
113 On entry, if SIDE = 'R' or 'B' and HOWMNY = 'B', VR must con‐
114 tain an N-by-N matrix Z (usually the orthogonal matrix Z of
115 right Schur vectors returned by SHGEQZ).
116
117 On exit, if SIDE = 'R' or 'B', VR contains: if HOWMNY = 'A',
118 the matrix X of right eigenvectors of (S,P); if HOWMNY = 'B' or
119 'b', the matrix Z*X; if HOWMNY = 'S' or 's', the right eigen‐
120 vectors of (S,P) specified by SELECT, stored consecutively in
121 the columns of VR, in the same order as their eigenvalues.
122
123 A complex eigenvector corresponding to a complex eigenvalue is
124 stored in two consecutive columns, the first holding the real
125 part and the second the imaginary part. Not referenced if SIDE
126 = 'L'.
127
128 LDVR (input) INTEGER
129 The leading dimension of the array VR. LDVR >= 1, and if SIDE
130 = 'R' or 'B', LDVR >= N.
131
132 MM (input) INTEGER
133 The number of columns in the arrays VL and/or VR. MM >= M.
134
135 M (output) INTEGER
136 The number of columns in the arrays VL and/or VR actually used
137 to store the eigenvectors. If HOWMNY = 'A' or 'B', M is set to
138 N. Each selected real eigenvector occupies one column and each
139 selected complex eigenvector occupies two columns.
140
141 WORK (workspace) REAL array, dimension (6*N)
142
143 INFO (output) INTEGER
144 = 0: successful exit.
145 < 0: if INFO = -i, the i-th argument had an illegal value.
146 > 0: the 2-by-2 block (INFO:INFO+1) does not have a complex
147 eigenvalue.
148
150 Allocation of workspace:
151 ---------- -- ---------
152
153 WORK( j ) = 1-norm of j-th column of A, above the diagonal
154 WORK( N+j ) = 1-norm of j-th column of B, above the diagonal
155 WORK( 2*N+1:3*N ) = real part of eigenvector
156 WORK( 3*N+1:4*N ) = imaginary part of eigenvector
157 WORK( 4*N+1:5*N ) = real part of back-transformed eigenvector
158 WORK( 5*N+1:6*N ) = imaginary part of back-transformed eigenvector
159
160 Rowwise vs. columnwise solution methods:
161 ------- -- ---------- -------- -------
162
163 Finding a generalized eigenvector consists basically of solving the
164 singular triangular system
165
166 (A - w B) x = 0 (for right) or: (A - w B)**H y = 0 (for left)
167
168 Consider finding the i-th right eigenvector (assume all eigenvalues are
169 real). The equation to be solved is:
170 n i
171 0 = sum C(j,k) v(k) = sum C(j,k) v(k) for j = i,. . .,1
172 k=j k=j
173
174 where C = (A - w B) (The components v(i+1:n) are 0.)
175
176 The "rowwise" method is:
177
178 (1) v(i) := 1
179 for j = i-1,. . .,1:
180 i
181 (2) compute s = - sum C(j,k) v(k) and
182 k=j+1
183
184 (3) v(j) := s / C(j,j)
185
186 Step 2 is sometimes called the "dot product" step, since it is an inner
187 product between the j-th row and the portion of the eigenvector that
188 has been computed so far.
189
190 The "columnwise" method consists basically in doing the sums for all
191 the rows in parallel. As each v(j) is computed, the contribution of
192 v(j) times the j-th column of C is added to the partial sums. Since
193 FORTRAN arrays are stored columnwise, this has the advantage that at
194 each step, the elements of C that are accessed are adjacent to one
195 another, whereas with the rowwise method, the elements accessed at a
196 step are spaced LDS (and LDP) words apart.
197
198 When finding left eigenvectors, the matrix in question is the transpose
199 of the one in storage, so the rowwise method then actually accesses
200 columns of A and B at each step, and so is the preferred method.
201
202
203
204
205 LAPACK routine (version 3.1) November 2006 STGEVC(1)