1DGGEVX(1) LAPACK driver routine (version 3.2) DGGEVX(1)
2
3
4
6 DGGEVX - computes for a pair of N-by-N real nonsymmetric matrices (A,B)
7
9 SUBROUTINE DGGEVX( BALANC, JOBVL, JOBVR, SENSE, N, A, LDA, B, LDB,
10 ALPHAR, ALPHAI, BETA, VL, LDVL, VR, LDVR, ILO, IHI,
11 LSCALE, RSCALE, ABNRM, BBNRM, RCONDE, RCONDV, WORK,
12 LWORK, IWORK, BWORK, INFO )
13
14 CHARACTER BALANC, JOBVL, JOBVR, SENSE
15
16 INTEGER IHI, ILO, INFO, LDA, LDB, LDVL, LDVR, LWORK, N
17
18 DOUBLE PRECISION ABNRM, BBNRM
19
20 LOGICAL BWORK( * )
21
22 INTEGER IWORK( * )
23
24 DOUBLE PRECISION A( LDA, * ), ALPHAI( * ), ALPHAR( * ), B(
25 LDB, * ), BETA( * ), LSCALE( * ), RCONDE( * ),
26 RCONDV( * ), RSCALE( * ), VL( LDVL, * ), VR( LDVR, *
27 ), WORK( * )
28
30 DGGEVX computes for a pair of N-by-N real nonsymmetric matrices (A,B)
31 the generalized eigenvalues, and optionally, the left and/or right gen‐
32 eralized eigenvectors.
33 Optionally also, it computes a balancing transformation to improve the
34 conditioning of the eigenvalues and eigenvectors (ILO, IHI, LSCALE,
35 RSCALE, ABNRM, and BBNRM), reciprocal condition numbers for the eigen‐
36 values (RCONDE), and reciprocal condition numbers for the right eigen‐
37 vectors (RCONDV).
38 A generalized eigenvalue for a pair of matrices (A,B) is a scalar
39 lambda or a ratio alpha/beta = lambda, such that A - lambda*B is singu‐
40 lar. It is usually represented as the pair (alpha,beta), as there is a
41 reasonable interpretation for beta=0, and even for both being zero.
42 The right eigenvector v(j) corresponding to the eigenvalue lambda(j) of
43 (A,B) satisfies
44 A * v(j) = lambda(j) * B * v(j) .
45 The left eigenvector u(j) corresponding to the eigenvalue lambda(j) of
46 (A,B) satisfies
47 u(j)**H * A = lambda(j) * u(j)**H * B.
48 where u(j)**H is the conjugate-transpose of u(j).
49
51 BALANC (input) CHARACTER*1
52 Specifies the balance option to be performed. = 'N': do not
53 diagonally scale or permute;
54 = 'P': permute only;
55 = 'S': scale only;
56 = 'B': both permute and scale. Computed reciprocal condition
57 numbers will be for the matrices after permuting and/or balanc‐
58 ing. Permuting does not change condition numbers (in exact
59 arithmetic), but balancing does.
60
61 JOBVL (input) CHARACTER*1
62 = 'N': do not compute the left generalized eigenvectors;
63 = 'V': compute the left generalized eigenvectors.
64
65 JOBVR (input) CHARACTER*1
66 = 'N': do not compute the right generalized eigenvectors;
67 = 'V': compute the right generalized eigenvectors.
68
69 SENSE (input) CHARACTER*1
70 Determines which reciprocal condition numbers are computed. =
71 'N': none are computed;
72 = 'E': computed for eigenvalues only;
73 = 'V': computed for eigenvectors only;
74 = 'B': computed for eigenvalues and eigenvectors.
75
76 N (input) INTEGER
77 The order of the matrices A, B, VL, and VR. N >= 0.
78
79 A (input/output) DOUBLE PRECISION array, dimension (LDA, N)
80 On entry, the matrix A in the pair (A,B). On exit, A has been
81 overwritten. If JOBVL='V' or JOBVR='V' or both, then A contains
82 the first part of the real Schur form of the "balanced" ver‐
83 sions of the input A and B.
84
85 LDA (input) INTEGER
86 The leading dimension of A. LDA >= max(1,N).
87
88 B (input/output) DOUBLE PRECISION array, dimension (LDB, N)
89 On entry, the matrix B in the pair (A,B). On exit, B has been
90 overwritten. If JOBVL='V' or JOBVR='V' or both, then B contains
91 the second part of the real Schur form of the "balanced" ver‐
92 sions of the input A and B.
93
94 LDB (input) INTEGER
95 The leading dimension of B. LDB >= max(1,N).
96
97 ALPHAR (output) DOUBLE PRECISION array, dimension (N)
98 ALPHAI (output) DOUBLE PRECISION array, dimension (N) BETA
99 (output) DOUBLE PRECISION array, dimension (N) On exit,
100 (ALPHAR(j) + ALPHAI(j)*i)/BETA(j), j=1,...,N, will be the gen‐
101 eralized eigenvalues. If ALPHAI(j) is zero, then the j-th ei‐
102 genvalue is real; if positive, then the j-th and (j+1)-st ei‐
103 genvalues are a complex conjugate pair, with ALPHAI(j+1) nega‐
104 tive. Note: the quotients ALPHAR(j)/BETA(j) and
105 ALPHAI(j)/BETA(j) may easily over- or underflow, and BETA(j)
106 may even be zero. Thus, the user should avoid naively comput‐
107 ing the ratio ALPHA/BETA. However, ALPHAR and ALPHAI will be
108 always less than and usually comparable with norm(A) in magni‐
109 tude, and BETA always less than and usually comparable with
110 norm(B).
111
112 VL (output) DOUBLE PRECISION array, dimension (LDVL,N)
113 If JOBVL = 'V', the left eigenvectors u(j) are stored one after
114 another in the columns of VL, in the same order as their eigen‐
115 values. If the j-th eigenvalue is real, then u(j) = VL(:,j),
116 the j-th column of VL. If the j-th and (j+1)-th eigenvalues
117 form a complex conjugate pair, then u(j) = VL(:,j)+i*VL(:,j+1)
118 and u(j+1) = VL(:,j)-i*VL(:,j+1). Each eigenvector will be
119 scaled so the largest component have abs(real part) + abs(imag.
120 part) = 1. Not referenced if JOBVL = 'N'.
121
122 LDVL (input) INTEGER
123 The leading dimension of the matrix VL. LDVL >= 1, and if JOBVL
124 = 'V', LDVL >= N.
125
126 VR (output) DOUBLE PRECISION array, dimension (LDVR,N)
127 If JOBVR = 'V', the right eigenvectors v(j) are stored one
128 after another in the columns of VR, in the same order as their
129 eigenvalues. If the j-th eigenvalue is real, then v(j) =
130 VR(:,j), the j-th column of VR. If the j-th and (j+1)-th eigen‐
131 values form a complex conjugate pair, then v(j) =
132 VR(:,j)+i*VR(:,j+1) and v(j+1) = VR(:,j)-i*VR(:,j+1). Each
133 eigenvector will be scaled so the largest component have
134 abs(real part) + abs(imag. part) = 1. Not referenced if JOBVR
135 = 'N'.
136
137 LDVR (input) INTEGER
138 The leading dimension of the matrix VR. LDVR >= 1, and if JOBVR
139 = 'V', LDVR >= N.
140
141 ILO (output) INTEGER
142 IHI (output) INTEGER ILO and IHI are integer values such
143 that on exit A(i,j) = 0 and B(i,j) = 0 if i > j and j =
144 1,...,ILO-1 or i = IHI+1,...,N. If BALANC = 'N' or 'S', ILO =
145 1 and IHI = N.
146
147 LSCALE (output) DOUBLE PRECISION array, dimension (N)
148 Details of the permutations and scaling factors applied to the
149 left side of A and B. If PL(j) is the index of the row inter‐
150 changed with row j, and DL(j) is the scaling factor applied to
151 row j, then LSCALE(j) = PL(j) for j = 1,...,ILO-1 = DL(j) for
152 j = ILO,...,IHI = PL(j) for j = IHI+1,...,N. The order in
153 which the interchanges are made is N to IHI+1, then 1 to ILO-1.
154
155 RSCALE (output) DOUBLE PRECISION array, dimension (N)
156 Details of the permutations and scaling factors applied to the
157 right side of A and B. If PR(j) is the index of the column
158 interchanged with column j, and DR(j) is the scaling factor
159 applied to column j, then RSCALE(j) = PR(j) for j =
160 1,...,ILO-1 = DR(j) for j = ILO,...,IHI = PR(j) for j =
161 IHI+1,...,N The order in which the interchanges are made is N
162 to IHI+1, then 1 to ILO-1.
163
164 ABNRM (output) DOUBLE PRECISION
165 The one-norm of the balanced matrix A.
166
167 BBNRM (output) DOUBLE PRECISION
168 The one-norm of the balanced matrix B.
169
170 RCONDE (output) DOUBLE PRECISION array, dimension (N)
171 If SENSE = 'E' or 'B', the reciprocal condition numbers of the
172 eigenvalues, stored in consecutive elements of the array. For
173 a complex conjugate pair of eigenvalues two consecutive ele‐
174 ments of RCONDE are set to the same value. Thus RCONDE(j),
175 RCONDV(j), and the j-th columns of VL and VR all correspond to
176 the j-th eigenpair. If SENSE = 'N or 'V', RCONDE is not refer‐
177 enced.
178
179 RCONDV (output) DOUBLE PRECISION array, dimension (N)
180 If SENSE = 'V' or 'B', the estimated reciprocal condition num‐
181 bers of the eigenvectors, stored in consecutive elements of the
182 array. For a complex eigenvector two consecutive elements of
183 RCONDV are set to the same value. If the eigenvalues cannot be
184 reordered to compute RCONDV(j), RCONDV(j) is set to 0; this can
185 only occur when the true value would be very small anyway. If
186 SENSE = 'N' or 'E', RCONDV is not referenced.
187
188 WORK (workspace/output) DOUBLE PRECISION array, dimension
189 (MAX(1,LWORK))
190 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
191
192 LWORK (input) INTEGER
193 The dimension of the array WORK. LWORK >= max(1,2*N). If BAL‐
194 ANC = 'S' or 'B', or JOBVL = 'V', or JOBVR = 'V', LWORK >=
195 max(1,6*N). If SENSE = 'E' or 'B', LWORK >= max(1,10*N). If
196 SENSE = 'V' or 'B', LWORK >= 2*N*N+8*N+16. If LWORK = -1, then
197 a workspace query is assumed; the routine only calculates the
198 optimal size of the WORK array, returns this value as the first
199 entry of the WORK array, and no error message related to LWORK
200 is issued by XERBLA.
201
202 IWORK (workspace) INTEGER array, dimension (N+6)
203 If SENSE = 'E', IWORK is not referenced.
204
205 BWORK (workspace) LOGICAL array, dimension (N)
206 If SENSE = 'N', BWORK is not referenced.
207
208 INFO (output) INTEGER
209 = 0: successful exit
210 < 0: if INFO = -i, the i-th argument had an illegal value.
211 = 1,...,N: The QZ iteration failed. No eigenvectors have been
212 calculated, but ALPHAR(j), ALPHAI(j), and BETA(j) should be
213 correct for j=INFO+1,...,N. > N: =N+1: other than QZ itera‐
214 tion failed in DHGEQZ.
215 =N+2: error return from DTGEVC.
216
218 Balancing a matrix pair (A,B) includes, first, permuting rows and col‐
219 umns to isolate eigenvalues, second, applying diagonal similarity
220 transformation to the rows and columns to make the rows and columns as
221 close in norm as possible. The computed reciprocal condition numbers
222 correspond to the balanced matrix. Permuting rows and columns will not
223 change the condition numbers (in exact arithmetic) but diagonal scaling
224 will. For further explanation of balancing, see section 4.11.1.2 of
225 LAPACK Users' Guide.
226 An approximate error bound on the chordal distance between the i-th
227 computed generalized eigenvalue w and the corresponding exact eigenval‐
228 ue lambda is
229 chord(w, lambda) <= EPS * norm(ABNRM, BBNRM) / RCONDE(I) An
230 approximate error bound for the angle between the i-th computed eigen‐
231 vector VL(i) or VR(i) is given by
232 EPS * norm(ABNRM, BBNRM) / DIF(i).
233 For further explanation of the reciprocal condition numbers RCONDE and
234 RCONDV, see section 4.11 of LAPACK User's Guide.
235
236
237
238 LAPACK driver routine (version 3.N2o)vember 2008 DGGEVX(1)