splitmix-distributions-1.0.0: Random samplers for some common distributions, based on splitmix.
Safe HaskellNone
LanguageHaskell2010

System.Random.SplitMix.Distributions

Description

Random samplers for few common distributions, with an interface similar to that of mwc-probability.

Usage

Compose your random sampler out of simpler ones thanks to the Applicative and Monad interface, e.g. this is how you would declare and sample a binary mixture of Gaussian random variables:

import Control.Monad (replicateM)
import System.Random.SplitMix.Distributions (Gen, sample, bernoulli, normal)

process :: Gen Double
process = do
  coin <- bernoulli 0.7
  if coin
    then
      normal 0 2
    else
      normal 3 1

dataset :: [Double]
dataset = sample 1234 $ replicateM 20 process

and sample your data in a pure (sample) or monadic (sampleT) setting.

Initializing the PRNG with a fixed seed makes all results fully reproducible across runs. If this behavior is not desired, one can sample the random seed itself from an IO-based entropy pool, and run the samplers with sampleIO and samplesIO.

Implementation details

The library is built on top of splitmix ( https://hackage.haskell.org/package/splitmix ), which provides fast pseudorandom number generation utilities.

Synopsis

Distributions

Continuous

stdUniform :: Monad m => GenT m Double Source #

Uniform in [0, 1)

uniformR Source #

Arguments

:: Monad m 
=> Double

low

-> Double

high

-> GenT m Double 

Uniform between two values

exponential Source #

Arguments

:: Monad m 
=> Double

rate parameter \( \lambda > 0 \)

-> GenT m Double 

Exponential distribution

stdNormal :: Monad m => GenT m Double Source #

Standard normal distribution

normal Source #

Arguments

:: Monad m 
=> Double

mean

-> Double

standard deviation \( \sigma \gt 0 \)

-> GenT m Double 

Normal distribution

beta Source #

Arguments

:: Monad m 
=> Double

shape parameter \( \alpha \gt 0 \)

-> Double

shape parameter \( \beta \gt 0 \)

-> GenT m Double 

Beta distribution, from two standard uniform samples

gamma Source #

Arguments

:: Monad m 
=> Double

shape parameter \( k \gt 0 \)

-> Double

scale parameter \( \theta \gt 0 \)

-> GenT m Double 

Gamma distribution, using Ahrens-Dieter accept-reject (algorithm GD):

Ahrens, J. H.; Dieter, U (January 1982). "Generating gamma variates by a modified rejection technique". Communications of the ACM. 25 (1): 47–54

pareto Source #

Arguments

:: Monad m 
=> Double

shape parameter \( \alpha \gt 0 \)

-> Double

scale parameter \( x_{min} \gt 0 \)

-> GenT m Double 

Pareto distribution

dirichlet Source #

Arguments

:: (Monad m, Traversable f) 
=> f Double

concentration parameters \( \gamma_i \gt 0 , \forall i \)

-> GenT m (f Double) 

The Dirichlet distribution with the provided concentration parameters. The dimension of the distribution is determined by the number of concentration parameters supplied.

>>> sample 1234 (dirichlet [0.1, 1, 10])
[2.3781130220132788e-11,6.646079701567026e-2,0.9335392029605486]

logNormal Source #

Arguments

:: Monad m 
=> Double 
-> Double

standard deviation \( \sigma \gt 0 \)

-> GenT m Double 

Log-normal distribution with specified mean and standard deviation.

laplace Source #

Arguments

:: Monad m 
=> Double

location parameter

-> Double

scale parameter \( s \gt 0 \)

-> GenT m Double 

Laplace or double-exponential distribution with provided location and scale parameters.

weibull Source #

Arguments

:: Monad m 
=> Double

shape \( a \gt 0 \)

-> Double

scale \( b \gt 0 \)

-> GenT m Double 

Weibull distribution with provided shape and scale parameters.

Discrete

bernoulli Source #

Arguments

:: Monad m 
=> Double

bias parameter \( 0 \lt p \lt 1 \)

-> GenT m Bool 

Bernoulli trial

fairCoin :: Monad m => GenT m Bool Source #

A fair coin toss returns either value with probability 0.5

multinomial Source #

Arguments

:: (Monad m, Foldable t) 
=> Int

number of Bernoulli trials \( n \gt 0 \)

-> t Double

probability vector \( p_i \gt 0 , \forall i \) (does not need to be normalized)

-> GenT m (Maybe [Int]) 

Multinomial distribution

NB : returns Nothing if any of the input probabilities is negative

categorical Source #

Arguments

:: (Monad m, Foldable t) 
=> t Double

probability vector \( p_i \gt 0 , \forall i \) (does not need to be normalized)

-> GenT m (Maybe Int) 

Categorical distribution

Picks one index out of a discrete set with probability proportional to those supplied as input parameter vector

discrete Source #

Arguments

:: (Monad m, Foldable t) 
=> t (Double, b)

(probability, item) vector \( p_i \gt 0 , \forall i \) (does not need to be normalized)

-> GenT m (Maybe b) 

Discrete distribution

Pick one item with probability proportional to those supplied as input parameter vector

zipf Source #

Arguments

:: (Monad m, Integral i) 
=> Double

\( \alpha \gt 1 \)

-> GenT m i 

The Zipf-Mandelbrot distribution.

Note that values of the parameter close to 1 are very computationally intensive.

>>> samples 10 1234 (zipf 1.1)
[3170051793,2,668775891,146169301649651,23,36,5,6586194257347,21,37911]
>>> samples 10 1234 (zipf 1.5)
[79,1,58,680,3,1,2,1,366,1]

crp Source #

Arguments

:: Monad m 
=> Double

concentration parameter \( \alpha \gt 1 \)

-> Int

number of customers \( n > 0 \)

-> GenT m [Integer] 

Chinese restaurant process

>>> sample 1234 $ crp 1.02 50
[24,18,7,1]
>>> sample 1234 $ crp 2 50
[17,8,13,3,3,3,2,1]
>>> sample 1234 $ crp 10 50
[5,7,1,6,1,3,5,1,1,3,1,1,1,4,3,1,3,1,1,1]

PRNG

Pure

type Gen = GenT Identity Source #

Pure random generation

sample Source #

Arguments

:: Word64

random seed

-> Gen a 
-> a 

Pure sampling

samples Source #

Arguments

:: Int

sample size

-> Word64

random seed

-> Gen a 
-> [a] 

Sample a batch

Monadic

data GenT m a Source #

Random generator

wraps splitmix state-passing inside a StateT monad

useful for embedding random generation inside a larger effect stack

Instances

Instances details
MonadTrans GenT Source # 
Instance details

Defined in System.Random.SplitMix.Distributions

Methods

lift :: Monad m => m a -> GenT m a #

MonadState s m => MonadState s (GenT m) Source # 
Instance details

Defined in System.Random.SplitMix.Distributions

Methods

get :: GenT m s #

put :: s -> GenT m () #

state :: (s -> (a, s)) -> GenT m a #

MonadReader r m => MonadReader r (GenT m) Source # 
Instance details

Defined in System.Random.SplitMix.Distributions

Methods

ask :: GenT m r #

local :: (r -> r) -> GenT m a -> GenT m a #

reader :: (r -> a) -> GenT m a #

Monad m => Monad (GenT m) Source # 
Instance details

Defined in System.Random.SplitMix.Distributions

Methods

(>>=) :: GenT m a -> (a -> GenT m b) -> GenT m b #

(>>) :: GenT m a -> GenT m b -> GenT m b #

return :: a -> GenT m a #

Functor m => Functor (GenT m) Source # 
Instance details

Defined in System.Random.SplitMix.Distributions

Methods

fmap :: (a -> b) -> GenT m a -> GenT m b #

(<$) :: a -> GenT m b -> GenT m a #

Monad m => Applicative (GenT m) Source # 
Instance details

Defined in System.Random.SplitMix.Distributions

Methods

pure :: a -> GenT m a #

(<*>) :: GenT m (a -> b) -> GenT m a -> GenT m b #

liftA2 :: (a -> b -> c) -> GenT m a -> GenT m b -> GenT m c #

(*>) :: GenT m a -> GenT m b -> GenT m b #

(<*) :: GenT m a -> GenT m b -> GenT m a #

MonadIO m => MonadIO (GenT m) Source # 
Instance details

Defined in System.Random.SplitMix.Distributions

Methods

liftIO :: IO a -> GenT m a #

MonadThrow m => MonadThrow (GenT m) Source # 
Instance details

Defined in System.Random.SplitMix.Distributions

Methods

throwM :: Exception e => e -> GenT m a #

sampleT Source #

Arguments

:: Monad m 
=> Word64

random seed

-> GenT m a 
-> m a 

Sample in a monadic context

samplesT Source #

Arguments

:: Monad m 
=> Int

size of sample

-> Word64

random seed

-> GenT m a 
-> m [a] 

Sample a batch

IO-based

sampleIO :: MonadIO m => GenT m b -> m b Source #

Initialize a splitmix random generator from system entropy (current time etc.) and sample from the PRNG.

samplesIO :: MonadIO m => Int -> GenT m a -> m [a] Source #

Initialize a splitmix random generator from system entropy (current time etc.) and sample n times from the PRNG.

splitmix utilities

withGen Source #

Arguments

:: Monad m 
=> (SMGen -> (a, SMGen))

explicit generator passing (e.g. nextDouble)

-> GenT m a 

Wrap a splitmix PRNG function