aivika-transformers-5.9.1: Transformers for the Aivika simulation library
CopyrightCopyright (c) 2009-2017 David Sorokin <david.sorokin@gmail.com>
LicenseBSD3
MaintainerDavid Sorokin <david.sorokin@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Simulation.Aivika.Trans.Generator

Description

Tested with: GHC 8.0.1

Below is defined a random number generator.

Synopsis

Documentation

class (Functor m, Monad m) => MonadGenerator m where Source #

Defines a monad whithin which computation the random number generator can work.

Associated Types

data Generator m :: * Source #

Defines a random number generator.

Methods

generateUniform :: Generator m -> Double -> Double -> m Double Source #

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

generateUniformInt :: Generator m -> Int -> Int -> m Int Source #

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

generateTriangular :: Generator m -> Double -> Double -> Double -> m Double Source #

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

generateNormal :: Generator m -> Double -> Double -> m Double Source #

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

generateLogNormal :: Generator m -> Double -> Double -> m Double Source #

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

generateExponential :: Generator m -> Double -> m Double Source #

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

generateErlang :: Generator m -> Double -> Int -> m Double Source #

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

generatePoisson :: Generator m -> Double -> m Int Source #

Generate the Poisson random number with the specified mean.

generateBinomial :: Generator m -> Double -> Int -> m Int Source #

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

generateGamma :: Generator m -> Double -> Double -> m Double Source #

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 :: Generator m -> Double -> Double -> m Double Source #

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 :: Generator m -> Double -> Double -> m Double Source #

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

generateDiscrete :: forall a. Generator m -> DiscretePDF a -> m a Source #

Generate a random value from the specified discrete distribution.

generateSequenceNo :: Generator m -> m Int Source #

Generate a sequence number which can be considered quite unique.

newGenerator :: GeneratorType m -> m (Generator m) Source #

Create a new random number generator.

newRandomGenerator :: RandomGen g => g -> m (Generator m) Source #

Create a new random generator by the specified standard generator.

newRandomGenerator01 :: m Double -> m (Generator m) Source #

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

data GeneratorType m Source #

Defines a type of the random number generator.

Constructors

SimpleGenerator

The simple random number generator.

SimpleGeneratorWithSeed Word32

The simple random number generator with the specified seed.

CustomGenerator (m (Generator m))

The custom random number generator.

CustomGenerator01 (m Double)

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

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

A discrete probability density function.