1DGGEVX(1)             LAPACK driver routine (version 3.1)            DGGEVX(1)
2
3
4

NAME

6       DGGEVX - for a pair of N-by-N real nonsymmetric matrices (A,B)
7

SYNOPSIS

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

PURPOSE

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
34       Optionally  also, it computes a balancing transformation to improve the
35       conditioning of the eigenvalues and  eigenvectors  (ILO,  IHI,  LSCALE,
36       RSCALE,  ABNRM, and BBNRM), reciprocal condition numbers for the eigen‐
37       values (RCONDE), and reciprocal condition numbers for the right  eigen‐
38       vectors (RCONDV).
39
40       A  generalized  eigenvalue  for  a  pair  of matrices (A,B) is a scalar
41       lambda or a ratio alpha/beta = lambda, such that A - lambda*B is singu‐
42       lar.  It is usually represented as the pair (alpha,beta), as there is a
43       reasonable interpretation for beta=0, and even for both being zero.
44
45       The right eigenvector v(j) corresponding to the eigenvalue lambda(j) of
46       (A,B) satisfies
47
48                        A * v(j) = lambda(j) * B * v(j) .
49
50       The  left eigenvector u(j) corresponding to the eigenvalue lambda(j) of
51       (A,B) satisfies
52
53                        u(j)**H * A  = lambda(j) * u(j)**H * B.
54
55       where u(j)**H is the conjugate-transpose of u(j).
56
57
58

ARGUMENTS

