distribution-1.0.0.0: Finite discrete probability distributions.

Safe HaskellSafe-Inferred

Data.Distribution.Core

Contents

Description

This modules defines types and functions for manipulating finite discrete probability distributions.

Synopsis

Probability

type Probability = RationalSource

Probability. Should be between 0 and 1.

Distribution

data Distribution a Source

Distribution over values of type a.

Due to their internal representations, Distribution can not have Functor or Monad instances. However, select is the equivalent of fmap for distributions and always and andThen are respectively the equivalent of return and >>=.

Instances

Bounded a => Bounded (Distribution a)

Lifts the bounds to the distributions that return them with probability one.

Note that the degenerate distributions of size 0 will be less than the distribution minBound.

Appart from that, all other distributions d have the property that minBound <= d <= maxBound if this property holds on the values of the distribution.

Eq a => Eq (Distribution a) 
(Ord a, Floating a) => Floating (Distribution a) 
(Ord a, Fractional a) => Fractional (Distribution a) 
(Ord a, Num a) => Num (Distribution a)

Literals are interpreted as distributions that always return the given value.

>>> 42 == always 42
True

Binary operations on distributions are defined to be the binary operation on each pair of elements.

For this reason, (+) and (*) are not related in the same way as they are on natural numbers.

For instance, it is not always the case that: 3 * d == d + d + d

>>> let d = uniform [0, 1]
>>> 3 * d
fromList [(0,1 % 2),(3,1 % 2)]
>>> d + d + d
fromList [(0,1 % 8),(1,3 % 8),(2,3 % 8),(3,1 % 8)]

For this particular behavior, see the times function.

Ord a => Ord (Distribution a)

A distribution d1 is less than some other distribution d2 if the smallest value that has a different probability in d1 and d2 is more probable in d1.

By convention, empty distributions are less than everything except themselves.

Show a => Show (Distribution a) 
(Ord a, Monoid a) => Monoid (Distribution a) 

toMap :: Distribution a -> Map a ProbabilitySource

Converts the distribution to a mapping from values to their probability. Values with probability 0 are not included in the resulting mapping.

toList :: Distribution a -> [(a, Probability)]Source

Converts the distribution to a list of increasing values whose probability is greater than 0. To each value is associated its probability.

Properties

size :: Distribution a -> IntSource

 Returns the number of elements with non-zero probability in the distribution.

support :: Distribution a -> Set aSource

Values in the distribution with non-zero probability.

Creation

fromList :: (Ord a, Real p) => [(a, p)] -> Distribution aSource

Distribution that assigns to each value from the given (value, weight) pairs a probability proportional to weight.

>>> fromList [('A', 1), ('B', 2), ('C', 1)]
fromList [('A',1 % 4),('B',1 % 2),('C',1 % 4)]

Values may appear multiple times in the list. In this case, their total weight is the sum of the different associated weights. Values whose total weight is zero or negative are ignored.

always :: a -> Distribution aSource

Distribution that assigns to x the probability of 1.

>>> always 0
fromList [(0,1 % 1)]
>>> always 42
fromList [(42,1 % 1)]

uniform :: Ord a => [a] -> Distribution aSource

Uniform distribution over the values. The probability of each element is proportional to its number of appearance in the list.

>>> uniform [1 .. 6]
fromList [(1,1 % 6),(2,1 % 6),(3,1 % 6),(4,1 % 6),(5,1 % 6),(6,1 % 6)]

withProbability :: Real p => p -> Distribution BoolSource

True with given probability and False with complementary probability.

Transformation

select :: Ord b => (a -> b) -> Distribution a -> Distribution bSource

Applies a function to the values in the distribution.

>>> select abs $ uniform [-1, 0, 1]
fromList [(0,1 % 3),(1,2 % 3)]

assuming :: (a -> Bool) -> Distribution a -> Distribution aSource

Returns a new distribution conditioning on the predicate holding on the value.

>>> assuming (> 2) $ uniform [1 .. 6]
fromList [(3,1 % 4),(4,1 % 4),(5,1 % 4),(6,1 % 4)]

Note that the resulting distribution will be empty if the predicate does not hold on any of the values.

>>> assuming (> 7) $ uniform [1 .. 6]
fromList []

Combination

combine :: (Ord a, Real p) => [(Distribution a, p)] -> Distribution aSource

Combines multiple weighted distributions into a single distribution.

The probability of each element is the weighted sum of the element's probability in every distribution.

>>> combine [(always 2, 1 / 3), (uniform [1..6], 2 / 3)]
fromList [(1,1 % 9),(2,4 % 9),(3,1 % 9),(4,1 % 9),(5,1 % 9),(6,1 % 9)]

Note that the weights do not have to sum up to 1. Distributions with negative or null weight will be ignored.

Sequences

Independant experiments

trials :: Int -> Distribution Bool -> Distribution IntSource

Binomial distribution. Assigns to each number of successes its probability.

>>> trials 2 $ uniform [True, False]
fromList [(0,1 % 4),(1,1 % 2),(2,1 % 4)]

times :: (Num a, Ord a) => Int -> Distribution a -> Distribution aSource

Takes n samples from the distribution and returns the distribution of their sum.

>>> times 2 $ uniform [1 .. 3]
fromList [(2,1 % 9),(3,2 % 9),(4,1 % 3),(5,2 % 9),(6,1 % 9)]

This function makes use of the more efficient trials functions for input distributions of size 2.

>>> size $ times 10000 $ uniform [1, 10]
10001

Dependant experiments

andThen :: Ord b => Distribution a -> (a -> Distribution b) -> Distribution bSource

Computes for each value in the distribution a new distribution, and then combines those distributions, giving each the weight of the original value.

>>> uniform [1 .. 3] `andThen` (\ n -> uniform [1 .. n])
fromList [(1,11 % 18),(2,5 % 18),(3,1 % 9)]

See the on function for a convenient way to chain distributions.

on :: Ord c => (a -> b -> c) -> Distribution b -> a -> Distribution cSource

Utility to partially apply a function on a distribution. A use case for on is to use it in conjunction with andThen to combine distributions.

>>> uniform [1 .. 3] `andThen` (+) `on` uniform [1 .. 2]
fromList [(2,1 % 6),(3,1 % 3),(4,1 % 3),(5,1 % 6)]