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