LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
slarnv.f
Go to the documentation of this file.
1*> \brief \b SLARNV returns a vector of random numbers from a uniform or normal distribution.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download SLARNV + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slarnv.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slarnv.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slarnv.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SLARNV( IDIST, ISEED, N, X )
20*
21* .. Scalar Arguments ..
22* INTEGER IDIST, N
23* ..
24* .. Array Arguments ..
25* INTEGER ISEED( 4 )
26* REAL X( * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> SLARNV returns a vector of n random real numbers from a uniform or
36*> normal distribution.
37*> \endverbatim
38*
39* Arguments:
40* ==========
41*
42*> \param[in] IDIST
43*> \verbatim
44*> IDIST is INTEGER
45*> Specifies the distribution of the random numbers:
46*> = 1: uniform (0,1)
47*> = 2: uniform (-1,1)
48*> = 3: normal (0,1)
49*> \endverbatim
50*>
51*> \param[in,out] ISEED
52*> \verbatim
53*> ISEED is INTEGER array, dimension (4)
54*> On entry, the seed of the random number generator; the array
55*> elements must be between 0 and 4095, and ISEED(4) must be
56*> odd.
57*> On exit, the seed is updated.
58*> \endverbatim
59*>
60*> \param[in] N
61*> \verbatim
62*> N is INTEGER
63*> The number of random numbers to be generated.
64*> \endverbatim
65*>
66*> \param[out] X
67*> \verbatim
68*> X is REAL array, dimension (N)
69*> The generated random numbers.
70*> \endverbatim
71*
72* Authors:
73* ========
74*
75*> \author Univ. of Tennessee
76*> \author Univ. of California Berkeley
77*> \author Univ. of Colorado Denver
78*> \author NAG Ltd.
79*
80*> \ingroup larnv
81*
82*> \par Further Details:
83* =====================
84*>
85*> \verbatim
86*>
87*> This routine calls the auxiliary routine SLARUV to generate random
88*> real numbers from a uniform (0,1) distribution, in batches of up to
89*> 128 using vectorisable code. The Box-Muller method is used to
90*> transform numbers from a uniform to a normal distribution.
91*> \endverbatim
92*>
93* =====================================================================
94 SUBROUTINE slarnv( IDIST, ISEED, N, X )
95*
96* -- LAPACK auxiliary routine --
97* -- LAPACK is a software package provided by Univ. of Tennessee, --
98* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
99*
100* .. Scalar Arguments ..
101 INTEGER IDIST, N
102* ..
103* .. Array Arguments ..
104 INTEGER ISEED( 4 )
105 REAL X( * )
106* ..
107*
108* =====================================================================
109*
110* .. Parameters ..
111 REAL ONE, TWO
112 parameter( one = 1.0e+0, two = 2.0e+0 )
113 INTEGER LV
114 parameter( lv = 128 )
115 REAL TWOPI
116 parameter( twopi = 6.28318530717958647692528676655900576839e+0 )
117* ..
118* .. Local Scalars ..
119 INTEGER I, IL, IL2, IV
120* ..
121* .. Local Arrays ..
122 REAL U( LV )
123* ..
124* .. Intrinsic Functions ..
125 INTRINSIC cos, log, min, sqrt
126* ..
127* .. External Subroutines ..
128 EXTERNAL slaruv
129* ..
130* .. Executable Statements ..
131*
132 DO 40 iv = 1, n, lv / 2
133 il = min( lv / 2, n-iv+1 )
134 IF( idist.EQ.3 ) THEN
135 il2 = 2*il
136 ELSE
137 il2 = il
138 END IF
139*
140* Call SLARUV to generate IL2 numbers from a uniform (0,1)
141* distribution (IL2 <= LV)
142*
143 CALL slaruv( iseed, il2, u )
144*
145 IF( idist.EQ.1 ) THEN
146*
147* Copy generated numbers
148*
149 DO 10 i = 1, il
150 x( iv+i-1 ) = u( i )
151 10 CONTINUE
152 ELSE IF( idist.EQ.2 ) THEN
153*
154* Convert generated numbers to uniform (-1,1) distribution
155*
156 DO 20 i = 1, il
157 x( iv+i-1 ) = two*u( i ) - one
158 20 CONTINUE
159 ELSE IF( idist.EQ.3 ) THEN
160*
161* Convert generated numbers to normal (0,1) distribution
162*
163 DO 30 i = 1, il
164 x( iv+i-1 ) = sqrt( -two*log( u( 2*i-1 ) ) )*
165 $ cos( twopi*u( 2*i ) )
166 30 CONTINUE
167 END IF
168 40 CONTINUE
169 RETURN
170*
171* End of SLARNV
172*
173 END
subroutine slarnv(idist, iseed, n, x)
SLARNV returns a vector of random numbers from a uniform or normal distribution.
Definition slarnv.f:95
subroutine slaruv(iseed, n, x)
SLARUV returns a vector of n random real numbers from a uniform distribution.
Definition slaruv.f:93