1STGSEN(1) LAPACK routine (version 3.2) STGSEN(1)
2
3
4
6 STGSEN - reorders the generalized real Schur decomposition of a real
7 matrix pair (A, B) (in terms of an orthonormal equivalence trans- for‐
8 mation Q' * (A, B) * Z), so that a selected cluster of eigenvalues
9 appears in the leading diagonal blocks of the upper quasi-triangular
10 matrix A and the upper triangular B
11
13 SUBROUTINE STGSEN( IJOB, WANTQ, WANTZ, SELECT, N, A, LDA, B, LDB,
14 ALPHAR, ALPHAI, BETA, Q, LDQ, Z, LDZ, M, PL, PR,
15 DIF, WORK, LWORK, IWORK, LIWORK, INFO )
16
17 LOGICAL WANTQ, WANTZ
18
19 INTEGER IJOB, INFO, LDA, LDB, LDQ, LDZ, LIWORK, LWORK, M, N
20
21 REAL PL, PR
22
23 LOGICAL SELECT( * )
24
25 INTEGER IWORK( * )
26
27 REAL A( LDA, * ), ALPHAI( * ), ALPHAR( * ), B( LDB, * ),
28 BETA( * ), DIF( * ), Q( LDQ, * ), WORK( * ), Z( LDZ,
29 * )
30
32 STGSEN reorders the generalized real Schur decomposition of a real
33 matrix pair (A, B) (in terms of an orthonormal equivalence trans- for‐
34 mation Q' * (A, B) * Z), so that a selected cluster of eigenvalues
35 appears in the leading diagonal blocks of the upper quasi-triangular
36 matrix A and the upper triangular B. The leading columns of Q and Z
37 form orthonormal bases of the corresponding left and right eigen- spa‐
38 ces (deflating subspaces). (A, B) must be in generalized real Schur
39 canonical form (as returned by SGGES), i.e. A is block upper triangular
40 with 1-by-1 and 2-by-2 diagonal blocks. B is upper triangular.
41 STGSEN also computes the generalized eigenvalues
42 w(j) = (ALPHAR(j) + i*ALPHAI(j))/BETA(j)
43 of the reordered matrix pair (A, B).
44 Optionally, STGSEN computes the estimates of reciprocal condition num‐
45 bers for eigenvalues and eigenspaces. These are Difu[(A11,B11),
46 (A22,B22)] and Difl[(A11,B11), (A22,B22)], i.e. the separation(s)
47 between the matrix pairs (A11, B11) and (A22,B22) that correspond to
48 the selected cluster and the eigenvalues outside the cluster, resp.,
49 and norms of "projections" onto left and right eigenspaces w.r.t. the
50 selected cluster in the (1,1)-block.
51
53 IJOB (input) INTEGER
54 Specifies whether condition numbers are required for the clus‐
55 ter of eigenvalues (PL and PR) or the deflating subspaces (Difu
56 and Difl):
57 =0: Only reorder w.r.t. SELECT. No extras.
58 =1: Reciprocal of norms of "projections" onto left and right
59 eigenspaces w.r.t. the selected cluster (PL and PR). =2: Upper
60 bounds on Difu and Difl. F-norm-based estimate
61 (DIF(1:2)).
62 =3: Estimate of Difu and Difl. 1-norm-based estimate
63 (DIF(1:2)). About 5 times as expensive as IJOB = 2. =4: Com‐
64 pute PL, PR and DIF (i.e. 0, 1 and 2 above): Economic version
65 to get it all. =5: Compute PL, PR and DIF (i.e. 0, 1 and 3
66 above)
67
68 WANTQ (input) LOGICAL
69
70 WANTZ (input) LOGICAL
71
72 SELECT (input) LOGICAL array, dimension (N)
73 SELECT specifies the eigenvalues in the selected cluster. To
74 select a real eigenvalue w(j), SELECT(j) must be set to .TRUE..
75 To select a complex conjugate pair of eigenvalues w(j) and
76 w(j+1), corresponding to a 2-by-2 diagonal block, either
77 SELECT(j) or SELECT(j+1) or both must be set to .TRUE.; a com‐
78 plex conjugate pair of eigenvalues must be either both included
79 in the cluster or both excluded.
80
81 N (input) INTEGER
82 The order of the matrices A and B. N >= 0.
83
84 A (input/output) REAL array, dimension(LDA,N)
85 On entry, the upper quasi-triangular matrix A, with (A, B) in
86 generalized real Schur canonical form. On exit, A is overwrit‐
87 ten by the reordered matrix A.
88
89 LDA (input) INTEGER
90 The leading dimension of the array A. LDA >= max(1,N).
91
92 B (input/output) REAL array, dimension(LDB,N)
93 On entry, the upper triangular matrix B, with (A, B) in gener‐
94 alized real Schur canonical form. On exit, B is overwritten by
95 the reordered matrix B.
96
97 LDB (input) INTEGER
98 The leading dimension of the array B. LDB >= max(1,N).
99
100 ALPHAR (output) REAL array, dimension (N)
101 ALPHAI (output) REAL array, dimension (N) BETA (output)
102 REAL array, dimension (N) On exit, (ALPHAR(j) +
103 ALPHAI(j)*i)/BETA(j), j=1,...,N, will be the generalized eigen‐
104 values. ALPHAR(j) + ALPHAI(j)*i and BETA(j),j=1,...,N are the
105 diagonals of the complex Schur form (S,T) that would result if
106 the 2-by-2 diagonal blocks of the real generalized Schur form
107 of (A,B) were further reduced to triangular form using complex
108 unitary transformations. If ALPHAI(j) is zero, then the j-th
109 eigenvalue is real; if positive, then the j-th and (j+1)-st ei‐
110 genvalues are a complex conjugate pair, with ALPHAI(j+1) nega‐
111 tive.
112
113 Q (input/output) REAL array, dimension (LDQ,N)
114 On entry, if WANTQ = .TRUE., Q is an N-by-N matrix. On exit, Q
115 has been postmultiplied by the left orthogonal transformation
116 matrix which reorder (A, B); The leading M columns of Q form
117 orthonormal bases for the specified pair of left eigenspaces
118 (deflating subspaces). If WANTQ = .FALSE., Q is not refer‐
119 enced.
120
121 LDQ (input) INTEGER
122 The leading dimension of the array Q. LDQ >= 1; and if WANTQ =
123 .TRUE., LDQ >= N.
124
125 Z (input/output) REAL array, dimension (LDZ,N)
126 On entry, if WANTZ = .TRUE., Z is an N-by-N matrix. On exit, Z
127 has been postmultiplied by the left orthogonal transformation
128 matrix which reorder (A, B); The leading M columns of Z form
129 orthonormal bases for the specified pair of left eigenspaces
130 (deflating subspaces). If WANTZ = .FALSE., Z is not refer‐
131 enced.
132
133 LDZ (input) INTEGER
134 The leading dimension of the array Z. LDZ >= 1; If WANTZ =
135 .TRUE., LDZ >= N.
136
137 M (output) INTEGER
138 The dimension of the specified pair of left and right eigen-
139 spaces (deflating subspaces). 0 <= M <= N.
140
141 PL (output) REAL
142 PR (output) REAL If IJOB = 1, 4 or 5, PL, PR are lower
143 bounds on the reciprocal of the norm of "projections" onto left
144 and right eigenspaces with respect to the selected cluster. 0
145 < PL, PR <= 1. If M = 0 or M = N, PL = PR = 1. If IJOB = 0,
146 2 or 3, PL and PR are not referenced.
147
148 DIF (output) REAL array, dimension (2).
149 If IJOB >= 2, DIF(1:2) store the estimates of Difu and Difl.
150 If IJOB = 2 or 4, DIF(1:2) are F-norm-based upper bounds on
151 Difu and Difl. If IJOB = 3 or 5, DIF(1:2) are 1-norm-based
152 estimates of Difu and Difl. If M = 0 or N, DIF(1:2) = F-
153 norm([A, B]). If IJOB = 0 or 1, DIF is not referenced.
154
155 WORK (workspace/output) REAL array, dimension (MAX(1,LWORK))
156 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
157
158 LWORK (input) INTEGER
159 The dimension of the array WORK. LWORK >= 4*N+16. If IJOB =
160 1, 2 or 4, LWORK >= MAX(4*N+16, 2*M*(N-M)). If IJOB = 3 or 5,
161 LWORK >= MAX(4*N+16, 4*M*(N-M)). If LWORK = -1, then a
162 workspace query is assumed; the routine only calculates the
163 optimal size of the WORK array, returns this value as the first
164 entry of the WORK array, and no error message related to LWORK
165 is issued by XERBLA.
166
167 IWORK (workspace/output) INTEGER array, dimension (MAX(1,LIWORK))
168 IF IJOB = 0, IWORK is not referenced. Otherwise, on exit, if
169 INFO = 0, IWORK(1) returns the optimal LIWORK.
170
171 LIWORK (input) INTEGER
172 The dimension of the array IWORK. LIWORK >= 1. If IJOB = 1, 2
173 or 4, LIWORK >= N+6. If IJOB = 3 or 5, LIWORK >= MAX(2*M*(N-
174 M), N+6). If LIWORK = -1, then a workspace query is assumed;
175 the routine only calculates the optimal size of the IWORK
176 array, returns this value as the first entry of the IWORK
177 array, and no error message related to LIWORK is issued by
178 XERBLA.
179
180 INFO (output) INTEGER
181 =0: Successful exit.
182 <0: If INFO = -i, the i-th argument had an illegal value.
183 =1: Reordering of (A, B) failed because the transformed matrix
184 pair (A, B) would be too far from generalized Schur form; the
185 problem is very ill-conditioned. (A, B) may have been par‐
186 tially reordered. If requested, 0 is returned in DIF(*), PL
187 and PR.
188
190 STGSEN first collects the selected eigenvalues by computing orthogonal
191 U and W that move them to the top left corner of (A, B). In other
192 words, the selected eigenvalues are the eigenvalues of (A11, B11) in:
193 U'*(A, B)*W = (A11 A12) (B11 B12) n1
194 ( 0 A22),( 0 B22) n2
195 n1 n2 n1 n2
196 where N = n1+n2 and U' means the transpose of U. The first n1 columns
197 of U and W span the specified pair of left and right eigenspaces
198 (deflating subspaces) of (A, B).
199 If (A, B) has been obtained from the generalized real Schur decomposi‐
200 tion of a matrix pair (C, D) = Q*(A, B)*Z', then the reordered general‐
201 ized real Schur form of (C, D) is given by
202 (C, D) = (Q*U)*(U'*(A, B)*W)*(Z*W)',
203 and the first n1 columns of Q*U and Z*W span the corresponding deflat‐
204 ing subspaces of (C, D) (Q and Z store Q*U and Z*W, resp.). Note that
205 if the selected eigenvalue is sufficiently ill-conditioned, then its
206 value may differ significantly from its value before reordering.
207 The reciprocal condition numbers of the left and right eigenspaces
208 spanned by the first n1 columns of U and W (or Q*U and Z*W) may be
209 returned in DIF(1:2), corresponding to Difu and Difl, resp. The Difu
210 and Difl are defined as:
211 Difu[(A11, B11), (A22, B22)] = sigma-min( Zu )
212 and
213 Difl[(A11, B11), (A22, B22)] = Difu[(A22, B22), (A11, B11)], where
214 sigma-min(Zu) is the smallest singular value of the
215 (2*n1*n2)-by-(2*n1*n2) matrix
216 Zu = [ kron(In2, A11) -kron(A22', In1) ]
217 [ kron(In2, B11) -kron(B22', In1) ].
218 Here, Inx is the identity matrix of size nx and A22' is the transpose
219 of A22. kron(X, Y) is the Kronecker product between the matrices X and
220 Y.
221 When DIF(2) is small, small changes in (A, B) can cause large changes
222 in the deflating subspace. An approximate (asymptotic) bound on the
223 maximum angular error in the computed deflating subspaces is
224 EPS * norm((A, B)) / DIF(2),
225 where EPS is the machine precision.
226 The reciprocal norm of the projectors on the left and right eigenspaces
227 associated with (A11, B11) may be returned in PL and PR. They are com‐
228 puted as follows. First we compute L and R so that P*(A, B)*Q is block
229 diagonal, where
230 P = ( I -L ) n1 Q = ( I R ) n1
231 ( 0 I ) n2 and ( 0 I ) n2
232 n1 n2 n1 n2
233 and (L, R) is the solution to the generalized Sylvester equation
234 A11*R - L*A22 = -A12
235 B11*R - L*B22 = -B12
236 Then PL = (F-norm(L)**2+1)**(-1/2) and PR = (F-norm(R)**2+1)**(-1/2).
237 An approximate (asymptotic) bound on the average absolute error of the
238 selected eigenvalues is
239 EPS * norm((A, B)) / PL.
240 There are also global error bounds which valid for perturbations up to
241 a certain restriction: A lower bound (x) on the smallest F-norm(E,F)
242 for which an eigenvalue of (A11, B11) may move and coalesce with an ei‐
243 genvalue of (A22, B22) under perturbation (E,F), (i.e. (A + E, B + F),
244 is
245 x = min(Difu,Difl)/((1/(PL*PL)+1/(PR*PR))**(1/2)+2*max(1/PL,1/PR)).
246 An approximate bound on x can be computed from DIF(1:2), PL and PR. If
247 y = ( F-norm(E,F) / x) <= 1, the angles between the perturbed (L', R')
248 and unperturbed (L, R) left and right deflating subspaces associated
249 with the selected cluster in the (1,1)-blocks can be bounded as
250 max-angle(L, L') <= arctan( y * PL / (1 - y * (1 - PL * PL)**(1/2))
251 max-angle(R, R') <= arctan( y * PR / (1 - y * (1 - PR * PR)**(1/2))
252 See LAPACK User's Guide section 4.11 or the following references for
253 more information.
254 Note that if the default method for computing the Frobenius-norm- based
255 estimate DIF is not wanted (see SLATDF), then the parameter IDIFJB (see
256 below) should be changed from 3 to 4 (routine SLATDF (IJOB = 2 will be
257 used)). See STGSYL for more details.
258 Based on contributions by
259 Bo Kagstrom and Peter Poromaa, Department of Computing Science,
260 Umea University, S-901 87 Umea, Sweden.
261 References
262 ==========
263 [1] B. Kagstrom; A Direct Method for Reordering Eigenvalues in the
264 Generalized Real Schur Form of a Regular Matrix Pair (A, B), in
265 M.S. Moonen et al (eds), Linear Algebra for Large Scale and
266 Real-Time Applications, Kluwer Academic Publ. 1993, pp 195-218.
267 [2] B. Kagstrom and P. Poromaa; Computing Eigenspaces with Specified
268 Eigenvalues of a Regular Matrix Pair (A, B) and Condition
269 Estimation: Theory, Algorithms and Software,
270 Report UMINF - 94.04, Department of Computing Science, Umea
271 University, S-901 87 Umea, Sweden, 1994. Also as LAPACK Working
272 Note 87. To appear in Numerical Algorithms, 1996.
273 [3] B. Kagstrom and P. Poromaa, LAPACK-Style Algorithms and Software
274 for Solving the Generalized Sylvester Equation and Estimating the
275 Separation between Regular Matrix Pairs, Report UMINF - 93.23,
276 Department of Computing Science, Umea University, S-901 87 Umea,
277 Sweden, December 1993, Revised April 1994, Also as LAPACK Working
278 Note 75. To appear in ACM Trans. on Math. Software, Vol 22, No 1,
279 1996.
280
281
282
283 LAPACK routine (version 3.2) November 2008 STGSEN(1)