202 SUBROUTINE slasd1( NL, NR, SQRE, D, ALPHA, BETA, U, LDU, VT, LDVT,
203 $ IDXQ, IWORK, WORK, INFO )
210 INTEGER INFO, LDU, LDVT, NL, NR, SQRE
214 INTEGER IDXQ( * ), IWORK( * )
215 REAL D( * ), U( LDU, * ), VT( LDVT, * ), WORK( * )
223 parameter( one = 1.0e+0, zero = 0.0e+0 )
226 INTEGER COLTYP, I, IDX, IDXC, IDXP, IQ, ISIGMA, IU2,
227 $ ivt2, iz, k, ldq, ldu2, ldvt2, m, n, n1, n2
244 ELSE IF( nr.LT.1 )
THEN
246 ELSE IF( ( sqre.LT.0 ) .OR. ( sqre.GT.1 ) )
THEN
250 CALL xerbla(
'SLASD1', -info )
277 orgnrm = max( abs( alpha ), abs( beta ) )
280 IF( abs( d( i ) ).GT.orgnrm )
THEN
281 orgnrm = abs( d( i ) )
284 CALL slascl(
'G', 0, 0, orgnrm, one, n, 1, d, n, info )
285 alpha = alpha / orgnrm
290 CALL slasd2( nl, nr, sqre, k, d, work( iz ), alpha, beta, u, ldu,
291 $ vt, ldvt, work( isigma ), work( iu2 ), ldu2,
292 $ work( ivt2 ), ldvt2, iwork( idxp ), iwork( idx ),
293 $ iwork( idxc ), idxq, iwork( coltyp ), info )
298 CALL slasd3( nl, nr, sqre, k, d, work( iq ), ldq, work( isigma ),
299 $ u, ldu, work( iu2 ), ldu2, vt, ldvt, work( ivt2 ),
300 $ ldvt2, iwork( idxc ), iwork( coltyp ), work( iz ),
311 CALL slascl(
'G', 0, 0, one, orgnrm, n, 1, d, n, info )
317 CALL slamrg( n1, n2, d, 1, -1, idxq )
subroutine xerbla(srname, info)
subroutine slamrg(n1, n2, a, strd1, strd2, index)
SLAMRG creates a permutation list to merge the entries of two independently sorted sets into a single...
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 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 slasd2(nl, nr, sqre, k, d, z, alpha, beta, u, ldu, vt, ldvt, dsigma, u2, ldu2, vt2, ldvt2, idxp, idx, idxc, idxq, coltyp, info)
SLASD2 merges the two sets of singular values together into a single sorted set. Used by sbdsdc.
subroutine slasd3(nl, nr, sqre, k, d, q, ldq, dsigma, u, ldu, u2, ldu2, vt, ldvt, vt2, ldvt2, idxc, ctot, z, info)
SLASD3 finds all square roots of the roots of the secular equation, as defined by the values in D and...