aivika-4.3.3: A multi-paradigm simulation library

CopyrightCopyright (c) 2009-2015, David Sorokin <david.sorokin@gmail.com>
LicenseBSD3
MaintainerDavid Sorokin <david.sorokin@gmail.com>
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

Simulation.Aivika.Generator

Description

Tested with: GHC 7.10.1

Below is defined a type class of the random number generator.

Synopsis

Documentation

data Generator Source

Defines a random number generator.

Constructors

Generator 

Fields

generateUniform :: Double -> Double -> IO Double

Generate an uniform random number with the specified minimum and maximum.

generateUniformInt :: Int -> Int -> IO Int

Generate an uniform integer random number with the specified minimum and maximum.

generateTriangular :: Double -> Double -> Double -> IO Double

Generate a triangular random number by the specified minimum, median and maximum.

generateNormal :: Double -> Double -> IO Double

Generate the normal random number with the specified mean and deviation.

generateLogNormal :: Double -> Double -> IO Double

Generate a random number from the lognormal distribution derived from a normal distribution with the specified mean and deviation.

generateExponential :: Double -> IO Double

Generate the random number distributed exponentially with the specified mean (the reciprocal of the rate).

generateErlang :: Double -> Int -> IO Double

Generate the Erlang random number with the specified scale (the reciprocal of the rate) and integer shape.

generatePoisson :: Double -> IO Int

Generate the Poisson random number with the specified mean.

generateBinomial :: Double -> Int -> IO Int

Generate the binomial random number with the specified probability and number of trials.

generateGamma :: Double -> Double -> IO Double

Generate a random number from the Gamma distribution with the specified shape (kappa) and scale (theta, a reciprocal of the rate).

The probability density for the Gamma distribution is

f x = x ** (kappa - 1) * exp (- x / theta) / theta ** kappa * Gamma kappa
generateBeta :: Double -> Double -> IO Double

Generate a random number from the Beta distribution by the specified shape parameters (alpha and beta).

The probability density for the Beta distribution is

f x = x ** (alpha - 1) * (1 - x) ** (beta - 1) / B alpha beta
generateWeibull :: Double -> Double -> IO Double

Generate a random number from the Weibull distribution by the specified shape and scale.

generateDiscrete :: forall a. DiscretePDF a -> IO a

Generate a random value from the specified discrete distribution.

data GeneratorType Source

Defines a type of the random number generator.

Constructors

SimpleGenerator

The simple random number generator.

SimpleGeneratorWithSeed Int

The simple random number generator with the specified seed.

CustomGenerator (IO Generator)

The custom random number generator.

CustomGenerator01 (IO Double)

The custom random number generator by the specified uniform generator of numbers from 0 to 1.

type DiscretePDF a = [(a, Double)] Source

A discrete probability density function.

newGenerator :: GeneratorType -> IO Generator Source

Create a new random number generator by the specified type.

newRandomGenerator :: RandomGen g => g -> IO Generator Source

Create a new random generator by the specified standard generator.

newRandomGenerator01 :: IO Double -> IO Generator Source

Create a new random generator by the specified uniform generator of numbers from 0 to 1.