LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Modules Pages

◆ slatm1()

subroutine slatm1 ( integer mode,
real cond,
integer irsign,
integer idist,
integer, dimension( 4 ) iseed,
real, dimension( * ) d,
integer n,
integer info )

SLATM1

Purpose:
!> !> SLATM1 computes the entries of D(1..N) as specified by !> MODE, COND and IRSIGN. IDIST and ISEED determine the generation !> of random numbers. SLATM1 is called by SLATMR to generate !> random test matrices for LAPACK programs. !>
Parameters
[in]MODE
!> MODE is INTEGER !> On entry describes how D is to be computed: !> MODE = 0 means do not change D. !> MODE = 1 sets D(1)=1 and D(2:N)=1.0/COND !> MODE = 2 sets D(1:N-1)=1 and D(N)=1.0/COND !> MODE = 3 sets D(I)=COND**(-(I-1)/(N-1)) !> MODE = 4 sets D(i)=1 - (i-1)/(N-1)*(1 - 1/COND) !> MODE = 5 sets D to random numbers in the range !> ( 1/COND , 1 ) such that their logarithms !> are uniformly distributed. !> MODE = 6 set D to random numbers from same distribution !> as the rest of the matrix. !> MODE < 0 has the same meaning as ABS(MODE), except that !> the order of the elements of D is reversed. !> Thus if MODE is positive, D has entries ranging from !> 1 to 1/COND, if negative, from 1/COND to 1, !> Not modified. !>
[in]COND
!> COND is REAL !> On entry, used as described under MODE above. !> If used, it must be >= 1. Not modified. !>
[in]IRSIGN
!> IRSIGN is INTEGER !> On entry, if MODE neither -6, 0 nor 6, determines sign of !> entries of D !> 0 => leave entries of D unchanged !> 1 => multiply each entry of D by 1 or -1 with probability .5 !>
[in]IDIST
!> IDIST is INTEGER !> On entry, IDIST specifies the type of distribution to be !> used to generate a random matrix . !> 1 => UNIFORM( 0, 1 ) !> 2 => UNIFORM( -1, 1 ) !> 3 => NORMAL( 0, 1 ) !> Not modified. !>
[in,out]ISEED
!> ISEED is INTEGER array, dimension ( 4 ) !> On entry ISEED specifies the seed of the random number !> generator. The random number generator uses a !> linear congruential sequence limited to small !> integers, and so should produce machine independent !> random numbers. The values of ISEED are changed on !> exit, and can be used in the next call to SLATM1 !> to continue the same random number sequence. !> Changed on exit. !>
[in,out]D
!> D is REAL array, dimension ( N ) !> Array to be computed according to MODE, COND and IRSIGN. !> May be changed on exit if MODE is nonzero. !>
[in]N
!> N is INTEGER !> Number of entries of D. Not modified. !>
[out]INFO
!> INFO is INTEGER !> 0 => normal termination !> -1 => if MODE not in range -6 to 6 !> -2 => if MODE neither -6, 0 nor 6, and !> IRSIGN neither 0 nor 1 !> -3 => if MODE neither -6, 0 nor 6 and COND less than 1 !> -4 => if MODE equals 6 or -6 and IDIST not in range 1 to 3 !> -7 => if N negative !>
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 134 of file slatm1.f.

