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