LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ sqrt13()

subroutine sqrt13 ( integer scale,
integer m,
integer n,
real, dimension( lda, * ) a,
integer lda,
real norma,
integer, dimension( 4 ) iseed )

SQRT13

Purpose:
!>
!> SQRT13 generates a full-rank matrix that may be scaled to have large
!> or small norm.
!> 
Parameters
[in]SCALE
!>          SCALE is INTEGER
!>          SCALE = 1: normally scaled matrix
!>          SCALE = 2: matrix scaled up
!>          SCALE = 3: matrix scaled down
!> 
[in]M
!>          M is INTEGER
!>          The number of rows of the matrix A.
!> 
[in]N
!>          N is INTEGER
!>          The number of columns of A.
!> 
[out]A
!>          A is REAL array, dimension (LDA,N)
!>          The M-by-N matrix A.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A.
!> 
[out]NORMA
!>          NORMA is REAL
!>          The one-norm of A.
!> 
[in,out]ISEED
!>          ISEED is integer array, dimension (4)
!>          Seed for random number generator
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 90 of file sqrt13.f.

91*
92* -- LAPACK test routine --
93* -- LAPACK is a software package provided by Univ. of Tennessee, --
94* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
95*
96* .. Scalar Arguments ..
97 INTEGER LDA, M, N, SCALE
98 REAL NORMA
99* ..
100* .. Array Arguments ..
101 INTEGER ISEED( 4 )
102 REAL A( LDA, * )
103* ..
104*
105* =====================================================================
106*
107* .. Parameters ..
108 REAL ONE
109 parameter( one = 1.0e0 )
110* ..
111* .. Local Scalars ..
112 INTEGER INFO, J
113 REAL BIGNUM, SMLNUM
114* ..
115* .. External Functions ..
116 REAL SASUM, SLAMCH, SLANGE
117 EXTERNAL sasum, slamch, slange
118* ..
119* .. External Subroutines ..
120 EXTERNAL slarnv, slascl
121* ..
122* .. Intrinsic Functions ..
123 INTRINSIC sign
124* ..
125* .. Local Arrays ..
126 REAL DUMMY( 1 )
127* ..
128* .. Executable Statements ..
129*
130 IF( m.LE.0 .OR. n.LE.0 )
131 $ RETURN
132*
133* benign matrix
134*
135 DO 10 j = 1, n
136 CALL slarnv( 2, iseed, m, a( 1, j ) )
137 IF( j.LE.m ) THEN
138 a( j, j ) = a( j, j ) + sign( sasum( m, a( 1, j ), 1 ),
139 $ a( j, j ) )
140 END IF
141 10 CONTINUE
142*
143* scaled versions
144*
145 IF( scale.NE.1 ) THEN
146 norma = slange( 'Max', m, n, a, lda, dummy )
147 smlnum = slamch( 'Safe minimum' )
148 bignum = one / smlnum
149 smlnum = smlnum / slamch( 'Epsilon' )
150 bignum = one / smlnum
151*
152 IF( scale.EQ.2 ) THEN
153*
154* matrix scaled up
155*
156 CALL slascl( 'General', 0, 0, norma, bignum, m, n, a, lda,
157 $ info )
158 ELSE IF( scale.EQ.3 ) THEN
159*
160* matrix scaled down
161*
162 CALL slascl( 'General', 0, 0, norma, smlnum, m, n, a, lda,
163 $ info )
164 END IF
165 END IF
166*
167 norma = slange( 'One-norm', m, n, a, lda, dummy )
168 RETURN
169*
170* End of SQRT13
171*
real function sasum(n, sx, incx)
SASUM
Definition sasum.f:72
real function slamch(cmach)
SLAMCH
Definition slamch.f:68
real function slange(norm, m, n, a, lda, work)
SLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition slange.f:112
subroutine slarnv(idist, iseed, n, x)
SLARNV returns a vector of random numbers from a uniform or normal distribution.
Definition slarnv.f:95
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.
Definition slascl.f:142
Here is the call graph for this function:
Here is the caller graph for this function: