1 *> \brief \b ZLARNV returns a vector of random numbers from a uniform or normal distribution.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZLARNV + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlarnv.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlarnv.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlarnv.f">
21 * SUBROUTINE ZLARNV( IDIST, ISEED, N, X )
23 * .. Scalar Arguments ..
26 * .. Array Arguments ..
37 *> ZLARNV returns a vector of n random complex numbers from a uniform or
38 *> normal distribution.
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
55 *> \param[in,out] ISEED
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
61 *> On exit, the seed is updated.
67 *> The number of random numbers to be generated.
72 *> X is COMPLEX*16 array, dimension (N)
73 *> The generated random numbers.
79 *> \author Univ. of Tennessee
80 *> \author Univ. of California Berkeley
81 *> \author Univ. of Colorado Denver
84 *> \date September 2012
86 *> \ingroup complex16OTHERauxiliary
88 *> \par Further Details:
89 * =====================
93 *> This routine calls the auxiliary routine DLARUV to generate random
94 *> real numbers from a uniform (0,1) distribution, in batches of up to
95 *> 128 using vectorisable code. The Box-Muller method is used to
96 *> transform numbers from a uniform to a normal distribution.
99 * =====================================================================
100 SUBROUTINE ZLARNV( IDIST, ISEED, N, X )
102 * -- LAPACK auxiliary routine (version 3.4.2) --
103 * -- LAPACK is a software package provided by Univ. of Tennessee, --
104 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
107 * .. Scalar Arguments ..
110 * .. Array Arguments ..
115 * =====================================================================
118 DOUBLE PRECISION ZERO, ONE, TWO
119 PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0, TWO = 2.0D+0 )
121 PARAMETER ( LV = 128 )
122 DOUBLE PRECISION TWOPI
123 PARAMETER ( TWOPI = 6.2831853071795864769252867663D+0 )
125 * .. Local Scalars ..
129 DOUBLE PRECISION U( LV )
131 * .. Intrinsic Functions ..
132 INTRINSIC DCMPLX, EXP, LOG, MIN, SQRT
134 * .. External Subroutines ..
137 * .. Executable Statements ..
139 DO 60 IV = 1, N, LV / 2
140 IL = MIN( LV / 2, N-IV+1 )
142 * Call DLARUV to generate 2*IL real numbers from a uniform (0,1)
143 * distribution (2*IL <= LV)
145 CALL DLARUV( ISEED, 2*IL, U )
147 IF( IDIST.EQ.1 ) THEN
149 * Copy generated numbers
152 X( IV+I-1 ) = DCMPLX( U( 2*I-1 ), U( 2*I ) )
154 ELSE IF( IDIST.EQ.2 ) THEN
156 * Convert generated numbers to uniform (-1,1) distribution
159 X( IV+I-1 ) = DCMPLX( TWO*U( 2*I-1 )-ONE,
162 ELSE IF( IDIST.EQ.3 ) THEN
164 * Convert generated numbers to normal (0,1) distribution
167 X( IV+I-1 ) = SQRT( -TWO*LOG( U( 2*I-1 ) ) )*
168 $ EXP( DCMPLX( ZERO, TWOPI*U( 2*I ) ) )
170 ELSE IF( IDIST.EQ.4 ) THEN
172 * Convert generated numbers to complex numbers uniformly
173 * distributed on the unit disk
176 X( IV+I-1 ) = SQRT( U( 2*I-1 ) )*
177 $ EXP( DCMPLX( ZERO, TWOPI*U( 2*I ) ) )
179 ELSE IF( IDIST.EQ.5 ) THEN
181 * Convert generated numbers to complex numbers uniformly
182 * distributed on the unit circle
185 X( IV+I-1 ) = EXP( DCMPLX( ZERO, TWOPI*U( 2*I ) ) )