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

NAME

6       SGGESX  -  computes  for  a  pair  of N-by-N real nonsymmetric matrices
7       (A,B), the generalized eigenvalues, the real Schur form (S,T), and,
8

SYNOPSIS

10       SUBROUTINE SGGESX( JOBVSL, JOBVSR, SORT, SELCTG, SENSE, N, A,  LDA,  B,
11                          LDB,  SDIM,  ALPHAR,  ALPHAI, BETA, VSL, LDVSL, VSR,
12                          LDVSR, RCONDE, RCONDV, WORK, LWORK,  IWORK,  LIWORK,
13                          BWORK, INFO )
14
15           CHARACTER      JOBVSL, JOBVSR, SENSE, SORT
16
17           INTEGER        INFO, LDA, LDB, LDVSL, LDVSR, LIWORK, LWORK, N, SDIM
18
19           LOGICAL        BWORK( * )
20
21           INTEGER        IWORK( * )
22
23           REAL           A(  LDA, * ), ALPHAI( * ), ALPHAR( * ), B( LDB, * ),
24                          BETA( * ), RCONDE( 2 ), RCONDV( 2 ), VSL(  LDVSL,  *
25                          ), VSR( LDVSR, * ), WORK( * )
26
27           LOGICAL        SELCTG
28
29           EXTERNAL       SELCTG
30

PURPOSE

32       SGGESX  computes for a pair of N-by-N real nonsymmetric matrices (A,B),
33       the generalized eigenvalues, the real Schur form  (S,T),  and,  option‐
34       ally,  the  left  and/or right matrices of Schur vectors (VSL and VSR).
35       This gives the generalized Schur factorization
36            (A,B) = ( (VSL) S (VSR)**T, (VSL) T (VSR)**T )
37       Optionally, it also orders the eigenvalues so that a  selected  cluster
38       of  eigenvalues  appears  in  the  leading diagonal blocks of the upper
39       quasi-triangular matrix S and the upper triangular matrix T; computes a
40       reciprocal condition number for the average of the selected eigenvalues
41       (RCONDE); and computes a reciprocal condition number for the right  and
42       left  deflating  subspaces  corresponding  to  the selected eigenvalues
43       (RCONDV). The leading columns of VSL and VSR then form  an  orthonormal
44       basis  for the corresponding left and right eigenspaces (deflating sub‐
45       spaces).
46       A generalized eigenvalue for a pair of matrices (A,B) is a scalar w  or
47       a  ratio alpha/beta = w, such that  A - w*B is singular.  It is usually
48       represented as the pair (alpha,beta), as there is a  reasonable  inter‐
49       pretation  for beta=0 or for both being zero.  A pair of matrices (S,T)
50       is in generalized real Schur form if T is upper  triangular  with  non-
51       negative  diagonal  and  S  is  block  upper triangular with 1-by-1 and
52       2-by-2 blocks.  1-by-1 blocks correspond to real generalized  eigenval‐
53       ues, while 2-by-2 blocks of S will be "standardized" by making the cor‐
54       responding elements of T have the form:
55               [  a  0  ]
56               [  0  b  ]
57       and the pair of corresponding 2-by-2 blocks in S and T will have a com‐
58       plex conjugate pair of generalized eigenvalues.
59

ARGUMENTS

