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