Lots of trailing whitespaces in the files of Syd. Cleaning this. No big deal.
[platform/upstream/lapack.git] / SRC / zlarnv.f
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 *> \htmlonly
9 *> Download ZLARNV + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlarnv.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlarnv.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlarnv.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE ZLARNV( IDIST, ISEED, N, X )
22 *
23 *       .. Scalar Arguments ..
24 *       INTEGER            IDIST, N
25 *       ..
26 *       .. Array Arguments ..
27 *       INTEGER            ISEED( 4 )
28 *       COMPLEX*16         X( * )
29 *       ..
30 *
31 *
32 *> \par Purpose:
33 *  =============
34 *>
35 *> \verbatim
36 *>
37 *> ZLARNV returns a vector of n random complex numbers from a uniform or
38 *> normal distribution.
39 *> \endverbatim
40 *
41 *  Arguments:
42 *  ==========
43 *
44 *> \param[in] IDIST
45 *> \verbatim
46 *>          IDIST is INTEGER
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
53 *> \endverbatim
54 *>
55 *> \param[in,out] ISEED
56 *> \verbatim
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
60 *>          odd.
61 *>          On exit, the seed is updated.
62 *> \endverbatim
63 *>
64 *> \param[in] N
65 *> \verbatim
66 *>          N is INTEGER
67 *>          The number of random numbers to be generated.
68 *> \endverbatim
69 *>
70 *> \param[out] X
71 *> \verbatim
72 *>          X is COMPLEX*16 array, dimension (N)
73 *>          The generated random numbers.
74 *> \endverbatim
75 *
76 *  Authors:
77 *  ========
78 *
79 *> \author Univ. of Tennessee
80 *> \author Univ. of California Berkeley
81 *> \author Univ. of Colorado Denver
82 *> \author NAG Ltd.
83 *
84 *> \date September 2012
85 *
86 *> \ingroup complex16OTHERauxiliary
87 *
88 *> \par Further Details:
89 *  =====================
90 *>
91 *> \verbatim
92 *>
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.
97 *> \endverbatim
98 *>
99 *  =====================================================================
100       SUBROUTINE ZLARNV( IDIST, ISEED, N, X )
101 *
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..--
105 *     September 2012
106 *
107 *     .. Scalar Arguments ..
108       INTEGER            IDIST, N
109 *     ..
110 *     .. Array Arguments ..
111       INTEGER            ISEED( 4 )
112       COMPLEX*16         X( * )
113 *     ..
114 *
115 *  =====================================================================
116 *
117 *     .. Parameters ..
118       DOUBLE PRECISION   ZERO, ONE, TWO
119       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0, TWO = 2.0D+0 )
120       INTEGER            LV
121       PARAMETER          ( LV = 128 )
122       DOUBLE PRECISION   TWOPI
123       PARAMETER          ( TWOPI = 6.2831853071795864769252867663D+0 )
124 *     ..
125 *     .. Local Scalars ..
126       INTEGER            I, IL, IV
127 *     ..
128 *     .. Local Arrays ..
129       DOUBLE PRECISION   U( LV )
130 *     ..
131 *     .. Intrinsic Functions ..
132       INTRINSIC          DCMPLX, EXP, LOG, MIN, SQRT
133 *     ..
134 *     .. External Subroutines ..
135       EXTERNAL           DLARUV
136 *     ..
137 *     .. Executable Statements ..
138 *
139       DO 60 IV = 1, N, LV / 2
140          IL = MIN( LV / 2, N-IV+1 )
141 *
142 *        Call DLARUV to generate 2*IL real numbers from a uniform (0,1)
143 *        distribution (2*IL <= LV)
144 *
145          CALL DLARUV( ISEED, 2*IL, U )
146 *
147          IF( IDIST.EQ.1 ) THEN
148 *
149 *           Copy generated numbers
150 *
151             DO 10 I = 1, IL
152                X( IV+I-1 ) = DCMPLX( U( 2*I-1 ), U( 2*I ) )
153    10       CONTINUE
154          ELSE IF( IDIST.EQ.2 ) THEN
155 *
156 *           Convert generated numbers to uniform (-1,1) distribution
157 *
158             DO 20 I = 1, IL
159                X( IV+I-1 ) = DCMPLX( TWO*U( 2*I-1 )-ONE,
160      $                       TWO*U( 2*I )-ONE )
161    20       CONTINUE
162          ELSE IF( IDIST.EQ.3 ) THEN
163 *
164 *           Convert generated numbers to normal (0,1) distribution
165 *
166             DO 30 I = 1, IL
167                X( IV+I-1 ) = SQRT( -TWO*LOG( U( 2*I-1 ) ) )*
168      $                       EXP( DCMPLX( ZERO, TWOPI*U( 2*I ) ) )
169    30       CONTINUE
170          ELSE IF( IDIST.EQ.4 ) THEN
171 *
172 *           Convert generated numbers to complex numbers uniformly
173 *           distributed on the unit disk
174 *
175             DO 40 I = 1, IL
176                X( IV+I-1 ) = SQRT( U( 2*I-1 ) )*
177      $                       EXP( DCMPLX( ZERO, TWOPI*U( 2*I ) ) )
178    40       CONTINUE
179          ELSE IF( IDIST.EQ.5 ) THEN
180 *
181 *           Convert generated numbers to complex numbers uniformly
182 *           distributed on the unit circle
183 *
184             DO 50 I = 1, IL
185                X( IV+I-1 ) = EXP( DCMPLX( ZERO, TWOPI*U( 2*I ) ) )
186    50       CONTINUE
187          END IF
188    60 CONTINUE
189       RETURN
190 *
191 *     End of ZLARNV
192 *
193       END