61       JOBVSL  (input) CHARACTER*1
62               = 'N':  do not compute the left Schur vectors;
63               = 'V':  compute the left Schur vectors.
64
65       JOBVSR  (input) CHARACTER*1
66               = 'N':  do not compute the right Schur vectors;
67               = 'V':  compute the right Schur vectors.
68
69       SORT    (input) CHARACTER*1
70               Specifies whether or not to order the eigenvalues on the diago‐
71               nal of the generalized Schur form.  = 'N':  Eigenvalues are not
72               ordered;
73               = 'S':  Eigenvalues are ordered (see SELCTG).
74
75       SELCTG  (external procedure) LOGICAL FUNCTION of three REAL arguments
76               SELCTG must be declared EXTERNAL in the calling subroutine.  If
77               SORT = 'N', SELCTG is not referenced.  If SORT = 'S', SELCTG is
78               used to select eigenvalues to sort to the top left of the Schur
79               form.  An eigenvalue (ALPHAR(j)+ALPHAI(j))/BETA(j) is  selected
80               if  SELCTG(ALPHAR(j),ALPHAI(j),BETA(j)) is true; i.e. if either
81               one of a complex conjugate pair  of  eigenvalues  is  selected,
82               then  both  complex  eigenvalues  are  selected.   Note  that a
83               selected   complex   eigenvalue   may   no    longer    satisfy
84               SELCTG(ALPHAR(j),ALPHAI(j),BETA(j))  =  .TRUE.  after ordering,
85               since ordering may change  the  value  of  complex  eigenvalues
86               (especially if the eigenvalue is ill-conditioned), in this case
87               INFO is set to N+3.
88
89       SENSE   (input) CHARACTER*1
90               Determines which reciprocal condition numbers are computed.   =
91               'N' : None are computed;
92               = 'E' : Computed for average of selected eigenvalues only;
93               = 'V' : Computed for selected deflating subspaces only;
94               =  'B'  : Computed for both.  If SENSE = 'E', 'V', or 'B', SORT
95               must equal 'S'.
96
97       N       (input) INTEGER
98               The order of the matrices A, B, VSL, and VSR.  N >= 0.
99
100       A       (input/output) REAL array, dimension (LDA, N)
101               On entry, the first of the pair of matrices.  On  exit,  A  has
102               been overwritten by its generalized Schur form S.
103
104       LDA     (input) INTEGER
105               The leading dimension of A.  LDA >= max(1,N).
106
107       B       (input/output) REAL array, dimension (LDB, N)
108               On  entry,  the second of the pair of matrices.  On exit, B has
109               been overwritten by its generalized Schur form T.
110
111       LDB     (input) INTEGER
112               The leading dimension of B.  LDB >= max(1,N).
113
114       SDIM    (output) INTEGER
115               If SORT = 'N', SDIM = 0.  If SORT = 'S', SDIM = number  of  ei‐
116               genvalues  (after  sorting) for which SELCTG is true.  (Complex
117               conjugate pairs for which SELCTG is true for either  eigenvalue
118               count as 2.)
119
120       ALPHAR  (output) REAL array, dimension (N)
121               ALPHAI   (output)  REAL  array,  dimension (N) BETA    (output)
122               REAL   array,   dimension   (N)   On   exit,    (ALPHAR(j)    +
123               ALPHAI(j)*i)/BETA(j), j=1,...,N, will be the generalized eigen‐
124               values.  ALPHAR(j) + ALPHAI(j)*i and BETA(j),j=1,...,N  are the
125               diagonals  of the complex Schur form (S,T) that would result if
126               the 2-by-2 diagonal blocks of the real Schur form of (A,B) were
127               further reduced to triangular form using 2-by-2 complex unitary
128               transformations.  If ALPHAI(j) is zero, then the j-th eigenval‐
129               ue is real; if positive, then the j-th and (j+1)-st eigenvalues
130               are a complex conjugate pair, with ALPHAI(j+1) negative.  Note:
131               the  quotients ALPHAR(j)/BETA(j) and ALPHAI(j)/BETA(j) may eas‐
132               ily over- or underflow, and BETA(j) may even  be  zero.   Thus,
133               the  user  should  avoid naively computing the ratio.  However,
134               ALPHAR and ALPHAI will be always less than and usually compara‐
135               ble  with  norm(A)  in magnitude, and BETA always less than and
136               usually comparable with norm(B).
137
138       VSL     (output) REAL array, dimension (LDVSL,N)
139               If JOBVSL = 'V', VSL will contain the left Schur vectors.   Not
140               referenced if JOBVSL = 'N'.
141
142       LDVSL   (input) INTEGER
143               The leading dimension of the matrix VSL. LDVSL >=1, and if JOB‐
144               VSL = 'V', LDVSL >= N.
145
146       VSR     (output) REAL array, dimension (LDVSR,N)
147               If JOBVSR = 'V', VSR will contain the right Schur vectors.  Not
148               referenced if JOBVSR = 'N'.
149
150       LDVSR   (input) INTEGER
151               The  leading  dimension  of  the matrix VSR. LDVSR >= 1, and if
152               JOBVSR = 'V', LDVSR >= N.
153
154       RCONDE  (output) REAL array, dimension ( 2 )
155               If SENSE = 'E' or 'B',  RCONDE(1)  and  RCONDE(2)  contain  the
156               reciprocal  condition  numbers  for the average of the selected
157               eigenvalues.  Not referenced if SENSE = 'N' or 'V'.
158
159       RCONDV  (output) REAL array, dimension ( 2 )
160               If SENSE = 'V' or 'B',  RCONDV(1)  and  RCONDV(2)  contain  the
161               reciprocal  condition  numbers  for the selected deflating sub‐
162               spaces.  Not referenced if SENSE = 'N' or 'E'.
163
164       WORK    (workspace/output) REAL array, dimension (MAX(1,LWORK))
165               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
166
167       LWORK   (input) INTEGER
168               The dimension of the array WORK.  If N = 0, LWORK >= 1, else if
169               SENSE = 'E', 'V', or 'B', LWORK >= max( 8*N, 6*N+16, 2*SDIM*(N-
170               SDIM)  ),  else  LWORK  >=  max(  8*N,  6*N+16  ).   Note  that
171               2*SDIM*(N-SDIM)  <=  N*N/2.   Note  also  that an error is only
172               returned if LWORK < max( 8*N, 6*N+16), but if SENSE  =  'E'  or
173               'V' or 'B' this may not be large enough.  If LWORK = -1, then a
174               workspace query is assumed; the  routine  only  calculates  the
175               bound  on  the  optimal  size of the WORK array and the minimum
176               size of the IWORK array, returns  these  values  as  the  first
177               entries  of  the  WORK  and  IWORK arrays, and no error message
178               related to LWORK or LIWORK is issued by XERBLA.
179
180       IWORK   (workspace) INTEGER array, dimension (MAX(1,LIWORK))
181               On exit, if INFO = 0, IWORK(1) returns the minimum LIWORK.
182
183       LIWORK  (input) INTEGER
184               The dimension of the array IWORK.  If SENSE = 'N'  or  N  =  0,
185               LIWORK  >=  1, otherwise LIWORK >= N+6.  If LIWORK = -1, then a
186               workspace query is assumed; the  routine  only  calculates  the
187               bound  on  the  optimal  size of the WORK array and the minimum
188               size of the IWORK array, returns  these  values  as  the  first
189               entries  of  the  WORK  and  IWORK arrays, and no error message
190               related to LWORK or LIWORK is issued by XERBLA.
191
192       BWORK   (workspace) LOGICAL array, dimension (N)
193               Not referenced if SORT = 'N'.
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.  (A,B)  are  not  in  Schur
199               form,  but  ALPHAR(j), ALPHAI(j), and BETA(j) should be correct
200               for j=INFO+1,...,N.  > N:  =N+1: other than QZ iteration failed
201               in SHGEQZ
202               =N+2: after reordering, roundoff changed values of some complex
203               eigenvalues so that  leading  eigenvalues  in  the  Generalized
204               Schur  form no longer satisfy SELCTG=.TRUE.  This could also be
205               caused due to scaling.  =N+3: reordering failed in STGSEN.
206

FURTHER DETAILS

208       An approximate (asymptotic) bound on the average absolute error of  the
209       selected eigenvalues is
210            EPS * norm((A, B)) / RCONDE( 1 ).
211       An  approximate  (asymptotic) bound on the maximum angular error in the
212       computed deflating subspaces is
213            EPS * norm((A, B)) / RCONDV( 2 ).
214       See LAPACK User's Guide, section 4.11 for more information.
215
216
217
218 LAPACK driver routine (version 3.N2o)vember 2008                       SGGESX(1)
Impressum