261 SUBROUTINE dlalsa( ICOMPQ, SMLSIZ, N, NRHS, B, LDB, BX, LDBX,
263 $ LDU, VT, K, DIFL, DIFR, Z, POLES, GIVPTR,
264 $ GIVCOL, LDGCOL, PERM, GIVNUM, C, S, WORK,
272 INTEGER ICOMPQ, INFO, LDB, LDBX, LDGCOL, LDU, N, NRHS,
276 INTEGER GIVCOL( LDGCOL, * ), GIVPTR( * ), IWORK( * ),
277 $ K( * ), PERM( LDGCOL, * )
278 DOUBLE PRECISION B( LDB, * ), BX( LDBX, * ), C( * ),
279 $ DIFL( LDU, * ), DIFR( LDU, * ),
280 $ givnum( ldu, * ), poles( ldu, * ), s( * ),
281 $ u( ldu, * ), vt( ldu, * ), work( * ),
288 DOUBLE PRECISION ZERO, ONE
289 PARAMETER ( ZERO = 0.0d0, one = 1.0d0 )
292 INTEGER I, I1, IC, IM1, INODE, J, LF, LL, LVL, LVL2,
293 $ nd, ndb1, ndiml, ndimr, nl, nlf, nlp1, nlvl,
294 $ 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(
'DLALSA', -info )
334 CALL dlasdt( 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 dgemm(
'T',
'N', nl, nrhs, nl, one, u( nlf, 1 ), ldu,
365 $ b( nlf, 1 ), ldb, zero, bx( nlf, 1 ), ldbx )
366 CALL dgemm(
'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 dcopy( 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 dlals0( icompq, nl, nr, sqre, nrhs, bx( nlf, 1 ),
407 $ b( nlf, 1 ), ldb, perm( nlf, lvl ),
408 $ givptr( j ), givcol( nlf, lvl2 ), ldgcol,
409 $ givnum( nlf, lvl2 ), ldu, poles( nlf, lvl2 ),
410 $ difl( nlf, lvl ), difr( nlf, lvl2 ),
411 $ z( nlf, lvl ), k( j ), c( j ), s( j ), work,
440 ic = iwork( inode+im1 )
441 nl = iwork( ndiml+im1 )
442 nr = iwork( ndimr+im1 )
451 CALL dlals0( icompq, nl, nr, sqre, nrhs, b( nlf, 1 ),
453 $ bx( nlf, 1 ), ldbx, perm( nlf, lvl ),
454 $ givptr( j ), givcol( nlf, lvl2 ), ldgcol,
455 $ givnum( nlf, lvl2 ), ldu, poles( nlf, lvl2 ),
456 $ difl( nlf, lvl ), difr( nlf, lvl2 ),
457 $ z( nlf, lvl ), k( j ), c( j ), s( j ), work,
469 ic = iwork( inode+i1 )
470 nl = iwork( ndiml+i1 )
471 nr = iwork( ndimr+i1 )
480 CALL dgemm(
'T',
'N', nlp1, nrhs, nlp1, one, vt( nlf, 1 ),
482 $ b( nlf, 1 ), ldb, zero, bx( nlf, 1 ), ldbx )
483 CALL dgemm(
'T',
'N', nrp1, nrhs, nrp1, one, vt( nrf, 1 ),
485 $ b( nrf, 1 ), ldb, zero, bx( nrf, 1 ), ldbx )
subroutine dlals0(icompq, nl, nr, sqre, nrhs, b, ldb, bx, ldbx, perm, givptr, givcol, ldgcol, givnum, ldgnum, poles, difl, difr, z, k, c, s, work, info)
DLALS0 applies back multiplying factors in solving the least squares problem using divide and conquer...
subroutine dlalsa(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)
DLALSA computes the SVD of the coefficient matrix in compact form. Used by sgelsd.