001:       SUBROUTINE DLARNV( IDIST, ISEED, N, X )
002: *
003: *  -- LAPACK auxiliary routine (version 3.2) --
004: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
005: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
006: *     November 2006
007: *
008: *     .. Scalar Arguments ..
009:       INTEGER            IDIST, N
010: *     ..
011: *     .. Array Arguments ..
012:       INTEGER            ISEED( 4 )
013:       DOUBLE PRECISION   X( * )
014: *     ..
015: *
016: *  Purpose
017: *  =======
018: *
019: *  DLARNV returns a vector of n random real numbers from a uniform or
020: *  normal distribution.
021: *
022: *  Arguments
023: *  =========
024: *
025: *  IDIST   (input) INTEGER
026: *          Specifies the distribution of the random numbers:
027: *          = 1:  uniform (0,1)
028: *          = 2:  uniform (-1,1)
029: *          = 3:  normal (0,1)
030: *
031: *  ISEED   (input/output) INTEGER array, dimension (4)
032: *          On entry, the seed of the random number generator; the array
033: *          elements must be between 0 and 4095, and ISEED(4) must be
034: *          odd.
035: *          On exit, the seed is updated.
036: *
037: *  N       (input) INTEGER
038: *          The number of random numbers to be generated.
039: *
040: *  X       (output) DOUBLE PRECISION array, dimension (N)
041: *          The generated random numbers.
042: *
043: *  Further Details
044: *  ===============
045: *
046: *  This routine calls the auxiliary routine DLARUV to generate random
047: *  real numbers from a uniform (0,1) distribution, in batches of up to
048: *  128 using vectorisable code. The Box-Muller method is used to
049: *  transform numbers from a uniform to a normal distribution.
050: *
051: *  =====================================================================
052: *
053: *     .. Parameters ..
054:       DOUBLE PRECISION   ONE, TWO
055:       PARAMETER          ( ONE = 1.0D+0, TWO = 2.0D+0 )
056:       INTEGER            LV
057:       PARAMETER          ( LV = 128 )
058:       DOUBLE PRECISION   TWOPI
059:       PARAMETER          ( TWOPI = 6.2831853071795864769252867663D+0 )
060: *     ..
061: *     .. Local Scalars ..
062:       INTEGER            I, IL, IL2, IV
063: *     ..
064: *     .. Local Arrays ..
065:       DOUBLE PRECISION   U( LV )
066: *     ..
067: *     .. Intrinsic Functions ..
068:       INTRINSIC          COS, LOG, MIN, SQRT
069: *     ..
070: *     .. External Subroutines ..
071:       EXTERNAL           DLARUV
072: *     ..
073: *     .. Executable Statements ..
074: *
075:       DO 40 IV = 1, N, LV / 2
076:          IL = MIN( LV / 2, N-IV+1 )
077:          IF( IDIST.EQ.3 ) THEN
078:             IL2 = 2*IL
079:          ELSE
080:             IL2 = IL
081:          END IF
082: *
083: *        Call DLARUV to generate IL2 numbers from a uniform (0,1)
084: *        distribution (IL2 <= LV)
085: *
086:          CALL DLARUV( ISEED, IL2, U )
087: *
088:          IF( IDIST.EQ.1 ) THEN
089: *
090: *           Copy generated numbers
091: *
092:             DO 10 I = 1, IL
093:                X( IV+I-1 ) = U( I )
094:    10       CONTINUE
095:          ELSE IF( IDIST.EQ.2 ) THEN
096: *
097: *           Convert generated numbers to uniform (-1,1) distribution
098: *
099:             DO 20 I = 1, IL
100:                X( IV+I-1 ) = TWO*U( I ) - ONE
101:    20       CONTINUE
102:          ELSE IF( IDIST.EQ.3 ) THEN
103: *
104: *           Convert generated numbers to normal (0,1) distribution
105: *
106:             DO 30 I = 1, IL
107:                X( IV+I-1 ) = SQRT( -TWO*LOG( U( 2*I-1 ) ) )*
108:      $                       COS( TWOPI*U( 2*I ) )
109:    30       CONTINUE
110:          END IF
111:    40 CONTINUE
112:       RETURN
113: *
114: *     End of DLARNV
115: *
116:       END
117: