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

◆ 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.

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