1CGEGV(1) LAPACK driver routine (version 3.1) CGEGV(1)
2
3
4
6 CGEGV - i deprecated and has been replaced by routine CGGEV
7
9 SUBROUTINE CGEGV( JOBVL, JOBVR, N, A, LDA, B, LDB, ALPHA, BETA, VL,
10 LDVL, VR, LDVR, WORK, LWORK, RWORK, INFO )
11
12 CHARACTER JOBVL, JOBVR
13
14 INTEGER INFO, LDA, LDB, LDVL, LDVR, LWORK, N
15
16 REAL RWORK( * )
17
18 COMPLEX A( LDA, * ), ALPHA( * ), B( LDB, * ), BETA( * ), VL(
19 LDVL, * ), VR( LDVR, * ), WORK( * )
20
22 This routine is deprecated and has been replaced by routine CGGEV.
23
24 CGEGV computes the eigenvalues and, optionally, the left and/or right
25 eigenvectors of a complex matrix pair (A,B).
26 Given two square matrices A and B,
27 the generalized nonsymmetric eigenvalue problem (GNEP) is to find the
28 eigenvalues lambda and corresponding (non-zero) eigenvectors x such
29 that
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 mu*A*y = B*y.
35
36 These two forms are equivalent with mu = 1/lambda and x = y if neither
37 lambda nor mu is zero. In order to deal with the case that lambda or
38 mu is zero or small, two values alpha and beta are returned for each
39 eigenvalue, such that lambda = alpha/beta and
40 mu = beta/alpha.
41
42 The vectors x and y in the above equations are right eigenvectors of
43 the matrix pair (A,B). Vectors u and v satisfying
44 u**H*A = lambda*u**H*B or mu*v**H*A = v**H*B
45 are left eigenvectors of (A,B).
46
47 Note: this routine performs "full balancing" on A and B -- see "Further
48 Details", below.
49
51 JOBVL (input) CHARACTER*1
52 = 'N': do not compute the left generalized eigenvectors;
53 = 'V': compute the left generalized eigenvectors (returned in
54 VL).
55
56 JOBVR (input) CHARACTER*1
57 = 'N': do not compute the right generalized eigenvectors;
58 = 'V': compute the right generalized eigenvectors (returned in
59 VR).
60
61 N (input) INTEGER
62 The order of the matrices A, B, VL, and VR. N >= 0.
63
64 A (input/output) COMPLEX array, dimension (LDA, N)
65 On entry, the matrix A. If JOBVL = 'V' or JOBVR = 'V', then on
66 exit A contains the Schur form of A from the generalized Schur
67 factorization of the pair (A,B) after balancing. If no eigenā
68 vectors were computed, then only the diagonal elements of the
69 Schur form will be correct. See CGGHRD and CHGEQZ for details.
70
71 LDA (input) INTEGER
72 The leading dimension of A. LDA >= max(1,N).
73
74 B (input/output) COMPLEX array, dimension (LDB, N)
75 On entry, the matrix B. If JOBVL = 'V' or JOBVR = 'V', then on
76 exit B contains the upper triangular matrix obtained from B in
77 the generalized Schur factorization of the pair (A,B) after
78 balancing. If no eigenvectors were computed, then only the
79 diagonal elements of B will be correct. See CGGHRD and CHGEQZ
80 for details.
81
82 LDB (input) INTEGER
83 The leading dimension of B. LDB >= max(1,N).
84
85 ALPHA (output) COMPLEX array, dimension (N)
86 The complex scalars alpha that define the eigenvalues of GNEP.
87
88 BETA (output) COMPLEX array, dimension (N)
89 The complex scalars beta that define the eigenvalues of GNEP.
90 Together, the quantities alpha = ALPHA(j) and beta = BETA(j)
91 represent the j-th eigenvalue of the matrix pair (A,B), in one
92 of the forms lambda = alpha/beta or mu = beta/alpha. Since
93 either lambda or mu may overflow, they should not, in general,
94 be computed.
95
96 VL (output) COMPLEX array, dimension (LDVL,N)
97 If JOBVL = 'V', the left eigenvectors u(j) are stored in the
98 columns of VL, in the same order as their eigenvalues. Each
99 eigenvector is scaled so that its largest component has
100 abs(real part) + abs(imag. part) = 1, except for eigenvectors
101 corresponding to an eigenvalue with alpha = beta = 0, which are
102 set to zero. Not referenced if JOBVL = 'N'.
103
104 LDVL (input) INTEGER
105 The leading dimension of the matrix VL. LDVL >= 1, and if JOBVL
106 = 'V', LDVL >= N.
107
108 VR (output) COMPLEX array, dimension (LDVR,N)
109 If JOBVR = 'V', the right eigenvectors x(j) are stored in the
110 columns of VR, in the same order as their eigenvalues. Each
111 eigenvector is scaled so that its largest component has
112 abs(real part) + abs(imag. part) = 1, except for eigenvectors
113 corresponding to an eigenvalue with alpha = beta = 0, which are
114 set to zero. Not referenced if JOBVR = 'N'.
115
116 LDVR (input) INTEGER
117 The leading dimension of the matrix VR. LDVR >= 1, and if JOBVR
118 = 'V', LDVR >= N.
119
120 WORK (workspace/output) COMPLEX array, dimension (MAX(1,LWORK))
121 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
122
123 LWORK (input) INTEGER
124 The dimension of the array WORK. LWORK >= max(1,2*N). For
125 good performance, LWORK must generally be larger. To compute
126 the optimal value of LWORK, call ILAENV to get blocksizes (for
127 CGEQRF, CUNMQR, and CUNGQR.) Then compute: NB -- MAX of the
128 blocksizes for CGEQRF, CUNMQR, and CUNGQR; The optimal LWORK is
129 MAX( 2*N, N*(NB+1) ).
130
131 If LWORK = -1, then a workspace query is assumed; the routine
132 only calculates the optimal size of the WORK array, returns
133 this value as the first entry of the WORK array, and no error
134 message related to LWORK is issued by XERBLA.
135
136 RWORK (workspace/output) REAL array, dimension (8*N)
137
138 INFO (output) INTEGER
139 = 0: successful exit
140 < 0: if INFO = -i, the i-th argument had an illegal value.
141 =1,...,N: The QZ iteration failed. No eigenvectors have been
142 calculated, but ALPHA(j) and BETA(j) should be correct for
143 j=INFO+1,...,N. > N: errors that usually indicate LAPACK
144 problems:
145 =N+1: error return from CGGBAL
146 =N+2: error return from CGEQRF
147 =N+3: error return from CUNMQR
148 =N+4: error return from CUNGQR
149 =N+5: error return from CGGHRD
150 =N+6: error return from CHGEQZ (other than failed iteration)
151 =N+7: error return from CTGEVC
152 =N+8: error return from CGGBAK (computing VL)
153 =N+9: error return from CGGBAK (computing VR)
154 =N+10: error return from CLASCL (various calls)
155
157 Balancing
158 ---------
159
160 This driver calls CGGBAL to both permute and scale rows and columns of
161 A and B. The permutations PL and PR are chosen so that PL*A*PR and
162 PL*B*R will be upper triangular except for the diagonal blocks
163 A(i:j,i:j) and B(i:j,i:j), with i and j as close together as possible.
164 The diagonal scaling matrices DL and DR are chosen so that the pair
165 DL*PL*A*PR*DR, DL*PL*B*PR*DR have elements close to one (except for the
166 elements that start out zero.)
167
168 After the eigenvalues and eigenvectors of the balanced matrices have
169 been computed, CGGBAK transforms the eigenvectors back to what they
170 would have been (in perfect arithmetic) if they had not been balanced.
171
172 Contents of A and B on Exit
173 -------- -- - --- - -- ----
174
175 If any eigenvectors are computed (either JOBVL='V' or JOBVR='V' or
176 both), then on exit the arrays A and B will contain the complex Schur
177 form[*] of the "balanced" versions of A and B. If no eigenvectors are
178 computed, then only the diagonal blocks will be correct.
179
180 [*] In other words, upper triangular form.
181
182
183
184
185 LAPACK driver routine (version 3.N1o)vember 2006 CGEGV(1)