mwc-probability-2.0.1: Sampling function-based probability distributions.

Copyright(c) 2015-2017 Jared Tobin Marco Zocca
LicenseMIT
MaintainerJared Tobin <jared@jtobin.ca>, Marco Zocca <zocca.marco gmail>
Stabilityunstable
Portabilityghc
Safe HaskellNone
LanguageHaskell2010

System.Random.MWC.Probability

Contents

Description

A probability monad based on sampling functions.

Probability distributions are abstract constructs that can be represented in a variety of ways. The sampling function representation is particularly useful - it's computationally efficient, and collections of samples are amenable to much practical work.

Probability monads propagate uncertainty under the hood. An expression like beta 1 8 >>= binomial 10 corresponds to a beta-binomial distribution in which the uncertainty captured by beta 1 8 has been marginalized out.

The distribution resulting from a series of effects is called the predictive distribution of the model described by the corresponding expression. The monadic structure lets one piece together a hierarchical structure from simpler, local conditionals:

hierarchicalModel = do
  [c, d, e, f] <- replicateM 4 $ uniformR (1, 10)
  a <- gamma c d
  b <- gamma e f
  p <- beta a b
  n <- uniformR (5, 10)
  binomial n p

The functor instance for a probability monad transforms the support of the distribution while leaving its density structure invariant in some sense. For example, uniform is a distribution over the 0-1 interval, but fmap (+ 1) uniform is the translated distribution over the 1-2 interval.

>>> create >>= sample (fmap (+ 1) uniform)
1.5480073474340754

Running the examples

In the following we will assume an interactive GHCi session; the user should first declare a random number generator:

>>> gen <- create

which will be reused throughout all examples. Note: creating a random generator is an expensive operation, so it should be only performed once in the code (usually in the top-level IO action, e.g main).

Synopsis

Documentation

newtype Prob m a Source #

A probability distribution characterized by a sampling function.

>>> sample uniform gen
0.4208881170464097

Constructors

Prob 

Fields

Instances

MonadTrans Prob Source # 

Methods

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

Monad m => Monad (Prob m) Source # 

Methods

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

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

return :: a -> Prob m a #

fail :: String -> Prob m a #

Functor m => Functor (Prob m) Source # 

Methods

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

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

Monad m => Applicative (Prob m) Source # 

Methods

pure :: a -> Prob m a #

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

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

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

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

MonadIO m => MonadIO (Prob m) Source # 

Methods

liftIO :: IO a -> Prob m a #

PrimMonad m => PrimMonad (Prob m) Source # 

Associated Types

type PrimState (Prob m :: * -> *) :: * #

Methods

