1DHSEIN(1) LAPACK routine (version 3.2) DHSEIN(1)
2
3
4
6 DHSEIN - uses inverse iteration to find specified right and/or left
7 eigenvectors of a real upper Hessenberg matrix H
8
10 SUBROUTINE DHSEIN( SIDE, EIGSRC, INITV, SELECT, N, H, LDH, WR, WI, VL,
11 LDVL, VR, LDVR, MM, M, WORK, IFAILL, IFAILR, INFO )
12
13 CHARACTER EIGSRC, INITV, SIDE
14
15 INTEGER INFO, LDH, LDVL, LDVR, M, MM, N
16
17 LOGICAL SELECT( * )
18
19 INTEGER IFAILL( * ), IFAILR( * )
20
21 DOUBLE PRECISION H( LDH, * ), VL( LDVL, * ), VR( LDVR, * ),
22 WI( * ), WORK( * ), WR( * )
23
25 DHSEIN uses inverse iteration to find specified right and/or left
26 eigenvectors of a real upper Hessenberg matrix H. The right eigenvec‐
27 tor x and the left eigenvector y of the matrix H corresponding to an
28 eigenvalue w are defined by:
29 H * x = w * x, y**h * H = w * y**h
30 where y**h denotes the conjugate transpose of the vector y.
31
33 SIDE (input) CHARACTER*1
34 = 'R': compute right eigenvectors only;
35 = 'L': compute left eigenvectors only;
36 = 'B': compute both right and left eigenvectors.
37
38 EIGSRC (input) CHARACTER*1
39 Specifies the source of eigenvalues supplied in (WR,WI):
40 = 'Q': the eigenvalues were found using DHSEQR; thus, if H has
41 zero subdiagonal elements, and so is block-triangular, then the
42 j-th eigenvalue can be assumed to be an eigenvalue of the block
43 containing the j-th row/column. This property allows DHSEIN to
44 perform inverse iteration on just one diagonal block. = 'N':
45 no assumptions are made on the correspondence between eigenval‐
46 ues and diagonal blocks. In this case, DHSEIN must always per‐
47 form inverse iteration using the whole matrix H.
48
49 INITV (input) CHARACTER*1
50 = 'N': no initial vectors are supplied;
51 = 'U': user-supplied initial vectors are stored in the arrays
52 VL and/or VR.
53
54 SELECT (input/output) LOGICAL array, dimension (N)
55 Specifies the eigenvectors to be computed. To select the real
56 eigenvector corresponding to a real eigenvalue WR(j), SELECT(j)
57 must be set to .TRUE.. To select the complex eigenvector corre‐
58 sponding to a complex eigenvalue (WR(j),WI(j)), with complex
59 conjugate (WR(j+1),WI(j+1)), either SELECT(j) or SELECT(j+1) or
60 both must be set to .TRUE.; then on exit SELECT(j) is .TRUE.
61 and SELECT(j+1) is .FALSE..
62
63 N (input) INTEGER
64 The order of the matrix H. N >= 0.
65
66 H (input) DOUBLE PRECISION array, dimension (LDH,N)
67 The upper Hessenberg matrix H.
68
69 LDH (input) INTEGER
70 The leading dimension of the array H. LDH >= max(1,N).
71
72 WR (input/output) DOUBLE PRECISION array, dimension (N)
73 WI (input) DOUBLE PRECISION array, dimension (N) On entry,
74 the real and imaginary parts of the eigenvalues of H; a complex
75 conjugate pair of eigenvalues must be stored in consecutive
76 elements of WR and WI. On exit, WR may have been altered since
77 close eigenvalues are perturbed slightly in searching for inde‐
78 pendent eigenvectors.
79
80 VL (input/output) DOUBLE PRECISION array, dimension (LDVL,MM)
81 On entry, if INITV = 'U' and SIDE = 'L' or 'B', VL must contain
82 starting vectors for the inverse iteration for the left eigen‐
83 vectors; the starting vector for each eigenvector must be in
84 the same column(s) in which the eigenvector will be stored. On
85 exit, if SIDE = 'L' or 'B', the left eigenvectors specified by
86 SELECT will be stored consecutively in the columns of VL, in
87 the same order as their eigenvalues. A complex eigenvector cor‐
88 responding to a complex eigenvalue is stored in two consecutive
89 columns, the first holding the real part and the second the
90 imaginary part. If SIDE = 'R', VL is not referenced.
91
92 LDVL (input) INTEGER
93 The leading dimension of the array VL. LDVL >= max(1,N) if
94 SIDE = 'L' or 'B'; LDVL >= 1 otherwise.
95
96 VR (input/output) DOUBLE PRECISION array, dimension (LDVR,MM)
97 On entry, if INITV = 'U' and SIDE = 'R' or 'B', VR must contain
98 starting vectors for the inverse iteration for the right eigen‐
99 vectors; the starting vector for each eigenvector must be in
100 the same column(s) in which the eigenvector will be stored. On
101 exit, if SIDE = 'R' or 'B', the right eigenvectors specified by
102 SELECT will be stored consecutively in the columns of VR, in
103 the same order as their eigenvalues. A complex eigenvector cor‐
104 responding to a complex eigenvalue is stored in two consecutive
105 columns, the first holding the real part and the second the
106 imaginary part. If SIDE = 'L', VR is not referenced.
107
108 LDVR (input) INTEGER
109 The leading dimension of the array VR. LDVR >= max(1,N) if
110 SIDE = 'R' or 'B'; LDVR >= 1 otherwise.
111
112 MM (input) INTEGER
113 The number of columns in the arrays VL and/or VR. MM >= M.
114
115 M (output) INTEGER
116 The number of columns in the arrays VL and/or VR required to
117 store the eigenvectors; each selected real eigenvector occupies
118 one column and each selected complex eigenvector occupies two
119 columns.
120
121 WORK (workspace) DOUBLE PRECISION array, dimension ((N+2)*N)
122
123 IFAILL (output) INTEGER array, dimension (MM)
124 If SIDE = 'L' or 'B', IFAILL(i) = j > 0 if the left eigenvector
125 in the i-th column of VL (corresponding to the eigenvalue w(j))
126 failed to converge; IFAILL(i) = 0 if the eigenvector converged
127 satisfactorily. If the i-th and (i+1)th columns of VL hold a
128 complex eigenvector, then IFAILL(i) and IFAILL(i+1) are set to
129 the same value. If SIDE = 'R', IFAILL is not referenced.
130
131 IFAILR (output) INTEGER array, dimension (MM)
132 If SIDE = 'R' or 'B', IFAILR(i) = j > 0 if the right eigenvec‐
133 tor in the i-th column of VR (corresponding to the eigenvalue
134 w(j)) failed to converge; IFAILR(i) = 0 if the eigenvector con‐
135 verged satisfactorily. If the i-th and (i+1)th columns of VR
136 hold a complex eigenvector, then IFAILR(i) and IFAILR(i+1) are
137 set to the same value. If SIDE = 'L', IFAILR is not refer‐
138 enced.
139
140 INFO (output) INTEGER
141 = 0: successful exit
142 < 0: if INFO = -i, the i-th argument had an illegal value
143 > 0: if INFO = i, i is the number of eigenvectors which failed
144 to converge; see IFAILL and IFAILR for further details.
145
147 Each eigenvector is normalized so that the element of largest magnitude
148 has magnitude 1; here the magnitude of a complex number (x,y) is taken
149 to be |x|+|y|.
150
151
152
153 LAPACK routine (version 3.2) November 2008 DHSEIN(1)