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

NAME

6       ZGGEVX  -  for a pair of N-by-N complex nonsymmetric matrices (A,B) the
7       generalized eigenvalues, and optionally, the left and/or right general‐
8       ized eigenvectors
9

SYNOPSIS

11       SUBROUTINE ZGGEVX( BALANC,  JOBVL,  JOBVR,  SENSE,  N,  A, LDA, B, LDB,
12                          ALPHA, BETA, VL, LDVL, VR, LDVR, ILO,  IHI,  LSCALE,
13                          RSCALE,  ABNRM,  BBNRM, RCONDE, RCONDV, WORK, LWORK,
14                          RWORK, IWORK, BWORK, INFO )
15
16           CHARACTER      BALANC, JOBVL, JOBVR, SENSE
17
18           INTEGER        IHI, ILO, INFO, LDA, LDB, LDVL, LDVR, LWORK, N
19
20           DOUBLE         PRECISION ABNRM, BBNRM
21
22           LOGICAL        BWORK( * )
23
24           INTEGER        IWORK( * )
25
26           DOUBLE         PRECISION LSCALE( * ), RCONDE( *  ),  RCONDV(  *  ),
27                          RSCALE( * ), RWORK( * )
28
29           COMPLEX*16     A( LDA, * ), ALPHA( * ), B( LDB, * ), BETA( * ), VL(
30                          LDVL, * ), VR( LDVR, * ), WORK( * )
31

PURPOSE

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

ARGUMENTS

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

FURTHER DETAILS

214       Balancing a matrix pair (A,B) includes, first, permuting rows and  col‐
215       umns  to  isolate  eigenvalues,  second,  applying  diagonal similarity
216       transformation to the rows and columns to make the rows and columns  as
217       close  in  norm  as possible. The computed reciprocal condition numbers
218       correspond to the balanced matrix. Permuting rows and columns will  not
219       change the condition numbers (in exact arithmetic) but diagonal scaling
220       will.  For further explanation of balancing, see  section  4.11.1.2  of
221       LAPACK Users' Guide.
222
223       An  approximate  error  bound  on the chordal distance between the i-th
224       computed generalized eigenvalue w and the corresponding exact eigenval‐
225       ue lambda is
226
227            chord(w, lambda) <= EPS * norm(ABNRM, BBNRM) / RCONDE(I)
228
229       An  approximate  error  bound  for  the angle between the i-th computed
230       eigenvector VL(i) or VR(i) is given by
231
232            EPS * norm(ABNRM, BBNRM) / DIF(i).
233
234       For further explanation of the reciprocal condition numbers RCONDE  and
235       RCONDV, see section 4.11 of LAPACK User's Guide.
236
237
238
239
240 LAPACK driver routine (version 3.N1o)vember 2006                       ZGGEVX(1)
Impressum