60       BALANC  (input) CHARACTER*1
61               Specifies the balance option to be performed.  = 'N':   do  not
62               diagonally scale or permute;
63               = 'P':  permute only;
64               = 'S':  scale only;
65               =  'B':  both permute and scale.  Computed reciprocal condition
66               numbers will be for the matrices after permuting and/or balanc‐
67               ing.  Permuting  does  not  change  condition numbers (in exact
68               arithmetic), but balancing does.
69
70       JOBVL   (input) CHARACTER*1
71               = 'N':  do not compute the left generalized eigenvectors;
72               = 'V':  compute the left generalized eigenvectors.
73
74       JOBVR   (input) CHARACTER*1
75               = 'N':  do not compute the right generalized eigenvectors;
76               = 'V':  compute the right generalized eigenvectors.
77
78       SENSE   (input) CHARACTER*1
79               Determines which reciprocal condition numbers are computed.   =
80               'N': none are computed;
81               = 'E': computed for eigenvalues only;
82               = 'V': computed for eigenvectors only;
83               = 'B': computed for eigenvalues and eigenvectors.
84
85       N       (input) INTEGER
86               The order of the matrices A, B, VL, and VR.  N >= 0.
87
88       A       (input/output) DOUBLE PRECISION array, dimension (LDA, N)
89               On  entry, the matrix A in the pair (A,B).  On exit, A has been
90               overwritten. If JOBVL='V' or JOBVR='V' or both, then A contains
91               the  first  part  of the real Schur form of the "balanced" ver‐
92               sions of the input A and B.
93
94       LDA     (input) INTEGER
95               The leading dimension of A.  LDA >= max(1,N).
96
97       B       (input/output) DOUBLE PRECISION array, dimension (LDB, N)
98               On entry, the matrix B in the pair (A,B).  On exit, B has  been
99               overwritten. If JOBVL='V' or JOBVR='V' or both, then B contains
100               the second part of the real Schur form of the  "balanced"  ver‐
101               sions of the input A and B.
102
103       LDB     (input) INTEGER
104               The leading dimension of B.  LDB >= max(1,N).
105
106       ALPHAR  (output) DOUBLE PRECISION array, dimension (N)
107               ALPHAI   (output)  DOUBLE  PRECISION  array, dimension (N) BETA
108               (output)  DOUBLE  PRECISION  array,  dimension  (N)  On   exit,
109               (ALPHAR(j)  + ALPHAI(j)*i)/BETA(j), j=1,...,N, will be the gen‐
110               eralized eigenvalues.  If ALPHAI(j) is zero, then the j-th  ei‐
111               genvalue  is  real; if positive, then the j-th and (j+1)-st ei‐
112               genvalues are a complex conjugate pair, with ALPHAI(j+1)  nega‐
113               tive.
114
115               Note: the quotients ALPHAR(j)/BETA(j) and ALPHAI(j)/BETA(j) may
116               easily over- or underflow, and BETA(j) may even be zero.  Thus,
117               the  user  should avoid naively computing the ratio ALPHA/BETA.
118               However, ALPHAR and ALPHAI will be always less than and usually
119               comparable with norm(A) in magnitude, and BETA always less than
120               and usually comparable with norm(B).
121
122       VL      (output) DOUBLE PRECISION array, dimension (LDVL,N)
123               If JOBVL = 'V', the left eigenvectors u(j) are stored one after
124               another in the columns of VL, in the same order as their eigen‐
125               values. If the j-th eigenvalue is real, then  u(j)  =  VL(:,j),
126               the  j-th  column  of  VL. If the j-th and (j+1)-th eigenvalues
127               form a complex conjugate pair, then u(j) =  VL(:,j)+i*VL(:,j+1)
128               and  u(j+1)  =  VL(:,j)-i*VL(:,j+1).   Each eigenvector will be
129               scaled so the largest component have abs(real part) + abs(imag.
130               part) = 1.  Not referenced if JOBVL = 'N'.
131
132       LDVL    (input) INTEGER
133               The leading dimension of the matrix VL. LDVL >= 1, and if JOBVL
134               = 'V', LDVL >= N.
135
136       VR      (output) DOUBLE PRECISION array, dimension (LDVR,N)
137               If JOBVR = 'V', the right  eigenvectors  v(j)  are  stored  one
138               after  another in the columns of VR, in the same order as their
139               eigenvalues. If the  j-th  eigenvalue  is  real,  then  v(j)  =
140               VR(:,j), the j-th column of VR. If the j-th and (j+1)-th eigen‐
141               values  form  a   complex   conjugate   pair,   then   v(j)   =
142               VR(:,j)+i*VR(:,j+1)  and  v(j+1)  =  VR(:,j)-i*VR(:,j+1).  Each
143               eigenvector will  be  scaled  so  the  largest  component  have
144               abs(real  part) + abs(imag. part) = 1.  Not referenced if JOBVR
145               = 'N'.
146
147       LDVR    (input) INTEGER
148               The leading dimension of the matrix VR. LDVR >= 1, and if JOBVR
149               = 'V', LDVR >= N.
150
151       ILO     (output) INTEGER
152               IHI      (output)  INTEGER  ILO and IHI are integer values such
153               that on exit A(i,j) = 0 and B(i,j) =  0  if  i  >  j  and  j  =
154               1,...,ILO-1  or i = IHI+1,...,N.  If BALANC = 'N' or 'S', ILO =
155               1 and IHI = N.
156
157       LSCALE  (output) DOUBLE PRECISION array, dimension (N)
158               Details of the permutations and scaling factors applied to  the
159               left  side of A and B.  If PL(j) is the index of the row inter‐
160               changed with row j, and DL(j) is the scaling factor applied  to
161               row j, then LSCALE(j) = PL(j)  for j = 1,...,ILO-1 = DL(j)  for
162               j = ILO,...,IHI = PL(j)  for j =  IHI+1,...,N.   The  order  in
163               which the interchanges are made is N to IHI+1, then 1 to ILO-1.
164
165       RSCALE  (output) DOUBLE PRECISION array, dimension (N)
166               Details  of the permutations and scaling factors applied to the
167               right side of A and B.  If PR(j) is the  index  of  the  column
168               interchanged  with  column  j,  and DR(j) is the scaling factor
169               applied  to  column  j,  then  RSCALE(j)  =  PR(j)   for  j   =
170               1,...,ILO-1  =  DR(j)   for  j  =  ILO,...,IHI = PR(j)  for j =
171               IHI+1,...,N The order in which the interchanges are made  is  N
172               to IHI+1, then 1 to ILO-1.
173
174       ABNRM   (output) DOUBLE PRECISION
175               The one-norm of the balanced matrix A.
176
177       BBNRM   (output) DOUBLE PRECISION
178               The one-norm of the balanced matrix B.
179
180       RCONDE  (output) DOUBLE PRECISION array, dimension (N)
181               If  SENSE = 'E' or 'B', the reciprocal condition numbers of the
182               eigenvalues, stored in consecutive elements of the array.   For
183               a  complex  conjugate  pair of eigenvalues two consecutive ele‐
184               ments of RCONDE are set to  the  same  value.  Thus  RCONDE(j),
185               RCONDV(j),  and the j-th columns of VL and VR all correspond to
186               the j-th eigenpair.  If SENSE = 'N or 'V', RCONDE is not refer‐
187               enced.
188
189       RCONDV  (output) DOUBLE PRECISION array, dimension (N)
190               If  SENSE = 'V' or 'B', the estimated reciprocal condition num‐
191               bers of the eigenvectors, stored in consecutive elements of the
192               array.  For  a  complex eigenvector two consecutive elements of
193               RCONDV are set to the same value. If the eigenvalues cannot  be
194               reordered to compute RCONDV(j), RCONDV(j) is set to 0; this can
195               only occur when the true value would be very small anyway.   If
196               SENSE = 'N' or 'E', RCONDV is not referenced.
197
198       WORK       (workspace/output)   DOUBLE   PRECISION   array,   dimension
199       (MAX(1,LWORK))
200               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
201
202       LWORK   (input) INTEGER
203               The dimension of the array WORK. LWORK >= max(1,2*N).  If  BAL‐
204               ANC  =  'S'  or  'B',  or JOBVL = 'V', or JOBVR = 'V', LWORK >=
205               max(1,6*N).  If SENSE = 'E' or 'B', LWORK >=  max(1,10*N).   If
206               SENSE = 'V' or 'B', LWORK >= 2*N*N+8*N+16.
207
208               If  LWORK  = -1, then a workspace query is assumed; the routine
209               only calculates the optimal size of  the  WORK  array,  returns
210               this  value  as the first entry of the WORK array, and no error
211               message related to LWORK is issued by XERBLA.
212
213       IWORK   (workspace) INTEGER array, dimension (N+6)
214               If SENSE = 'E', IWORK is not referenced.
215
216       BWORK   (workspace) LOGICAL array, dimension (N)
217               If SENSE = 'N', BWORK is not referenced.
218
219       INFO    (output) INTEGER
220               = 0:  successful exit
221               < 0:  if INFO = -i, the i-th argument had an illegal value.
222               = 1,...,N: The QZ iteration failed.  No eigenvectors have  been
223               calculated,  but  ALPHAR(j),  ALPHAI(j),  and BETA(j) should be
224               correct for j=INFO+1,...,N.  > N:  =N+1: other than  QZ  itera‐
225               tion failed in DHGEQZ.
226               =N+2: error return from DTGEVC.
227

