prob-0.1.1: Discrete probability monad
Safe HaskellSafe-Inferred
LanguageHaskell2010

Probability.Distribution

Description

This module defines the Distribution monad and its operations.

A Distribution a is a discrete probability distribution over values of type a.

You can define distributions in several ways:

Once you have a distribution, you can sample from it using sample, list its outcomes and their probabilities using probabilities or possibilities, and compute various statistics using probability, approxProbability, expectation, variance, stddev, entropy, relativeEntropy, or mutualInformation.

It's important to make a distinction between *finite* and *infinite* distributions. An infinite distribution is one whose list of possibilities is infinite. Note that this *includes* distributions for which there are only finitely many distinct outcomes, but still an infinite number of paths to reach these outcomes. Infinite distributions typically arise from recursive expressions. Certain functions only work on finite distributions, and will hang or OOM if given an infinite distribution.

For example, if you express the process of rolling a six-sided die, but always rerolling if the result is one, then there are five distinct outcomes: 2, 3, 4, 5, or 6. Nevertheless, this is an infinite distribution, because it's possible to roll any number of ones prior to the final result.

Synopsis

Types

data Distribution prob a Source #

A probability distribution of values.

Instances

Instances details
Bifunctor Distribution Source # 
Instance details

Defined in Probability.Distribution

Methods

bimap :: (a -> b) -> (c -> d) -> Distribution a c -> Distribution b d #

first :: (a -> b) -> Distribution a c -> Distribution b c #

second :: (b -> c) -> Distribution a b -> Distribution a c #

Applicative (Distribution prob) Source # 
Instance details

Defined in Probability.Distribution

Methods

pure :: a -> Distribution prob a #

(<*>) :: Distribution prob (a -> b) -> Distribution prob a -> Distribution prob b #

liftA2 :: (a -> b -> c) -> Distribution prob a -> Distribution prob b -> Distribution prob c #

(*>) :: Distribution prob a -> Distribution prob b -> Distribution prob b #

(<*) :: Distribution prob a -> Distribution prob b -> Distribution prob a #

Functor (Distribution prob) Source # 
Instance details

Defined in Probability.Distribution

Methods

fmap :: (a -> b) -> Distribution prob a -> Distribution prob b #

(<$) :: a -> Distribution prob b -> Distribution prob a #

Monad (Distribution prob) Source # 
Instance details

Defined in Probability.Distribution

Methods

(>>=) :: Distribution prob a -> (a -> Distribution prob b) -> Distribution prob b #

(>>) :: Distribution prob a -> Distribution prob b -> Distribution prob b #

return :: a -> Distribution prob a #

Num a => Num (Distribution prob a) Source # 
Instance details

Defined in Probability.Distribution

Methods

(+) :: Distribution prob a -> Distribution prob a -> Distribution prob a #

(-) :: Distribution prob a -> Distribution prob a -> Distribution prob a #

(*) :: Distribution prob a -> Distribution prob a -> Distribution prob a #

negate :: Distribution prob a -> Distribution prob a #

abs :: Distribution prob a -> Distribution prob a #

signum :: Distribution prob a -> Distribution prob a #

fromInteger :: Integer -> Distribution prob a #

Fractional a => Fractional (Distribution prob a) Source # 
Instance details

Defined in Probability.Distribution

Methods

(/) :: Distribution prob a -> Distribution prob a -> Distribution prob a #

recip :: Distribution prob a -> Distribution prob a #

fromRational :: Rational -> Distribution prob a #

type Event s = s -> Bool Source #

An event is a predicate on values from a sample space.

type RandVar s a = s -> a Source #

A random variable is a function mapping each element of a sample space to the corresponding value of the random variable.

data EventView prob s Source #

A view of a probability distribution from the point of view of a given event. The event either always happens, never happens, or happens sometimes with some probability. In the latter case, there are posterior distributions for when the event does or does not happen.

Constructors

Always (Distribution prob s) 
Never (Distribution prob s) 
Sometimes prob (Distribution prob s) (Distribution prob s) 

Basic operations

possibilities :: Num prob => Distribution prob a -> [(prob, a)] Source #

Gives the list of all possible values of a given probability distribution. The list will often contain multiple entries for the same outcome, in which case the true probability for that outcome is the sum of probabilities of all entries.

In the finite case, multiple entries can be combined by using simplify on the Distribution first.

probabilities :: (Num prob, Ord a) => Distribution prob a -> Map a prob Source #

Gives a map from outcomes to their probabilities in the given distribution.

This only works for finite distributions. Infinite distributions (including even distributions with finitely many outcomes, but infinitely many paths to reach those outcomes) will hang.

simplify :: (Fractional prob, Ord a) => Distribution prob a -> Distribution prob a Source #

Simplifies a finite distribution.

This only works for finite distributions. Infinite distributions (including even distributions with finitely many outcomes, but infinitely many paths to reach those outcomes) will hang.

sample :: Real prob => Distribution prob a -> IO a Source #

Samples the probability distribution to produce a value.

viewEvent :: Fractional prob => Event s -> Distribution prob s -> EventView prob s Source #

Gives a view on a probability distribution relative to some event.

The following are guaranteed. 1. fromEventView . viewEvent ev = id 2. If viewEvent ev dist = Always dist', then dist = dist' and probability ev dist = 1. 3. If viewEvent ev dist = Never dist', then dist = dist' and probability ev dist = 0. 4. If viewEvent ev dist = Sometimes p a b, then probability ev dist = p and: * dist = bernoulli p >>= bool a b * probability ev a = 1 * probability ev b = 0

This only works for finite distributions. Infinite distributions (including even distributions with finitely many outcomes, but infinitely many paths to reach those outcomes) will hang.

