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