1 | SUBROUTINE SLALSA( ICOMPQ, SMLSIZ, N, NRHS, B, LDB, BX, LDBX, U,
|
---|
2 | $ LDU, VT, K, DIFL, DIFR, Z, POLES, GIVPTR,
|
---|
3 | $ GIVCOL, LDGCOL, PERM, GIVNUM, C, S, WORK,
|
---|
4 | $ IWORK, INFO )
|
---|
5 | *
|
---|
6 | * -- LAPACK routine (version 3.1) --
|
---|
7 | * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
|
---|
8 | * November 2006
|
---|
9 | *
|
---|
10 | * .. Scalar Arguments ..
|
---|
11 | INTEGER ICOMPQ, INFO, LDB, LDBX, LDGCOL, LDU, N, NRHS,
|
---|
12 | $ SMLSIZ
|
---|
13 | * ..
|
---|
14 | * .. Array Arguments ..
|
---|
15 | INTEGER GIVCOL( LDGCOL, * ), GIVPTR( * ), IWORK( * ),
|
---|
16 | $ K( * ), PERM( LDGCOL, * )
|
---|
17 | REAL B( LDB, * ), BX( LDBX, * ), C( * ),
|
---|
18 | $ DIFL( LDU, * ), DIFR( LDU, * ),
|
---|
19 | $ GIVNUM( LDU, * ), POLES( LDU, * ), S( * ),
|
---|
20 | $ U( LDU, * ), VT( LDU, * ), WORK( * ),
|
---|
21 | $ Z( LDU, * )
|
---|
22 | * ..
|
---|
23 | *
|
---|
24 | * Purpose
|
---|
25 | * =======
|
---|
26 | *
|
---|
27 | * SLALSA is an itermediate step in solving the least squares problem
|
---|
28 | * by computing the SVD of the coefficient matrix in compact form (The
|
---|
29 | * singular vectors are computed as products of simple orthorgonal
|
---|
30 | * matrices.).
|
---|
31 | *
|
---|
32 | * If ICOMPQ = 0, SLALSA applies the inverse of the left singular vector
|
---|
33 | * matrix of an upper bidiagonal matrix to the right hand side; and if
|
---|
34 | * ICOMPQ = 1, SLALSA applies the right singular vector matrix to the
|
---|
35 | * right hand side. The singular vector matrices were generated in
|
---|
36 | * compact form by SLALSA.
|
---|
37 | *
|
---|
38 | * Arguments
|
---|
39 | * =========
|
---|
40 | *
|
---|
41 | *
|
---|
42 | * ICOMPQ (input) INTEGER
|
---|
43 | * Specifies whether the left or the right singular vector
|
---|
44 | * matrix is involved.
|
---|
45 | * = 0: Left singular vector matrix
|
---|
46 | * = 1: Right singular vector matrix
|
---|
47 | *
|
---|
48 | * SMLSIZ (input) INTEGER
|
---|
49 | * The maximum size of the subproblems at the bottom of the
|
---|
50 | * computation tree.
|
---|
51 | *
|
---|
52 | * N (input) INTEGER
|
---|
53 | * The row and column dimensions of the upper bidiagonal matrix.
|
---|
54 | *
|
---|
55 | * NRHS (input) INTEGER
|
---|
56 | * The number of columns of B and BX. NRHS must be at least 1.
|
---|
57 | *
|
---|
58 | * B (input/output) REAL array, dimension ( LDB, NRHS )
|
---|
59 | * On input, B contains the right hand sides of the least
|
---|
60 | * squares problem in rows 1 through M.
|
---|
61 | * On output, B contains the solution X in rows 1 through N.
|
---|
62 | *
|
---|
63 | * LDB (input) INTEGER
|
---|
64 | * The leading dimension of B in the calling subprogram.
|
---|
65 | * LDB must be at least max(1,MAX( M, N ) ).
|
---|
66 | *
|
---|
67 | * BX (output) REAL array, dimension ( LDBX, NRHS )
|
---|
68 | * On exit, the result of applying the left or right singular
|
---|
69 | * vector matrix to B.
|
---|
70 | *
|
---|
71 | * LDBX (input) INTEGER
|
---|
72 | * The leading dimension of BX.
|
---|
73 | *
|
---|
74 | * U (input) REAL array, dimension ( LDU, SMLSIZ ).
|
---|
75 | * On entry, U contains the left singular vector matrices of all
|
---|
76 | * subproblems at the bottom level.
|
---|
77 | *
|
---|
78 | * LDU (input) INTEGER, LDU = > N.
|
---|
79 | * The leading dimension of arrays U, VT, DIFL, DIFR,
|
---|
80 | * POLES, GIVNUM, and Z.
|
---|
81 | *
|
---|
82 | * VT (input) REAL array, dimension ( LDU, SMLSIZ+1 ).
|
---|
83 | * On entry, VT' contains the right singular vector matrices of
|
---|
84 | * all subproblems at the bottom level.
|
---|
85 | *
|
---|
86 | * K (input) INTEGER array, dimension ( N ).
|
---|
87 | *
|
---|
88 | * DIFL (input) REAL array, dimension ( LDU, NLVL ).
|
---|
89 | * where NLVL = INT(log_2 (N/(SMLSIZ+1))) + 1.
|
---|
90 | *
|
---|
91 | * DIFR (input) REAL array, dimension ( LDU, 2 * NLVL ).
|
---|
92 | * On entry, DIFL(*, I) and DIFR(*, 2 * I -1) record
|
---|
93 | * distances between singular values on the I-th level and
|
---|
94 | * singular values on the (I -1)-th level, and DIFR(*, 2 * I)
|
---|
95 | * record the normalizing factors of the right singular vectors
|
---|
96 | * matrices of subproblems on I-th level.
|
---|
97 | *
|
---|
98 | * Z (input) REAL array, dimension ( LDU, NLVL ).
|
---|
99 | * On entry, Z(1, I) contains the components of the deflation-
|
---|
100 | * adjusted updating row vector for subproblems on the I-th
|
---|
101 | * level.
|
---|
102 | *
|
---|
103 | * POLES (input) REAL array, dimension ( LDU, 2 * NLVL ).
|
---|
104 | * On entry, POLES(*, 2 * I -1: 2 * I) contains the new and old
|
---|
105 | * singular values involved in the secular equations on the I-th
|
---|
106 | * level.
|
---|
107 | *
|
---|
108 | * GIVPTR (input) INTEGER array, dimension ( N ).
|
---|
109 | * On entry, GIVPTR( I ) records the number of Givens
|
---|
110 | * rotations performed on the I-th problem on the computation
|
---|
111 | * tree.
|
---|
112 | *
|
---|
113 | * GIVCOL (input) INTEGER array, dimension ( LDGCOL, 2 * NLVL ).
|
---|
114 | * On entry, for each I, GIVCOL(*, 2 * I - 1: 2 * I) records the
|
---|
115 | * locations of Givens rotations performed on the I-th level on
|
---|
116 | * the computation tree.
|
---|
117 | *
|
---|
118 | * LDGCOL (input) INTEGER, LDGCOL = > N.
|
---|
119 | * The leading dimension of arrays GIVCOL and PERM.
|
---|
120 | *
|
---|
121 | * PERM (input) INTEGER array, dimension ( LDGCOL, NLVL ).
|
---|
122 | * On entry, PERM(*, I) records permutations done on the I-th
|
---|
123 | * level of the computation tree.
|
---|
124 | *
|
---|
125 | * GIVNUM (input) REAL array, dimension ( LDU, 2 * NLVL ).
|
---|
126 | * On entry, GIVNUM(*, 2 *I -1 : 2 * I) records the C- and S-
|
---|
127 | * values of Givens rotations performed on the I-th level on the
|
---|
128 | * computation tree.
|
---|
129 | *
|
---|
130 | * C (input) REAL array, dimension ( N ).
|
---|
131 | * On entry, if the I-th subproblem is not square,
|
---|
132 | * C( I ) contains the C-value of a Givens rotation related to
|
---|
133 | * the right null space of the I-th subproblem.
|
---|
134 | *
|
---|
135 | * S (input) REAL array, dimension ( N ).
|
---|
136 | * On entry, if the I-th subproblem is not square,
|
---|
137 | * S( I ) contains the S-value of a Givens rotation related to
|
---|
138 | * the right null space of the I-th subproblem.
|
---|
139 | *
|
---|
140 | * WORK (workspace) REAL array.
|
---|
141 | * The dimension must be at least N.
|
---|
142 | *
|
---|
143 | * IWORK (workspace) INTEGER array.
|
---|
144 | * The dimension must be at least 3 * N
|
---|
145 | *
|
---|
146 | * INFO (output) INTEGER
|
---|
147 | * = 0: successful exit.
|
---|
148 | * < 0: if INFO = -i, the i-th argument had an illegal value.
|
---|
149 | *
|
---|
150 | * Further Details
|
---|
151 | * ===============
|
---|
152 | *
|
---|
153 | * Based on contributions by
|
---|
154 | * Ming Gu and Ren-Cang Li, Computer Science Division, University of
|
---|
155 | * California at Berkeley, USA
|
---|
156 | * Osni Marques, LBNL/NERSC, USA
|
---|
157 | *
|
---|
158 | * =====================================================================
|
---|
159 | *
|
---|
160 | * .. Parameters ..
|
---|
161 | REAL ZERO, ONE
|
---|
162 | PARAMETER ( ZERO = 0.0E0, ONE = 1.0E0 )
|
---|
163 | * ..
|
---|
164 | * .. Local Scalars ..
|
---|
165 | INTEGER I, I1, IC, IM1, INODE, J, LF, LL, LVL, LVL2,
|
---|
166 | $ ND, NDB1, NDIML, NDIMR, NL, NLF, NLP1, NLVL,
|
---|
167 | $ NR, NRF, NRP1, SQRE
|
---|
168 | * ..
|
---|
169 | * .. External Subroutines ..
|
---|
170 | EXTERNAL SCOPY, SGEMM, SLALS0, SLASDT, XERBLA
|
---|
171 | * ..
|
---|
172 | * .. Executable Statements ..
|
---|
173 | *
|
---|
174 | * Test the input parameters.
|
---|
175 | *
|
---|
176 | INFO = 0
|
---|
177 | *
|
---|
178 | IF( ( ICOMPQ.LT.0 ) .OR. ( ICOMPQ.GT.1 ) ) THEN
|
---|
179 | INFO = -1
|
---|
180 | ELSE IF( SMLSIZ.LT.3 ) THEN
|
---|
181 | INFO = -2
|
---|
182 | ELSE IF( N.LT.SMLSIZ ) THEN
|
---|
183 | INFO = -3
|
---|
184 | ELSE IF( NRHS.LT.1 ) THEN
|
---|
185 | INFO = -4
|
---|
186 | ELSE IF( LDB.LT.N ) THEN
|
---|
187 | INFO = -6
|
---|
188 | ELSE IF( LDBX.LT.N ) THEN
|
---|
189 | INFO = -8
|
---|
190 | ELSE IF( LDU.LT.N ) THEN
|
---|
191 | INFO = -10
|
---|
192 | ELSE IF( LDGCOL.LT.N ) THEN
|
---|
193 | INFO = -19
|
---|
194 | END IF
|
---|
195 | IF( INFO.NE.0 ) THEN
|
---|
196 | CALL XERBLA( 'SLALSA', -INFO )
|
---|
197 | RETURN
|
---|
198 | END IF
|
---|
199 | *
|
---|
200 | * Book-keeping and setting up the computation tree.
|
---|
201 | *
|
---|
202 | INODE = 1
|
---|
203 | NDIML = INODE + N
|
---|
204 | NDIMR = NDIML + N
|
---|
205 | *
|
---|
206 | CALL SLASDT( N, NLVL, ND, IWORK( INODE ), IWORK( NDIML ),
|
---|
207 | $ IWORK( NDIMR ), SMLSIZ )
|
---|
208 | *
|
---|
209 | * The following code applies back the left singular vector factors.
|
---|
210 | * For applying back the right singular vector factors, go to 50.
|
---|
211 | *
|
---|
212 | IF( ICOMPQ.EQ.1 ) THEN
|
---|
213 | GO TO 50
|
---|
214 | END IF
|
---|
215 | *
|
---|
216 | * The nodes on the bottom level of the tree were solved
|
---|
217 | * by SLASDQ. The corresponding left and right singular vector
|
---|
218 | * matrices are in explicit form. First apply back the left
|
---|
219 | * singular vector matrices.
|
---|
220 | *
|
---|
221 | NDB1 = ( ND+1 ) / 2
|
---|
222 | DO 10 I = NDB1, ND
|
---|
223 | *
|
---|
224 | * IC : center row of each node
|
---|
225 | * NL : number of rows of left subproblem
|
---|
226 | * NR : number of rows of right subproblem
|
---|
227 | * NLF: starting row of the left subproblem
|
---|
228 | * NRF: starting row of the right subproblem
|
---|
229 | *
|
---|
230 | I1 = I - 1
|
---|
231 | IC = IWORK( INODE+I1 )
|
---|
232 | NL = IWORK( NDIML+I1 )
|
---|
233 | NR = IWORK( NDIMR+I1 )
|
---|
234 | NLF = IC - NL
|
---|
235 | NRF = IC + 1
|
---|
236 | CALL SGEMM( 'T', 'N', NL, NRHS, NL, ONE, U( NLF, 1 ), LDU,
|
---|
237 | $ B( NLF, 1 ), LDB, ZERO, BX( NLF, 1 ), LDBX )
|
---|
238 | CALL SGEMM( 'T', 'N', NR, NRHS, NR, ONE, U( NRF, 1 ), LDU,
|
---|
239 | $ B( NRF, 1 ), LDB, ZERO, BX( NRF, 1 ), LDBX )
|
---|
240 | 10 CONTINUE
|
---|
241 | *
|
---|
242 | * Next copy the rows of B that correspond to unchanged rows
|
---|
243 | * in the bidiagonal matrix to BX.
|
---|
244 | *
|
---|
245 | DO 20 I = 1, ND
|
---|
246 | IC = IWORK( INODE+I-1 )
|
---|
247 | CALL SCOPY( NRHS, B( IC, 1 ), LDB, BX( IC, 1 ), LDBX )
|
---|
248 | 20 CONTINUE
|
---|
249 | *
|
---|
250 | * Finally go through the left singular vector matrices of all
|
---|
251 | * the other subproblems bottom-up on the tree.
|
---|
252 | *
|
---|
253 | J = 2**NLVL
|
---|
254 | SQRE = 0
|
---|
255 | *
|
---|
256 | DO 40 LVL = NLVL, 1, -1
|
---|
257 | LVL2 = 2*LVL - 1
|
---|
258 | *
|
---|
259 | * find the first node LF and last node LL on
|
---|
260 | * the current level LVL
|
---|
261 | *
|
---|
262 | IF( LVL.EQ.1 ) THEN
|
---|
263 | LF = 1
|
---|
264 | LL = 1
|
---|
265 | ELSE
|
---|
266 | LF = 2**( LVL-1 )
|
---|
267 | LL = 2*LF - 1
|
---|
268 | END IF
|
---|
269 | DO 30 I = LF, LL
|
---|
270 | IM1 = I - 1
|
---|
271 | IC = IWORK( INODE+IM1 )
|
---|
272 | NL = IWORK( NDIML+IM1 )
|
---|
273 | NR = IWORK( NDIMR+IM1 )
|
---|
274 | NLF = IC - NL
|
---|
275 | NRF = IC + 1
|
---|
276 | J = J - 1
|
---|
277 | CALL SLALS0( ICOMPQ, NL, NR, SQRE, NRHS, BX( NLF, 1 ), LDBX,
|
---|
278 | $ B( NLF, 1 ), LDB, PERM( NLF, LVL ),
|
---|
279 | $ GIVPTR( J ), GIVCOL( NLF, LVL2 ), LDGCOL,
|
---|
280 | $ GIVNUM( NLF, LVL2 ), LDU, POLES( NLF, LVL2 ),
|
---|
281 | $ DIFL( NLF, LVL ), DIFR( NLF, LVL2 ),
|
---|
282 | $ Z( NLF, LVL ), K( J ), C( J ), S( J ), WORK,
|
---|
283 | $ INFO )
|
---|
284 | 30 CONTINUE
|
---|
285 | 40 CONTINUE
|
---|
286 | GO TO 90
|
---|
287 | *
|
---|
288 | * ICOMPQ = 1: applying back the right singular vector factors.
|
---|
289 | *
|
---|
290 | 50 CONTINUE
|
---|
291 | *
|
---|
292 | * First now go through the right singular vector matrices of all
|
---|
293 | * the tree nodes top-down.
|
---|
294 | *
|
---|
295 | J = 0
|
---|
296 | DO 70 LVL = 1, NLVL
|
---|
297 | LVL2 = 2*LVL - 1
|
---|
298 | *
|
---|
299 | * Find the first node LF and last node LL on
|
---|
300 | * the current level LVL.
|
---|
301 | *
|
---|
302 | IF( LVL.EQ.1 ) THEN
|
---|
303 | LF = 1
|
---|
304 | LL = 1
|
---|
305 | ELSE
|
---|
306 | LF = 2**( LVL-1 )
|
---|
307 | LL = 2*LF - 1
|
---|
308 | END IF
|
---|
309 | DO 60 I = LL, LF, -1
|
---|
310 | IM1 = I - 1
|
---|
311 | IC = IWORK( INODE+IM1 )
|
---|
312 | NL = IWORK( NDIML+IM1 )
|
---|
313 | NR = IWORK( NDIMR+IM1 )
|
---|
314 | NLF = IC - NL
|
---|
315 | NRF = IC + 1
|
---|
316 | IF( I.EQ.LL ) THEN
|
---|
317 | SQRE = 0
|
---|
318 | ELSE
|
---|
319 | SQRE = 1
|
---|
320 | END IF
|
---|
321 | J = J + 1
|
---|
322 | CALL SLALS0( ICOMPQ, NL, NR, SQRE, NRHS, B( NLF, 1 ), LDB,
|
---|
323 | $ BX( NLF, 1 ), LDBX, PERM( NLF, LVL ),
|
---|
324 | $ GIVPTR( J ), GIVCOL( NLF, LVL2 ), LDGCOL,
|
---|
325 | $ GIVNUM( NLF, LVL2 ), LDU, POLES( NLF, LVL2 ),
|
---|
326 | $ DIFL( NLF, LVL ), DIFR( NLF, LVL2 ),
|
---|
327 | $ Z( NLF, LVL ), K( J ), C( J ), S( J ), WORK,
|
---|
328 | $ INFO )
|
---|
329 | 60 CONTINUE
|
---|
330 | 70 CONTINUE
|
---|
331 | *
|
---|
332 | * The nodes on the bottom level of the tree were solved
|
---|
333 | * by SLASDQ. The corresponding right singular vector
|
---|
334 | * matrices are in explicit form. Apply them back.
|
---|
335 | *
|
---|
336 | NDB1 = ( ND+1 ) / 2
|
---|
337 | DO 80 I = NDB1, ND
|
---|
338 | I1 = I - 1
|
---|
339 | IC = IWORK( INODE+I1 )
|
---|
340 | NL = IWORK( NDIML+I1 )
|
---|
341 | NR = IWORK( NDIMR+I1 )
|
---|
342 | NLP1 = NL + 1
|
---|
343 | IF( I.EQ.ND ) THEN
|
---|
344 | NRP1 = NR
|
---|
345 | ELSE
|
---|
346 | NRP1 = NR + 1
|
---|
347 | END IF
|
---|
348 | NLF = IC - NL
|
---|
349 | NRF = IC + 1
|
---|
350 | CALL SGEMM( 'T', 'N', NLP1, NRHS, NLP1, ONE, VT( NLF, 1 ), LDU,
|
---|
351 | $ B( NLF, 1 ), LDB, ZERO, BX( NLF, 1 ), LDBX )
|
---|
352 | CALL SGEMM( 'T', 'N', NRP1, NRHS, NRP1, ONE, VT( NRF, 1 ), LDU,
|
---|
353 | $ B( NRF, 1 ), LDB, ZERO, BX( NRF, 1 ), LDBX )
|
---|
354 | 80 CONTINUE
|
---|
355 | *
|
---|
356 | 90 CONTINUE
|
---|
357 | *
|
---|
358 | RETURN
|
---|
359 | *
|
---|
360 | * End of SLALSA
|
---|
361 | *
|
---|
362 | END
|
---|