147 SUBROUTINE cqrt15( SCALE, RKSEL, M, N, NRHS, A, LDA, B, LDB, S,
148 $ RANK, NORMA, NORMB, ISEED, WORK, LWORK )
155 INTEGER LDA, LDB, LWORK, M, N, NRHS, RANK, RKSEL, SCALE
161 COMPLEX A( LDA, * ), B( LDB, * ), WORK( LWORK )
167 REAL ZERO, ONE, TWO, SVMIN
168 parameter( zero = 0.0e+0, one = 1.0e+0, two = 2.0e+0,
171 parameter( czero = ( 0.0e+0, 0.0e+0 ),
172 $ cone = ( 1.0e+0, 0.0e+0 ) )
176 REAL BIGNUM, EPS, SMLNUM, TEMP
182 REAL CLANGE, SASUM, SCNRM2, SLAMCH, SLARND
183 EXTERNAL clange, sasum, scnrm2, slamch, slarnd
190 INTRINSIC abs, cmplx, max, min
195 IF( lwork.LT.max( m+mn, mn*nrhs, 2*n+m ) )
THEN
196 CALL xerbla(
'CQRT15', 16 )
200 smlnum = slamch(
'Safe minimum' )
201 bignum = one / smlnum
202 eps = slamch(
'Epsilon' )
203 smlnum = ( smlnum / eps ) / eps
204 bignum = one / smlnum
208 IF( rksel.EQ.1 )
THEN
210 ELSE IF( rksel.EQ.2 )
THEN
212 DO 10 j = rank + 1, mn
216 CALL xerbla(
'CQRT15', 2 )
226 temp = slarnd( 1, iseed )
227 IF( temp.GT.svmin )
THEN
233 CALL slaord(
'Decreasing', rank, s, 1 )
237 CALL clarnv( 2, iseed, m, work )
238 CALL csscal( m, one / scnrm2( m, work, 1 ), work, 1 )
239 CALL claset(
'Full', m, rank, czero, cone, a, lda )
240 CALL clarf(
'Left', m, rank, work, 1, cmplx( two ), a, lda,
247 CALL clarnv( 2, iseed, rank*nrhs, work )
248 CALL cgemm(
'No transpose',
'No transpose', m, nrhs, rank,
249 $ cone, a, lda, work, rank, czero, b, ldb )
256 CALL csscal( m, s( j ), a( 1, j ), 1 )
259 $
CALL claset(
'Full', m, n-rank, czero, czero,
260 $ a( 1, rank+1 ), lda )
261 CALL claror(
'Right',
'No initialization', m, n, a, lda, iseed,
273 CALL claset(
'Full', m, n, czero, czero, a, lda )
274 CALL claset(
'Full', m, nrhs, czero, czero, b, ldb )
280 IF( scale.NE.1 )
THEN
281 norma = clange(
'Max', m, n, a, lda, dummy )
282 IF( norma.NE.zero )
THEN
283 IF( scale.EQ.2 )
THEN
287 CALL clascl(
'General', 0, 0, norma, bignum, m, n, a,
289 CALL slascl(
'General', 0, 0, norma, bignum, mn, 1, s,
291 CALL clascl(
'General', 0, 0, norma, bignum, m, nrhs, b,
293 ELSE IF( scale.EQ.3 )
THEN
297 CALL clascl(
'General', 0, 0, norma, smlnum, m, n, a,
299 CALL slascl(
'General', 0, 0, norma, smlnum, mn, 1, s,
301 CALL clascl(
'General', 0, 0, norma, smlnum, m, nrhs, b,
304 CALL xerbla(
'CQRT15', 1 )
310 norma = sasum( mn, s, 1 )
311 normb = clange(
'One-norm', m, nrhs, b, ldb, dummy )
subroutine xerbla(srname, info)
subroutine claror(side, init, m, n, a, lda, iseed, x, info)
CLAROR
subroutine cqrt15(scale, rksel, m, n, nrhs, a, lda, b, ldb, s, rank, norma, normb, iseed, work, lwork)
CQRT15
subroutine cgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
CGEMM
subroutine clarf(side, m, n, v, incv, tau, c, ldc, work)
CLARF applies an elementary reflector to a general rectangular matrix.
subroutine clarnv(idist, iseed, n, x)
CLARNV returns a vector of random numbers from a uniform or normal distribution.
subroutine clascl(type, kl, ku, cfrom, cto, m, n, a, lda, info)
CLASCL multiplies a general rectangular matrix by a real scalar defined as cto/cfrom.
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 claset(uplo, m, n, alpha, beta, a, lda)
CLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
subroutine csscal(n, sa, cx, incx)
CSSCAL
subroutine slaord(job, n, x, incx)
SLAORD