90 SUBROUTINE cqrt13( SCALE, M, N, A, LDA, NORMA, ISEED )
97 INTEGER LDA, M, N, SCALE
109 parameter( one = 1.0e0 )
116 REAL CLANGE, SCASUM, SLAMCH
117 EXTERNAL clange, scasum, slamch
123 INTRINSIC cmplx, real, sign
130 IF( m.LE.0 .OR. n.LE.0 )
136 CALL clarnv( 2, iseed, m, a( 1, j ) )
138 a( j, j ) = a( j, j ) + cmplx( sign( scasum( m, a( 1, j ),
139 $ 1 ), real( a( j, j ) ) ) )
145 IF( scale.NE.1 )
THEN
146 norma = clange(
'Max', m, n, a, lda, dummy )
147 smlnum = slamch(
'Safe minimum' )
148 bignum = one / smlnum
149 smlnum = smlnum / slamch(
'Epsilon' )
150 bignum = one / smlnum
152 IF( scale.EQ.2 )
THEN
156 CALL clascl(
'General', 0, 0, norma, bignum, m, n, a, lda,
158 ELSE IF( scale.EQ.3 )
THEN
162 CALL clascl(
'General', 0, 0, norma, smlnum, m, n, a, lda,
167 norma = clange(
'One-norm', m, n, a, lda, dummy )
subroutine cqrt13(scale, m, n, a, lda, norma, iseed)
CQRT13
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.