ScaLAPACK 2.1  2.1
ScaLAPACK: Scalable Linear Algebra PACKage
clarnv.f
Go to the documentation of this file.
1  SUBROUTINE clarnv( IDIST, ISEED, N, X )
2 *
3 * -- LAPACK auxiliary routine (version 3.0) --
4 * Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
5 * Courant Institute, Argonne National Lab, and Rice University
6 * September 30, 1994
7 *
8 * .. Scalar Arguments ..
9  INTEGER IDIST, N
10 * ..
11 * .. Array Arguments ..
12  INTEGER ISEED( 4 )
13  COMPLEX X( * )
14 * ..
15 *
16 * Purpose
17 * =======
18 *
19 * CLARNV returns a vector of n random complex numbers from a uniform or
20 * normal distribution.
21 *
22 * Arguments
23 * =========
24 *
25 * IDIST (input) INTEGER
26 * Specifies the distribution of the random numbers:
27 * = 1: real and imaginary parts each uniform (0,1)
28 * = 2: real and imaginary parts each uniform (-1,1)
29 * = 3: real and imaginary parts each normal (0,1)
30 * = 4: uniformly distributed on the disc abs(z) < 1
31 * = 5: uniformly distributed on the circle abs(z) = 1
32 *
33 * ISEED (input/output) INTEGER array, dimension (4)
34 * On entry, the seed of the random number generator; the array
35 * elements must be between 0 and 4095, and ISEED(4) must be
36 * odd.
37 * On exit, the seed is updated.
38 *
39 * N (input) INTEGER
40 * The number of random numbers to be generated.
41 *
42 * X (output) COMPLEX array, dimension (N)
43 * The generated random numbers.
44 *
45 * Further Details
46 * ===============
47 *
48 * This routine calls the auxiliary routine SLARUV to generate random
49 * real numbers from a uniform (0,1) distribution, in batches of up to
50 * 128 using vectorisable code. The Box-Muller method is used to
51 * transform numbers from a uniform to a normal distribution.
52 *
53 * =====================================================================
54 *
55 * .. Parameters ..
56  REAL ZERO, ONE, TWO
57  parameter( zero = 0.0e+0, one = 1.0e+0, two = 2.0e+0 )
58  INTEGER LV
59  parameter( lv = 128 )
60  REAL TWOPI
61  parameter( twopi = 6.2831853071795864769252867663e+0 )
62 * ..
63 * .. Local Scalars ..
64  INTEGER I, IL, IV
65 * ..
66 * .. Local Arrays ..
67  REAL U( LV )
68 * ..
69 * .. Intrinsic Functions ..
70  INTRINSIC cmplx, exp, log, min, sqrt
71 * ..
72 * .. External Subroutines ..
73  EXTERNAL slaruv
74 * ..
75 * .. Executable Statements ..
76 *
77  DO 60 iv = 1, n, lv / 2
78  il = min( lv / 2, n-iv+1 )
79 *
80 * Call SLARUV to generate 2*IL real numbers from a uniform (0,1)
81 * distribution (2*IL <= LV)
82 *
83  CALL slaruv( iseed, 2*il, u )
84 *
85  IF( idist.EQ.1 ) THEN
86 *
87 * Copy generated numbers
88 *
89  DO 10 i = 1, il
90  x( iv+i-1 ) = cmplx( u( 2*i-1 ), u( 2*i ) )
91  10 CONTINUE
92  ELSE IF( idist.EQ.2 ) THEN
93 *
94 * Convert generated numbers to uniform (-1,1) distribution
95 *
96  DO 20 i = 1, il
97  x( iv+i-1 ) = cmplx( two*u( 2*i-1 )-one,
98  $ two*u( 2*i )-one )
99  20 CONTINUE
100  ELSE IF( idist.EQ.3 ) THEN
101 *
102 * Convert generated numbers to normal (0,1) distribution
103 *
104  DO 30 i = 1, il
105  x( iv+i-1 ) = sqrt( -two*log( u( 2*i-1 ) ) )*
106  $ exp( cmplx( zero, twopi*u( 2*i ) ) )
107  30 CONTINUE
108  ELSE IF( idist.EQ.4 ) THEN
109 *
110 * Convert generated numbers to complex numbers uniformly
111 * distributed on the unit disk
112 *
113  DO 40 i = 1, il
114  x( iv+i-1 ) = sqrt( u( 2*i-1 ) )*
115  $ exp( cmplx( zero, twopi*u( 2*i ) ) )
116  40 CONTINUE
117  ELSE IF( idist.EQ.5 ) THEN
118 *
119 * Convert generated numbers to complex numbers uniformly
120 * distributed on the unit circle
121 *
122  DO 50 i = 1, il
123  x( iv+i-1 ) = exp( cmplx( zero, twopi*u( 2*i ) ) )
124  50 CONTINUE
125  END IF
126  60 CONTINUE
127  RETURN
128 *
129 * End of CLARNV
130 *
131  END
cmplx
float cmplx[2]
Definition: pblas.h:132
clarnv
subroutine clarnv(IDIST, ISEED, N, X)
Definition: clarnv.f:2
min
#define min(A, B)
Definition: pcgemr.c:181