FURTHER DETAILS

229       Balancing  a matrix pair (A,B) includes, first, permuting rows and col‐
230       umns to  isolate  eigenvalues,  second,  applying  diagonal  similarity
231       transformation  to the rows and columns to make the rows and columns as
232       close in norm as possible. The computed  reciprocal  condition  numbers
233       correspond  to the balanced matrix. Permuting rows and columns will not
234       change the condition numbers (in exact arithmetic) but diagonal scaling
235       will.   For  further  explanation of balancing, see section 4.11.1.2 of
236       LAPACK Users' Guide.
237
238       An approximate error bound on the chordal  distance  between  the  i-th
239       computed generalized eigenvalue w and the corresponding exact eigenval‐
240       ue lambda is
241
242            chord(w, lambda) <= EPS * norm(ABNRM, BBNRM) / RCONDE(I)
243
244       An approximate error bound for the  angle  between  the  i-th  computed
245       eigenvector VL(i) or VR(i) is given by
246
247            EPS * norm(ABNRM, BBNRM) / DIF(i).
248
249       For  further explanation of the reciprocal condition numbers RCONDE and
250       RCONDV, see section 4.11 of LAPACK User's Guide.
251
252
253
254
255 LAPACK driver routine (version 3.N1o)vember 2006                       DGGEVX(1)
Impressum