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

Copyright(c) 2015 Jared Tobin
LicenseMIT
MaintainerJared Tobin <jared@jtobin.ca>
Stabilityunstable
Portabilityghc
Safe HaskellNone
LanguageHaskell2010

System.Random.MWC.Probability

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.

>>> sample (fmap (+ 1) uniform) gen
1.5480073474340754

Synopsis

Documentation

newtype Prob m a Source

A probability distribution characterized by a sampling function.

>>> gen <- create
>>> sample uniform gen
0.4208881170464097

Constructors

Prob 

Fields

sample :: Gen (PrimState m) -> m a
 

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]

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

The uniform distribution.

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

The uniform distribution over the provided interval.

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

The discrete uniform distribution.

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

A categorical distribution defined by the supplied list of probabilities.

standard :: PrimMonad m => Prob m Double Source

The standard normal distribution (a Gaussian with mean 0 and variance 1).

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

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

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.

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

The gamma distribution.

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

The inverse-gamma distribution.

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

The chi-square distribution.

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

The beta distribution.

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

The Dirichlet distribution.

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

The symmetric Dirichlet distribution (with equal concentration parameters).

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.

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

Student's t distribution.

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

An isotropic or spherical Gaussian distribution.

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

The Poisson distribution.