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