1 SUBROUTINE DLASDA( ICOMPQ, SMLSIZ, N, SQRE, D, E, U, LDU, VT, K,
2 $ DIFL, DIFR, Z, POLES, GIVPTR, GIVCOL, LDGCOL,
3 $ PERM, GIVNUM, C, S, WORK, IWORK, INFO )
4 *
5 * -- LAPACK auxiliary routine (version 3.2.2) --
6 * -- LAPACK is a software package provided by Univ. of Tennessee, --
7 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
8 * June 2010
9 *
10 * .. Scalar Arguments ..
11 INTEGER ICOMPQ, INFO, LDGCOL, LDU, N, SMLSIZ, SQRE
12 * ..
13 * .. Array Arguments ..
14 INTEGER GIVCOL( LDGCOL, * ), GIVPTR( * ), IWORK( * ),
15 $ K( * ), PERM( LDGCOL, * )
16 DOUBLE PRECISION C( * ), D( * ), DIFL( LDU, * ), DIFR( LDU, * ),
17 $ E( * ), GIVNUM( LDU, * ), POLES( LDU, * ),
18 $ S( * ), U( LDU, * ), VT( LDU, * ), WORK( * ),
19 $ Z( LDU, * )
20 * ..
21 *
22 * Purpose
23 * =======
24 *
25 * Using a divide and conquer approach, DLASDA computes the singular
26 * value decomposition (SVD) of a real upper bidiagonal N-by-M matrix
27 * B with diagonal D and offdiagonal E, where M = N + SQRE. The
28 * algorithm computes the singular values in the SVD B = U * S * VT.
29 * The orthogonal matrices U and VT are optionally computed in
30 * compact form.
31 *
32 * A related subroutine, DLASD0, computes the singular values and
33 * the singular vectors in explicit form.
34 *
35 * Arguments
36 * =========
37 *
38 * ICOMPQ (input) INTEGER
39 * Specifies whether singular vectors are to be computed
40 * in compact form, as follows
41 * = 0: Compute singular values only.
42 * = 1: Compute singular vectors of upper bidiagonal
43 * matrix in compact form.
44 *
45 * SMLSIZ (input) INTEGER
46 * The maximum size of the subproblems at the bottom of the
47 * computation tree.
48 *
49 * N (input) INTEGER
50 * The row dimension of the upper bidiagonal matrix. This is
51 * also the dimension of the main diagonal array D.
52 *
53 * SQRE (input) INTEGER
54 * Specifies the column dimension of the bidiagonal matrix.
55 * = 0: The bidiagonal matrix has column dimension M = N;
56 * = 1: The bidiagonal matrix has column dimension M = N + 1.
57 *
58 * D (input/output) DOUBLE PRECISION array, dimension ( N )
59 * On entry D contains the main diagonal of the bidiagonal
60 * matrix. On exit D, if INFO = 0, contains its singular values.
61 *
62 * E (input) DOUBLE PRECISION array, dimension ( M-1 )
63 * Contains the subdiagonal entries of the bidiagonal matrix.
64 * On exit, E has been destroyed.
65 *
66 * U (output) DOUBLE PRECISION array,
67 * dimension ( LDU, SMLSIZ ) if ICOMPQ = 1, and not referenced
68 * if ICOMPQ = 0. If ICOMPQ = 1, on exit, U contains the left
69 * singular vector matrices of all subproblems at the bottom
70 * level.
71 *
72 * LDU (input) INTEGER, LDU = > N.
73 * The leading dimension of arrays U, VT, DIFL, DIFR, POLES,
74 * GIVNUM, and Z.
75 *
76 * VT (output) DOUBLE PRECISION array,
77 * dimension ( LDU, SMLSIZ+1 ) if ICOMPQ = 1, and not referenced
78 * if ICOMPQ = 0. If ICOMPQ = 1, on exit, VT**T contains the right
79 * singular vector matrices of all subproblems at the bottom
80 * level.
81 *
82 * K (output) INTEGER array,
83 * dimension ( N ) if ICOMPQ = 1 and dimension 1 if ICOMPQ = 0.
84 * If ICOMPQ = 1, on exit, K(I) is the dimension of the I-th
85 * secular equation on the computation tree.
86 *
87 * DIFL (output) DOUBLE PRECISION array, dimension ( LDU, NLVL ),
88 * where NLVL = floor(log_2 (N/SMLSIZ))).
89 *
90 * DIFR (output) DOUBLE PRECISION array,
91 * dimension ( LDU, 2 * NLVL ) if ICOMPQ = 1 and
92 * dimension ( N ) if ICOMPQ = 0.
93 * If ICOMPQ = 1, on exit, DIFL(1:N, I) and DIFR(1:N, 2 * I - 1)
94 * record distances between singular values on the I-th
95 * level and singular values on the (I -1)-th level, and
96 * DIFR(1:N, 2 * I ) contains the normalizing factors for
97 * the right singular vector matrix. See DLASD8 for details.
98 *
99 * Z (output) DOUBLE PRECISION array,
100 * dimension ( LDU, NLVL ) if ICOMPQ = 1 and
101 * dimension ( N ) if ICOMPQ = 0.
102 * The first K elements of Z(1, I) contain the components of
103 * the deflation-adjusted updating row vector for subproblems
104 * on the I-th level.
105 *
106 * POLES (output) DOUBLE PRECISION array,
107 * dimension ( LDU, 2 * NLVL ) if ICOMPQ = 1, and not referenced
108 * if ICOMPQ = 0. If ICOMPQ = 1, on exit, POLES(1, 2*I - 1) and
109 * POLES(1, 2*I) contain the new and old singular values
110 * involved in the secular equations on the I-th level.
111 *
112 * GIVPTR (output) INTEGER array,
113 * dimension ( N ) if ICOMPQ = 1, and not referenced if
114 * ICOMPQ = 0. If ICOMPQ = 1, on exit, GIVPTR( I ) records
115 * the number of Givens rotations performed on the I-th
116 * problem on the computation tree.
117 *
118 * GIVCOL (output) INTEGER array,
119 * dimension ( LDGCOL, 2 * NLVL ) if ICOMPQ = 1, and not
120 * referenced if ICOMPQ = 0. If ICOMPQ = 1, on exit, for each I,
121 * GIVCOL(1, 2 *I - 1) and GIVCOL(1, 2 *I) record the locations
122 * of Givens rotations performed on the I-th level on the
123 * computation tree.
124 *
125 * LDGCOL (input) INTEGER, LDGCOL = > N.
126 * The leading dimension of arrays GIVCOL and PERM.
127 *
128 * PERM (output) INTEGER array,
129 * dimension ( LDGCOL, NLVL ) if ICOMPQ = 1, and not referenced
130 * if ICOMPQ = 0. If ICOMPQ = 1, on exit, PERM(1, I) records
131 * permutations done on the I-th level of the computation tree.
132 *
133 * GIVNUM (output) DOUBLE PRECISION array,
134 * dimension ( LDU, 2 * NLVL ) if ICOMPQ = 1, and not
135 * referenced if ICOMPQ = 0. If ICOMPQ = 1, on exit, for each I,
136 * GIVNUM(1, 2 *I - 1) and GIVNUM(1, 2 *I) record the C- and S-
137 * values of Givens rotations performed on the I-th level on
138 * the computation tree.
139 *
140 * C (output) DOUBLE PRECISION array,
141 * dimension ( N ) if ICOMPQ = 1, and dimension 1 if ICOMPQ = 0.
142 * If ICOMPQ = 1 and the I-th subproblem is not square, on exit,
143 * C( I ) contains the C-value of a Givens rotation related to
144 * the right null space of the I-th subproblem.
145 *
146 * S (output) DOUBLE PRECISION array, dimension ( N ) if
147 * ICOMPQ = 1, and dimension 1 if ICOMPQ = 0. If ICOMPQ = 1
148 * and the I-th subproblem is not square, on exit, S( I )
149 * contains the S-value of a Givens rotation related to
150 * the right null space of the I-th subproblem.
151 *
152 * WORK (workspace) DOUBLE PRECISION array, dimension
153 * (6 * N + (SMLSIZ + 1)*(SMLSIZ + 1)).
154 *
155 * IWORK (workspace) INTEGER array.
156 * Dimension must be at least (7 * N).
157 *
158 * INFO (output) INTEGER
159 * = 0: successful exit.
160 * < 0: if INFO = -i, the i-th argument had an illegal value.
161 * > 0: if INFO = 1, a singular value did not converge
162 *
163 * Further Details
164 * ===============
165 *
166 * Based on contributions by
167 * Ming Gu and Huan Ren, Computer Science Division, University of
168 * California at Berkeley, USA
169 *
170 * =====================================================================
171 *
172 * .. Parameters ..
173 DOUBLE PRECISION ZERO, ONE
174 PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0 )
175 * ..
176 * .. Local Scalars ..
177 INTEGER I, I1, IC, IDXQ, IDXQI, IM1, INODE, ITEMP, IWK,
178 $ J, LF, LL, LVL, LVL2, M, NCC, ND, NDB1, NDIML,
179 $ NDIMR, NL, NLF, NLP1, NLVL, NR, NRF, NRP1, NRU,
180 $ NWORK1, NWORK2, SMLSZP, SQREI, VF, VFI, VL, VLI
181 DOUBLE PRECISION ALPHA, BETA
182 * ..
183 * .. External Subroutines ..
184 EXTERNAL DCOPY, DLASD6, DLASDQ, DLASDT, DLASET, XERBLA
185 * ..
186 * .. Executable Statements ..
187 *
188 * Test the input parameters.
189 *
190 INFO = 0
191 *
192 IF( ( ICOMPQ.LT.0 ) .OR. ( ICOMPQ.GT.1 ) ) THEN
193 INFO = -1
194 ELSE IF( SMLSIZ.LT.3 ) THEN
195 INFO = -2
196 ELSE IF( N.LT.0 ) THEN
197 INFO = -3
198 ELSE IF( ( SQRE.LT.0 ) .OR. ( SQRE.GT.1 ) ) THEN
199 INFO = -4
200 ELSE IF( LDU.LT.( N+SQRE ) ) THEN
201 INFO = -8
202 ELSE IF( LDGCOL.LT.N ) THEN
203 INFO = -17
204 END IF
205 IF( INFO.NE.0 ) THEN
206 CALL XERBLA( 'DLASDA', -INFO )
207 RETURN
208 END IF
209 *
210 M = N + SQRE
211 *
212 * If the input matrix is too small, call DLASDQ to find the SVD.
213 *
214 IF( N.LE.SMLSIZ ) THEN
215 IF( ICOMPQ.EQ.0 ) THEN
216 CALL DLASDQ( 'U', SQRE, N, 0, 0, 0, D, E, VT, LDU, U, LDU,
217 $ U, LDU, WORK, INFO )
218 ELSE
219 CALL DLASDQ( 'U', SQRE, N, M, N, 0, D, E, VT, LDU, U, LDU,
220 $ U, LDU, WORK, INFO )
221 END IF
222 RETURN
223 END IF
224 *
225 * Book-keeping and set up the computation tree.
226 *
227 INODE = 1
228 NDIML = INODE + N
229 NDIMR = NDIML + N
230 IDXQ = NDIMR + N
231 IWK = IDXQ + N
232 *
233 NCC = 0
234 NRU = 0
235 *
236 SMLSZP = SMLSIZ + 1
237 VF = 1
238 VL = VF + M
239 NWORK1 = VL + M
240 NWORK2 = NWORK1 + SMLSZP*SMLSZP
241 *
242 CALL DLASDT( N, NLVL, ND, IWORK( INODE ), IWORK( NDIML ),
243 $ IWORK( NDIMR ), SMLSIZ )
244 *
245 * for the nodes on bottom level of the tree, solve
246 * their subproblems by DLASDQ.
247 *
248 NDB1 = ( ND+1 ) / 2
249 DO 30 I = NDB1, ND
250 *
251 * IC : center row of each node
252 * NL : number of rows of left subproblem
253 * NR : number of rows of right subproblem
254 * NLF: starting row of the left subproblem
255 * NRF: starting row of the right subproblem
256 *
257 I1 = I - 1
258 IC = IWORK( INODE+I1 )
259 NL = IWORK( NDIML+I1 )
260 NLP1 = NL + 1
261 NR = IWORK( NDIMR+I1 )
262 NLF = IC - NL
263 NRF = IC + 1
264 IDXQI = IDXQ + NLF - 2
265 VFI = VF + NLF - 1
266 VLI = VL + NLF - 1
267 SQREI = 1
268 IF( ICOMPQ.EQ.0 ) THEN
269 CALL DLASET( 'A', NLP1, NLP1, ZERO, ONE, WORK( NWORK1 ),
270 $ SMLSZP )
271 CALL DLASDQ( 'U', SQREI, NL, NLP1, NRU, NCC, D( NLF ),
272 $ E( NLF ), WORK( NWORK1 ), SMLSZP,
273 $ WORK( NWORK2 ), NL, WORK( NWORK2 ), NL,
274 $ WORK( NWORK2 ), INFO )
275 ITEMP = NWORK1 + NL*SMLSZP
276 CALL DCOPY( NLP1, WORK( NWORK1 ), 1, WORK( VFI ), 1 )
277 CALL DCOPY( NLP1, WORK( ITEMP ), 1, WORK( VLI ), 1 )
278 ELSE
279 CALL DLASET( 'A', NL, NL, ZERO, ONE, U( NLF, 1 ), LDU )
280 CALL DLASET( 'A', NLP1, NLP1, ZERO, ONE, VT( NLF, 1 ), LDU )
281 CALL DLASDQ( 'U', SQREI, NL, NLP1, NL, NCC, D( NLF ),
282 $ E( NLF ), VT( NLF, 1 ), LDU, U( NLF, 1 ), LDU,
283 $ U( NLF, 1 ), LDU, WORK( NWORK1 ), INFO )
284 CALL DCOPY( NLP1, VT( NLF, 1 ), 1, WORK( VFI ), 1 )
285 CALL DCOPY( NLP1, VT( NLF, NLP1 ), 1, WORK( VLI ), 1 )
286 END IF
287 IF( INFO.NE.0 ) THEN
288 RETURN
289 END IF
290 DO 10 J = 1, NL
291 IWORK( IDXQI+J ) = J
292 10 CONTINUE
293 IF( ( I.EQ.ND ) .AND. ( SQRE.EQ.0 ) ) THEN
294 SQREI = 0
295 ELSE
296 SQREI = 1
297 END IF
298 IDXQI = IDXQI + NLP1
299 VFI = VFI + NLP1
300 VLI = VLI + NLP1
301 NRP1 = NR + SQREI
302 IF( ICOMPQ.EQ.0 ) THEN
303 CALL DLASET( 'A', NRP1, NRP1, ZERO, ONE, WORK( NWORK1 ),
304 $ SMLSZP )
305 CALL DLASDQ( 'U', SQREI, NR, NRP1, NRU, NCC, D( NRF ),
306 $ E( NRF ), WORK( NWORK1 ), SMLSZP,
307 $ WORK( NWORK2 ), NR, WORK( NWORK2 ), NR,
308 $ WORK( NWORK2 ), INFO )
309 ITEMP = NWORK1 + ( NRP1-1 )*SMLSZP
310 CALL DCOPY( NRP1, WORK( NWORK1 ), 1, WORK( VFI ), 1 )
311 CALL DCOPY( NRP1, WORK( ITEMP ), 1, WORK( VLI ), 1 )
312 ELSE
313 CALL DLASET( 'A', NR, NR, ZERO, ONE, U( NRF, 1 ), LDU )
314 CALL DLASET( 'A', NRP1, NRP1, ZERO, ONE, VT( NRF, 1 ), LDU )
315 CALL DLASDQ( 'U', SQREI, NR, NRP1, NR, NCC, D( NRF ),
316 $ E( NRF ), VT( NRF, 1 ), LDU, U( NRF, 1 ), LDU,
317 $ U( NRF, 1 ), LDU, WORK( NWORK1 ), INFO )
318 CALL DCOPY( NRP1, VT( NRF, 1 ), 1, WORK( VFI ), 1 )
319 CALL DCOPY( NRP1, VT( NRF, NRP1 ), 1, WORK( VLI ), 1 )
320 END IF
321 IF( INFO.NE.0 ) THEN
322 RETURN
323 END IF
324 DO 20 J = 1, NR
325 IWORK( IDXQI+J ) = J
326 20 CONTINUE
327 30 CONTINUE
328 *
329 * Now conquer each subproblem bottom-up.
330 *
331 J = 2**NLVL
332 DO 50 LVL = NLVL, 1, -1
333 LVL2 = LVL*2 - 1
334 *
335 * Find the first node LF and last node LL on
336 * the current level LVL.
337 *
338 IF( LVL.EQ.1 ) THEN
339 LF = 1
340 LL = 1
341 ELSE
342 LF = 2**( LVL-1 )
343 LL = 2*LF - 1
344 END IF
345 DO 40 I = LF, LL
346 IM1 = I - 1
347 IC = IWORK( INODE+IM1 )
348 NL = IWORK( NDIML+IM1 )
349 NR = IWORK( NDIMR+IM1 )
350 NLF = IC - NL
351 NRF = IC + 1
352 IF( I.EQ.LL ) THEN
353 SQREI = SQRE
354 ELSE
355 SQREI = 1
356 END IF
357 VFI = VF + NLF - 1
358 VLI = VL + NLF - 1
359 IDXQI = IDXQ + NLF - 1
360 ALPHA = D( IC )
361 BETA = E( IC )
362 IF( ICOMPQ.EQ.0 ) THEN
363 CALL DLASD6( ICOMPQ, NL, NR, SQREI, D( NLF ),
364 $ WORK( VFI ), WORK( VLI ), ALPHA, BETA,
365 $ IWORK( IDXQI ), PERM, GIVPTR( 1 ), GIVCOL,
366 $ LDGCOL, GIVNUM, LDU, POLES, DIFL, DIFR, Z,
367 $ K( 1 ), C( 1 ), S( 1 ), WORK( NWORK1 ),
368 $ IWORK( IWK ), INFO )
369 ELSE
370 J = J - 1
371 CALL DLASD6( ICOMPQ, NL, NR, SQREI, D( NLF ),
372 $ WORK( VFI ), WORK( VLI ), ALPHA, BETA,
373 $ IWORK( IDXQI ), PERM( NLF, LVL ),
374 $ GIVPTR( J ), GIVCOL( NLF, LVL2 ), LDGCOL,
375 $ GIVNUM( NLF, LVL2 ), LDU,
376 $ POLES( NLF, LVL2 ), DIFL( NLF, LVL ),
377 $ DIFR( NLF, LVL2 ), Z( NLF, LVL ), K( J ),
378 $ C( J ), S( J ), WORK( NWORK1 ),
379 $ IWORK( IWK ), INFO )
380 END IF
381 IF( INFO.NE.0 ) THEN
382 RETURN
383 END IF
384 40 CONTINUE
385 50 CONTINUE
386 *
387 RETURN
388 *
389 * End of DLASDA
390 *
391 END
2 $ DIFL, DIFR, Z, POLES, GIVPTR, GIVCOL, LDGCOL,
3 $ PERM, GIVNUM, C, S, WORK, IWORK, INFO )
4 *
5 * -- LAPACK auxiliary routine (version 3.2.2) --
6 * -- LAPACK is a software package provided by Univ. of Tennessee, --
7 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
8 * June 2010
9 *
10 * .. Scalar Arguments ..
11 INTEGER ICOMPQ, INFO, LDGCOL, LDU, N, SMLSIZ, SQRE
12 * ..
13 * .. Array Arguments ..
14 INTEGER GIVCOL( LDGCOL, * ), GIVPTR( * ), IWORK( * ),
15 $ K( * ), PERM( LDGCOL, * )
16 DOUBLE PRECISION C( * ), D( * ), DIFL( LDU, * ), DIFR( LDU, * ),
17 $ E( * ), GIVNUM( LDU, * ), POLES( LDU, * ),
18 $ S( * ), U( LDU, * ), VT( LDU, * ), WORK( * ),
19 $ Z( LDU, * )
20 * ..
21 *
22 * Purpose
23 * =======
24 *
25 * Using a divide and conquer approach, DLASDA computes the singular
26 * value decomposition (SVD) of a real upper bidiagonal N-by-M matrix
27 * B with diagonal D and offdiagonal E, where M = N + SQRE. The
28 * algorithm computes the singular values in the SVD B = U * S * VT.
29 * The orthogonal matrices U and VT are optionally computed in
30 * compact form.
31 *
32 * A related subroutine, DLASD0, computes the singular values and
33 * the singular vectors in explicit form.
34 *
35 * Arguments
36 * =========
37 *
38 * ICOMPQ (input) INTEGER
39 * Specifies whether singular vectors are to be computed
40 * in compact form, as follows
41 * = 0: Compute singular values only.
42 * = 1: Compute singular vectors of upper bidiagonal
43 * matrix in compact form.
44 *
45 * SMLSIZ (input) INTEGER
46 * The maximum size of the subproblems at the bottom of the
47 * computation tree.
48 *
49 * N (input) INTEGER
50 * The row dimension of the upper bidiagonal matrix. This is
51 * also the dimension of the main diagonal array D.
52 *
53 * SQRE (input) INTEGER
54 * Specifies the column dimension of the bidiagonal matrix.
55 * = 0: The bidiagonal matrix has column dimension M = N;
56 * = 1: The bidiagonal matrix has column dimension M = N + 1.
57 *
58 * D (input/output) DOUBLE PRECISION array, dimension ( N )
59 * On entry D contains the main diagonal of the bidiagonal
60 * matrix. On exit D, if INFO = 0, contains its singular values.
61 *
62 * E (input) DOUBLE PRECISION array, dimension ( M-1 )
63 * Contains the subdiagonal entries of the bidiagonal matrix.
64 * On exit, E has been destroyed.
65 *
66 * U (output) DOUBLE PRECISION array,
67 * dimension ( LDU, SMLSIZ ) if ICOMPQ = 1, and not referenced
68 * if ICOMPQ = 0. If ICOMPQ = 1, on exit, U contains the left
69 * singular vector matrices of all subproblems at the bottom
70 * level.
71 *
72 * LDU (input) INTEGER, LDU = > N.
73 * The leading dimension of arrays U, VT, DIFL, DIFR, POLES,
74 * GIVNUM, and Z.
75 *
76 * VT (output) DOUBLE PRECISION array,
77 * dimension ( LDU, SMLSIZ+1 ) if ICOMPQ = 1, and not referenced
78 * if ICOMPQ = 0. If ICOMPQ = 1, on exit, VT**T contains the right
79 * singular vector matrices of all subproblems at the bottom
80 * level.
81 *
82 * K (output) INTEGER array,
83 * dimension ( N ) if ICOMPQ = 1 and dimension 1 if ICOMPQ = 0.
84 * If ICOMPQ = 1, on exit, K(I) is the dimension of the I-th
85 * secular equation on the computation tree.
86 *
87 * DIFL (output) DOUBLE PRECISION array, dimension ( LDU, NLVL ),
88 * where NLVL = floor(log_2 (N/SMLSIZ))).
89 *
90 * DIFR (output) DOUBLE PRECISION array,
91 * dimension ( LDU, 2 * NLVL ) if ICOMPQ = 1 and
92 * dimension ( N ) if ICOMPQ = 0.
93 * If ICOMPQ = 1, on exit, DIFL(1:N, I) and DIFR(1:N, 2 * I - 1)
94 * record distances between singular values on the I-th
95 * level and singular values on the (I -1)-th level, and
96 * DIFR(1:N, 2 * I ) contains the normalizing factors for
97 * the right singular vector matrix. See DLASD8 for details.
98 *
99 * Z (output) DOUBLE PRECISION array,
100 * dimension ( LDU, NLVL ) if ICOMPQ = 1 and
101 * dimension ( N ) if ICOMPQ = 0.
102 * The first K elements of Z(1, I) contain the components of
103 * the deflation-adjusted updating row vector for subproblems
104 * on the I-th level.
105 *
106 * POLES (output) DOUBLE PRECISION array,
107 * dimension ( LDU, 2 * NLVL ) if ICOMPQ = 1, and not referenced
108 * if ICOMPQ = 0. If ICOMPQ = 1, on exit, POLES(1, 2*I - 1) and
109 * POLES(1, 2*I) contain the new and old singular values
110 * involved in the secular equations on the I-th level.
111 *
112 * GIVPTR (output) INTEGER array,
113 * dimension ( N ) if ICOMPQ = 1, and not referenced if
114 * ICOMPQ = 0. If ICOMPQ = 1, on exit, GIVPTR( I ) records
115 * the number of Givens rotations performed on the I-th
116 * problem on the computation tree.
117 *
118 * GIVCOL (output) INTEGER array,
119 * dimension ( LDGCOL, 2 * NLVL ) if ICOMPQ = 1, and not
120 * referenced if ICOMPQ = 0. If ICOMPQ = 1, on exit, for each I,
121 * GIVCOL(1, 2 *I - 1) and GIVCOL(1, 2 *I) record the locations
122 * of Givens rotations performed on the I-th level on the
123 * computation tree.
124 *
125 * LDGCOL (input) INTEGER, LDGCOL = > N.
126 * The leading dimension of arrays GIVCOL and PERM.
127 *
128 * PERM (output) INTEGER array,
129 * dimension ( LDGCOL, NLVL ) if ICOMPQ = 1, and not referenced
130 * if ICOMPQ = 0. If ICOMPQ = 1, on exit, PERM(1, I) records
131 * permutations done on the I-th level of the computation tree.
132 *
133 * GIVNUM (output) DOUBLE PRECISION array,
134 * dimension ( LDU, 2 * NLVL ) if ICOMPQ = 1, and not
135 * referenced if ICOMPQ = 0. If ICOMPQ = 1, on exit, for each I,
136 * GIVNUM(1, 2 *I - 1) and GIVNUM(1, 2 *I) record the C- and S-
137 * values of Givens rotations performed on the I-th level on
138 * the computation tree.
139 *
140 * C (output) DOUBLE PRECISION array,
141 * dimension ( N ) if ICOMPQ = 1, and dimension 1 if ICOMPQ = 0.
142 * If ICOMPQ = 1 and the I-th subproblem is not square, on exit,
143 * C( I ) contains the C-value of a Givens rotation related to
144 * the right null space of the I-th subproblem.
145 *
146 * S (output) DOUBLE PRECISION array, dimension ( N ) if
147 * ICOMPQ = 1, and dimension 1 if ICOMPQ = 0. If ICOMPQ = 1
148 * and the I-th subproblem is not square, on exit, S( I )
149 * contains the S-value of a Givens rotation related to
150 * the right null space of the I-th subproblem.
151 *
152 * WORK (workspace) DOUBLE PRECISION array, dimension
153 * (6 * N + (SMLSIZ + 1)*(SMLSIZ + 1)).
154 *
155 * IWORK (workspace) INTEGER array.
156 * Dimension must be at least (7 * N).
157 *
158 * INFO (output) INTEGER
159 * = 0: successful exit.
160 * < 0: if INFO = -i, the i-th argument had an illegal value.
161 * > 0: if INFO = 1, a singular value did not converge
162 *
163 * Further Details
164 * ===============
165 *
166 * Based on contributions by
167 * Ming Gu and Huan Ren, Computer Science Division, University of
168 * California at Berkeley, USA
169 *
170 * =====================================================================
171 *
172 * .. Parameters ..
173 DOUBLE PRECISION ZERO, ONE
174 PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0 )
175 * ..
176 * .. Local Scalars ..
177 INTEGER I, I1, IC, IDXQ, IDXQI, IM1, INODE, ITEMP, IWK,
178 $ J, LF, LL, LVL, LVL2, M, NCC, ND, NDB1, NDIML,
179 $ NDIMR, NL, NLF, NLP1, NLVL, NR, NRF, NRP1, NRU,
180 $ NWORK1, NWORK2, SMLSZP, SQREI, VF, VFI, VL, VLI
181 DOUBLE PRECISION ALPHA, BETA
182 * ..
183 * .. External Subroutines ..
184 EXTERNAL DCOPY, DLASD6, DLASDQ, DLASDT, DLASET, XERBLA
185 * ..
186 * .. Executable Statements ..
187 *
188 * Test the input parameters.
189 *
190 INFO = 0
191 *
192 IF( ( ICOMPQ.LT.0 ) .OR. ( ICOMPQ.GT.1 ) ) THEN
193 INFO = -1
194 ELSE IF( SMLSIZ.LT.3 ) THEN
195 INFO = -2
196 ELSE IF( N.LT.0 ) THEN
197 INFO = -3
198 ELSE IF( ( SQRE.LT.0 ) .OR. ( SQRE.GT.1 ) ) THEN
199 INFO = -4
200 ELSE IF( LDU.LT.( N+SQRE ) ) THEN
201 INFO = -8
202 ELSE IF( LDGCOL.LT.N ) THEN
203 INFO = -17
204 END IF
205 IF( INFO.NE.0 ) THEN
206 CALL XERBLA( 'DLASDA', -INFO )
207 RETURN
208 END IF
209 *
210 M = N + SQRE
211 *
212 * If the input matrix is too small, call DLASDQ to find the SVD.
213 *
214 IF( N.LE.SMLSIZ ) THEN
215 IF( ICOMPQ.EQ.0 ) THEN
216 CALL DLASDQ( 'U', SQRE, N, 0, 0, 0, D, E, VT, LDU, U, LDU,
217 $ U, LDU, WORK, INFO )
218 ELSE
219 CALL DLASDQ( 'U', SQRE, N, M, N, 0, D, E, VT, LDU, U, LDU,
220 $ U, LDU, WORK, INFO )
221 END IF
222 RETURN
223 END IF
224 *
225 * Book-keeping and set up the computation tree.
226 *
227 INODE = 1
228 NDIML = INODE + N
229 NDIMR = NDIML + N
230 IDXQ = NDIMR + N
231 IWK = IDXQ + N
232 *
233 NCC = 0
234 NRU = 0
235 *
236 SMLSZP = SMLSIZ + 1
237 VF = 1
238 VL = VF + M
239 NWORK1 = VL + M
240 NWORK2 = NWORK1 + SMLSZP*SMLSZP
241 *
242 CALL DLASDT( N, NLVL, ND, IWORK( INODE ), IWORK( NDIML ),
243 $ IWORK( NDIMR ), SMLSIZ )
244 *
245 * for the nodes on bottom level of the tree, solve
246 * their subproblems by DLASDQ.
247 *
248 NDB1 = ( ND+1 ) / 2
249 DO 30 I = NDB1, ND
250 *
251 * IC : center row of each node
252 * NL : number of rows of left subproblem
253 * NR : number of rows of right subproblem
254 * NLF: starting row of the left subproblem
255 * NRF: starting row of the right subproblem
256 *
257 I1 = I - 1
258 IC = IWORK( INODE+I1 )
259 NL = IWORK( NDIML+I1 )
260 NLP1 = NL + 1
261 NR = IWORK( NDIMR+I1 )
262 NLF = IC - NL
263 NRF = IC + 1
264 IDXQI = IDXQ + NLF - 2
265 VFI = VF + NLF - 1
266 VLI = VL + NLF - 1
267 SQREI = 1
268 IF( ICOMPQ.EQ.0 ) THEN
269 CALL DLASET( 'A', NLP1, NLP1, ZERO, ONE, WORK( NWORK1 ),
270 $ SMLSZP )
271 CALL DLASDQ( 'U', SQREI, NL, NLP1, NRU, NCC, D( NLF ),
272 $ E( NLF ), WORK( NWORK1 ), SMLSZP,
273 $ WORK( NWORK2 ), NL, WORK( NWORK2 ), NL,
274 $ WORK( NWORK2 ), INFO )
275 ITEMP = NWORK1 + NL*SMLSZP
276 CALL DCOPY( NLP1, WORK( NWORK1 ), 1, WORK( VFI ), 1 )
277 CALL DCOPY( NLP1, WORK( ITEMP ), 1, WORK( VLI ), 1 )
278 ELSE
279 CALL DLASET( 'A', NL, NL, ZERO, ONE, U( NLF, 1 ), LDU )
280 CALL DLASET( 'A', NLP1, NLP1, ZERO, ONE, VT( NLF, 1 ), LDU )
281 CALL DLASDQ( 'U', SQREI, NL, NLP1, NL, NCC, D( NLF ),
282 $ E( NLF ), VT( NLF, 1 ), LDU, U( NLF, 1 ), LDU,
283 $ U( NLF, 1 ), LDU, WORK( NWORK1 ), INFO )
284 CALL DCOPY( NLP1, VT( NLF, 1 ), 1, WORK( VFI ), 1 )
285 CALL DCOPY( NLP1, VT( NLF, NLP1 ), 1, WORK( VLI ), 1 )
286 END IF
287 IF( INFO.NE.0 ) THEN
288 RETURN
289 END IF
290 DO 10 J = 1, NL
291 IWORK( IDXQI+J ) = J
292 10 CONTINUE
293 IF( ( I.EQ.ND ) .AND. ( SQRE.EQ.0 ) ) THEN
294 SQREI = 0
295 ELSE
296 SQREI = 1
297 END IF
298 IDXQI = IDXQI + NLP1
299 VFI = VFI + NLP1
300 VLI = VLI + NLP1
301 NRP1 = NR + SQREI
302 IF( ICOMPQ.EQ.0 ) THEN
303 CALL DLASET( 'A', NRP1, NRP1, ZERO, ONE, WORK( NWORK1 ),
304 $ SMLSZP )
305 CALL DLASDQ( 'U', SQREI, NR, NRP1, NRU, NCC, D( NRF ),
306 $ E( NRF ), WORK( NWORK1 ), SMLSZP,
307 $ WORK( NWORK2 ), NR, WORK( NWORK2 ), NR,
308 $ WORK( NWORK2 ), INFO )
309 ITEMP = NWORK1 + ( NRP1-1 )*SMLSZP
310 CALL DCOPY( NRP1, WORK( NWORK1 ), 1, WORK( VFI ), 1 )
311 CALL DCOPY( NRP1, WORK( ITEMP ), 1, WORK( VLI ), 1 )
312 ELSE
313 CALL DLASET( 'A', NR, NR, ZERO, ONE, U( NRF, 1 ), LDU )
314 CALL DLASET( 'A', NRP1, NRP1, ZERO, ONE, VT( NRF, 1 ), LDU )
315 CALL DLASDQ( 'U', SQREI, NR, NRP1, NR, NCC, D( NRF ),
316 $ E( NRF ), VT( NRF, 1 ), LDU, U( NRF, 1 ), LDU,
317 $ U( NRF, 1 ), LDU, WORK( NWORK1 ), INFO )
318 CALL DCOPY( NRP1, VT( NRF, 1 ), 1, WORK( VFI ), 1 )
319 CALL DCOPY( NRP1, VT( NRF, NRP1 ), 1, WORK( VLI ), 1 )
320 END IF
321 IF( INFO.NE.0 ) THEN
322 RETURN
323 END IF
324 DO 20 J = 1, NR
325 IWORK( IDXQI+J ) = J
326 20 CONTINUE
327 30 CONTINUE
328 *
329 * Now conquer each subproblem bottom-up.
330 *
331 J = 2**NLVL
332 DO 50 LVL = NLVL, 1, -1
333 LVL2 = LVL*2 - 1
334 *
335 * Find the first node LF and last node LL on
336 * the current level LVL.
337 *
338 IF( LVL.EQ.1 ) THEN
339 LF = 1
340 LL = 1
341 ELSE
342 LF = 2**( LVL-1 )
343 LL = 2*LF - 1
344 END IF
345 DO 40 I = LF, LL
346 IM1 = I - 1
347 IC = IWORK( INODE+IM1 )
348 NL = IWORK( NDIML+IM1 )
349 NR = IWORK( NDIMR+IM1 )
350 NLF = IC - NL
351 NRF = IC + 1
352 IF( I.EQ.LL ) THEN
353 SQREI = SQRE
354 ELSE
355 SQREI = 1
356 END IF
357 VFI = VF + NLF - 1
358 VLI = VL + NLF - 1
359 IDXQI = IDXQ + NLF - 1
360 ALPHA = D( IC )
361 BETA = E( IC )
362 IF( ICOMPQ.EQ.0 ) THEN
363 CALL DLASD6( ICOMPQ, NL, NR, SQREI, D( NLF ),
364 $ WORK( VFI ), WORK( VLI ), ALPHA, BETA,
365 $ IWORK( IDXQI ), PERM, GIVPTR( 1 ), GIVCOL,
366 $ LDGCOL, GIVNUM, LDU, POLES, DIFL, DIFR, Z,
367 $ K( 1 ), C( 1 ), S( 1 ), WORK( NWORK1 ),
368 $ IWORK( IWK ), INFO )
369 ELSE
370 J = J - 1
371 CALL DLASD6( ICOMPQ, NL, NR, SQREI, D( NLF ),
372 $ WORK( VFI ), WORK( VLI ), ALPHA, BETA,
373 $ IWORK( IDXQI ), PERM( NLF, LVL ),
374 $ GIVPTR( J ), GIVCOL( NLF, LVL2 ), LDGCOL,
375 $ GIVNUM( NLF, LVL2 ), LDU,
376 $ POLES( NLF, LVL2 ), DIFL( NLF, LVL ),
377 $ DIFR( NLF, LVL2 ), Z( NLF, LVL ), K( J ),
378 $ C( J ), S( J ), WORK( NWORK1 ),
379 $ IWORK( IWK ), INFO )
380 END IF
381 IF( INFO.NE.0 ) THEN
382 RETURN
383 END IF
384 40 CONTINUE
385 50 CONTINUE
386 *
387 RETURN
388 *
389 * End of DLASDA
390 *
391 END