1 *> \brief \b CLALSA computes the SVD of the coefficient matrix in compact form. Used by sgelsd.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CLALSA + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/clalsa.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/clalsa.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/clalsa.f">
21 * SUBROUTINE CLALSA( ICOMPQ, SMLSIZ, N, NRHS, B, LDB, BX, LDBX, U,
22 * LDU, VT, K, DIFL, DIFR, Z, POLES, GIVPTR,
23 * GIVCOL, LDGCOL, PERM, GIVNUM, C, S, RWORK,
26 * .. Scalar Arguments ..
27 * INTEGER ICOMPQ, INFO, LDB, LDBX, LDGCOL, LDU, N, NRHS,
30 * .. Array Arguments ..
31 * INTEGER GIVCOL( LDGCOL, * ), GIVPTR( * ), IWORK( * ),
32 * $ K( * ), PERM( LDGCOL, * )
33 * REAL C( * ), DIFL( LDU, * ), DIFR( LDU, * ),
34 * $ GIVNUM( LDU, * ), POLES( LDU, * ), RWORK( * ),
35 * $ S( * ), U( LDU, * ), VT( LDU, * ), Z( LDU, * )
36 * COMPLEX B( LDB, * ), BX( LDBX, * )
45 *> CLALSA is an itermediate step in solving the least squares problem
46 *> by computing the SVD of the coefficient matrix in compact form (The
47 *> singular vectors are computed as products of simple orthorgonal
50 *> If ICOMPQ = 0, CLALSA applies the inverse of the left singular vector
51 *> matrix of an upper bidiagonal matrix to the right hand side; and if
52 *> ICOMPQ = 1, CLALSA applies the right singular vector matrix to the
53 *> right hand side. The singular vector matrices were generated in
54 *> compact form by CLALSA.
63 *> Specifies whether the left or the right singular vector
64 *> matrix is involved.
65 *> = 0: Left singular vector matrix
66 *> = 1: Right singular vector matrix
72 *> The maximum size of the subproblems at the bottom of the
79 *> The row and column dimensions of the upper bidiagonal matrix.
85 *> The number of columns of B and BX. NRHS must be at least 1.
90 *> B is COMPLEX array, dimension ( LDB, NRHS )
91 *> On input, B contains the right hand sides of the least
92 *> squares problem in rows 1 through M.
93 *> On output, B contains the solution X in rows 1 through N.
99 *> The leading dimension of B in the calling subprogram.
100 *> LDB must be at least max(1,MAX( M, N ) ).
105 *> BX is COMPLEX array, dimension ( LDBX, NRHS )
106 *> On exit, the result of applying the left or right singular
107 *> vector matrix to B.
113 *> The leading dimension of BX.
118 *> U is REAL array, dimension ( LDU, SMLSIZ ).
119 *> On entry, U contains the left singular vector matrices of all
120 *> subproblems at the bottom level.
125 *> LDU is INTEGER, LDU = > N.
126 *> The leading dimension of arrays U, VT, DIFL, DIFR,
127 *> POLES, GIVNUM, and Z.
132 *> VT is REAL array, dimension ( LDU, SMLSIZ+1 ).
133 *> On entry, VT**H contains the right singular vector matrices of
134 *> all subproblems at the bottom level.
139 *> K is INTEGER array, dimension ( N ).
144 *> DIFL is REAL array, dimension ( LDU, NLVL ).
145 *> where NLVL = INT(log_2 (N/(SMLSIZ+1))) + 1.
150 *> DIFR is REAL array, dimension ( LDU, 2 * NLVL ).
151 *> On entry, DIFL(*, I) and DIFR(*, 2 * I -1) record
152 *> distances between singular values on the I-th level and
153 *> singular values on the (I -1)-th level, and DIFR(*, 2 * I)
154 *> record the normalizing factors of the right singular vectors
155 *> matrices of subproblems on I-th level.
160 *> Z is REAL array, dimension ( LDU, NLVL ).
161 *> On entry, Z(1, I) contains the components of the deflation-
162 *> adjusted updating row vector for subproblems on the I-th
168 *> POLES is REAL array, dimension ( LDU, 2 * NLVL ).
169 *> On entry, POLES(*, 2 * I -1: 2 * I) contains the new and old
170 *> singular values involved in the secular equations on the I-th
176 *> GIVPTR is INTEGER array, dimension ( N ).
177 *> On entry, GIVPTR( I ) records the number of Givens
178 *> rotations performed on the I-th problem on the computation
184 *> GIVCOL is INTEGER array, dimension ( LDGCOL, 2 * NLVL ).
185 *> On entry, for each I, GIVCOL(*, 2 * I - 1: 2 * I) records the
186 *> locations of Givens rotations performed on the I-th level on
187 *> the computation tree.
192 *> LDGCOL is INTEGER, LDGCOL = > N.
193 *> The leading dimension of arrays GIVCOL and PERM.
198 *> PERM is INTEGER array, dimension ( LDGCOL, NLVL ).
199 *> On entry, PERM(*, I) records permutations done on the I-th
200 *> level of the computation tree.
205 *> GIVNUM is REAL array, dimension ( LDU, 2 * NLVL ).
206 *> On entry, GIVNUM(*, 2 *I -1 : 2 * I) records the C- and S-
207 *> values of Givens rotations performed on the I-th level on the
213 *> C is REAL array, dimension ( N ).
214 *> On entry, if the I-th subproblem is not square,
215 *> C( I ) contains the C-value of a Givens rotation related to
216 *> the right null space of the I-th subproblem.
221 *> S is REAL array, dimension ( N ).
222 *> On entry, if the I-th subproblem is not square,
223 *> S( I ) contains the S-value of a Givens rotation related to
224 *> the right null space of the I-th subproblem.
229 *> RWORK is REAL array, dimension at least
230 *> MAX( (SMLSZ+1)*NRHS*3, N*(1+NRHS) + 2*NRHS ).
235 *> IWORK is INTEGER array.
236 *> The dimension must be at least 3 * N
242 *> = 0: successful exit.
243 *> < 0: if INFO = -i, the i-th argument had an illegal value.
249 *> \author Univ. of Tennessee
250 *> \author Univ. of California Berkeley
251 *> \author Univ. of Colorado Denver
254 *> \date September 2012
256 *> \ingroup complexOTHERcomputational
258 *> \par Contributors:
261 *> Ming Gu and Ren-Cang Li, Computer Science Division, University of
262 *> California at Berkeley, USA \n
263 *> Osni Marques, LBNL/NERSC, USA \n
265 * =====================================================================
266 SUBROUTINE CLALSA( ICOMPQ, SMLSIZ, N, NRHS, B, LDB, BX, LDBX, U,
267 $ LDU, VT, K, DIFL, DIFR, Z, POLES, GIVPTR,
268 $ GIVCOL, LDGCOL, PERM, GIVNUM, C, S, RWORK,
271 * -- LAPACK computational routine (version 3.4.2) --
272 * -- LAPACK is a software package provided by Univ. of Tennessee, --
273 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
276 * .. Scalar Arguments ..
277 INTEGER ICOMPQ, INFO, LDB, LDBX, LDGCOL, LDU, N, NRHS,
280 * .. Array Arguments ..
281 INTEGER GIVCOL( LDGCOL, * ), GIVPTR( * ), IWORK( * ),
282 $ K( * ), PERM( LDGCOL, * )
283 REAL C( * ), DIFL( LDU, * ), DIFR( LDU, * ),
284 $ GIVNUM( LDU, * ), POLES( LDU, * ), RWORK( * ),
285 $ S( * ), U( LDU, * ), VT( LDU, * ), Z( LDU, * )
286 COMPLEX B( LDB, * ), BX( LDBX, * )
289 * =====================================================================
293 PARAMETER ( ZERO = 0.0E0, ONE = 1.0E0 )
295 * .. Local Scalars ..
296 INTEGER I, I1, IC, IM1, INODE, J, JCOL, JIMAG, JREAL,
297 $ JROW, LF, LL, LVL, LVL2, ND, NDB1, NDIML,
298 $ NDIMR, NL, NLF, NLP1, NLVL, NR, NRF, NRP1, SQRE
300 * .. External Subroutines ..
301 EXTERNAL CCOPY, CLALS0, SGEMM, SLASDT, XERBLA
303 * .. Intrinsic Functions ..
304 INTRINSIC AIMAG, CMPLX, REAL
306 * .. Executable Statements ..
308 * Test the input parameters.
312 IF( ( ICOMPQ.LT.0 ) .OR. ( ICOMPQ.GT.1 ) ) THEN
314 ELSE IF( SMLSIZ.LT.3 ) THEN
316 ELSE IF( N.LT.SMLSIZ ) THEN
318 ELSE IF( NRHS.LT.1 ) THEN
320 ELSE IF( LDB.LT.N ) THEN
322 ELSE IF( LDBX.LT.N ) THEN
324 ELSE IF( LDU.LT.N ) THEN
326 ELSE IF( LDGCOL.LT.N ) THEN
330 CALL XERBLA( 'CLALSA', -INFO )
334 * Book-keeping and setting up the computation tree.
340 CALL SLASDT( N, NLVL, ND, IWORK( INODE ), IWORK( NDIML ),
341 $ IWORK( NDIMR ), SMLSIZ )
343 * The following code applies back the left singular vector factors.
344 * For applying back the right singular vector factors, go to 170.
346 IF( ICOMPQ.EQ.1 ) THEN
350 * The nodes on the bottom level of the tree were solved
351 * by SLASDQ. The corresponding left and right singular vector
352 * matrices are in explicit form. First apply back the left
353 * singular vector matrices.
358 * IC : center row of each node
359 * NL : number of rows of left subproblem
360 * NR : number of rows of right subproblem
361 * NLF: starting row of the left subproblem
362 * NRF: starting row of the right subproblem
365 IC = IWORK( INODE+I1 )
366 NL = IWORK( NDIML+I1 )
367 NR = IWORK( NDIMR+I1 )
371 * Since B and BX are complex, the following call to SGEMM
372 * is performed in two steps (real and imaginary parts).
374 * CALL SGEMM( 'T', 'N', NL, NRHS, NL, ONE, U( NLF, 1 ), LDU,
375 * $ B( NLF, 1 ), LDB, ZERO, BX( NLF, 1 ), LDBX )
379 DO 10 JROW = NLF, NLF + NL - 1
381 RWORK( J ) = REAL( B( JROW, JCOL ) )
384 CALL SGEMM( 'T', 'N', NL, NRHS, NL, ONE, U( NLF, 1 ), LDU,
385 $ RWORK( 1+NL*NRHS*2 ), NL, ZERO, RWORK( 1 ), NL )
388 DO 30 JROW = NLF, NLF + NL - 1
390 RWORK( J ) = AIMAG( B( JROW, JCOL ) )
393 CALL SGEMM( 'T', 'N', NL, NRHS, NL, ONE, U( NLF, 1 ), LDU,
394 $ RWORK( 1+NL*NRHS*2 ), NL, ZERO, RWORK( 1+NL*NRHS ),
399 DO 50 JROW = NLF, NLF + NL - 1
402 BX( JROW, JCOL ) = CMPLX( RWORK( JREAL ),
407 * Since B and BX are complex, the following call to SGEMM
408 * is performed in two steps (real and imaginary parts).
410 * CALL SGEMM( 'T', 'N', NR, NRHS, NR, ONE, U( NRF, 1 ), LDU,
411 * $ B( NRF, 1 ), LDB, ZERO, BX( NRF, 1 ), LDBX )
415 DO 70 JROW = NRF, NRF + NR - 1
417 RWORK( J ) = REAL( B( JROW, JCOL ) )
420 CALL SGEMM( 'T', 'N', NR, NRHS, NR, ONE, U( NRF, 1 ), LDU,
421 $ RWORK( 1+NR*NRHS*2 ), NR, ZERO, RWORK( 1 ), NR )
423 DO 100 JCOL = 1, NRHS
424 DO 90 JROW = NRF, NRF + NR - 1
426 RWORK( J ) = AIMAG( B( JROW, JCOL ) )
429 CALL SGEMM( 'T', 'N', NR, NRHS, NR, ONE, U( NRF, 1 ), LDU,
430 $ RWORK( 1+NR*NRHS*2 ), NR, ZERO, RWORK( 1+NR*NRHS ),
434 DO 120 JCOL = 1, NRHS
435 DO 110 JROW = NRF, NRF + NR - 1
438 BX( JROW, JCOL ) = CMPLX( RWORK( JREAL ),
445 * Next copy the rows of B that correspond to unchanged rows
446 * in the bidiagonal matrix to BX.
449 IC = IWORK( INODE+I-1 )
450 CALL CCOPY( NRHS, B( IC, 1 ), LDB, BX( IC, 1 ), LDBX )
453 * Finally go through the left singular vector matrices of all
454 * the other subproblems bottom-up on the tree.
459 DO 160 LVL = NLVL, 1, -1
462 * find the first node LF and last node LL on
463 * the current level LVL
474 IC = IWORK( INODE+IM1 )
475 NL = IWORK( NDIML+IM1 )
476 NR = IWORK( NDIMR+IM1 )
480 CALL CLALS0( ICOMPQ, NL, NR, SQRE, NRHS, BX( NLF, 1 ), LDBX,
481 $ B( NLF, 1 ), LDB, PERM( NLF, LVL ),
482 $ GIVPTR( J ), GIVCOL( NLF, LVL2 ), LDGCOL,
483 $ GIVNUM( NLF, LVL2 ), LDU, POLES( NLF, LVL2 ),
484 $ DIFL( NLF, LVL ), DIFR( NLF, LVL2 ),
485 $ Z( NLF, LVL ), K( J ), C( J ), S( J ), RWORK,
491 * ICOMPQ = 1: applying back the right singular vector factors.
495 * First now go through the right singular vector matrices of all
496 * the tree nodes top-down.
502 * Find the first node LF and last node LL on
503 * the current level LVL.
512 DO 180 I = LL, LF, -1
514 IC = IWORK( INODE+IM1 )
515 NL = IWORK( NDIML+IM1 )
516 NR = IWORK( NDIMR+IM1 )
525 CALL CLALS0( ICOMPQ, NL, NR, SQRE, NRHS, B( NLF, 1 ), LDB,
526 $ BX( NLF, 1 ), LDBX, PERM( NLF, LVL ),
527 $ GIVPTR( J ), GIVCOL( NLF, LVL2 ), LDGCOL,
528 $ GIVNUM( NLF, LVL2 ), LDU, POLES( NLF, LVL2 ),
529 $ DIFL( NLF, LVL ), DIFR( NLF, LVL2 ),
530 $ Z( NLF, LVL ), K( J ), C( J ), S( J ), RWORK,
535 * The nodes on the bottom level of the tree were solved
536 * by SLASDQ. The corresponding right singular vector
537 * matrices are in explicit form. Apply them back.
542 IC = IWORK( INODE+I1 )
543 NL = IWORK( NDIML+I1 )
544 NR = IWORK( NDIMR+I1 )
554 * Since B and BX are complex, the following call to SGEMM is
555 * performed in two steps (real and imaginary parts).
557 * CALL SGEMM( 'T', 'N', NLP1, NRHS, NLP1, ONE, VT( NLF, 1 ), LDU,
558 * $ B( NLF, 1 ), LDB, ZERO, BX( NLF, 1 ), LDBX )
561 DO 210 JCOL = 1, NRHS
562 DO 200 JROW = NLF, NLF + NLP1 - 1
564 RWORK( J ) = REAL( B( JROW, JCOL ) )
567 CALL SGEMM( 'T', 'N', NLP1, NRHS, NLP1, ONE, VT( NLF, 1 ), LDU,
568 $ RWORK( 1+NLP1*NRHS*2 ), NLP1, ZERO, RWORK( 1 ),
571 DO 230 JCOL = 1, NRHS
572 DO 220 JROW = NLF, NLF + NLP1 - 1
574 RWORK( J ) = AIMAG( B( JROW, JCOL ) )
577 CALL SGEMM( 'T', 'N', NLP1, NRHS, NLP1, ONE, VT( NLF, 1 ), LDU,
578 $ RWORK( 1+NLP1*NRHS*2 ), NLP1, ZERO,
579 $ RWORK( 1+NLP1*NRHS ), NLP1 )
582 DO 250 JCOL = 1, NRHS
583 DO 240 JROW = NLF, NLF + NLP1 - 1
586 BX( JROW, JCOL ) = CMPLX( RWORK( JREAL ),
591 * Since B and BX are complex, the following call to SGEMM is
592 * performed in two steps (real and imaginary parts).
594 * CALL SGEMM( 'T', 'N', NRP1, NRHS, NRP1, ONE, VT( NRF, 1 ), LDU,
595 * $ B( NRF, 1 ), LDB, ZERO, BX( NRF, 1 ), LDBX )
598 DO 270 JCOL = 1, NRHS
599 DO 260 JROW = NRF, NRF + NRP1 - 1
601 RWORK( J ) = REAL( B( JROW, JCOL ) )
604 CALL SGEMM( 'T', 'N', NRP1, NRHS, NRP1, ONE, VT( NRF, 1 ), LDU,
605 $ RWORK( 1+NRP1*NRHS*2 ), NRP1, ZERO, RWORK( 1 ),
608 DO 290 JCOL = 1, NRHS
609 DO 280 JROW = NRF, NRF + NRP1 - 1
611 RWORK( J ) = AIMAG( B( JROW, JCOL ) )
614 CALL SGEMM( 'T', 'N', NRP1, NRHS, NRP1, ONE, VT( NRF, 1 ), LDU,
615 $ RWORK( 1+NRP1*NRHS*2 ), NRP1, ZERO,
616 $ RWORK( 1+NRP1*NRHS ), NRP1 )
619 DO 310 JCOL = 1, NRHS
620 DO 300 JROW = NRF, NRF + NRP1 - 1
623 BX( JROW, JCOL ) = CMPLX( RWORK( JREAL ),