fromEventView :: EventView prob s -> Distribution prob s Source #

Converts from EventView back to a Distribution. The resulting distribution is equivalent to the source distribution.

finitize :: (Fractional prob, Ord prob) => prob -> Distribution prob a -> Distribution prob a Source #

Truncates an infinite distribution to make it finite. The epsilon parameter is the amount of tail probability that you're willing to ignore and assign to an arbitrary outcome.

finitizeMaybe :: (Fractional prob, Ord prob) => prob -> Distribution prob a -> Distribution prob (Maybe a) Source #

Truncates an infinite distribution to make it finite. This is equivalent to the original distribution, except with some arbitrary set of outcomes with probability less than epsilon replaced by Nothing.

conditional :: Event s -> Distribution prob s -> Distribution prob s Source #

Produces the conditional probability distribution, assuming some event. This function works for all distributions, but always produces an infinite distribution for non-trivial events.

finiteConditional :: Fractional prob => Event s -> Distribution prob s -> Distribution prob s Source #

Produces the conditional probability distribution, assuming some event.

This only works for finite distributions. Infinite distributions (including even distributions with finitely many outcomes, but infinitely many paths to reach those outcomes) will hang.

bayesian :: (param -> Distribution prob s) -> Event s -> Distribution prob param -> Distribution prob param Source #

Updates a prior distribution of parameters for a model, based on an observed event. This implements Bayes' Law for distributions.

This function works for all distributions, but always produces an infinite distribution for non-trivial events.

finiteBayesian :: Fractional prob => (param -> Distribution prob s) -> Event s -> Distribution prob param -> Distribution prob param Source #

Updates a prior distribution of parameters for a model, based on an observed event. This implements Bayes' Law for distributions.

This only works for finite distributions. Infinite distributions (including even distributions with finitely many outcomes, but infinitely many paths to reach those outcomes) will hang.

Common distributions

categorical :: Fractional prob => [(prob, a)] -> Distribution prob a Source #

A distribution with a fixed probability for each outcome. The probabilities should add to 1, but this is not checked.

uniform :: Fractional prob => [a] -> Distribution prob a Source #

A uniform distribution over a list of values.

geometric :: prob -> [a] -> Distribution prob a Source #

Geometric distribution over a list of possibilities.

bernoulli :: prob -> Distribution prob Bool Source #

A Bernoulli distribution. This gives True with probability p, and False otherwise.

binomial :: (Fractional prob, Integral n) => prob -> n -> Distribution prob n Source #

A binomial distribution. This gives the distribution of number of successes in n trials with probability p of success.

negativeBinomial :: (Fractional prob, Integral n) => prob -> n -> Distribution prob n Source #

Negative binomial distribution. This gives the distribution of number of failures before r successes with probability p of success.

hypergeometric :: (Fractional prob, Integral n) => n -> n -> n -> Distribution prob n Source #

Hypergeometric distribution. This gives the distribution of number of successful draws out of n attempts without replacement, when k possibilities are successful.

poisson :: (Floating prob, Integral n) => prob -> Distribution prob n Source #

Poisson distribution. Gives the number of independent events occurring in a fixed time interval, if events are occurring at the given expected rate per time interval.

Analysis

probability :: Num prob => Event s -> Distribution prob s -> prob Source #

Computes the probability of an event, represented by a predicate on values.

This only works for finite distributions. Infinite distributions (including even distributions with finitely many outcomes, but infinitely many paths to reach those outcomes) will hang.

probabilityBounds :: Num prob => Event s -> Distribution prob s -> [(prob, prob)] Source #

Like probability, but produces a lazy list of ever-improving bounds on the probability. This can be used on infinite distributions, for which the exact probability cannot be calculated.

approxProbability :: (Ord prob, Fractional prob) => prob -> Event s -> Distribution prob s -> prob Source #

Like probability, but produces a value that differs from the true probability by at most epsilon. This can be used on infinite distributions, for which the exact probability cannot be calculated.

expectation :: Num a => Distribution a a -> a Source #

Computes the expected value of a finite distribution.

This only works for finite distributions. Infinite distributions (including even distributions with finitely many outcomes, but infinitely many paths to reach those outcomes) will hang.

variance :: Num a => Distribution a a -> a Source #

Computes the variance of a finite distribution.

This only works for finite distributions. Infinite distributions (including even distributions with finitely many outcomes, but infinitely many paths to reach those outcomes) will hang.

stddev :: Floating a => Distribution a a -> a Source #

Computes the standard deviation of a finite distribution.

This only works for finite distributions. Infinite distributions (including even distributions with finitely many outcomes, but infinitely many paths to reach those outcomes) will hang.

entropy :: (Floating prob, Ord a) => Distribution prob a -> prob Source #

Computes the entropy of a distribution in bits.

This only works for finite distributions. Infinite distributions (including even distributions with finitely many outcomes, but infinitely many paths to reach those outcomes) will hang.

relativeEntropy :: (Eq prob, Floating prob, Ord a) => Distribution prob a -> Distribution prob a -> prob Source #

Computes the relative entropy, also known as Kullback-Leibler divergence, between two distributions in bits.

This only works for finite distributions. Infinite distributions (including even distributions with finitely many outcomes, but infinitely many paths to reach those outcomes) will hang.

mutualInformation :: (Eq prob, Floating prob, Ord a, Ord b) => RandVar s a -> RandVar s b -> Distribution prob s -> prob Source #

Computes the mutual information between two random variables, in bits. The given distribution is taken as a definition of a probability space, and the random variables are represented as functions from the sample space to values taken by the random variable.

This only works for finite distributions. Infinite distributions (including even distributions with finitely many outcomes, but infinitely many paths to reach those outcomes) will hang.