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