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

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

System.Random.MWC.Probability

Description

A probability monad based on sampling functions, implemented as a thin wrapper over the mwc-random library.

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 allows one to transforms the support of a distribution while leaving its density structure invariant. 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

The applicative instance guarantees that the generated samples are generated independently:

>>> create >>= sample ((,) <$> uniform <*> uniform)
Synopsis

Documentation

uniformVector :: (PrimMonad m, Variate a, Vector v a) => Gen (PrimState m) -> Int -> m (v a) #

Generate a vector of pseudo-random variates. This is not necessarily faster than invoking uniform repeatedly in a loop, but it may be more convenient to use in some situations.

createSystemRandom :: IO GenIO #

Seed a PRNG with data from the system's fast source of pseudo-random numbers. All the caveats of withSystemRandom apply here as well.

withSystemRandom :: PrimBase m => (Gen (PrimState m) -> m a) -> IO a #

Seed a PRNG with data from the system's fast source of pseudo-random numbers ("/dev/urandom" on Unix-like systems or RtlGenRandom on Windows), then run the given action.

This is a somewhat expensive function, and is intended to be called only occasionally (e.g. once per thread). You should use the Gen it creates to generate many random numbers.

restore :: PrimMonad m => Seed -> m (Gen (PrimState m)) #

Create a new Gen that mirrors the state of a saved Seed.

save :: PrimMonad m => Gen (PrimState m) -> m Seed #

Save the state of a Gen, for later use by restore.

toSeed :: Vector v Word32 => v Word32 -> Seed #

Convert vector to Seed. It acts similarily to initialize and will accept any vector. If you want to pass seed immediately to restore you better call initialize directly since following law holds:

restore (toSeed v) = initialize v

initialize :: (PrimMonad m, Vector v Word32) => v Word32 -> m (Gen (PrimState m)) #

Create a generator for variates using the given seed, of which up to 256 elements will be used. For arrays of less than 256 elements, part of the default seed will be used to finish initializing the generator's state.

Examples:

initialize (singleton 42)
initialize (fromList [4, 8, 15, 16, 23, 42])

If a seed contains fewer than 256 elements, it is first used verbatim, then its elements are xored against elements of the default seed until 256 elements are reached.

If a seed contains exactly 258 elements, then the last two elements are used to set the generator's initial state. This allows for complete generator reproducibility, so that e.g. gen' == gen in the following example:

gen' <- initialize . fromSeed =<< save

create :: PrimMonad m => m (Gen (PrimState m)) #

Create a generator for variates using a fixed seed.

asGenST :: (GenST s -> ST s a) -> GenST s -> ST s a #

Constrain the type of an action to run in the ST monad.

asGenIO :: (GenIO -> IO a) -> GenIO -> IO a #

Constrain the type of an action to run in the IO monad.

class Variate a #

The class of types for which we can generate uniformly distributed random variates.

The uniform PRNG uses Marsaglia's MWC256 (also known as MWC8222) multiply-with-carry generator, which has a period of 2^8222 and fares well in tests of randomness. It is also extremely fast, between 2 and 3 times faster than the Mersenne Twister.

Note: Marsaglia's PRNG is not known to be cryptographically secure, so you should not use it for cryptographic operations.

Minimal complete definition

uniform, uniformR

Instances
Variate Bool 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Bool #

uniformR :: PrimMonad m => (Bool, Bool) -> Gen (PrimState m) -> m Bool #

Variate Double 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Double #

uniformR :: PrimMonad m => (Double, Double) -> Gen (PrimState m) -> m Double #

Variate Float 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Float #

uniformR :: PrimMonad m => (Float, Float) -> Gen (PrimState m) -> m Float #

Variate Int 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Int #

uniformR :: PrimMonad m => (Int, Int) -> Gen (PrimState m) -> m Int #

Variate Int8 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Int8 #

uniformR :: PrimMonad m => (Int8, Int8) -> Gen (PrimState m) -> m Int8 #

Variate Int16 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Int16 #

uniformR :: PrimMonad m => (Int16, Int16) -> Gen (PrimState m) -> m Int16 #

Variate Int32 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Int32 #

uniformR :: PrimMonad m => (Int32, Int32) -> Gen (PrimState m) -> m Int32 #

Variate Int64 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Int64 #

uniformR :: PrimMonad m => (Int64, Int64) -> Gen (PrimState m) -> m Int64 #

Variate Word 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Word #

uniformR :: PrimMonad m => (Word, Word) -> Gen (PrimState m) -> m Word #

Variate Word8 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Word8 #

uniformR :: PrimMonad m => (Word8, Word8) -> Gen (PrimState m) -> m Word8 #

Variate Word16 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Word16 #

uniformR :: PrimMonad m => (Word16, Word16) -> Gen (PrimState m) -> m Word16 #

Variate Word32 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Word32 #

uniformR :: PrimMonad m => (Word32, Word32) -> Gen (PrimState m) -> m Word32 #

