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

NAME

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

SYNOPSIS

10       SUBROUTINE ZGGESX( 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           DOUBLE         PRECISION RCONDE( 2 ), RCONDV( 2 ), RWORK( * )
24
25           COMPLEX*16     A(  LDA,  *  ),  ALPHA( * ), B( LDB, * ), BETA( * ),
26                          VSL( LDVSL, * ), VSR( LDVSR, * ), WORK( * )
27
28           LOGICAL        SELCTG
29
30           EXTERNAL       SELCTG
31

PURPOSE

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

ARGUMENTS

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