1 *> \brief \b SLARNV 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 SLARNV + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slarnv.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slarnv.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slarnv.f">
21 * SUBROUTINE SLARNV( IDIST, ISEED, N, X )
23 * .. Scalar Arguments ..
26 * .. Array Arguments ..
37 *> SLARNV returns a vector of n random real numbers from a uniform or
38 *> normal distribution.
47 *> Specifies the distribution of the random numbers:
49 *> = 2: uniform (-1,1)
53 *> \param[in,out] ISEED
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
59 *> On exit, the seed is updated.
65 *> The number of random numbers to be generated.
70 *> X is REAL array, dimension (N)
71 *> The generated random numbers.
77 *> \author Univ. of Tennessee
78 *> \author Univ. of California Berkeley
79 *> \author Univ. of Colorado Denver
82 *> \date September 2012
84 *> \ingroup OTHERauxiliary
86 *> \par Further Details:
87 * =====================
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.
97 * =====================================================================
98 SUBROUTINE SLARNV( IDIST, ISEED, N, X )
100 * -- LAPACK auxiliary routine (version 3.4.2) --
101 * -- LAPACK is a software package provided by Univ. of Tennessee, --
102 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
105 * .. Scalar Arguments ..
108 * .. Array Arguments ..
113 * =====================================================================
117 PARAMETER ( ONE = 1.0E+0, TWO = 2.0E+0 )
119 PARAMETER ( LV = 128 )
121 PARAMETER ( TWOPI = 6.2831853071795864769252867663E+0 )
123 * .. Local Scalars ..
124 INTEGER I, IL, IL2, IV
129 * .. Intrinsic Functions ..
130 INTRINSIC COS, LOG, MIN, SQRT
132 * .. External Subroutines ..
135 * .. Executable Statements ..
137 DO 40 IV = 1, N, LV / 2
138 IL = MIN( LV / 2, N-IV+1 )
139 IF( IDIST.EQ.3 ) THEN
145 * Call SLARUV to generate IL2 numbers from a uniform (0,1)
146 * distribution (IL2 <= LV)
148 CALL SLARUV( ISEED, IL2, U )
150 IF( IDIST.EQ.1 ) THEN
152 * Copy generated numbers
157 ELSE IF( IDIST.EQ.2 ) THEN
159 * Convert generated numbers to uniform (-1,1) distribution
162 X( IV+I-1 ) = TWO*U( I ) - ONE
164 ELSE IF( IDIST.EQ.3 ) THEN
166 * Convert generated numbers to normal (0,1) distribution
169 X( IV+I-1 ) = SQRT( -TWO*LOG( U( 2*I-1 ) ) )*
170 $ COS( TWOPI*U( 2*I ) )