Variate Word64 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Word64 #

uniformR :: PrimMonad m => (Word64, Word64) -> Gen (PrimState m) -> m Word64 #

(Variate a, Variate b) => Variate (a, b) 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m (a, b) #

uniformR :: PrimMonad m => ((a, b), (a, b)) -> Gen (PrimState m) -> m (a, b) #

(Variate a, Variate b, Variate c) => Variate (a, b, c) 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m (a, b, c) #

uniformR :: PrimMonad m => ((a, b, c), (a, b, c)) -> Gen (PrimState m) -> m (a, b, c) #

(Variate a, Variate b, Variate c, Variate d) => Variate (a, b, c, d) 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m (a, b, c, d) #

uniformR :: PrimMonad m => ((a, b, c, d), (a, b, c, d)) -> Gen (PrimState m) -> m (a, b, c, d) #

data Gen s #

State of the pseudo-random number generator. It uses mutable state so same generator shouldn't be used from the different threads simultaneously.

type GenIO = Gen (PrimState IO) #

A shorter name for PRNG state in the IO monad.

type GenST s = Gen (PrimState (ST s)) #

A shorter name for PRNG state in the ST monad.

data Seed #

An immutable snapshot of the state of a Gen.

Instances
Eq Seed 
Instance details

Defined in System.Random.MWC

Methods

(==) :: Seed -> Seed -> Bool #

(/=) :: Seed -> Seed -> Bool #

Show Seed 
Instance details

Defined in System.Random.MWC

Methods

showsPrec :: Int -> Seed -> ShowS #

show :: Seed -> String #

showList :: [Seed] -> ShowS #

newtype Prob m a Source #

A probability distribution characterized by a sampling function.

>>> gen <- createSystemRandom
>>> sample uniform gen
0.4208881170464097

Constructors

Prob 

Fields

Instances
MonadTrans Prob Source # 
Instance details

Defined in System.Random.MWC.Probability

Methods

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

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

Defined in System.Random.MWC.Probability

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 # 
Instance details

Defined in System.Random.MWC.Probability

Methods

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

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

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

Defined in System.Random.MWC.Probability

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 # 
Instance details

Defined in System.Random.MWC.Probability

Methods

liftIO :: IO a -> Prob m a #

PrimMonad m => PrimMonad (Prob m) Source # 
Instance details

Defined in System.Random.MWC.Probability

Associated Types

type PrimState (Prob m) :: * #

Methods

primitive :: (State# (PrimState (Prob m)) -> (#State# (PrimState (Prob m)), a#)) -> Prob m a #

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

Defined in System.Random.MWC.Probability

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 # 
Instance details

Defined in System.Random.MWC.Probability

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]

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

The uniform distribution at a specified type.

Note that Double and Float variates are defined over the unit interval.

>>> 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 specified mean and standard deviation.

Note that sd should be positive.

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.

Note that sd should be positive.

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

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

Note that sd should be positive.

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

The exponential distribution with provided rate parameter.

Note that r should be positive.

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

The inverse Gaussian (also known as Wald) distribution with mean parameter mu and shape parameter lambda.

Note that both mu and lambda should be positive.

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

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

Note that sigma should be positive.

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)

Note that both parameters should be positive.

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

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

Note that both parameters should be positive.

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

The Normal-Gamma distribution.

Note that the lambda, a, and b parameters should be positive.

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

The Weibull distribution with provided shape and scale parameters.

Note that both parameters should be positive.

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

The chi-square distribution with the specified degrees of freedom.

Note that k should be positive.

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

The beta distribution with the specified shape parameters.

Note that both parameters should be positive.

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

Generalized Student's t distribution with location parameter m, scale parameter s, and degrees of freedom k.

Note that the s and k parameters should be positive.

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

Student's t distribution with k degrees of freedom.

Note that k should be positive.

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

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

Note that both parameters should be positive.

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

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

>>> sample (dirichlet [0.1, 1, 10]) gen
[1.2375387187120799e-5,3.4952460651813816e-3,0.9964923785476316]

Note that all concentration parameters should be positive.

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

The symmetric Dirichlet distribution with dimension n. The provided concentration parameter is simply replicated n times.

Note that a should be positive.

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.

Note that a should be positive, and that values close to 1 should be avoided as they are very computationally intensive.

>>> 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 probabilities.

Note that the supplied container of probabilities must sum to 1.

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

The Bernoulli distribution with success probability p.

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

The binomial distribution with number of trials n and success probability p.

>>> sample (binomial 10 0.3) gen
4

negativeBinomial :: (PrimMonad m, Integral a) => a -> Double -> Prob m Int Source #

The negative binomial distribution with number of trials n and success probability p.

>>> sample (negativeBinomial 10 0.3) gen
21

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

The multinomial distribution of n trials and category probabilities ps.

Note that ps is a vector of probabilities and should sum to one.

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

The Poisson distribution with rate parameter l.

Note that l should be positive.