263 SUBROUTINE slalsa( ICOMPQ, SMLSIZ, N, NRHS, B, LDB, BX, LDBX, U,
264 $ LDU, VT, K, DIFL, DIFR, Z, POLES, GIVPTR,
265 $ GIVCOL, LDGCOL, PERM, GIVNUM, C, S, WORK,
273 INTEGER ICOMPQ, INFO, LDB, LDBX, LDGCOL, LDU, N, NRHS,
277 INTEGER GIVCOL( LDGCOL, * ), GIVPTR( * ), IWORK( * ),
278 $ K( * ), PERM( LDGCOL, * )
279 REAL B( LDB, * ), BX( LDBX, * ), C( * ),
280 $ difl( ldu, * ), difr( ldu, * ),
281 $ givnum( ldu, * ), poles( ldu, * ), s( * ),
282 $ u( ldu, * ), vt( ldu, * ), work( * ),
290 PARAMETER ( ZERO = 0.0e0, one = 1.0e0 )
293 INTEGER I, I1, IC, IM1, INODE, J, LF, LL, LVL, LVL2,
294 $ ND, NDB1, NDIML, NDIMR, NL, NLF, NLP1, NLVL,
295 $ NR, NRF, NRP1, SQRE
306 IF( ( icompq.LT.0 ) .OR. ( icompq.GT.1 ) )
THEN
308 ELSE IF( smlsiz.LT.3 )
THEN
310 ELSE IF( n.LT.smlsiz )
THEN
312 ELSE IF( nrhs.LT.1 )
THEN
314 ELSE IF( ldb.LT.n )
THEN
316 ELSE IF( ldbx.LT.n )
THEN
318 ELSE IF( ldu.LT.n )
THEN
320 ELSE IF( ldgcol.LT.n )
THEN
324 CALL xerbla(
'SLALSA', -info )
334 CALL slasdt( n, nlvl, nd, iwork( inode ), iwork( ndiml ),
335 $ iwork( ndimr ), smlsiz )
340 IF( icompq.EQ.1 )
THEN
359 ic = iwork( inode+i1 )
360 nl = iwork( ndiml+i1 )
361 nr = iwork( ndimr+i1 )
364 CALL sgemm(
'T',
'N', nl, nrhs, nl, one, u( nlf, 1 ), ldu,
365 $ b( nlf, 1 ), ldb, zero, bx( nlf, 1 ), ldbx )
366 CALL sgemm(
'T',
'N', nr, nrhs, nr, one, u( nrf, 1 ), ldu,
367 $ b( nrf, 1 ), ldb, zero, bx( nrf, 1 ), ldbx )
374 ic = iwork( inode+i-1 )
375 CALL scopy( nrhs, b( ic, 1 ), ldb, bx( ic, 1 ), ldbx )
384 DO 40 lvl = nlvl, 1, -1
399 ic = iwork( inode+im1 )
400 nl = iwork( ndiml+im1 )
401 nr = iwork( ndimr+im1 )
405 CALL slals0( icompq, nl, nr, sqre, nrhs, bx( nlf, 1 ), ldbx,
406 $ b( nlf, 1 ), ldb, perm( nlf, lvl ),
407 $ givptr( j ), givcol( nlf, lvl2 ), ldgcol,
408 $ givnum( nlf, lvl2 ), ldu, poles( nlf, lvl2 ),
409 $ difl( nlf, lvl ), difr( nlf, lvl2 ),
410 $ z( nlf, lvl ), k( j ), c( j ), s( j ), work,
439 ic = iwork( inode+im1 )
440 nl = iwork( ndiml+im1 )
441 nr = iwork( ndimr+im1 )
450 CALL slals0( icompq, nl, nr, sqre, nrhs, b( nlf, 1 ), ldb,
451 $ bx( nlf, 1 ), ldbx, perm( nlf, lvl ),
452 $ givptr( j ), givcol( nlf, lvl2 ), ldgcol,
453 $ givnum( nlf, lvl2 ), ldu, poles( nlf, lvl2 ),
454 $ difl( nlf, lvl ), difr( nlf, lvl2 ),
455 $ z( nlf, lvl ), k( j ), c( j ), s( j ), work,
467 ic = iwork( inode+i1 )
468 nl = iwork( ndiml+i1 )
469 nr = iwork( ndimr+i1 )
478 CALL sgemm(
'T',
'N', nlp1, nrhs, nlp1, one, vt( nlf, 1 ), ldu,
479 $ b( nlf, 1 ), ldb, zero, bx( nlf, 1 ), ldbx )
480 CALL sgemm(
'T',
'N', nrp1, nrhs, nrp1, one, vt( nrf, 1 ), ldu,
481 $ b( nrf, 1 ), ldb, zero, bx( nrf, 1 ), ldbx )
subroutine xerbla(srname, info)
subroutine scopy(n, sx, incx, sy, incy)
SCOPY
subroutine sgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
SGEMM
subroutine slals0(icompq, nl, nr, sqre, nrhs, b, ldb, bx, ldbx, perm, givptr, givcol, ldgcol, givnum, ldgnum, poles, difl, difr, z, k, c, s, work, info)
SLALS0 applies back multiplying factors in solving the least squares problem using divide and conquer...
subroutine slalsa(icompq, smlsiz, n, nrhs, b, ldb, bx, ldbx, u, ldu, vt, k, difl, difr, z, poles, givptr, givcol, ldgcol, perm, givnum, c, s, work, iwork, info)
SLALSA computes the SVD of the coefficient matrix in compact form. Used by sgelsd.
subroutine slasdt(n, lvl, nd, inode, ndiml, ndimr, msub)
SLASDT creates a tree of subproblems for bidiagonal divide and conquer. Used by sbdsdc.