1STGSJA(1) LAPACK routine (version 3.1) STGSJA(1)
2
3
4
6 STGSJA - the generalized singular value decomposition (GSVD) of two
7 real upper triangular (or trapezoidal) matrices A and B
8
10 SUBROUTINE STGSJA( JOBU, JOBV, JOBQ, M, P, N, K, L, A, LDA, B, LDB,
11 TOLA, TOLB, ALPHA, BETA, U, LDU, V, LDV, Q, LDQ,
12 WORK, NCYCLE, INFO )
13
14 CHARACTER JOBQ, JOBU, JOBV
15
16 INTEGER INFO, K, L, LDA, LDB, LDQ, LDU, LDV, M, N, NCYCLE, P
17
18 REAL TOLA, TOLB
19
20 REAL A( LDA, * ), ALPHA( * ), B( LDB, * ), BETA( * ), Q(
21 LDQ, * ), U( LDU, * ), V( LDV, * ), WORK( * )
22
24 STGSJA computes the generalized singular value decomposition (GSVD) of
25 two real upper triangular (or trapezoidal) matrices A and B.
26
27 On entry, it is assumed that matrices A and B have the following forms,
28 which may be obtained by the preprocessing subroutine SGGSVP from a
29 general M-by-N matrix A and P-by-N matrix B:
30
31 N-K-L K L
32 A = K ( 0 A12 A13 ) if M-K-L >= 0;
33 L ( 0 0 A23 )
34 M-K-L ( 0 0 0 )
35
36 N-K-L K L
37 A = K ( 0 A12 A13 ) if M-K-L < 0;
38 M-K ( 0 0 A23 )
39
40 N-K-L K L
41 B = L ( 0 0 B13 )
42 P-L ( 0 0 0 )
43
44 where the K-by-K matrix A12 and L-by-L matrix B13 are nonsingular upper
45 triangular; A23 is L-by-L upper triangular if M-K-L >= 0, otherwise A23
46 is (M-K)-by-L upper trapezoidal.
47
48 On exit,
49
50 U'*A*Q = D1*( 0 R ), V'*B*Q = D2*( 0 R ),
51
52 where U, V and Q are orthogonal matrices, Z' denotes the transpose of
53 Z, R is a nonsingular upper triangular matrix, and D1 and D2 are
54 ``diagonal'' matrices, which are of the following structures:
55
56 If M-K-L >= 0,
57
58 K L
59 D1 = K ( I 0 )
60 L ( 0 C )
61 M-K-L ( 0 0 )
62
63 K L
64 D2 = L ( 0 S )
65 P-L ( 0 0 )
66
67 N-K-L K L
68 ( 0 R ) = K ( 0 R11 R12 ) K
69 L ( 0 0 R22 ) L
70
71 where
72
73 C = diag( ALPHA(K+1), ... , ALPHA(K+L) ),
74 S = diag( BETA(K+1), ... , BETA(K+L) ),
75 C**2 + S**2 = I.
76
77 R is stored in A(1:K+L,N-K-L+1:N) on exit.
78
79 If M-K-L < 0,
80
81 K M-K K+L-M
82 D1 = K ( I 0 0 )
83 M-K ( 0 C 0 )
84
85 K M-K K+L-M
86 D2 = M-K ( 0 S 0 )
87 K+L-M ( 0 0 I )
88 P-L ( 0 0 0 )
89
90 N-K-L K M-K K+L-M
91
92 M-K ( 0 0 R22 R23 )
93 K+L-M ( 0 0 0 R33 )
94
95 where
96 C = diag( ALPHA(K+1), ... , ALPHA(M) ),
97 S = diag( BETA(K+1), ... , BETA(M) ),
98 C**2 + S**2 = I.
99
100 R = ( R11 R12 R13 ) is stored in A(1:M, N-K-L+1:N) and R33 is stored
101 ( 0 R22 R23 )
102 in B(M-K+1:L,N+M-K-L+1:N) on exit.
103
104 The computation of the orthogonal transformation matrices U, V or Q is
105 optional. These matrices may either be formed explicitly, or they may
106 be postmultiplied into input matrices U1, V1, or Q1.
107
108
110 JOBU (input) CHARACTER*1
111 = 'U': U must contain an orthogonal matrix U1 on entry, and
112 the product U1*U is returned; = 'I': U is initialized to the
113 unit matrix, and the orthogonal matrix U is returned; = 'N': U
114 is not computed.
115
116 JOBV (input) CHARACTER*1
117 = 'V': V must contain an orthogonal matrix V1 on entry, and
118 the product V1*V is returned; = 'I': V is initialized to the
119 unit matrix, and the orthogonal matrix V is returned; = 'N': V
120 is not computed.
121
122 JOBQ (input) CHARACTER*1
123 = 'Q': Q must contain an orthogonal matrix Q1 on entry, and
124 the product Q1*Q is returned; = 'I': Q is initialized to the
125 unit matrix, and the orthogonal matrix Q is returned; = 'N': Q
126 is not computed.
127
128 M (input) INTEGER
129 The number of rows of the matrix A. M >= 0.
130
131 P (input) INTEGER
132 The number of rows of the matrix B. P >= 0.
133
134 N (input) INTEGER
135 The number of columns of the matrices A and B. N >= 0.
136
137 K (input) INTEGER
138 L (input) INTEGER K and L specify the subblocks in the
139 input matrices A and B:
140 A23 = A(K+1:MIN(K+L,M),N-L+1:N) and B13 = B(1:L,N-L+1:N) of A
141 and B, whose GSVD is going to be computed by STGSJA. See Fur‐
142 ther details.
143
144 A (input/output) REAL array, dimension (LDA,N)
145 On entry, the M-by-N matrix A. On exit, A(N-K+1:N,1:MIN(K+L,M)
146 ) contains the triangular matrix R or part of R. See Purpose
147 for details.
148
149 LDA (input) INTEGER
150 The leading dimension of the array A. LDA >= max(1,M).
151
152 B (input/output) REAL array, dimension (LDB,N)
153 On entry, the P-by-N matrix B. On exit, if necessary, B(M-
154 K+1:L,N+M-K-L+1:N) contains a part of R. See Purpose for
155 details.
156
157 LDB (input) INTEGER
158 The leading dimension of the array B. LDB >= max(1,P).
159
160 TOLA (input) REAL
161 TOLB (input) REAL TOLA and TOLB are the convergence criteria
162 for the Jacobi- Kogbetliantz iteration procedure. Generally,
163 they are the same as used in the preprocessing step, say TOLA =
164 max(M,N)*norm(A)*MACHEPS, TOLB = max(P,N)*norm(B)*MACHEPS.
165
166 ALPHA (output) REAL array, dimension (N)
167 BETA (output) REAL array, dimension (N) On exit, ALPHA and
168 BETA contain the generalized singular value pairs of A and B;
169 ALPHA(1:K) = 1,
170 BETA(1:K) = 0, and if M-K-L >= 0, ALPHA(K+1:K+L) = diag(C),
171 BETA(K+1:K+L) = diag(S), or if M-K-L < 0, ALPHA(K+1:M)= C,
172 ALPHA(M+1:K+L)= 0
173 BETA(K+1:M) = S, BETA(M+1:K+L) = 1. Furthermore, if K+L < N,
174 ALPHA(K+L+1:N) = 0 and
175 BETA(K+L+1:N) = 0.
176
177 U (input/output) REAL array, dimension (LDU,M)
178 On entry, if JOBU = 'U', U must contain a matrix U1 (usually
179 the orthogonal matrix returned by SGGSVP). On exit, if JOBU =
180 'I', U contains the orthogonal matrix U; if JOBU = 'U', U con‐
181 tains the product U1*U. If JOBU = 'N', U is not referenced.
182
183 LDU (input) INTEGER
184 The leading dimension of the array U. LDU >= max(1,M) if JOBU =
185 'U'; LDU >= 1 otherwise.
186
187 V (input/output) REAL array, dimension (LDV,P)
188 On entry, if JOBV = 'V', V must contain a matrix V1 (usually
189 the orthogonal matrix returned by SGGSVP). On exit, if JOBV =
190 'I', V contains the orthogonal matrix V; if JOBV = 'V', V con‐
191 tains the product V1*V. If JOBV = 'N', V is not referenced.
192
193 LDV (input) INTEGER
194 The leading dimension of the array V. LDV >= max(1,P) if JOBV =
195 'V'; LDV >= 1 otherwise.
196
197 Q (input/output) REAL array, dimension (LDQ,N)
198 On entry, if JOBQ = 'Q', Q must contain a matrix Q1 (usually
199 the orthogonal matrix returned by SGGSVP). On exit, if JOBQ =
200 'I', Q contains the orthogonal matrix Q; if JOBQ = 'Q', Q con‐
201 tains the product Q1*Q. If JOBQ = 'N', Q is not referenced.
202
203 LDQ (input) INTEGER
204 The leading dimension of the array Q. LDQ >= max(1,N) if JOBQ =
205 'Q'; LDQ >= 1 otherwise.
206
207 WORK (workspace) REAL array, dimension (2*N)
208
209 NCYCLE (output) INTEGER
210 The number of cycles required for convergence.
211
212 INFO (output) INTEGER
213 = 0: successful exit
214 < 0: if INFO = -i, the i-th argument had an illegal value.
215 = 1: the procedure does not converge after MAXIT cycles.
216
218 MAXIT INTEGER
219 MAXIT specifies the total loops that the iterative procedure
220 may take. If after MAXIT cycles, the routine fails to converge,
221 we return INFO = 1.
222
223 Further Details ===============
224
225 STGSJA essentially uses a variant of Kogbetliantz algorithm to
226 reduce min(L,M-K)-by-L triangular (or trapezoidal) matrix A23
227 and L-by-L matrix B13 to the form:
228
229 U1'*A13*Q1 = C1*R1; V1'*B13*Q1 = S1*R1,
230
231 where U1, V1 and Q1 are orthogonal matrix, and Z' is the trans‐
232 pose of Z. C1 and S1 are diagonal matrices satisfying
233
234 C1**2 + S1**2 = I,
235
236 and R1 is an L-by-L nonsingular upper triangular matrix.
237
238
239
240 LAPACK routine (version 3.1) November 2006 STGSJA(1)