| Copyright | (c) 2015 Jared Tobin |
|---|---|
| License | MIT |
| Maintainer | Jared Tobin <jared@jtobin.ca> |
| Stability | unstable |
| Portability | ghc |
| Safe Haskell | None |
| Language | Haskell2010 |
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
corresponds to a
beta-binomial
distribution in which the uncertainty captured by beta 1 8 >>= binomial 10 has been
marginalized out.beta 1 8
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, is a distribution over the 0-1 interval, but uniformfmap
(+ 1) uniform is the translated distribution over the 1-2 interval.
>>>sample (fmap (+ 1) uniform) gen1.5480073474340754
- newtype Prob m a = Prob {}
- samples :: PrimMonad m => Int -> Prob m a -> Gen (PrimState m) -> m [a]
- uniform :: (PrimMonad m, Variate a) => Prob m a
- uniformR :: (PrimMonad m, Variate a) => (a, a) -> Prob m a
- discreteUniform :: (PrimMonad m, Foldable f) => f a -> Prob m a
- categorical :: (Foldable f, PrimMonad m) => f Double -> Prob m Int
- standard :: PrimMonad m => Prob m Double
- normal :: PrimMonad m => Double -> Double -> Prob m Double
- logNormal :: PrimMonad m => Double -> Double -> Prob m Double
- exponential :: PrimMonad m => Double -> Prob m Double
- gamma :: PrimMonad m => Double -> Double -> Prob m Double
- inverseGamma :: PrimMonad m => Double -> Double -> Prob m Double
- chiSquare :: PrimMonad m => Int -> Prob m Double
- beta :: PrimMonad m => Double -> Double -> Prob m Double
- dirichlet :: (Traversable f, PrimMonad m) => f Double -> Prob m (f Double)
- symmetricDirichlet :: PrimMonad m => Int -> Double -> Prob m [Double]
- bernoulli :: PrimMonad m => Double -> Prob m Bool
- binomial :: PrimMonad m => Int -> Double -> Prob m Int
- multinomial :: (Foldable f, PrimMonad m) => Int -> f Double -> Prob m [Int]
- student :: PrimMonad m => Double -> Double -> Double -> Prob m Double
- isoGauss :: (Traversable f, PrimMonad m) => f Double -> Double -> Prob m (f Double)
- poisson :: PrimMonad m => Double -> Prob m Int
Documentation
A probability distribution characterized by a sampling function.
>>>gen <- create>>>sample uniform gen0.4208881170464097
Instances
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 over a type.
>>>gen <- create>>>sample uniform gen :: IO Double0.29308497534914946>>>sample uniform gen :: IO BoolFalse
uniformR :: (PrimMonad m, Variate a) => (a, a) -> Prob m a Source #
The uniform distribution over the provided interval.
>>>sample (uniformR (0, 1)) gen0.44984153252922365
discreteUniform :: (PrimMonad m, Foldable f) => f a -> Prob m a Source #
The discrete uniform distribution.
>>>sample (discreteUniform [0..10]) gen6>>>sample (discreteUniform "abcdefghijklmnopqrstuvwxyz") gen'a'
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 or Gaussian distribution (with mean 0 and standard deviation 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 with provided rate parameter.
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.
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.
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.