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

NAME

6       DGEGV - i deprecated and has been replaced by routine DGGEV
7

SYNOPSIS

9       SUBROUTINE DGEGV( JOBVL,  JOBVR,  N,  A,  LDA,  B, LDB, ALPHAR, ALPHAI,
10                         BETA, VL, LDVL, VR, LDVR, WORK, LWORK, INFO )
11
12           CHARACTER     JOBVL, JOBVR
13
14           INTEGER       INFO, LDA, LDB, LDVL, LDVR, LWORK, N
15
16           DOUBLE        PRECISION A( LDA, * ), ALPHAI( * ), ALPHAR( *  ),  B(
17                         LDB,  *  ),  BETA( * ), VL( LDVL, * ), VR( LDVR, * ),
18                         WORK( * )
19

PURPOSE

21       This routine is deprecated and has been replaced by routine DGGEV.
22
23       DGEGV computes the eigenvalues and, optionally, the left  and/or  right
24       eigenvectors of a real matrix pair (A,B).
25       Given two square matrices A and B,
26       the  generalized  nonsymmetric eigenvalue problem (GNEP) is to find the
27       eigenvalues lambda and corresponding  (non-zero)  eigenvectors  x  such
28       that
29
30          A*x = lambda*B*x.
31
32       An  alternate  form  is  to  find  the eigenvalues mu and corresponding
33       eigenvectors y such that
34
35          mu*A*y = B*y.
36
37       These two forms are equivalent with mu = 1/lambda and x = y if  neither
38       lambda  nor  mu is zero.  In order to deal with the case that lambda or
39       mu is zero or small, two values alpha and beta are  returned  for  each
40       eigenvalue, such that lambda = alpha/beta and
41       mu = beta/alpha.
42
43       The  vectors  x  and y in the above equations are right eigenvectors of
44       the matrix pair (A,B).  Vectors u and v satisfying
45
46          u**H*A = lambda*u**H*B  or  mu*v**H*A = v**H*B
47
48       are left eigenvectors of (A,B).
49
50       Note: this routine performs "full balancing" on A and B -- see "Further
51       Details", below.
52

ARGUMENTS

54       JOBVL   (input) CHARACTER*1
55               = 'N':  do not compute the left generalized eigenvectors;
56               =  'V':  compute the left generalized eigenvectors (returned in
57               VL).
58
59       JOBVR   (input) CHARACTER*1
60               = 'N':  do not compute the right generalized eigenvectors;
61               = 'V':  compute the right generalized eigenvectors (returned in
62               VR).
63
64       N       (input) INTEGER
65               The order of the matrices A, B, VL, and VR.  N >= 0.
66
67       A       (input/output) DOUBLE PRECISION array, dimension (LDA, N)
68               On entry, the matrix A.  If JOBVL = 'V' or JOBVR = 'V', then on
69               exit A contains the real Schur form of A from  the  generalized
70               Schur  factorization  of the pair (A,B) after balancing.  If no
71               eigenvectors were computed, then only the diagonal blocks  from
72               the  Schur  form  will  be  correct.  See DGGHRD and DHGEQZ for
73               details.
74
75       LDA     (input) INTEGER
76               The leading dimension of A.  LDA >= max(1,N).
77
78       B       (input/output) DOUBLE PRECISION array, dimension (LDB, N)
79               On entry, the matrix B.  If JOBVL = 'V' or JOBVR = 'V', then on
80               exit  B contains the upper triangular matrix obtained from B in
81               the generalized Schur factorization of  the  pair  (A,B)  after
82               balancing.   If  no eigenvectors were computed, then only those
83               elements of B corresponding to the  diagonal  blocks  from  the
84               Schur  form  of  A  will be correct.  See DGGHRD and DHGEQZ for
85               details.
86
87       LDB     (input) INTEGER
88               The leading dimension of B.  LDB >= max(1,N).
89
90       ALPHAR  (output) DOUBLE PRECISION array, dimension (N)
91               The real parts of each scalar alpha defining an  eigenvalue  of
92               GNEP.
93
94       ALPHAI  (output) DOUBLE PRECISION array, dimension (N)
95               The imaginary parts of each scalar alpha defining an eigenvalue
96               of GNEP.  If ALPHAI(j) is zero, then  the  j-th  eigenvalue  is
97               real; if positive, then the j-th and (j+1)-st eigenvalues are a
98               complex conjugate pair, with ALPHAI(j+1) = -ALPHAI(j).
99
100       BETA    (output) DOUBLE PRECISION array, dimension (N)
101               The  scalars  beta  that  define  the  eigenvalues   of   GNEP.
102               Together, the quantities alpha = (ALPHAR(j),ALPHAI(j)) and beta
103               = BETA(j) represent the j-th  eigenvalue  of  the  matrix  pair
104               (A,B),  in  one  of  the  forms  lambda  =  alpha/beta  or mu =
105               beta/alpha.  Since either  lambda  or  mu  may  overflow,  they
106               should not, in general, be computed.
107
108       VL      (output) DOUBLE PRECISION array, dimension (LDVL,N)
109               If  JOBVL  =  'V', the left eigenvectors u(j) are stored in the
110               columns of VL, in the same order as their eigenvalues.  If  the
111               j-th  eigenvalue is real, then u(j) = VL(:,j).  If the j-th and
112               (j+1)-st eigenvalues form a complex conjugate pair, then u(j) =
113               VL(:,j) + i*VL(:,j+1) and u(j+1) = VL(:,j) - i*VL(:,j+1).
114
115               Each  eigenvector  is  scaled so that its largest component has
116               abs(real part) + abs(imag. part) = 1, except  for  eigenvectors
117               corresponding to an eigenvalue with alpha = beta = 0, which are
118               set to zero.  Not referenced if JOBVL = 'N'.
119
120       LDVL    (input) INTEGER
121               The leading dimension of the matrix VL. LDVL >= 1, and if JOBVL
122               = 'V', LDVL >= N.
123
124       VR      (output) DOUBLE PRECISION array, dimension (LDVR,N)
125               If  JOBVR  = 'V', the right eigenvectors x(j) are stored in the
126               columns of VR, in the same order as their eigenvalues.  If  the
127               j-th  eigenvalue is real, then x(j) = VR(:,j).  If the j-th and
128               (j+1)-st eigenvalues form a complex conjugate pair, then x(j) =
129               VR(:,j) + i*VR(:,j+1) and x(j+1) = VR(:,j) - i*VR(:,j+1).
130
131               Each  eigenvector  is  scaled so that its largest component has
132               abs(real part) + abs(imag. part) = 1,  except  for  eigenvalues
133               corresponding to an eigenvalue with alpha = beta = 0, which are
134               set to zero.  Not referenced if JOBVR = 'N'.
135
136       LDVR    (input) INTEGER
137               The leading dimension of the matrix VR. LDVR >= 1, and if JOBVR
138               = 'V', LDVR >= N.
139
140       WORK       (workspace/output)   DOUBLE   PRECISION   array,   dimension
141       (MAX(1,LWORK))
142               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
143
144       LWORK   (input) INTEGER
145               The dimension of the array WORK.   LWORK  >=  max(1,8*N).   For
146               good  performance,  LWORK must generally be larger.  To compute
147               the optimal value of LWORK, call ILAENV to get blocksizes  (for
148               DGEQRF,  DORMQR,  and DORGQR.)  Then compute: NB  -- MAX of the
149               blocksizes for DGEQRF, DORMQR, and DORGQR;  The  optimal  LWORK
150               is: 2*N + MAX( 6*N, N*(NB+1) ).
151
152               If  LWORK  = -1, then a workspace query is assumed; the routine
153               only calculates the optimal size of  the  WORK  array,  returns
154               this  value  as the first entry of the WORK array, and no error
155               message related to LWORK is issued by XERBLA.
156
157       INFO    (output) INTEGER
158               = 0:  successful exit
159               < 0:  if INFO = -i, the i-th argument had an illegal value.
160               = 1,...,N: The QZ iteration failed.  No eigenvectors have  been
161               calculated,  but  ALPHAR(j),  ALPHAI(j),  and BETA(j) should be
162               correct for j=INFO+1,...,N.  > N:  errors that usually indicate
163               LAPACK problems:
164               =N+1: error return from DGGBAL
165               =N+2: error return from DGEQRF
166               =N+3: error return from DORMQR
167               =N+4: error return from DORGQR
168               =N+5: error return from DGGHRD
169               =N+6:  error  return  from DHGEQZ (other than failed iteration)
170               =N+7: error return from DTGEVC
171               =N+8: error return from DGGBAK (computing VL)
172               =N+9: error return from DGGBAK (computing VR)
173               =N+10: error return from DLASCL (various calls)
174

FURTHER DETAILS

176       Balancing
177       ---------
178
179       This driver calls DGGBAL to both permute and scale rows and columns  of
180       A  and  B.   The  permutations PL and PR are chosen so that PL*A*PR and
181       PL*B*R  will  be  upper  triangular  except  for  the  diagonal  blocks
182       A(i:j,i:j)  and B(i:j,i:j), with i and j as close together as possible.
183       The diagonal scaling matrices DL and DR are chosen  so  that  the  pair
184       DL*PL*A*PR*DR, DL*PL*B*PR*DR have elements close to one (except for the
185       elements that start out zero.)
186
187       After the eigenvalues and eigenvectors of the  balanced  matrices  have
188       been  computed,  DGGBAK  transforms  the eigenvectors back to what they
189       would have been (in perfect arithmetic) if they had not been balanced.
190
191       Contents of A and B on Exit
192       -------- -- - --- - -- ----
193
194       If any eigenvectors are computed  (either  JOBVL='V'  or  JOBVR='V'  or
195       both),  then  on  exit  the  arrays A and B will contain the real Schur
196       form[*] of the "balanced" versions of A and B.  If no eigenvectors  are
197       computed, then only the diagonal blocks will be correct.
198
199       [*] See DHGEQZ, DGEGS, or read the book "Matrix Computations",
200           by Golub & van Loan, pub. by Johns Hopkins U. Press.
201
202
203
204
205 LAPACK driver routine (version 3.N1o)vember 2006                        DGEGV(1)
Impressum