171 SUBROUTINE slalsd( UPLO, SMLSIZ, N, NRHS, D, E, B, LDB, RCOND,
172 $ RANK, WORK, IWORK, INFO )
180 INTEGER INFO, LDB, N, NRHS, RANK, SMLSIZ
185 REAL B( LDB, * ), D( * ), E( * ), WORK( * )
192 parameter( zero = 0.0e0, one = 1.0e0, two = 2.0e0 )
195 INTEGER BX, BXST, C, DIFL, DIFR, GIVCOL, GIVNUM,
196 $ givptr, i, icmpq1, icmpq2, iwk, j, k, nlvl,
197 $ nm1, nsize, nsub, nwork, perm, poles, s, sizei,
198 $ smlszp, sqre, st, st1, u, vt, z
199 REAL CS, EPS, ORGNRM, R, RCND, SN, TOL
204 EXTERNAL isamax, slamch, slanst
211 INTRINSIC abs, int, log, real, sign
221 ELSE IF( nrhs.LT.1 )
THEN
223 ELSE IF( ( ldb.LT.1 ) .OR. ( ldb.LT.n ) )
THEN
227 CALL xerbla(
'SLALSD', -info )
231 eps = slamch(
'Epsilon' )
235 IF( ( rcond.LE.zero ) .OR. ( rcond.GE.one ) )
THEN
247 ELSE IF( n.EQ.1 )
THEN
248 IF( d( 1 ).EQ.zero )
THEN
249 CALL slaset(
'A', 1, nrhs, zero, zero, b, ldb )
252 CALL slascl(
'G', 0, 0, d( 1 ), one, 1, nrhs, b, ldb, info )
253 d( 1 ) = abs( d( 1 ) )
260 IF( uplo.EQ.
'L' )
THEN
262 CALL slartg( d( i ), e( i ), cs, sn, r )
265 d( i+1 ) = cs*d( i+1 )
267 CALL srot( 1, b( i, 1 ), 1, b( i+1, 1 ), 1, cs, sn )
278 CALL srot( 1, b( j, i ), 1, b( j+1, i ), 1, cs, sn )
287 orgnrm = slanst(
'M', n, d, e )
288 IF( orgnrm.EQ.zero )
THEN
289 CALL slaset(
'A', n, nrhs, zero, zero, b, ldb )
293 CALL slascl(
'G', 0, 0, orgnrm, one, n, 1, d, n, info )
294 CALL slascl(
'G', 0, 0, orgnrm, one, nm1, 1, e, nm1, info )
299 IF( n.LE.smlsiz )
THEN
301 CALL slaset(
'A', n, n, zero, one, work, n )
302 CALL slasdq(
'U', 0, n, n, 0, nrhs, d, e, work, n, work, n, b,
303 $ ldb, work( nwork ), info )
307 tol = rcnd*abs( d( isamax( n, d, 1 ) ) )
309 IF( d( i ).LE.tol )
THEN
310 CALL slaset(
'A', 1, nrhs, zero, zero, b( i, 1 ), ldb )
312 CALL slascl(
'G', 0, 0, d( i ), one, 1, nrhs, b( i, 1 ),
317 CALL sgemm(
'T',
'N', n, nrhs, n, one, work, n, b, ldb, zero,
319 CALL slacpy(
'A', n, nrhs, work( nwork ), n, b, ldb )
323 CALL slascl(
'G', 0, 0, one, orgnrm, n, 1, d, n, info )
324 CALL slasrt(
'D', n, d, info )
325 CALL slascl(
'G', 0, 0, orgnrm, one, n, nrhs, b, ldb, info )
332 nlvl = int( log( real( n ) / real( smlsiz+1 ) ) / log( two ) ) + 1
344 givnum = poles + 2*nlvl*n
345 bx = givnum + 2*nlvl*n
352 givcol = perm + nlvl*n
353 iwk = givcol + nlvl*n*2
362 IF( abs( d( i ) ).LT.eps )
THEN
363 d( i ) = sign( eps, d( i ) )
368 IF( ( abs( e( i ) ).LT.eps ) .OR. ( i.EQ.nm1 ) )
THEN
380 iwork( sizei+nsub-1 ) = nsize
381 ELSE IF( abs( e( i ) ).GE.eps )
THEN
386 iwork( sizei+nsub-1 ) = nsize
394 iwork( sizei+nsub-1 ) = nsize
397 iwork( sizei+nsub-1 ) = 1
398 CALL scopy( nrhs, b( n, 1 ), ldb, work( bx+nm1 ), n )
401 IF( nsize.EQ.1 )
THEN
406 CALL scopy( nrhs, b( st, 1 ), ldb, work( bx+st1 ), n )
407 ELSE IF( nsize.LE.smlsiz )
THEN
411 CALL slaset(
'A', nsize, nsize, zero, one,
412 $ work( vt+st1 ), n )
413 CALL slasdq(
'U', 0, nsize, nsize, 0, nrhs, d( st ),
414 $ e( st ), work( vt+st1 ), n, work( nwork ),
415 $ n, b( st, 1 ), ldb, work( nwork ), info )
419 CALL slacpy(
'A', nsize, nrhs, b( st, 1 ), ldb,
420 $ work( bx+st1 ), n )
425 CALL slasda( icmpq1, smlsiz, nsize, sqre, d( st ),
426 $ e( st ), work( u+st1 ), n, work( vt+st1 ),
427 $ iwork( k+st1 ), work( difl+st1 ),
428 $ work( difr+st1 ), work( z+st1 ),
429 $ work( poles+st1 ), iwork( givptr+st1 ),
430 $ iwork( givcol+st1 ), n, iwork( perm+st1 ),
431 $ work( givnum+st1 ), work( c+st1 ),
432 $ work( s+st1 ), work( nwork ), iwork( iwk ),
438 CALL slalsa( icmpq2, smlsiz, nsize, nrhs, b( st, 1 ),
439 $ ldb, work( bxst ), n, work( u+st1 ), n,
440 $ work( vt+st1 ), iwork( k+st1 ),
441 $ work( difl+st1 ), work( difr+st1 ),
442 $ work( z+st1 ), work( poles+st1 ),
443 $ iwork( givptr+st1 ), iwork( givcol+st1 ), n,
444 $ iwork( perm+st1 ), work( givnum+st1 ),
445 $ work( c+st1 ), work( s+st1 ), work( nwork ),
446 $ iwork( iwk ), info )
457 tol = rcnd*abs( d( isamax( n, d, 1 ) ) )
464 IF( abs( d( i ) ).LE.tol )
THEN
465 CALL slaset(
'A', 1, nrhs, zero, zero, work( bx+i-1 ), n )
468 CALL slascl(
'G', 0, 0, d( i ), one, 1, nrhs,
469 $ work( bx+i-1 ), n, info )
471 d( i ) = abs( d( i ) )
480 nsize = iwork( sizei+i-1 )
482 IF( nsize.EQ.1 )
THEN
483 CALL scopy( nrhs, work( bxst ), n, b( st, 1 ), ldb )
484 ELSE IF( nsize.LE.smlsiz )
THEN
485 CALL sgemm(
'T',
'N', nsize, nrhs, nsize, one,
486 $ work( vt+st1 ), n, work( bxst ), n, zero,
489 CALL slalsa( icmpq2, smlsiz, nsize, nrhs, work( bxst ), n,
490 $ b( st, 1 ), ldb, work( u+st1 ), n,
491 $ work( vt+st1 ), iwork( k+st1 ),
492 $ work( difl+st1 ), work( difr+st1 ),
493 $ work( z+st1 ), work( poles+st1 ),
494 $ iwork( givptr+st1 ), iwork( givcol+st1 ), n,
495 $ iwork( perm+st1 ), work( givnum+st1 ),
496 $ work( c+st1 ), work( s+st1 ), work( nwork ),
497 $ iwork( iwk ), info )
506 CALL slascl(
'G', 0, 0, one, orgnrm, n, 1, d, n, info )
507 CALL slasrt(
'D', n, d, info )
508 CALL slascl(
'G', 0, 0, orgnrm, one, n, nrhs, b, ldb, info )
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 slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
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 slalsd(uplo, smlsiz, n, nrhs, d, e, b, ldb, rcond, rank, work, iwork, info)
SLALSD uses the singular value decomposition of A to solve the least squares problem.
subroutine slartg(f, g, c, s, r)
SLARTG generates a plane rotation with real cosine and real sine.
subroutine slascl(type, kl, ku, cfrom, cto, m, n, a, lda, info)
SLASCL multiplies a general rectangular matrix by a real scalar defined as cto/cfrom.
subroutine slasda(icompq, smlsiz, n, sqre, d, e, u, ldu, vt, k, difl, difr, z, poles, givptr, givcol, ldgcol, perm, givnum, c, s, work, iwork, info)
SLASDA computes the singular value decomposition (SVD) of a real upper bidiagonal matrix with diagona...
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 slaset(uplo, m, n, alpha, beta, a, lda)
SLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
subroutine slasrt(id, n, d, info)
SLASRT sorts numbers in increasing or decreasing order.
subroutine srot(n, sx, incx, sy, incy, c, s)
SROT