309 SUBROUTINE slasd6( ICOMPQ, NL, NR, SQRE, D, VF, VL, ALPHA, BETA,
310 $ IDXQ, PERM, GIVPTR, GIVCOL, LDGCOL, GIVNUM,
311 $ LDGNUM, POLES, DIFL, DIFR, Z, K, C, S, WORK,
319 INTEGER GIVPTR, ICOMPQ, INFO, K, LDGCOL, LDGNUM, NL,
321 REAL ALPHA, BETA, C, S
324 INTEGER GIVCOL( LDGCOL, * ), IDXQ( * ), IWORK( * ),
326 REAL D( * ), DIFL( * ), DIFR( * ),
327 $ givnum( ldgnum, * ), poles( ldgnum, * ),
328 $ vf( * ), vl( * ), work( * ), z( * )
335 PARAMETER ( ONE = 1.0e+0, zero = 0.0e+0 )
338 INTEGER I, IDX, IDXC, IDXP, ISIGMA, IVFW, IVLW, IW, M,
356 IF( ( icompq.LT.0 ) .OR. ( icompq.GT.1 ) )
THEN
358 ELSE IF( nl.LT.1 )
THEN
360 ELSE IF( nr.LT.1 )
THEN
362 ELSE IF( ( sqre.LT.0 ) .OR. ( sqre.GT.1 ) )
THEN
364 ELSE IF( ldgcol.LT.n )
THEN
366 ELSE IF( ldgnum.LT.n )
THEN
370 CALL xerbla(
'SLASD6', -info )
389 orgnrm = max( abs( alpha ), abs( beta ) )
392 IF( abs( d( i ) ).GT.orgnrm )
THEN
393 orgnrm = abs( d( i ) )
396 CALL slascl(
'G', 0, 0, orgnrm, one, n, 1, d, n, info )
397 alpha = alpha / orgnrm
402 CALL slasd7( icompq, nl, nr, sqre, k, d, z, work( iw ), vf,
403 $ work( ivfw ), vl, work( ivlw ), alpha, beta,
404 $ work( isigma ), iwork( idx ), iwork( idxp ), idxq,
405 $ perm, givptr, givcol, ldgcol, givnum, ldgnum, c, s,
410 CALL slasd8( icompq, k, d, z, vf, vl, difl, difr, ldgnum,
411 $ work( isigma ), work( iw ), info )
421 IF( icompq.EQ.1 )
THEN
422 CALL scopy( k, d, 1, poles( 1, 1 ), 1 )
423 CALL scopy( k, work( isigma ), 1, poles( 1, 2 ), 1 )
428 CALL slascl(
'G', 0, 0, one, orgnrm, n, 1, d, n, info )
434 CALL slamrg( n1, n2, d, 1, -1, idxq )
subroutine xerbla(srname, info)
subroutine scopy(n, sx, incx, sy, incy)
SCOPY
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 slasd6(icompq, nl, nr, sqre, d, vf, vl, alpha, beta, idxq, perm, givptr, givcol, ldgcol, givnum, ldgnum, poles, difl, difr, z, k, c, s, work, iwork, info)
SLASD6 computes the SVD of an updated upper bidiagonal matrix obtained by merging two smaller ones by...
subroutine slasd7(icompq, nl, nr, sqre, k, d, z, zw, vf, vfw, vl, vlw, alpha, beta, dsigma, idx, idxp, idxq, perm, givptr, givcol, ldgcol, givnum, ldgnum, c, s, info)
SLASD7 merges the two sets of singular values together into a single sorted set. Then it tries to def...
subroutine slasd8(icompq, k, d, z, vf, vl, difl, difr, lddifr, dsigma, work, info)
SLASD8 finds the square roots of the roots of the secular equation, and stores, for each element in D...