136*
137* -- LAPACK auxiliary routine --
138* -- LAPACK is a software package provided by Univ. of Tennessee, --
139* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
140*
141* .. Scalar Arguments ..
142 INTEGER IDIST, INFO, IRSIGN, MODE, N
143 REAL COND
144* ..
145* .. Array Arguments ..
146 INTEGER ISEED( 4 )
147 REAL D( * )
148* ..
149*
150* =====================================================================
151*
152* .. Parameters ..
153 REAL ONE
154 parameter( one = 1.0e0 )
155 REAL HALF
156 parameter( half = 0.5e0 )
157* ..
158* .. Local Scalars ..
159 INTEGER I
160 REAL ALPHA, TEMP
161* ..
162* .. External Functions ..
163 REAL SLARAN
164 EXTERNAL slaran
165* ..
166* .. External Subroutines ..
167 EXTERNAL slarnv, xerbla
168* ..
169* .. Intrinsic Functions ..
170 INTRINSIC abs, exp, log, real
171* ..
172* .. Executable Statements ..
173*
174* Decode and Test the input parameters. Initialize flags & seed.
175*
176 info = 0
177*
178* Quick return if possible
179*
180 IF( n.EQ.0 )
181 $ RETURN
182*
183* Set INFO if an error
184*
185 IF( mode.LT.-6 .OR. mode.GT.6 ) THEN
186 info = -1
187 ELSE IF( ( mode.NE.-6 .AND. mode.NE.0 .AND. mode.NE.6 ) .AND.
188 $ ( irsign.NE.0 .AND. irsign.NE.1 ) ) THEN
189 info = -2
190 ELSE IF( ( mode.NE.-6 .AND. mode.NE.0 .AND. mode.NE.6 ) .AND.
191 $ cond.LT.one ) THEN
192 info = -3
193 ELSE IF( ( mode.EQ.6 .OR. mode.EQ.-6 ) .AND.
194 $ ( idist.LT.1 .OR. idist.GT.3 ) ) THEN
195 info = -4
196 ELSE IF( n.LT.0 ) THEN
197 info = -7
198 END IF
199*
200 IF( info.NE.0 ) THEN
201 CALL xerbla( 'SLATM1', -info )
202 RETURN
203 END IF
204*
205* Compute D according to COND and MODE
206*
207 IF( mode.NE.0 ) THEN
208 GO TO ( 10, 30, 50, 70, 90, 110 )abs( mode )
209*
210* One large D value:
211*
212 10 CONTINUE
213 DO 20 i = 1, n
214 d( i ) = one / cond
215 20 CONTINUE
216 d( 1 ) = one
217 GO TO 120
218*
219* One small D value:
220*
221 30 CONTINUE
222 DO 40 i = 1, n
223 d( i ) = one
224 40 CONTINUE
225 d( n ) = one / cond
226 GO TO 120
227*
228* Exponentially distributed D values:
229*
230 50 CONTINUE
231 d( 1 ) = one
232 IF( n.GT.1 ) THEN
233 alpha = cond**( -one / real( n-1 ) )
234 DO 60 i = 2, n
235 d( i ) = alpha**( i-1 )
236 60 CONTINUE
237 END IF
238 GO TO 120
239*
240* Arithmetically distributed D values:
241*
242 70 CONTINUE
243 d( 1 ) = one
244 IF( n.GT.1 ) THEN
245 temp = one / cond
246 alpha = ( one-temp ) / real( n-1 )
247 DO 80 i = 2, n
248 d( i ) = real( n-i )*alpha + temp
249 80 CONTINUE
250 END IF
251 GO TO 120
252*
253* Randomly distributed D values on ( 1/COND , 1):
254*
255 90 CONTINUE
256 alpha = log( one / cond )
257 DO 100 i = 1, n
258 d( i ) = exp( alpha*slaran( iseed ) )
259 100 CONTINUE
260 GO TO 120
261*
262* Randomly distributed D values from IDIST
263*
264 110 CONTINUE
265 CALL slarnv( idist, iseed, n, d )
266*
267 120 CONTINUE
268*
269* If MODE neither -6 nor 0 nor 6, and IRSIGN = 1, assign
270* random signs to D
271*
272 IF( ( mode.NE.-6 .AND. mode.NE.0 .AND. mode.NE.6 ) .AND.
273 $ irsign.EQ.1 ) THEN
274 DO 130 i = 1, n
275 temp = slaran( iseed )
276 IF( temp.GT.half )
277 $ d( i ) = -d( i )
278 130 CONTINUE
279 END IF
280*
281* Reverse if MODE < 0
282*
283 IF( mode.LT.0 ) THEN
284 DO 140 i = 1, n / 2
285 temp = d( i )
286 d( i ) = d( n+1-i )
287 d( n+1-i ) = temp
288 140 CONTINUE
289 END IF
290*
291 END IF
292*
293 RETURN
294*
295* End of SLATM1
296*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine slarnv(idist, iseed, n, x)
SLARNV returns a vector of random numbers from a uniform or normal distribution.
Definition slarnv.f:95
real function slaran(iseed)
SLARAN
Definition slaran.f:67
Here is the call graph for this function:
Here is the caller graph for this function: