1SHGEQZ(1) LAPACK routine (version 3.1) SHGEQZ(1)
2
3
4
6 SHGEQZ - the eigenvalues of a real matrix pair (H,T),
7
9 SUBROUTINE SHGEQZ( JOB, COMPQ, COMPZ, N, ILO, IHI, H, LDH, T, LDT,
10 ALPHAR, ALPHAI, BETA, Q, LDQ, Z, LDZ, WORK, LWORK,
11 INFO )
12
13 CHARACTER COMPQ, COMPZ, JOB
14
15 INTEGER IHI, ILO, INFO, LDH, LDQ, LDT, LDZ, LWORK, N
16
17 REAL ALPHAI( * ), ALPHAR( * ), BETA( * ), H( LDH, * ), Q(
18 LDQ, * ), T( LDT, * ), WORK( * ), Z( LDZ, * )
19
21 SHGEQZ computes the eigenvalues of a real matrix pair (H,T), where H is
22 an upper Hessenberg matrix and T is upper triangular, using the double-
23 shift QZ method.
24 Matrix pairs of this type are produced by the reduction to generalized
25 upper Hessenberg form of a real matrix pair (A,B):
26
27 A = Q1*H*Z1**T, B = Q1*T*Z1**T,
28
29 as computed by SGGHRD.
30
31 If JOB='S', then the Hessenberg-triangular pair (H,T) is
32 also reduced to generalized Schur form,
33
34 H = Q*S*Z**T, T = Q*P*Z**T,
35
36 where Q and Z are orthogonal matrices, P is an upper triangular matrix,
37 and S is a quasi-triangular matrix with 1-by-1 and 2-by-2 diagonal
38 blocks.
39
40 The 1-by-1 blocks correspond to real eigenvalues of the matrix pair
41 (H,T) and the 2-by-2 blocks correspond to complex conjugate pairs of
42 eigenvalues.
43
44 Additionally, the 2-by-2 upper triangular diagonal blocks of P corre‐
45 sponding to 2-by-2 blocks of S are reduced to positive diagonal form,
46 i.e., if S(j+1,j) is non-zero, then P(j+1,j) = P(j,j+1) = 0, P(j,j) >
47 0, and P(j+1,j+1) > 0.
48
49 Optionally, the orthogonal matrix Q from the generalized Schur factor‐
50 ization may be postmultiplied into an input matrix Q1, and the orthogo‐
51 nal matrix Z may be postmultiplied into an input matrix Z1. If Q1 and
52 Z1 are the orthogonal matrices from SGGHRD that reduced the matrix pair
53 (A,B) to generalized upper Hessenberg form, then the output matrices
54 Q1*Q and Z1*Z are the orthogonal factors from the generalized Schur
55 factorization of (A,B):
56
57 A = (Q1*Q)*S*(Z1*Z)**T, B = (Q1*Q)*P*(Z1*Z)**T.
58
59 To avoid overflow, eigenvalues of the matrix pair (H,T) (equivalently,
60 of (A,B)) are computed as a pair of values (alpha,beta), where alpha is
61 complex and beta real.
62 If beta is nonzero, lambda = alpha / beta is an eigenvalue of the gen‐
63 eralized nonsymmetric eigenvalue problem (GNEP)
64 A*x = lambda*B*x
65 and if alpha is nonzero, mu = beta / alpha is an eigenvalue of the
66 alternate form of the GNEP
67 mu*A*y = B*y.
68 Real eigenvalues can be read directly from the generalized Schur form:
69 alpha = S(i,i), beta = P(i,i).
70
71 Ref: C.B. Moler & G.W. Stewart, "An Algorithm for Generalized Matrix
72 Eigenvalue Problems", SIAM J. Numer. Anal., 10(1973),
73 pp. 241--256.
74
75
77 JOB (input) CHARACTER*1
78 = 'E': Compute eigenvalues only;
79 = 'S': Compute eigenvalues and the Schur form.
80
81 COMPQ (input) CHARACTER*1
82 = 'N': Left Schur vectors (Q) are not computed;
83 = 'I': Q is initialized to the unit matrix and the matrix Q of
84 left Schur vectors of (H,T) is returned; = 'V': Q must contain
85 an orthogonal matrix Q1 on entry and the product Q1*Q is
86 returned.
87
88 COMPZ (input) CHARACTER*1
89 = 'N': Right Schur vectors (Z) are not computed;
90 = 'I': Z is initialized to the unit matrix and the matrix Z of
91 right Schur vectors of (H,T) is returned; = 'V': Z must contain
92 an orthogonal matrix Z1 on entry and the product Z1*Z is
93 returned.
94
95 N (input) INTEGER
96 The order of the matrices H, T, Q, and Z. N >= 0.
97
98 ILO (input) INTEGER
99 IHI (input) INTEGER ILO and IHI mark the rows and columns
100 of H which are in Hessenberg form. It is assumed that A is
101 already upper triangular in rows and columns 1:ILO-1 and
102 IHI+1:N. If N > 0, 1 <= ILO <= IHI <= N; if N = 0, ILO=1 and
103 IHI=0.
104
105 H (input/output) REAL array, dimension (LDH, N)
106 On entry, the N-by-N upper Hessenberg matrix H. On exit, if
107 JOB = 'S', H contains the upper quasi-triangular matrix S from
108 the generalized Schur factorization; 2-by-2 diagonal blocks
109 (corresponding to complex conjugate pairs of eigenvalues) are
110 returned in standard form, with H(i,i) = H(i+1,i+1) and
111 H(i+1,i)*H(i,i+1) < 0. If JOB = 'E', the diagonal blocks of H
112 match those of S, but the rest of H is unspecified.
113
114 LDH (input) INTEGER
115 The leading dimension of the array H. LDH >= max( 1, N ).
116
117 T (input/output) REAL array, dimension (LDT, N)
118 On entry, the N-by-N upper triangular matrix T. On exit, if
119 JOB = 'S', T contains the upper triangular matrix P from the
120 generalized Schur factorization; 2-by-2 diagonal blocks of P
121 corresponding to 2-by-2 blocks of S are reduced to positive
122 diagonal form, i.e., if H(j+1,j) is non-zero, then T(j+1,j) =
123 T(j,j+1) = 0, T(j,j) > 0, and T(j+1,j+1) > 0. If JOB = 'E',
124 the diagonal blocks of T match those of P, but the rest of T is
125 unspecified.
126
127 LDT (input) INTEGER
128 The leading dimension of the array T. LDT >= max( 1, N ).
129
130 ALPHAR (output) REAL array, dimension (N)
131 The real parts of each scalar alpha defining an eigenvalue of
132 GNEP.
133
134 ALPHAI (output) REAL array, dimension (N)
135 The imaginary parts of each scalar alpha defining an eigenvalue
136 of GNEP. If ALPHAI(j) is zero, then the j-th eigenvalue is
137 real; if positive, then the j-th and (j+1)-st eigenvalues are a
138 complex conjugate pair, with ALPHAI(j+1) = -ALPHAI(j).
139
140 BETA (output) REAL array, dimension (N)
141 The scalars beta that define the eigenvalues of GNEP.
142 Together, the quantities alpha = (ALPHAR(j),ALPHAI(j)) and beta
143 = BETA(j) represent the j-th eigenvalue of the matrix pair
144 (A,B), in one of the forms lambda = alpha/beta or mu =
145 beta/alpha. Since either lambda or mu may overflow, they
146 should not, in general, be computed.
147
148 Q (input/output) REAL array, dimension (LDQ, N)
149 On entry, if COMPZ = 'V', the orthogonal matrix Q1 used in the
150 reduction of (A,B) to generalized Hessenberg form. On exit, if
151 COMPZ = 'I', the orthogonal matrix of left Schur vectors of
152 (H,T), and if COMPZ = 'V', the orthogonal matrix of left Schur
153 vectors of (A,B). Not referenced if COMPZ = 'N'.
154
155 LDQ (input) INTEGER
156 The leading dimension of the array Q. LDQ >= 1. If COMPQ='V'
157 or 'I', then LDQ >= N.
158
159 Z (input/output) REAL array, dimension (LDZ, N)
160 On entry, if COMPZ = 'V', the orthogonal matrix Z1 used in the
161 reduction of (A,B) to generalized Hessenberg form. On exit, if
162 COMPZ = 'I', the orthogonal matrix of right Schur vectors of
163 (H,T), and if COMPZ = 'V', the orthogonal matrix of right Schur
164 vectors of (A,B). Not referenced if COMPZ = 'N'.
165
166 LDZ (input) INTEGER
167 The leading dimension of the array Z. LDZ >= 1. If COMPZ='V'
168 or 'I', then LDZ >= N.
169
170 WORK (workspace/output) REAL array, dimension (MAX(1,LWORK))
171 On exit, if INFO >= 0, WORK(1) returns the optimal LWORK.
172
173 LWORK (input) INTEGER
174 The dimension of the array WORK. LWORK >= max(1,N).
175
176 If LWORK = -1, then a workspace query is assumed; the routine
177 only calculates the optimal size of the WORK array, returns
178 this value as the first entry of the WORK array, and no error
179 message related to LWORK is issued by XERBLA.
180
181 INFO (output) INTEGER
182 = 0: successful exit
183 < 0: if INFO = -i, the i-th argument had an illegal value
184 = 1,...,N: the QZ iteration did not converge. (H,T) is not in
185 Schur form, but ALPHAR(i), ALPHAI(i), and BETA(i),
186 i=INFO+1,...,N should be correct. = N+1,...,2*N: the shift
187 calculation failed. (H,T) is not in Schur form, but ALPHAR(i),
188 ALPHAI(i), and BETA(i), i=INFO-N+1,...,N should be correct.
189
191 Iteration counters:
192
193 JITER -- counts iterations.
194 IITER -- counts iterations run since ILAST was last
195 changed. This is therefore reset only when a 1-by-1 or
196 2-by-2 block deflates off the bottom.
197
198
199
200
201 LAPACK routine (version 3.1) November 2006 SHGEQZ(1)