146 SUBROUTINE dqrt15( SCALE, RKSEL, M, N, NRHS, A, LDA, B, LDB, S,
147 $ RANK, NORMA, NORMB, ISEED, WORK, LWORK )
154 INTEGER LDA, LDB, LWORK, M, N, NRHS, RANK, RKSEL, SCALE
155 DOUBLE PRECISION NORMA, NORMB
159 DOUBLE PRECISION A( LDA, * ), B( LDB, * ), S( * ), WORK( LWORK )
165 DOUBLE PRECISION ZERO, ONE, TWO, SVMIN
166 parameter( zero = 0.0d0, one = 1.0d0, two = 2.0d0,
171 DOUBLE PRECISION BIGNUM, EPS, SMLNUM, TEMP
174 DOUBLE PRECISION DUMMY( 1 )
177 DOUBLE PRECISION DASUM, DLAMCH, DLANGE, DLARND, DNRM2
178 EXTERNAL dasum, dlamch, dlange, dlarnd, dnrm2
185 INTRINSIC abs, max, min
190 IF( lwork.LT.max( m+mn, mn*nrhs, 2*n+m ) )
THEN
191 CALL xerbla(
'DQRT15', 16 )
195 smlnum = dlamch(
'Safe minimum' )
196 bignum = one / smlnum
197 eps = dlamch(
'Epsilon' )
198 smlnum = ( smlnum / eps ) / eps
199 bignum = one / smlnum
203 IF( rksel.EQ.1 )
THEN
205 ELSE IF( rksel.EQ.2 )
THEN
207 DO 10 j = rank + 1, mn
211 CALL xerbla(
'DQRT15', 2 )
221 temp = dlarnd( 1, iseed )
222 IF( temp.GT.svmin )
THEN
228 CALL dlaord(
'Decreasing', rank, s, 1 )
232 CALL dlarnv( 2, iseed, m, work )
233 CALL dscal( m, one / dnrm2( m, work, 1 ), work, 1 )
234 CALL dlaset(
'Full', m, rank, zero, one, a, lda )
235 CALL dlarf(
'Left', m, rank, work, 1, two, a, lda,
242 CALL dlarnv( 2, iseed, rank*nrhs, work )
243 CALL dgemm(
'No transpose',
'No transpose', m, nrhs, rank, one,
244 $ a, lda, work, rank, zero, b, ldb )
251 CALL dscal( m, s( j ), a( 1, j ), 1 )
254 $
CALL dlaset(
'Full', m, n-rank, zero, zero, a( 1, rank+1 ),
256 CALL dlaror(
'Right',
'No initialization', m, n, a, lda, iseed,
268 CALL dlaset(
'Full', m, n, zero, zero, a, lda )
269 CALL dlaset(
'Full', m, nrhs, zero, zero, b, ldb )
275 IF( scale.NE.1 )
THEN
276 norma = dlange(
'Max', m, n, a, lda, dummy )
277 IF( norma.NE.zero )
THEN
278 IF( scale.EQ.2 )
THEN
282 CALL dlascl(
'General', 0, 0, norma, bignum, m, n, a,
284 CALL dlascl(
'General', 0, 0, norma, bignum, mn, 1, s,
286 CALL dlascl(
'General', 0, 0, norma, bignum, m, nrhs, b,
288 ELSE IF( scale.EQ.3 )
THEN
292 CALL dlascl(
'General', 0, 0, norma, smlnum, m, n, a,
294 CALL dlascl(
'General', 0, 0, norma, smlnum, mn, 1, s,
296 CALL dlascl(
'General', 0, 0, norma, smlnum, m, nrhs, b,
299 CALL xerbla(
'DQRT15', 1 )
305 norma = dasum( mn, s, 1 )
306 normb = dlange(
'One-norm', m, nrhs, b, ldb, dummy )
subroutine xerbla(srname, info)
subroutine dlaord(job, n, x, incx)
DLAORD
subroutine dlaror(side, init, m, n, a, lda, iseed, x, info)
DLAROR
subroutine dqrt15(scale, rksel, m, n, nrhs, a, lda, b, ldb, s, rank, norma, normb, iseed, work, lwork)
DQRT15
subroutine dgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
DGEMM
subroutine dlarf(side, m, n, v, incv, tau, c, ldc, work)
DLARF applies an elementary reflector to a general rectangular matrix.
subroutine dlarnv(idist, iseed, n, x)
DLARNV returns a vector of random numbers from a uniform or normal distribution.
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 dlaset(uplo, m, n, alpha, beta, a, lda)
DLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
subroutine dscal(n, da, dx, incx)
DSCAL