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

NAME

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

SYNOPSIS

9       SUBROUTINE DGGES( JOBVSL,  JOBVSR,  SORT,  SELCTG,  N,  A, LDA, B, LDB,
10                         SDIM, ALPHAR, ALPHAI, BETA, VSL, LDVSL,  VSR,  LDVSR,
11                         WORK, LWORK, BWORK, INFO )
12
13           CHARACTER     JOBVSL, JOBVSR, SORT
14
15           INTEGER       INFO, LDA, LDB, LDVSL, LDVSR, LWORK, N, SDIM
16
17           LOGICAL       BWORK( * )
18
19           DOUBLE        PRECISION  A(  LDA, * ), ALPHAI( * ), ALPHAR( * ), B(
20                         LDB, * ), BETA( * ), VSL( LDVSL, * ), VSR(  LDVSR,  *
21                         ), WORK( * )
22
23           LOGICAL       SELCTG
24
25           EXTERNAL      SELCTG
26

PURPOSE

28       DGGES  computes  for a pair of N-by-N real nonsymmetric matrices (A,B),
29       the generalized eigenvalues, the generalized  real  Schur  form  (S,T),
30       optionally,  the  left  and/or right matrices of Schur vectors (VSL and
31       VSR). This gives the generalized Schur factorization
32
33                (A,B) = ( (VSL)*S*(VSR)**T, (VSL)*T*(VSR)**T )
34
35       Optionally, it also orders the eigenvalues so that a  selected  cluster
36       of  eigenvalues  appears  in  the  leading diagonal blocks of the upper
37       quasi-triangular matrix S and the upper triangular matrix T.The leading
38       columns  of  VSL  and VSR then form an orthonormal basis for the corre‐
39       sponding left and right eigenspaces (deflating subspaces).
40
41       (If only the generalized eigenvalues are needed, use the  driver  DGGEV
42       instead, which is faster.)
43
44       A  generalized eigenvalue for a pair of matrices (A,B) is a scalar w or
45       a ratio alpha/beta = w, such that  A - w*B is singular.  It is  usually
46       represented  as  the pair (alpha,beta), as there is a reasonable inter‐
47       pretation for beta=0 or both being zero.
48
49       A pair of matrices (S,T) is in generalized real  Schur  form  if  T  is
50       upper triangular with non-negative diagonal and S is block upper trian‐
51       gular with 1-by-1 and 2-by-2 blocks.  1-by-1 blocks correspond to  real
52       generalized  eigenvalues,  while  2-by-2 blocks of S will be "standard‐
53       ized" by making the corresponding elements of T have the form:
54               [  a  0  ]
55               [  0  b  ]
56
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
60
61

ARGUMENTS