primitive :: (State# (PrimState (Prob m)) -> (#TupleRep [RuntimeRep], LiftedRep, State# (PrimState (Prob m)), a#)) -> Prob m a #

(Monad m, Num a) => Num (Prob m a) Source # 

Methods

(+) :: Prob m a -> Prob m a -> Prob m a #

(-) :: Prob m a -> Prob m a -> Prob m a #

(*) :: Prob m a -> Prob m a -> Prob m a #

negate :: Prob m a -> Prob m a #

abs :: Prob m a -> Prob m a #

signum :: Prob m a -> Prob m a #

fromInteger :: Integer -> Prob m a #

type PrimState (Prob m) Source # 
type PrimState (Prob m) = PrimState m

samples :: PrimMonad m => Int -> Prob m a -> Gen (PrimState m) -> m [a] Source #

Sample from a model n times.

>>> samples 2 uniform gen
[0.6738707766845254,0.9730405951541817]

Distributions

Continuous-valued

uniform :: (PrimMonad m, Variate a) => Prob m a Source #

The uniform distribution over a type.

>>> sample uniform gen :: IO Double
0.29308497534914946
>>> sample uniform gen :: IO Bool
False

uniformR :: (PrimMonad m, Variate a) => (a, a) -> Prob m a Source #

The uniform distribution over the provided interval.

>>> sample (uniformR (0, 1)) gen
0.44984153252922365

normal :: PrimMonad m => Double -> Double -> Prob m Double Source #

The normal or Gaussian distribution with a specified mean and standard deviation.

standardNormal :: PrimMonad m => Prob m Double Source #

The standard normal or Gaussian distribution (with mean 0 and standard deviation 1).

isoNormal :: (Traversable f, PrimMonad m) => f Double -> Double -> Prob m (f Double) Source #

An isotropic or spherical Gaussian distribution with specified mean vector and scalar standard deviation parameter.

logNormal :: PrimMonad m => Double -> Double -> Prob m Double Source #

The log-normal distribution with specified mean and standard deviation.

exponential :: PrimMonad m => Double -> Prob m Double Source #

The exponential distribution with provided rate parameter.

laplace :: (Floating a, Variate a, PrimMonad m) => a -> a -> Prob m a Source #

The Laplace distribution with provided location and scale parameters.

gamma :: PrimMonad m => Double -> Double -> Prob m Double Source #

The gamma distribution with shape parameter a and scale parameter b.

This is the parameterization used more traditionally in frequentist statistics. It has the following corresponding probability density function:

f(x; a, b) = 1 (Gamma(a) * b ^ a) x ^ (a - 1) e ^ (- x b)

inverseGamma :: PrimMonad m => Double -> Double -> Prob m Double Source #

The inverse-gamma distribution.

normalGamma :: PrimMonad m => Double -> Double -> Double -> Double -> Prob m Double Source #

The Normal-Gamma distribution of parameters mu, lambda, a, b

weibull :: (Floating a, Variate a, PrimMonad m) => a -> a -> Prob m a Source #

The Weibull distribution with provided shape and scale parameters.

chiSquare :: PrimMonad m => Int -> Prob m Double Source #

The chi-square distribution.

beta :: PrimMonad m => Double -> Double -> Prob m Double Source #

The beta distribution.

student :: PrimMonad m => Double -> Double -> Double -> Prob m Double Source #

Student's t distribution.

pareto :: PrimMonad m => Double -> Double -> Prob m Double Source #

The Pareto distribution with specified index a and minimum xmin parameters.

Both a and xmin must be positive.

Dirichlet process

dirichlet :: (Traversable f, PrimMonad m) => f Double -> Prob m (f Double) Source #

The Dirichlet distribution.

symmetricDirichlet :: PrimMonad m => Int -> Double -> Prob m [Double] Source #

The symmetric Dirichlet distribution of dimension n.

Discrete-valued

discreteUniform :: (PrimMonad m, Foldable f) => f a -> Prob m a Source #

The discrete uniform distribution.

>>> sample (discreteUniform [0..10]) gen
6
>>> sample (discreteUniform "abcdefghijklmnopqrstuvwxyz") gen
'a'

zipf :: (PrimMonad m, Integral b) => Double -> Prob m b Source #

The Zipf-Mandelbrot distribution, generated with the rejection sampling algorithm X.6.1 shown in L.Devroye, Non-Uniform Random Variate Generation.

The parameter should be positive, but values close to 1 should be avoided as they are very computationally intensive. The following code illustrates this behaviour.

>>> samples 10 (zipf 1.1) gen
[11315371987423520,2746946,653,609,2,13,85,4,256184577853,50]
>>> samples 10 (zipf 1.5) gen
[19,3,3,1,1,2,1,191,2,1]

categorical :: (Foldable f, PrimMonad m) => f Double -> Prob m Int Source #

A categorical distribution defined by the supplied list of probabilities.

bernoulli :: PrimMonad m => Double -> Prob m Bool Source #

The Bernoulli distribution.

binomial :: PrimMonad m => Int -> Double -> Prob m Int Source #

The binomial distribution.

multinomial :: (Foldable f, PrimMonad m) => Int -> f Double -> Prob m [Int] Source #

The multinomial distribution.

poisson :: PrimMonad m => Double -> Prob m Int Source #

The Poisson distribution.