1STREVC(1) LAPACK routine (version 3.1) STREVC(1)
2
3
4
6 STREVC - some or all of the right and/or left eigenvectors of a real
7 upper quasi-triangular matrix T
8
10 SUBROUTINE STREVC( SIDE, HOWMNY, SELECT, N, T, LDT, VL, LDVL, VR, LDVR,
11 MM, M, WORK, INFO )
12
13 CHARACTER HOWMNY, SIDE
14
15 INTEGER INFO, LDT, LDVL, LDVR, M, MM, N
16
17 LOGICAL SELECT( * )
18
19 REAL T( LDT, * ), VL( LDVL, * ), VR( LDVR, * ), WORK( * )
20
22 STREVC computes some or all of the right and/or left eigenvectors of a
23 real upper quasi-triangular matrix T. Matrices of this type are pro‐
24 duced by the Schur factorization of a real general matrix: A =
25 Q*T*Q**T, as computed by SHSEQR.
26
27 The right eigenvector x and the left eigenvector y of T corresponding
28 to an eigenvalue w are defined by:
29
30 T*x = w*x, (y**H)*T = w*(y**H)
31
32 where y**H denotes the conjugate transpose of y.
33 The eigenvalues are not input to this routine, but are read directly
34 from the diagonal blocks of T.
35
36 This routine returns the matrices X and/or Y of right and left eigen‐
37 vectors of T, or the products Q*X and/or Q*Y, where Q is an input
38 matrix. If Q is the orthogonal factor that reduces a matrix A to Schur
39 form T, then Q*X and Q*Y are the matrices of right and left eigenvec‐
40 tors of A.
41
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
53 selected right and/or left eigenvectors, as indicated by the
54 logical array SELECT.
55
56 SELECT (input/output) 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 Not referenced if
64 HOWMNY = 'A' or 'B'.
65
66 N (input) INTEGER
67 The order of the matrix T. N >= 0.
68
69 T (input) REAL array, dimension (LDT,N)
70 The upper quasi-triangular matrix T in Schur canonical form.
71
72 LDT (input) INTEGER
73 The leading dimension of the array T. LDT >= max(1,N).
74
75 VL (input/output) REAL array, dimension (LDVL,MM)
76 On entry, if SIDE = 'L' or 'B' and HOWMNY = 'B', VL must con‐
77 tain an N-by-N matrix Q (usually the orthogonal matrix Q of
78 Schur vectors returned by SHSEQR). On exit, if SIDE = 'L' or
79 'B', VL contains: if HOWMNY = 'A', the matrix Y of left eigen‐
80 vectors of T; if HOWMNY = 'B', the matrix Q*Y; if HOWMNY = 'S',
81 the left eigenvectors of T specified by SELECT, stored consecu‐
82 tively in the columns of VL, in the same order as their eigen‐
83 values. A complex eigenvector corresponding to a complex ei‐
84 genvalue is stored in two consecutive columns, the first hold‐
85 ing the real part, and the second the imaginary part. Not ref‐
86 erenced if SIDE = 'R'.
87
88 LDVL (input) INTEGER
89 The leading dimension of the array VL. LDVL >= 1, and if SIDE
90 = 'L' or 'B', LDVL >= N.
91
92 VR (input/output) REAL array, dimension (LDVR,MM)
93 On entry, if SIDE = 'R' or 'B' and HOWMNY = 'B', VR must con‐
94 tain an N-by-N matrix Q (usually the orthogonal matrix Q of
95 Schur vectors returned by SHSEQR). On exit, if SIDE = 'R' or
96 'B', VR contains: if HOWMNY = 'A', the matrix X of right eigen‐
97 vectors of T; if HOWMNY = 'B', the matrix Q*X; if HOWMNY = 'S',
98 the right eigenvectors of T specified by SELECT, stored consec‐
99 utively in the columns of VR, in the same order as their eigen‐
100 values. A complex eigenvector corresponding to a complex ei‐
101 genvalue is stored in two consecutive columns, the first hold‐
102 ing the real part and the second the imaginary part. Not ref‐
103 erenced if SIDE = 'L'.
104
105 LDVR (input) INTEGER
106 The leading dimension of the array VR. LDVR >= 1, and if SIDE
107 = 'R' or 'B', LDVR >= N.
108
109 MM (input) INTEGER
110 The number of columns in the arrays VL and/or VR. MM >= M.
111
112 M (output) INTEGER
113 The number of columns in the arrays VL and/or VR actually used
114 to store the eigenvectors. If HOWMNY = 'A' or 'B', M is set to
115 N. Each selected real eigenvector occupies one column and each
116 selected complex eigenvector occupies two columns.
117
118 WORK (workspace) REAL array, dimension (3*N)
119
120 INFO (output) INTEGER
121 = 0: successful exit
122 < 0: if INFO = -i, the i-th argument had an illegal value
123
125 The algorithm used in this program is basically backward (forward) sub‐
126 stitution, with scaling to make the the code robust against possible
127 overflow.
128
129 Each eigenvector is normalized so that the element of largest magnitude
130 has magnitude 1; here the magnitude of a complex number (x,y) is taken
131 to be |x| + |y|.
132
133
134
135
136 LAPACK routine (version 3.1) November 2006 STREVC(1)