normaldistribution-1.1.0.1: Minimum fuss normally distributed random values.

PortabilityHaskell 98
StabilityStable
Maintainerbjorn.buckwalter@gmail.com

Data.Random.Normal

Contents

Description

This purpose of this library is to have a simple API and no dependencies beyond Haskell 98 in order to let you produce normally distributed random values with a minimum of fuss. This library does not attempt to be blazingly fast nor to pass stringent tests of randomness. It attempts to be very easy to install and use while being "good enough" for many applications (simulations, games, etc.). The API builds upon and is largely analogous to that of the Haskell 98 Random module (more recently System.Random).

Pure:

 (sample,g) = normal  myRandomGen  -- using a Random.RandomGen
 samples    = normals myRandomGen  -- infinite list
 samples2   = mkNormals 10831452   -- infinite list using a seed

In the IO monad:

 sample    <- normalIO
 samples   <- normalsIO  -- infinite list

With custom mean and standard deviation:

 (sample,g) = normal'    (mean,sigma) myRandomGen
 samples    = normals'   (mean,sigma) myRandomGen
 samples2   = mkNormals' (mean,sigma) 10831452
 sample    <- normalIO'  (mean,sigma)
 samples   <- normalsIO' (mean,sigma)

Internally the library uses the Box-Muller method to generate normally distributed values from uniformly distributed random values. If more than one sample is needed taking samples off an infinite list (created by e.g. normals) will be roughly twice as efficient as repetedly generating individual samples with e.g. normal.

Synopsis

Pure interface

normal :: (RandomGen g, Random a, Floating a) => g -> (a, g)Source

Takes a random number generator g, and returns a random value normally distributed with mean 0 and standard deviation 1, together with a new generator. This function is ananalogous to random.

normals :: (RandomGen g, Random a, Floating a) => g -> [a]Source

Plural variant of normal, producing an infinite list of random values instead of returning a new generator. This function is ananalogous to randoms.

mkNormals :: (Random a, Floating a) => Int -> [a]Source

Creates a infinite list of normally distributed random values from the provided random generator seed. (In the implementation the seed is fed to mkStdGen to produce the random number generator.)

Custom mean and standard deviation

normal' :: (RandomGen g, Random a, Floating a) => (a, a) -> g -> (a, g)Source

Analogous to normal but uses the supplied (mean, standard deviation).

normals' :: (RandomGen g, Random a, Floating a) => (a, a) -> g -> [a]Source

Analogous to normals but uses the supplied (mean, standard deviation).

mkNormals' :: (Random a, Floating a) => (a, a) -> Int -> [a]Source

Analogous to mkNormals but uses the supplied (mean, standard deviation).

Using the global random number generator

normalIO :: (Random a, Floating a) => IO aSource

A variant of normal that uses the global random number generator. This function is analogous to randomIO.

normalsIO :: (Random a, Floating a) => IO [a]Source

Creates a infinite list of normally distributed random values using the global random number generator. (In the implementation newStdGen is used.)

Custom mean and standard deviation

normalIO' :: (Random a, Floating a) => (a, a) -> IO aSource

Analogous to normalIO but uses the supplied (mean, standard deviation).

normalsIO' :: (Random a, Floating a) => (a, a) -> IO [a]Source

Analogous to normalsIO but uses the supplied (mean, standard deviation).