152 SUBROUTINE dlasd0( N, SQRE, D, E, U, LDU, VT, LDVT, SMLSIZ, IWORK,
161 INTEGER INFO, LDU, LDVT, N, SMLSIZ, SQRE
165 DOUBLE PRECISION D( * ), E( * ), U( ldu, * ), VT( ldvt, * ),
172 INTEGER I, I1, IC, IDXQ, IDXQC, IM1, INODE, ITEMP, IWK,
173 $ j, lf, ll, lvl, m, ncc, nd, ndb1, ndiml, ndimr,
174 $ nl, nlf, nlp1, nlvl, nr, nrf, nrp1, sqrei
175 DOUBLE PRECISION ALPHA, BETA
188 ELSE IF( ( sqre.LT.0 ) .OR. ( sqre.GT.1 ) )
THEN
196 ELSE IF( ldvt.LT.m )
THEN
198 ELSE IF( smlsiz.LT.3 )
THEN
202 CALL xerbla(
'DLASD0', -info )
208 IF( n.LE.smlsiz )
THEN
209 CALL dlasdq(
'U', sqre, n, m, n, 0, d, e, vt, ldvt, u, ldu, u,
221 CALL dlasdt( n, nlvl, nd, iwork( inode ), iwork( ndiml ),
222 $ iwork( ndimr ), smlsiz )
238 ic = iwork( inode+i1 )
239 nl = iwork( ndiml+i1 )
241 nr = iwork( ndimr+i1 )
246 CALL dlasdq(
'U', sqrei, nl, nlp1, nl, ncc, d( nlf ), e( nlf ),
247 $ vt( nlf, nlf ), ldvt, u( nlf, nlf ), ldu,
248 $ u( nlf, nlf ), ldu, work, info )
252 itemp = idxq + nlf - 2
262 CALL dlasdq(
'U', sqrei, nr, nrp1, nr, ncc, d( nrf ), e( nrf ),
263 $ vt( nrf, nrf ), ldvt, u( nrf, nrf ), ldu,
264 $ u( nrf, nrf ), ldu, work, info )
270 iwork( itemp+j-1 ) = j
276 DO 50 lvl = nlvl, 1, -1
290 ic = iwork( inode+im1 )
291 nl = iwork( ndiml+im1 )
292 nr = iwork( ndimr+im1 )
294 IF( ( sqre.EQ.0 ) .AND. ( i.EQ.ll ) )
THEN
299 idxqc = idxq + nlf - 1
302 CALL dlasd1( nl, nr, sqrei, d( nlf ), alpha, beta,
303 $ u( nlf, nlf ), ldu, vt( nlf, nlf ), ldvt,
304 $ iwork( idxqc ), iwork( iwk ), work, info )
subroutine dlasdt(N, LVL, ND, INODE, NDIML, NDIMR, MSUB)
DLASDT creates a tree of subproblems for bidiagonal divide and conquer. Used by sbdsdc.
subroutine xerbla(SRNAME, INFO)
XERBLA
subroutine dlasdq(UPLO, SQRE, N, NCVT, NRU, NCC, D, E, VT, LDVT, U, LDU, C, LDC, WORK, INFO)
DLASDQ computes the SVD of a real bidiagonal matrix with diagonal d and off-diagonal e...
subroutine dlasd0(N, SQRE, D, E, U, LDU, VT, LDVT, SMLSIZ, IWORK, WORK, INFO)
DLASD0 computes the singular values of a real upper bidiagonal n-by-m matrix B with diagonal d and of...
subroutine dlasd1(NL, NR, SQRE, D, ALPHA, BETA, U, LDU, VT, LDVT, IDXQ, IWORK, WORK, INFO)
DLASD1 computes the SVD of an upper bidiagonal matrix B of the specified size. Used by sbdsdc...