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

NAME

6       SGGEVX - 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
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
39       A generalized eigenvalue for a pair  of  matrices  (A,B)  is  a  scalar
40       lambda or a ratio alpha/beta = lambda, such that A - lambda*B is singu‐
41       lar. It is usually represented as the pair (alpha,beta), as there is  a
42       reasonable interpretation for beta=0, and even for both being zero.
43
44       The right eigenvector v(j) corresponding to the eigenvalue lambda(j) of
45       (A,B) satisfies
46
47                        A * v(j) = lambda(j) * B * v(j) .
48
49       The left eigenvector u(j) corresponding to the eigenvalue lambda(j)  of
50       (A,B) satisfies
51
52                        u(j)**H * A  = lambda(j) * u(j)**H * B.
53
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.  = 'N':  do not
61               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) REAL 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 real 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) REAL 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 real Schur form of the "balanced" ver‐
100               sions of the input A and B.
101
102       LDB     (input) INTEGER
103               The leading dimension of B.  LDB >= max(1,N).
104
105       ALPHAR  (output) REAL array, dimension (N)
106               ALPHAI  (output) REAL array,  dimension  (N)  BETA     (output)
107               REAL    array,    dimension   (N)   On   exit,   (ALPHAR(j)   +
108               ALPHAI(j)*i)/BETA(j), j=1,...,N, will be the generalized eigen‐
109               values.   If  ALPHAI(j)  is  zero,  then the j-th eigenvalue is
110               real; if positive, then the j-th and (j+1)-st eigenvalues are a
111               complex conjugate pair, with ALPHAI(j+1) negative.
112
113               Note: the quotients ALPHAR(j)/BETA(j) and ALPHAI(j)/BETA(j) may
114               easily over- or underflow, and BETA(j) may even be zero.  Thus,
115               the  user  should avoid naively computing the ratio ALPHA/BETA.
116               However, ALPHAR and ALPHAI will be always less than and usually
117               comparable with norm(A) in magnitude, and BETA always less than
118               and usually comparable with norm(B).
119
120       VL      (output) REAL array, dimension (LDVL,N)
121               If JOBVL = 'V', the left eigenvectors u(j) are stored one after
122               another in the columns of VL, in the same order as their eigen‐
123               values. If the j-th eigenvalue is real, then  u(j)  =  VL(:,j),
124               the  j-th  column  of  VL. If the j-th and (j+1)-th eigenvalues
125               form a complex conjugate pair, then u(j) =  VL(:,j)+i*VL(:,j+1)
126               and  u(j+1)  =  VL(:,j)-i*VL(:,j+1).   Each eigenvector will be
127               scaled so the largest component have abs(real part) + abs(imag.
128               part) = 1.  Not referenced if JOBVL = 'N'.
129
130       LDVL    (input) INTEGER
131               The leading dimension of the matrix VL. LDVL >= 1, and if JOBVL
132               = 'V', LDVL >= N.
133
134       VR      (output) REAL array, dimension (LDVR,N)
135               If JOBVR = 'V', the right  eigenvectors  v(j)  are  stored  one
136               after  another in the columns of VR, in the same order as their
137               eigenvalues. If the  j-th  eigenvalue  is  real,  then  v(j)  =
138               VR(:,j), the j-th column of VR. If the j-th and (j+1)-th eigen‐
139               values  form  a   complex   conjugate   pair,   then   v(j)   =
140               VR(:,j)+i*VR(:,j+1)  and  v(j+1)  =  VR(:,j)-i*VR(:,j+1).  Each
141               eigenvector will  be  scaled  so  the  largest  component  have
142               abs(real  part) + abs(imag. part) = 1.  Not referenced if JOBVR
143               = 'N'.
144
145       LDVR    (input) INTEGER
146               The leading dimension of the matrix VR. LDVR >= 1, and if JOBVR
147               = 'V', LDVR >= N.
148
149       ILO     (output) INTEGER
150               IHI      (output)  INTEGER  ILO and IHI are integer values such
151               that on exit A(i,j) = 0 and B(i,j) =  0  if  i  >  j  and  j  =
152               1,...,ILO-1  or i = IHI+1,...,N.  If BALANC = 'N' or 'S', ILO =
153               1 and IHI = N.
154
155       LSCALE  (output) REAL array, dimension (N)
156               Details of the permutations and scaling factors applied to  the
157               left  side of A and B.  If PL(j) is the index of the row inter‐
158               changed with row j, and DL(j) is the scaling factor applied  to
159               row j, then LSCALE(j) = PL(j)  for j = 1,...,ILO-1 = DL(j)  for
160               j = ILO,...,IHI = PL(j)  for j =  IHI+1,...,N.   The  order  in
161               which the interchanges are made is N to IHI+1, then 1 to ILO-1.
162
163       RSCALE  (output) REAL array, dimension (N)
164               Details  of the permutations and scaling factors applied to the
165               right side of A and B.  If PR(j) is the  index  of  the  column
166               interchanged  with  column  j,  and DR(j) is the scaling factor
167               applied  to  column  j,  then  RSCALE(j)  =  PR(j)   for  j   =
168               1,...,ILO-1  =  DR(j)   for  j  =  ILO,...,IHI = PR(j)  for j =
169               IHI+1,...,N The order in which the interchanges are made  is  N
170               to IHI+1, then 1 to ILO-1.
171
172       ABNRM   (output) REAL
173               The one-norm of the balanced matrix A.
174
175       BBNRM   (output) REAL
176               The one-norm of the balanced matrix B.
177
178       RCONDE  (output) REAL array, dimension (N)
179               If  SENSE = 'E' or 'B', the reciprocal condition numbers of the
180               eigenvalues, stored in consecutive elements of the array.   For
181               a  complex  conjugate  pair of eigenvalues two consecutive ele‐
182               ments of RCONDE are set to  the  same  value.  Thus  RCONDE(j),
183               RCONDV(j),  and the j-th columns of VL and VR all correspond to
184               the j-th eigenpair.  If SENSE = 'N' or 'V', RCONDE is not  ref‐
185               erenced.
186
187       RCONDV  (output) REAL array, dimension (N)
188               If  SENSE = 'V' or 'B', the estimated reciprocal condition num‐
189               bers of the eigenvectors, stored in consecutive elements of the
190               array.  For  a  complex eigenvector two consecutive elements of
191               RCONDV are set to the same value. If the eigenvalues cannot  be
192               reordered to compute RCONDV(j), RCONDV(j) is set to 0; this can
193               only occur when the true value would be very small anyway.   If
194               SENSE = 'N' or 'E', RCONDV is not referenced.
195
196       WORK    (workspace/output) REAL array, dimension (MAX(1,LWORK))
197               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
198
199       LWORK   (input) INTEGER
200               The  dimension of the array WORK. LWORK >= max(1,2*N).  If BAL‐
201               ANC = 'S' or 'B', or JOBVL = 'V', or  JOBVR  =  'V',  LWORK  >=
202               max(1,6*N).   If SENSE = 'E', LWORK >= max(1,10*N).  If SENSE =
203               'V' or 'B', LWORK >= 2*N*N+8*N+16.
204
205               If LWORK = -1, then a workspace query is assumed;  the  routine
206               only  calculates  the  optimal  size of the WORK array, returns
207               this value as the first entry of the WORK array, and  no  error
208               message related to LWORK is issued by XERBLA.
209
210       IWORK   (workspace) INTEGER array, dimension (N+6)
211               If SENSE = 'E', IWORK is not referenced.
212
213       BWORK   (workspace) LOGICAL array, dimension (N)
214               If SENSE = 'N', BWORK is not referenced.
215
216       INFO    (output) INTEGER
217               = 0:  successful exit
218               < 0:  if INFO = -i, the i-th argument had an illegal value.
219               =  1,...,N: The QZ iteration failed.  No eigenvectors have been
220               calculated, but ALPHAR(j), ALPHAI(j),  and  BETA(j)  should  be
221               correct  for  j=INFO+1,...,N.  > N:  =N+1: other than QZ itera‐
222               tion failed in SHGEQZ.
223               =N+2: error return from STGEVC.
224

FURTHER DETAILS

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