63       JOBVSL  (input) CHARACTER*1
64               = 'N':  do not compute the left Schur vectors;
65               = 'V':  compute the left Schur vectors.
66
67       JOBVSR  (input) CHARACTER*1
68               = 'N':  do not compute the right Schur vectors;
69               = 'V':  compute the right Schur vectors.
70
71       SORT    (input) CHARACTER*1
72               Specifies whether or not to order the eigenvalues on the diago‐
73               nal of the generalized Schur form.  = 'N':  Eigenvalues are not
74               ordered;
75               = 'S':  Eigenvalues are ordered (see SELCTG);
76
77       SELCTG  (external procedure) LOGICAL FUNCTION of three DOUBLE PRECISION
78       arguments
79               SELCTG must be declared EXTERNAL in the calling subroutine.  If
80               SORT = 'N', SELCTG is not referenced.  If SORT = 'S', SELCTG is
81               used to select eigenvalues to sort to the top left of the Schur
82               form.   An eigenvalue (ALPHAR(j)+ALPHAI(j))/BETA(j) is selected
83               if SELCTG(ALPHAR(j),ALPHAI(j),BETA(j)) is true; i.e. if  either
84               one  of  a  complex  conjugate pair of eigenvalues is selected,
85               then both complex eigenvalues are selected.
86
87               Note that in the ill-conditioned case, a selected  complex  ei‐
88               genvalue  may  no  longer  satisfy  SELCTG(ALPHAR(j),ALPHAI(j),
89               BETA(j)) = .TRUE. after ordering. INFO is to be set to  N+2  in
90               this case.
91
92       N       (input) INTEGER
93               The order of the matrices A, B, VSL, and VSR.  N >= 0.
94
95       A       (input/output) DOUBLE PRECISION array, dimension (LDA, N)
96               On  entry,  the  first of the pair of matrices.  On exit, A has
97               been overwritten by its generalized Schur form S.
98
99       LDA     (input) INTEGER
100               The leading dimension of A.  LDA >= max(1,N).
101
102       B       (input/output) DOUBLE PRECISION array, dimension (LDB, N)
103               On entry, the second of the pair of matrices.  On exit,  B  has
104               been overwritten by its generalized Schur form T.
105
106       LDB     (input) INTEGER
107               The leading dimension of B.  LDB >= max(1,N).
108
109       SDIM    (output) INTEGER
110               If  SORT  = 'N', SDIM = 0.  If SORT = 'S', SDIM = number of ei‐
111               genvalues (after sorting) for which SELCTG is  true.   (Complex
112               conjugate  pairs for which SELCTG is true for either eigenvalue
113               count as 2.)
114
115       ALPHAR  (output) DOUBLE PRECISION array, dimension (N)
116               ALPHAI  (output) DOUBLE PRECISION  array,  dimension  (N)  BETA
117               (output)   DOUBLE  PRECISION  array,  dimension  (N)  On  exit,
118               (ALPHAR(j) + ALPHAI(j)*i)/BETA(j), j=1,...,N, will be the  gen‐
119               eralized    eigenvalues.     ALPHAR(j)   +   ALPHAI(j)*i,   and
120               BETA(j),j=1,...,N are the diagonals of the complex  Schur  form
121               (S,T)  that  would  result if the 2-by-2 diagonal blocks of the
122               real Schur form of (A,B) were  further  reduced  to  triangular
123               form   using   2-by-2   complex  unitary  transformations.   If
124               ALPHAI(j) is zero, then the j-th eigenvalue is real;  if  posi‐
125               tive, then the j-th and (j+1)-st eigenvalues are a complex con‐
126               jugate pair, with ALPHAI(j+1) negative.
127
128               Note: the quotients ALPHAR(j)/BETA(j) and ALPHAI(j)/BETA(j) may
129               easily over- or underflow, and BETA(j) may even be zero.  Thus,
130               the user should avoid naively computing  the  ratio.   However,
131               ALPHAR and ALPHAI will be always less than and usually compara‐
132               ble with norm(A) in magnitude, and BETA always  less  than  and
133               usually comparable with norm(B).
134
135       VSL     (output) DOUBLE PRECISION array, dimension (LDVSL,N)
136               If  JOBVSL = 'V', VSL will contain the left Schur vectors.  Not
137               referenced if JOBVSL = 'N'.
138
139       LDVSL   (input) INTEGER
140               The leading dimension of the matrix VSL. LDVSL >=1, and if JOB‐
141               VSL = 'V', LDVSL >= N.
142
143       VSR     (output) DOUBLE PRECISION array, dimension (LDVSR,N)
144               If JOBVSR = 'V', VSR will contain the right Schur vectors.  Not
145               referenced if JOBVSR = 'N'.
146
147       LDVSR   (input) INTEGER
148               The leading dimension of the matrix VSR. LDVSR  >=  1,  and  if
149               JOBVSR = 'V', LDVSR >= N.
150
151       WORK       (workspace/output)   DOUBLE   PRECISION   array,   dimension
152       (MAX(1,LWORK))
153               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
154
155       LWORK   (input) INTEGER
156               The dimension of the array WORK.  If N = 0, LWORK  >=  1,  else
157               LWORK  >=  8*N+16.  For good performance , LWORK must generally
158               be larger.
159
160               If LWORK = -1, then a workspace query is assumed;  the  routine
161               only  calculates  the  optimal  size of the WORK array, returns
162               this value as the first entry of the WORK array, and  no  error
163               message related to LWORK is issued by XERBLA.
164
165       BWORK   (workspace) LOGICAL array, dimension (N)
166               Not referenced if SORT = 'N'.
167
168       INFO    (output) INTEGER
169               = 0:  successful exit
170               < 0:  if INFO = -i, the i-th argument had an illegal value.
171               =  1,...,N:  The  QZ  iteration failed.  (A,B) are not in Schur
172               form, but ALPHAR(j), ALPHAI(j), and BETA(j) should  be  correct
173               for j=INFO+1,...,N.  > N:  =N+1: other than QZ iteration failed
174               in DHGEQZ.
175               =N+2: after reordering, roundoff changed values of some complex
176               eigenvalues  so  that  leading  eigenvalues  in the Generalized
177               Schur form no longer satisfy SELCTG=.TRUE.  This could also  be
178               caused due to scaling.  =N+3: reordering failed in DTGSEN.
179
180
181
182 LAPACK driver routine (version 3.N1o)vember 2006                        DGGES(1)
Impressum