1CTGSNA(1) LAPACK routine (version 3.1) CTGSNA(1)
2
3
4
6 CTGSNA - reciprocal condition numbers for specified eigenvalues and/or
7 eigenvectors of a matrix pair (A, B)
8
10 SUBROUTINE CTGSNA( JOB, HOWMNY, SELECT, N, A, LDA, B, LDB, VL, LDVL,
11 VR, LDVR, S, DIF, MM, M, WORK, LWORK, IWORK, INFO )
12
13 CHARACTER HOWMNY, JOB
14
15 INTEGER INFO, LDA, LDB, LDVL, LDVR, LWORK, M, MM, N
16
17 LOGICAL SELECT( * )
18
19 INTEGER IWORK( * )
20
21 REAL DIF( * ), S( * )
22
23 COMPLEX A( LDA, * ), B( LDB, * ), VL( LDVL, * ), VR( LDVR, *
24 ), WORK( * )
25
27 CTGSNA estimates reciprocal condition numbers for specified eigenvalues
28 and/or eigenvectors of a matrix pair (A, B).
29
30 (A, B) must be in generalized Schur canonical form, that is, A and B
31 are both upper triangular.
32
33
35 JOB (input) CHARACTER*1
36 Specifies whether condition numbers are required for eigenval‐
37 ues (S) or eigenvectors (DIF):
38 = 'E': for eigenvalues only (S);
39 = 'V': for eigenvectors only (DIF);
40 = 'B': for both eigenvalues and eigenvectors (S and DIF).
41
42 HOWMNY (input) CHARACTER*1
43 = 'A': compute condition numbers for all eigenpairs;
44 = 'S': compute condition numbers for selected eigenpairs speci‐
45 fied by the array SELECT.
46
47 SELECT (input) LOGICAL array, dimension (N)
48 If HOWMNY = 'S', SELECT specifies the eigenpairs for which con‐
49 dition numbers are required. To select condition numbers for
50 the corresponding j-th eigenvalue and/or eigenvector, SELECT(j)
51 must be set to .TRUE.. If HOWMNY = 'A', SELECT is not refer‐
52 enced.
53
54 N (input) INTEGER
55 The order of the square matrix pair (A, B). N >= 0.
56
57 A (input) COMPLEX array, dimension (LDA,N)
58 The upper triangular matrix A in the pair (A,B).
59
60 LDA (input) INTEGER
61 The leading dimension of the array A. LDA >= max(1,N).
62
63 B (input) COMPLEX array, dimension (LDB,N)
64 The upper triangular matrix B in the pair (A, B).
65
66 LDB (input) INTEGER
67 The leading dimension of the array B. LDB >= max(1,N).
68
69 VL (input) COMPLEX array, dimension (LDVL,M)
70 IF JOB = 'E' or 'B', VL must contain left eigenvectors of (A,
71 B), corresponding to the eigenpairs specified by HOWMNY and
72 SELECT. The eigenvectors must be stored in consecutive columns
73 of VL, as returned by CTGEVC. If JOB = 'V', VL is not refer‐
74 enced.
75
76 LDVL (input) INTEGER
77 The leading dimension of the array VL. LDVL >= 1; and If JOB =
78 'E' or 'B', LDVL >= N.
79
80 VR (input) COMPLEX array, dimension (LDVR,M)
81 IF JOB = 'E' or 'B', VR must contain right eigenvectors of (A,
82 B), corresponding to the eigenpairs specified by HOWMNY and
83 SELECT. The eigenvectors must be stored in consecutive columns
84 of VR, as returned by CTGEVC. If JOB = 'V', VR is not refer‐
85 enced.
86
87 LDVR (input) INTEGER
88 The leading dimension of the array VR. LDVR >= 1; If JOB = 'E'
89 or 'B', LDVR >= N.
90
91 S (output) REAL array, dimension (MM)
92 If JOB = 'E' or 'B', the reciprocal condition numbers of the
93 selected eigenvalues, stored in consecutive elements of the
94 array. If JOB = 'V', S is not referenced.
95
96 DIF (output) REAL array, dimension (MM)
97 If JOB = 'V' or 'B', the estimated reciprocal condition numbers
98 of the selected eigenvectors, stored in consecutive elements of
99 the array. If the eigenvalues cannot be reordered to compute
100 DIF(j), DIF(j) is set to 0; this can only occur when the true
101 value would be very small anyway. For each eigenvalue/vector
102 specified by SELECT, DIF stores a Frobenius norm-based estimate
103 of Difl. If JOB = 'E', DIF is not referenced.
104
105 MM (input) INTEGER
106 The number of elements in the arrays S and DIF. MM >= M.
107
108 M (output) INTEGER
109 The number of elements of the arrays S and DIF used to store
110 the specified condition numbers; for each selected eigenvalue
111 one element is used. If HOWMNY = 'A', M is set to N.
112
113 WORK (workspace/output) COMPLEX array, dimension (MAX(1,LWORK))
114 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
115
116 LWORK (input) INTEGER
117 The dimension of the array WORK. LWORK >= max(1,N). If JOB =
118 'V' or 'B', LWORK >= max(1,2*N*N).
119
120 IWORK (workspace) INTEGER array, dimension (N+2)
121 If JOB = 'E', IWORK is not referenced.
122
123 INFO (output) INTEGER
124 = 0: Successful exit
125 < 0: If INFO = -i, the i-th argument had an illegal value
126
128 The reciprocal of the condition number of the i-th generalized eigen‐
129 value w = (a, b) is defined as
130
131 S(I) = (|v'Au|**2 + |v'Bu|**2)**(1/2) / (norm(u)*norm(v))
132
133 where u and v are the right and left eigenvectors of (A, B) correspond‐
134 ing to w; |z| denotes the absolute value of the complex number, and
135 norm(u) denotes the 2-norm of the vector u. The pair (a, b) corresponds
136 to an eigenvalue w = a/b (= v'Au/v'Bu) of the matrix pair (A, B). If
137 both a and b equal zero, then (A,B) is singular and S(I) = -1 is
138 returned.
139
140 An approximate error bound on the chordal distance between the i-th
141 computed generalized eigenvalue w and the corresponding exact eigenval‐
142 ue lambda is
143
144 chord(w, lambda) <= EPS * norm(A, B) / S(I),
145
146 where EPS is the machine precision.
147
148 The reciprocal of the condition number of the right eigenvector u and
149 left eigenvector v corresponding to the generalized eigenvalue w is
150 defined as follows. Suppose
151
152 (A, B) = ( a * ) ( b * ) 1
153 ( 0 A22 ),( 0 B22 ) n-1
154 1 n-1 1 n-1
155
156 Then the reciprocal condition number DIF(I) is
157
158 Difl[(a, b), (A22, B22)] = sigma-min( Zl )
159
160 where sigma-min(Zl) denotes the smallest singular value of
161
162 Zl = [ kron(a, In-1) -kron(1, A22) ]
163 [ kron(b, In-1) -kron(1, B22) ].
164
165 Here In-1 is the identity matrix of size n-1 and X' is the conjugate
166 transpose of X. kron(X, Y) is the Kronecker product between the matri‐
167 ces X and Y.
168
169 We approximate the smallest singular value of Zl with an upper bound.
170 This is done by CLATDF.
171
172 An approximate error bound for a computed eigenvector VL(i) or VR(i) is
173 given by
174
175 EPS * norm(A, B) / DIF(i).
176
177 See ref. [2-3] for more details and further references.
178
179 Based on contributions by
180 Bo Kagstrom and Peter Poromaa, Department of Computing Science,
181 Umea University, S-901 87 Umea, Sweden.
182
183 References
184 ==========
185
186 [1] B. Kagstrom; A Direct Method for Reordering Eigenvalues in the
187 Generalized Real Schur Form of a Regular Matrix Pair (A, B), in
188 M.S. Moonen et al (eds), Linear Algebra for Large Scale and
189 Real-Time Applications, Kluwer Academic Publ. 1993, pp 195-218.
190
191 [2] B. Kagstrom and P. Poromaa; Computing Eigenspaces with Specified
192 Eigenvalues of a Regular Matrix Pair (A, B) and Condition
193 Estimation: Theory, Algorithms and Software, Report
194 UMINF - 94.04, Department of Computing Science, Umea University,
195 S-901 87 Umea, Sweden, 1994. Also as LAPACK Working Note 87.
196 To appear in Numerical Algorithms, 1996.
197
198 [3] B. Kagstrom and P. Poromaa, LAPACK-Style Algorithms and Software
199 for Solving the Generalized Sylvester Equation and Estimating the
200 Separation between Regular Matrix Pairs, Report UMINF - 93.23,
201 Department of Computing Science, Umea University, S-901 87 Umea,
202 Sweden, December 1993, Revised April 1994, Also as LAPACK Working
203 Note 75.
204 To appear in ACM Trans. on Math. Software, Vol 22, No 1, 1996.
205
206
207
208
209 LAPACK routine (version 3.1) November 2006 CTGSNA(1)