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

NAME

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

SYNOPSIS

9       SUBROUTINE SGGEVX( 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           REAL           ABNRM, BBNRM
19
20           LOGICAL        BWORK( * )
21
22           INTEGER        IWORK( * )
23
24           REAL           A( LDA, * ), ALPHAI( * ), ALPHAR( * ), B( LDB, *  ),
25                          BETA(  *  ),  LSCALE( * ), RCONDE( * ), RCONDV( * ),
26                          RSCALE( * ), VL( LDVL, * ), VR( LDVR, * ), WORK( * )
27

PURPOSE

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

ARGUMENTS

50       BALANC  (input) CHARACTER*1
51               Specifies  the  balance option to be performed.  = 'N':  do not
52               diagonally scale or permute;
53               = 'P':  permute only;
54               = 'S':  scale only;
55               = 'B':  both permute and scale.  Computed reciprocal  condition
56               numbers will be for the matrices after permuting and/or balanc‐
57               ing. Permuting does not  change  condition  numbers  (in  exact
58               arithmetic), but balancing does.
59
60       JOBVL   (input) CHARACTER*1
61               = 'N':  do not compute the left generalized eigenvectors;
62               = 'V':  compute the left generalized eigenvectors.
63
64       JOBVR   (input) CHARACTER*1
65               = 'N':  do not compute the right generalized eigenvectors;
66               = 'V':  compute the right generalized eigenvectors.
67
68       SENSE   (input) CHARACTER*1
69               Determines  which reciprocal condition numbers are computed.  =
70               'N': none are computed;
71               = 'E': computed for eigenvalues only;
72               = 'V': computed for eigenvectors only;
73               = 'B': computed for eigenvalues and eigenvectors.
74
75       N       (input) INTEGER
76               The order of the matrices A, B, VL, and VR.  N >= 0.
77
78       A       (input/output) REAL array, dimension (LDA, N)
79               On entry, the matrix A in the pair (A,B).  On exit, A has  been
80               overwritten. If JOBVL='V' or JOBVR='V' or both, then A contains
81               the first part of the real Schur form of  the  "balanced"  ver‐
82               sions of the input A and B.
83
84       LDA     (input) INTEGER
85               The leading dimension of A.  LDA >= max(1,N).
86
87       B       (input/output) REAL array, dimension (LDB, N)
88               On  entry, the matrix B in the pair (A,B).  On exit, B has been
89               overwritten. If JOBVL='V' or JOBVR='V' or both, then B contains
90               the  second  part of the real Schur form of the "balanced" ver‐
91               sions of the input A and B.
92
93       LDB     (input) INTEGER
94               The leading dimension of B.  LDB >= max(1,N).
95
96       ALPHAR  (output) REAL array, dimension (N)
97               ALPHAI  (output) REAL array,  dimension  (N)  BETA     (output)
98               REAL    array,    dimension   (N)   On   exit,   (ALPHAR(j)   +
99               ALPHAI(j)*i)/BETA(j), j=1,...,N, will be the generalized eigen‐
100               values.   If  ALPHAI(j)  is  zero,  then the j-th eigenvalue is
101               real; if positive, then the j-th and (j+1)-st eigenvalues are a
102               complex  conjugate  pair, with ALPHAI(j+1) negative.  Note: the
103               quotients ALPHAR(j)/BETA(j) and  ALPHAI(j)/BETA(j)  may  easily
104               over-  or  underflow,  and BETA(j) may even be zero.  Thus, the
105               user should avoid naively computing the ratio ALPHA/BETA.  How‐
106               ever,  ALPHAR  and  ALPHAI will be always less than and usually
107               comparable with norm(A) in magnitude, and BETA always less than
108               and usually comparable with norm(B).
109
110       VL      (output) REAL array, dimension (LDVL,N)
111               If JOBVL = 'V', the left eigenvectors u(j) are stored one after
112               another in the columns of VL, in the same order as their eigen‐
113               values.  If  the  j-th eigenvalue is real, then u(j) = VL(:,j),
114               the j-th column of VL. If the  j-th  and  (j+1)-th  eigenvalues
115               form  a complex conjugate pair, then u(j) = VL(:,j)+i*VL(:,j+1)
116               and u(j+1) = VL(:,j)-i*VL(:,j+1).   Each  eigenvector  will  be
117               scaled so the largest component have abs(real part) + abs(imag.
118               part) = 1.  Not referenced if JOBVL = 'N'.
119
120       LDVL    (input) INTEGER
121               The leading dimension of the matrix VL. LDVL >= 1, and if JOBVL
122               = 'V', LDVL >= N.
123
124       VR      (output) REAL array, dimension (LDVR,N)
125               If  JOBVR  =  'V',  the  right eigenvectors v(j) are stored one
126               after another in the columns of VR, in the same order as  their
127               eigenvalues.  If  the  j-th  eigenvalue  is  real,  then v(j) =
128               VR(:,j), the j-th column of VR. If the j-th and (j+1)-th eigen‐
129               values   form   a   complex   conjugate   pair,   then  v(j)  =
130               VR(:,j)+i*VR(:,j+1) and  v(j+1)  =  VR(:,j)-i*VR(:,j+1).   Each
131               eigenvector  will  be  scaled  so  the  largest  component have
132               abs(real part) + abs(imag. part) = 1.  Not referenced if  JOBVR
133               = '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) REAL 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) REAL 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) REAL
163               The one-norm of the balanced matrix A.
164
165       BBNRM   (output) REAL
166               The one-norm of the balanced matrix B.
167
168       RCONDE  (output) REAL array, dimension (N)
169               If SENSE = 'E' or 'B', the reciprocal condition numbers of  the
170               eigenvalues,  stored in consecutive elements of the array.  For
171               a complex conjugate pair of eigenvalues  two  consecutive  ele‐
172               ments  of  RCONDE  are  set  to the same value. Thus RCONDE(j),
173               RCONDV(j), and the j-th columns of VL and VR all correspond  to
174               the  j-th eigenpair.  If SENSE = 'N' or 'V', RCONDE is not ref‐
175               erenced.
176
177       RCONDV  (output) REAL array, dimension (N)
178               If SENSE = 'V' or 'B', the estimated reciprocal condition  num‐
179               bers of the eigenvectors, stored in consecutive elements of the
180               array. For a complex eigenvector two  consecutive  elements  of
181               RCONDV  are set to the same value. If the eigenvalues cannot be
182               reordered to compute RCONDV(j), RCONDV(j) is set to 0; this can
183               only  occur when the true value would be very small anyway.  If
184               SENSE = 'N' or 'E', RCONDV is not referenced.
185
186       WORK    (workspace/output) REAL array, dimension (MAX(1,LWORK))
187               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
188
189       LWORK   (input) INTEGER
190               The dimension of the array WORK. LWORK >= max(1,2*N).  If  BAL‐
191               ANC  =  'S'  or  'B',  or JOBVL = 'V', or JOBVR = 'V', LWORK >=
192               max(1,6*N).  If SENSE = 'E', LWORK >= max(1,10*N).  If SENSE  =
193               'V'  or  'B',  LWORK  >=  2*N*N+8*N+16.   If LWORK = -1, then a
194               workspace query is assumed; the  routine  only  calculates  the
195               optimal size of the WORK array, returns this value as the first
196               entry of the WORK array, and no error message related to  LWORK
197               is issued by XERBLA.
198
199       IWORK   (workspace) INTEGER array, dimension (N+6)
200               If SENSE = 'E', IWORK is not referenced.
201
202       BWORK   (workspace) LOGICAL array, dimension (N)
203               If SENSE = 'N', BWORK is not referenced.
204
205       INFO    (output) INTEGER
206               = 0:  successful exit
207               < 0:  if INFO = -i, the i-th argument had an illegal value.
208               =  1,...,N: The QZ iteration failed.  No eigenvectors have been
209               calculated, but ALPHAR(j), ALPHAI(j),  and  BETA(j)  should  be
210               correct  for  j=INFO+1,...,N.  > N:  =N+1: other than QZ itera‐
211               tion failed in SHGEQZ.
212               =N+2: error return from STGEVC.
213

FURTHER DETAILS

215       Balancing a matrix pair (A,B) includes, first, permuting rows and  col‐
216       umns  to  isolate  eigenvalues,  second,  applying  diagonal similarity
217       transformation to the rows and columns to make the rows and columns  as
218       close  in  norm  as possible. The computed reciprocal condition numbers
219       correspond to the balanced matrix. Permuting rows and columns will  not
220       change the condition numbers (in exact arithmetic) but diagonal scaling
221       will.  For further explanation of balancing, see  section  4.11.1.2  of
222       LAPACK Users' Guide.
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            chord(w,  lambda)  <=  EPS  *  norm(ABNRM,  BBNRM)  / RCONDE(I) An
227       approximate error bound for the angle between the i-th computed  eigen‐
228       vector VL(i) or VR(i) is given by
229            EPS * norm(ABNRM, BBNRM) / DIF(i).
230       For  further explanation of the reciprocal condition numbers RCONDE and
231       RCONDV, see section 4.11 of LAPACK User's Guide.
232
233
234
235 LAPACK driver routine (version 3.N2o)vember 2008                       SGGEVX(1)
Impressum