309 SUBROUTINE dlasd6( 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 DOUBLE PRECISION ALPHA, BETA, C, S
324 INTEGER GIVCOL( LDGCOL, * ), IDXQ( * ), IWORK( * ),
326 DOUBLE PRECISION D( * ), DIFL( * ), DIFR( * ),
327 $ givnum( ldgnum, * ), poles( ldgnum, * ),
328 $ vf( * ), vl( * ), work( * ), z( * )
334 DOUBLE PRECISION ONE, ZERO
335 PARAMETER ( ONE = 1.0d+0, zero = 0.0d+0 )
338 INTEGER I, IDX, IDXC, IDXP, ISIGMA, IVFW, IVLW, IW, M,
340 DOUBLE PRECISION ORGNRM
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(
'DLASD6', -info )
389 orgnrm = max( abs( alpha ), abs( beta ) )
392 IF( abs( d( i ) ).GT.orgnrm )
THEN
393 orgnrm = abs( d( i ) )
396 CALL dlascl(
'G', 0, 0, orgnrm, one, n, 1, d, n, info )
397 alpha = alpha / orgnrm
402 CALL dlasd7( 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 dlasd8( icompq, k, d, z, vf, vl, difl, difr, ldgnum,
411 $ work( isigma ), work( iw ), info )
421 IF( icompq.EQ.1 )
THEN
422 CALL dcopy( k, d, 1, poles( 1, 1 ), 1 )
423 CALL dcopy( k, work( isigma ), 1, poles( 1, 2 ), 1 )
428 CALL dlascl(
'G', 0, 0, one, orgnrm, n, 1, d, n, info )
434 CALL dlamrg( n1, n2, d, 1, -1, idxq )
subroutine xerbla(srname, info)
subroutine dcopy(n, dx, incx, dy, incy)
DCOPY
subroutine dlamrg(n1, n2, a, dtrd1, dtrd2, index)
DLAMRG creates a permutation list to merge the entries of two independently sorted sets into a single...
subroutine dlascl(type, kl, ku, cfrom, cto, m, n, a, lda, info)
DLASCL multiplies a general rectangular matrix by a real scalar defined as cto/cfrom.
subroutine dlasd6(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)
DLASD6 computes the SVD of an updated upper bidiagonal matrix obtained by merging two smaller ones by...
subroutine dlasd7(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)
DLASD7 merges the two sets of singular values together into a single sorted set. Then it tries to def...
subroutine dlasd8(icompq, k, d, z, vf, vl, difl, difr, lddifr, dsigma, work, info)
DLASD8 finds the square roots of the roots of the secular equation, and stores, for each element in D...