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

NAME

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

SYNOPSIS

10       SUBROUTINE CGGESX( JOBVSL, JOBVSR, SORT, SELCTG, SENSE, N, A,  LDA,  B,
11                          LDB,  SDIM,  ALPHA,  BETA,  VSL,  LDVSL, VSR, LDVSR,
12                          RCONDE, RCONDV, WORK, LWORK, RWORK,  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           RCONDE( 2 ), RCONDV( 2 ), RWORK( * )
24
25           COMPLEX        A(  LDA,  *  ),  ALPHA( * ), B( LDB, * ), BETA( * ),
26                          VSL( LDVSL, * ), VSR( LDVSR, * ), WORK( * )
27
28           LOGICAL        SELCTG
29
30           EXTERNAL       SELCTG
31

PURPOSE

33       CGGESX computes for a pair  of  N-by-N  complex  nonsymmetric  matrices
34       (A,B),  the generalized eigenvalues, the complex Schur form (S,T), and,
35       optionally, the left and/or right matrices of Schur  vectors  (VSL  and
36       VSR).  This gives the generalized Schur factorization
37            (A,B) = ( (VSL) S (VSR)**H, (VSL) T (VSR)**H )
38       where (VSR)**H is the conjugate-transpose of VSR.
39       Optionally,  it  also orders the eigenvalues so that a selected cluster
40       of eigenvalues appears in the leading diagonal blocks of the upper tri‐
41       angular matrix S and the upper triangular matrix T; computes a recipro‐
42       cal condition number  for  the  average  of  the  selected  eigenvalues
43       (RCONDE);  and computes a reciprocal condition number for the right and
44       left deflating subspaces  corresponding  to  the  selected  eigenvalues
45       (RCONDV).  The  leading columns of VSL and VSR then form an orthonormal
46       basis for the corresponding left and right eigenspaces (deflating  sub‐
47       spaces).
48       A  generalized eigenvalue for a pair of matrices (A,B) is a scalar w or
49       a ratio alpha/beta = w, such that  A - w*B is singular.  It is  usually
50       represented  as  the pair (alpha,beta), as there is a reasonable inter‐
51       pretation for beta=0 or for both being zero.  A pair of matrices  (S,T)
52       is in generalized complex Schur form if T is upper triangular with non-
53       negative diagonal and S is upper triangular.
54

ARGUMENTS

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