ProbabilityMonads-0.1.0: Probability distribution monads.ContentsIndex
Control.Monad.Distribution.Base
Stabilityexperimental
Contents
Common interface
Bayes' rule
Random sampling functions
Discrete, finite distributions
Description

Common interface for probability distribution monads. Heavily inspired by Martin Erwig's and Steve Kollmansberger's Probabilistic Functional Programming, which can be found at http://web.engr.oregonstate.edu/~erwig/pfp/.

For background, see Michele Giry, A Categorical Approach to Probability Theory.

Synopsis
class (Functor d, Monad d) => Dist d where
weighted :: [(a, Rational)] -> d a
weighted :: Dist d => [(a, Rational)] -> d a
uniform :: Dist d => [a] -> d a
MonadPlus (mzero, mplus)
mzero
mplus
guard
module Control.Monad.Random
sample :: MonadRandom m => m a -> Int -> m [a]
sampleIO :: Rand StdGen a -> Int -> IO [a]
type BRand g = MaybeT (Rand g)
sampleBayes :: MonadRandom m => MaybeT m a -> Int -> m [a]
sampleBayesIO :: BRand StdGen a -> Int -> IO [a]
bayes :: Probability p => MaybeT (MVT p []) a -> Maybe (MVT p [] a)
Common interface

Common interfaces to probability monads. For example, if we assume that a family has two children, each a boy or a girl, we can build a probability distribution representing all such families.


import Control.Monad.Distribution

data Child = Girl | Boy
  deriving (Show, Eq, Ord)

child = uniform [Girl, Boy]

family = do
  child1 <- child
  child2 <- child
  return [child1, child2]

The use of NoMonomorphismRestriction is optional. It eliminates the need for type declarations on child and family:

child :: (Dist d) => d Child
child = uniform [Girl, Boy]

family :: (Dist d) => d [Child]
family = ...

Unfortunately, using NoMonomorphismRestriction may hide potential performance issues. In either of the above examples, Haskell compilers may recompute child from scratch each time it is called, because the actual type of the distribution d is unknown. Normally, Haskell requires an explicit type declaration in this case, in hope that you will notice the potential performance issue. By enabling NoMonomorphismRestriction, you indicate that you intended the code to work this way, and don't wish to use type declarations on every definition.

class (Functor d, Monad d) => Dist d where
Represents a probability distribution.
Methods
weighted :: [(a, Rational)] -> d a
Creates a new distribution from a weighted list of values. The individual weights must be non-negative, and they must sum to a positive number.
show/hide Instances
Dist d => Dist (MaybeT d)
RandomGen g => Dist (Rand g)
Probability p => Dist (MVT p [])
(Monad m, RandomGen g) => Dist (RandT g m)
weighted :: Dist d => [(a, Rational)] -> d a
Creates a new distribution from a weighted list of values. The individual weights must be non-negative, and they must sum to a positive number.
uniform :: Dist d => [a] -> d a
Creates a new distribution from a list of values, weighting it evenly.
Bayes' rule

Using guard, it's possible to calculate conditional probabilities using Bayes' rule. In the example below, we choose to Control.Monad.Distribution.Rational, which calculates probabilities using exact rational numbers. This is useful for small, interactive programs where you want answers like 13 and 23 instead of 0.3333333 and 0.6666666.


import Control.Monad
import Control.Monad.Distribution.Rational
import Data.List

data Coin = Heads | Tails
  deriving (Eq, Ord, Show)

toss = uniform [Heads, Tails]

tosses n = sequence (replicate n toss)

tossesWithAtLeastOneHead n = do
  result <- tosses n
  guard (Heads `elem` result)
  return result

In this example, we use guard to discard possible outcomes where no coin comes up heads.

MonadPlus (mzero, mplus)
mzero
mplus
guard
Random sampling functions

Support for probability distributions represented by sampling functions. This API is heavily inspired by Sungwoo Park and colleagues' $lambda_{bigcirc}$ caculus http://citeseer.ist.psu.edu/752237.html.

Two sampling-function monads are available: Rand and BRand. The former provides ordinary sampling functions, and the latter supports Bayesian reasoning.

It's possible run code in the Rand monad using either sample or sampleIO.

sampleIO family 3
-- [[Boy,Girl],[Boy,Girl],[Girl,Girl]]

If the probability distribution uses guard, you can run it using sampleBayesIO. Note that one of the outcomes below was discarded, leaving 3 outcomes instead of the expected 4:

sampleBayesIO (tossesWithAtLeastOneHead 2) 4
-- [[Tails,Heads],[Heads,Heads],[Tails,Heads]]
module Control.Monad.Random
sample :: MonadRandom m => m a -> Int -> m [a]
Take n samples from the distribution r.
sampleIO :: Rand StdGen a -> Int -> IO [a]
Take n samples from the distribution r using the IO monad.
type BRand g = MaybeT (Rand g)
A random distribution where some samples may be discarded.
sampleBayes :: MonadRandom m => MaybeT m a -> Int -> m [a]
Take n samples from the distribution r, and eliminate any samples which fail a guard condition.
sampleBayesIO :: BRand StdGen a -> Int -> IO [a]
Take n samples from the distribution r using the IO monad, and eliminate any samples which fail a guard condition.
Discrete, finite distributions

Using the DDist and BDDist monads, you can compute exact distributions. For example:

ddist family
-- [MV 0.25 [Girl,Girl],
--  MV 0.25 [Girl,Boy],
--  MV 0.25 [Boy,Girl],
--  MV 0.25 [Boy,Boy]]

If the probability distribution uses guard, you can run it using bddist.

bddist (tossesWithAtLeastOneHead 2)
-- Just [MV 1%3 [Heads,Heads],
--       MV 1%3 [Heads,Tails],
--       MV 1%3 [Tails,Heads]]

Note that we see rational numbers in this second example, because we used Control.Monad.Distribution.Rational above.

bayes :: Probability p => MaybeT (MVT p []) a -> Maybe (MVT p [] a)

Apply Bayes' rule, discarding impossible outcomes and normalizing the probabilities that remain.

TODO: It's entirely possible that this method should be moved to a type class.

Produced by Haddock version 0.8