exciting-0.9.218
[exciting.git] / src / LAPACK / dlarnv.f
blobbc3273c0d5d65533758defa7628f975f090c115c
1 SUBROUTINE DLARNV( IDIST, ISEED, N, X )
3 * -- LAPACK auxiliary routine (version 3.1) --
4 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
5 * November 2006
7 * .. Scalar Arguments ..
8 INTEGER IDIST, N
9 * ..
10 * .. Array Arguments ..
11 INTEGER ISEED( 4 )
12 DOUBLE PRECISION X( * )
13 * ..
15 * Purpose
16 * =======
18 * DLARNV returns a vector of n random real numbers from a uniform or
19 * normal distribution.
21 * Arguments
22 * =========
24 * IDIST (input) INTEGER
25 * Specifies the distribution of the random numbers:
26 * = 1: uniform (0,1)
27 * = 2: uniform (-1,1)
28 * = 3: normal (0,1)
30 * ISEED (input/output) INTEGER array, dimension (4)
31 * On entry, the seed of the random number generator; the array
32 * elements must be between 0 and 4095, and ISEED(4) must be
33 * odd.
34 * On exit, the seed is updated.
36 * N (input) INTEGER
37 * The number of random numbers to be generated.
39 * X (output) DOUBLE PRECISION array, dimension (N)
40 * The generated random numbers.
42 * Further Details
43 * ===============
45 * This routine calls the auxiliary routine DLARUV to generate random
46 * real numbers from a uniform (0,1) distribution, in batches of up to
47 * 128 using vectorisable code. The Box-Muller method is used to
48 * transform numbers from a uniform to a normal distribution.
50 * =====================================================================
52 * .. Parameters ..
53 DOUBLE PRECISION ONE, TWO
54 PARAMETER ( ONE = 1.0D+0, TWO = 2.0D+0 )
55 INTEGER LV
56 PARAMETER ( LV = 128 )
57 DOUBLE PRECISION TWOPI
58 PARAMETER ( TWOPI = 6.2831853071795864769252867663D+0 )
59 * ..
60 * .. Local Scalars ..
61 INTEGER I, IL, IL2, IV
62 * ..
63 * .. Local Arrays ..
64 DOUBLE PRECISION U( LV )
65 * ..
66 * .. Intrinsic Functions ..
67 INTRINSIC COS, LOG, MIN, SQRT
68 * ..
69 * .. External Subroutines ..
70 EXTERNAL DLARUV
71 * ..
72 * .. Executable Statements ..
74 DO 40 IV = 1, N, LV / 2
75 IL = MIN( LV / 2, N-IV+1 )
76 IF( IDIST.EQ.3 ) THEN
77 IL2 = 2*IL
78 ELSE
79 IL2 = IL
80 END IF
82 * Call DLARUV to generate IL2 numbers from a uniform (0,1)
83 * distribution (IL2 <= LV)
85 CALL DLARUV( ISEED, IL2, U )
87 IF( IDIST.EQ.1 ) THEN
89 * Copy generated numbers
91 DO 10 I = 1, IL
92 X( IV+I-1 ) = U( I )
93 10 CONTINUE
94 ELSE IF( IDIST.EQ.2 ) THEN
96 * Convert generated numbers to uniform (-1,1) distribution
98 DO 20 I = 1, IL
99 X( IV+I-1 ) = TWO*U( I ) - ONE
100 20 CONTINUE
101 ELSE IF( IDIST.EQ.3 ) THEN
103 * Convert generated numbers to normal (0,1) distribution
105 DO 30 I = 1, IL
106 X( IV+I-1 ) = SQRT( -TWO*LOG( U( 2*I-1 ) ) )*
107 $ COS( TWOPI*U( 2*I ) )
108 30 CONTINUE
109 END IF
110 40 CONTINUE
111 RETURN
113 * End of DLARNV