92 SUBROUTINE dqrt13( SCALE, M, N, A, LDA, NORMA, ISEED )
100 INTEGER LDA, M, N, SCALE
101 DOUBLE PRECISION NORMA
105 DOUBLE PRECISION A( lda, * )
112 parameter ( one = 1.0d0 )
116 DOUBLE PRECISION BIGNUM, SMLNUM
119 DOUBLE PRECISION DASUM, DLAMCH, DLANGE
120 EXTERNAL dasum, dlamch, dlange
129 DOUBLE PRECISION DUMMY( 1 )
133 IF( m.LE.0 .OR. n.LE.0 )
139 CALL dlarnv( 2, iseed, m, a( 1, j ) )
141 a( j, j ) = a( j, j ) + sign( dasum( m, a( 1, j ), 1 ),
148 IF( scale.NE.1 )
THEN
149 norma = dlange(
'Max', m, n, a, lda, dummy )
150 smlnum = dlamch(
'Safe minimum' )
151 bignum = one / smlnum
152 CALL dlabad( smlnum, bignum )
153 smlnum = smlnum / dlamch(
'Epsilon' )
154 bignum = one / smlnum
156 IF( scale.EQ.2 )
THEN
160 CALL dlascl(
'General', 0, 0, norma, bignum, m, n, a, lda,
162 ELSE IF( scale.EQ.3 )
THEN
166 CALL dlascl(
'General', 0, 0, norma, smlnum, m, n, a, lda,
171 norma = dlange(
'One-norm', m, n, a, lda, dummy )
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 dlabad(SMALL, LARGE)
DLABAD
subroutine dqrt13(SCALE, M, N, A, LDA, NORMA, ISEED)
DQRT13
subroutine dlarnv(IDIST, ISEED, N, X)
DLARNV returns a vector of random numbers from a uniform or normal distribution.