1CGGEVX(1)             LAPACK driver routine (version 3.2)            CGGEVX(1)
2
3
4

NAME

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

SYNOPSIS

11       SUBROUTINE CGGEVX( 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           REAL           ABNRM, BBNRM
21
22           LOGICAL        BWORK( * )
23
24           INTEGER        IWORK( * )
25
26           REAL           LSCALE( * ), RCONDE( * ), RCONDV( * ), RSCALE( *  ),
27                          RWORK( * )
28
29           COMPLEX        A( LDA, * ), ALPHA( * ), B( LDB, * ), BETA( * ), VL(
30                          LDVL, * ), VR( LDVR, * ), WORK( * )
31

PURPOSE

33       CGGEVX 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.  Optionally, it also computes a balanc‐
36       ing  transformation  to improve the conditioning of the eigenvalues and
37       eigenvectors (ILO, IHI, LSCALE, RSCALE, ABNRM, and  BBNRM),  reciprocal
38       condition  numbers  for the eigenvalues (RCONDE), and reciprocal condi‐
39       tion numbers for the right eigenvectors (RCONDV).
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       The right eigenvector v(j) corresponding to the eigenvalue lambda(j) of
45       (A,B) satisfies
46                        A * v(j) = lambda(j) * B * v(j) .
47       The left eigenvector u(j) corresponding to the eigenvalue lambda(j)  of
48       (A,B) satisfies
49                        u(j)**H * A  = lambda(j) * u(j)**H * B.
50       where u(j)**H is the conjugate-transpose of u(j).
51

ARGUMENTS

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

FURTHER DETAILS

205       Balancing  a matrix pair (A,B) includes, first, permuting rows and col‐
206       umns to  isolate  eigenvalues,  second,  applying  diagonal  similarity
207       transformation  to the rows and columns to make the rows and columns as
208       close in norm as possible. The computed  reciprocal  condition  numbers
209       correspond  to the balanced matrix. Permuting rows and columns will not
210       change the condition numbers (in exact arithmetic) but diagonal scaling
211       will.   For  further  explanation of balancing, see section 4.11.1.2 of
212       LAPACK Users' Guide.
213       An approximate error bound on the chordal  distance  between  the  i-th
214       computed generalized eigenvalue w and the corresponding exact eigenval‐
215       ue lambda is
216            chord(w, lambda) <=  EPS  *  norm(ABNRM,  BBNRM)  /  RCONDE(I)  An
217       approximate  error bound for the angle between the i-th computed eigen‐
218       vector VL(i) or VR(i) is given by
219            EPS * norm(ABNRM, BBNRM) / DIF(i).
220       For further explanation of the reciprocal condition numbers RCONDE  and
221       RCONDV, see section 4.11 of LAPACK User's Guide.
222
223
224
225 LAPACK driver routine (version 3.N2o)vember 2008                       CGGEVX(1)
Impressum