mersenne-random-1.0.0.1: Generate high quality pseudorandom numbers using a SIMD Fast Mersenne Twister

PortabilityCPP, FFI
Stabilityexperimental
MaintainerDon Stewart <dons@galois.com>

System.Random.Mersenne

Contents

Description

Tested with: GHC 6.8.2

Generate pseudo-random numbers using the SIMD-oriented Fast Mersenne Twister(SFMT) pseudorandom number generator. This is a much faster generator than the default System.Random generator for Haskell (~50x faster generation for Doubles, on a core 2 duo), however, it is not nearly as flexible.

This library may be compiled with the '-f use_sse2' or '-f use_altivec' flags to configure, on intel and powerpc machines respectively, to enable high performance vector instructions to be used. This typically results in a 2-3x speedup in generation time.

This will work for newer intel chips such as Pentium 4s, and Core, Core2* chips.

Synopsis

The random number generator

data MTGen Source

A single, global SIMD fast mersenne twister random number generator This generator is evidence that you have initialised the generator,

Initialising the generator

newMTGen :: Maybe Word32 -> IO MTGenSource

Return an initialised SIMD Fast Mersenne Twister. The generator is initialised based on the clock time, if Nothing is passed as a seed. For deterministic behaviour, pass an explicit seed.

Due to the current SFMT library being vastly impure, currently only a single generator is allowed per-program. Attempts to reinitialise it will fail.

Random values of various types

Instances MTRandom for Word, Word64, Word32, Word16, Word8 all return, quickly, a random inhabintant of that type, in its full range. Similarly for Int types.

Int and Word will be 32 bits on a 32 bit machine, and 64 on a 64 bit machine. The double precision will be 32 bits on a 32 bit machine, and 53 on a 64 bit machine.

The MTRandom instance for Double returns a Double in the interval [0,1). The Bool instance takes the lower bit off a random word.

class MTRandom a whereSource

Given an initialised SFMT generator, the MTRandom allows the programmer to extract values of a variety of types.

Minimal complete definition: random.

Methods

random :: MTGen -> IO aSource

The same as randomR, but using a default range determined by the type:

  • For bounded types (instances of Bounded, such as Char), the range is normally the whole type.
  • For fractional types, the range is normally the semi-closed interval [0,1).
  • For Integer, the range is (arbitrarily) the range of Int.

randoms :: MTGen -> IO [a]Source

Plural variant of random, producing an infinite list of random values instead of returning a new generator.

randomIO :: IO aSource

A variant of random that uses the global random number generator (see System.Random). Essentially a convenience function if you're already in IO.

Note that there are performance penalties calling randomIO in an inner loop, rather than random applied to a global generator. The cost comes in retrieving the random gen from an IORef, which is non-trivial. Expect a 3x slow down in speed of random generation.

There is a single, implicit, global random number generator of type StdGen, held in some global variable maintained by the IO monad. It is initialised automatically in some system-dependent fashion. To get deterministic behaviour, use setStdGen.

getStdRandom :: (MTGen -> IO a) -> IO aSource

Uses the supplied function to get a value from the current global random generator, and updates the global generator with the new generator returned by the function. For example, rollDice gets a random integer between 1 and 6:

  rollDice :: IO Int
  rollDice = getMTRandom (randomR (1,6))

getStdGen :: IO MTGenSource

Gets the global random number generator.

setStdGen :: MTGen -> IO ()Source

Sets the global random number generator.

Miscellaneous

version :: StringSource

Returns the identification string for the SMFT version. The string shows the word size, the Mersenne exponent, and all parameters of this generator.

An example, calculation of pi via a monte carlo method:

 import System.Random.Mersenne
 import System.Environment

We'll roll the dice lim times,

 main = do
    [lim] <- mapM readIO =<< getArgs

Now, define a loop that runs this many times, plotting a x and y position, then working out if its in and outside the circle. The ratio of inside/total points at then gives us an approximation of pi.

 let go :: Int -> Int -> IO Double
     go throws ins
         | throws >= lim  = return ((4 * fromIntegral ins) / (fromIntegral throws))
         | otherwise = do
             x <- random g :: IO Double
             y <- random g :: IO Double
             if x * x + y * y < 1
                 then go (throws+1) $! ins + 1
                 else go (throws+1) ins

Compiling this, '-fexcess-precision', for accurate Doubles,

 $ ghc -fexcess-precision -fvia-C pi.hs -o pi
 $ ./pi 10000000                                                 
 3.1417304