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

NAME

6       SGEGV - routine i deprecated and has been replaced by routine SGGEV
7

SYNOPSIS

9       SUBROUTINE SGEGV( 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           REAL          A( LDA, * ), ALPHAI( * ), ALPHAR( * ), B( LDB,  *  ),
17                         BETA( * ), VL( LDVL, * ), VR( LDVR, * ), WORK( * )
18

PURPOSE

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

ARGUMENTS

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

FURTHER DETAILS

162       Balancing
163       ---------
164       This driver calls SGGBAL to both permute and scale rows and columns  of
165       A  and  B.   The  permutations PL and PR are chosen so that PL*A*PR and
166       PL*B*R  will  be  upper  triangular  except  for  the  diagonal  blocks
167       A(i:j,i:j)  and B(i:j,i:j), with i and j as close together as possible.
168       The diagonal scaling matrices DL and DR are chosen  so  that  the  pair
169       DL*PL*A*PR*DR, DL*PL*B*PR*DR have elements close to one (except for the
170       elements that start out zero.)
171       After the eigenvalues and eigenvectors of the  balanced  matrices  have
172       been  computed,  SGGBAK  transforms  the eigenvectors back to what they
173       would have been (in perfect arithmetic) if they had not been balanced.
174       Contents of A and B on Exit
175       -------- -- - --- - -- ----
176       If any eigenvectors are computed  (either  JOBVL='V'  or  JOBVR='V'  or
177       both),  then  on  exit  the  arrays A and B will contain the real Schur
178       form[*] of the "balanced" versions of A and B.  If no eigenvectors  are
179       computed,  then  only  the  diagonal  blocks  will be correct.  [*] See
180       SHGEQZ, SGEGS, or read the book "Matrix Computations",
181           by Golub & van Loan, pub. by Johns Hopkins U. Press.
182
183
184
185 LAPACK driver routine (version 3.N2o)vember 2008                        SGEGV(1)
Impressum