150 SUBROUTINE slasd0( N, SQRE, D, E, U, LDU, VT, LDVT, SMLSIZ, IWORK,
159 INTEGER INFO, LDU, LDVT, N, SMLSIZ, SQRE
163 REAL D( * ), E( * ), U( ldu, * ), VT( ldvt, * ),
170 INTEGER I, I1, IC, IDXQ, IDXQC, IM1, INODE, ITEMP, IWK,
171 $ j, lf, ll, lvl, m, ncc, nd, ndb1, ndiml, ndimr,
172 $ nl, nlf, nlp1, nlvl, nr, nrf, nrp1, sqrei
186 ELSE IF( ( sqre.LT.0 ) .OR. ( sqre.GT.1 ) )
THEN
194 ELSE IF( ldvt.LT.m )
THEN
196 ELSE IF( smlsiz.LT.3 )
THEN
200 CALL xerbla(
'SLASD0', -info )
206 IF( n.LE.smlsiz )
THEN
207 CALL slasdq(
'U', sqre, n, m, n, 0, d, e, vt, ldvt, u, ldu, u,
219 CALL slasdt( n, nlvl, nd, iwork( inode ), iwork( ndiml ),
220 $ iwork( ndimr ), smlsiz )
236 ic = iwork( inode+i1 )
237 nl = iwork( ndiml+i1 )
239 nr = iwork( ndimr+i1 )
244 CALL slasdq(
'U', sqrei, nl, nlp1, nl, ncc, d( nlf ), e( nlf ),
245 $ vt( nlf, nlf ), ldvt, u( nlf, nlf ), ldu,
246 $ u( nlf, nlf ), ldu, work, info )
250 itemp = idxq + nlf - 2
260 CALL slasdq(
'U', sqrei, nr, nrp1, nr, ncc, d( nrf ), e( nrf ),
261 $ vt( nrf, nrf ), ldvt, u( nrf, nrf ), ldu,
262 $ u( nrf, nrf ), ldu, work, info )
268 iwork( itemp+j-1 ) = j
274 DO 50 lvl = nlvl, 1, -1
288 ic = iwork( inode+im1 )
289 nl = iwork( ndiml+im1 )
290 nr = iwork( ndimr+im1 )
292 IF( ( sqre.EQ.0 ) .AND. ( i.EQ.ll ) )
THEN
297 idxqc = idxq + nlf - 1
300 CALL slasd1( nl, nr, sqrei, d( nlf ), alpha, beta,
301 $ u( nlf, nlf ), ldu, vt( nlf, nlf ), ldvt,
302 $ iwork( idxqc ), iwork( iwk ), work, info )
subroutine slasdt(N, LVL, ND, INODE, NDIML, NDIMR, MSUB)
SLASDT creates a tree of subproblems for bidiagonal divide and conquer. Used by sbdsdc.
subroutine slasd1(NL, NR, SQRE, D, ALPHA, BETA, U, LDU, VT, LDVT, IDXQ, IWORK, WORK, INFO)
SLASD1 computes the SVD of an upper bidiagonal matrix B of the specified size. Used by sbdsdc...
subroutine xerbla(SRNAME, INFO)
XERBLA
subroutine slasdq(UPLO, SQRE, N, NCVT, NRU, NCC, D, E, VT, LDVT, U, LDU, C, LDC, WORK, INFO)
SLASDQ computes the SVD of a real bidiagonal matrix with diagonal d and off-diagonal e...
subroutine slasd0(N, SQRE, D, E, U, LDU, VT, LDVT, SMLSIZ, IWORK, WORK, INFO)
SLASD0 computes the singular values of a real upper bidiagonal n-by-m matrix B with diagonal d and of...