probability-0.2.5: Probabilistic Functional Programming

Safe HaskellSafe-Inferred
LanguageHaskell98

Numeric.Probability.Distribution

Contents

Description

Deterministic and probabilistic values

Synopsis

Events

type Event a = a -> Bool Source

oneOf :: Eq a => [a] -> Event a Source

just :: Eq a => a -> Event a Source

Distributions

newtype T prob a Source

Probability disribution

The underlying data structure is a list. Unfortunately we cannot use a more efficient data structure because the key type must be of class Ord, but the Monad class does not allow constraints for result types. The Monad instance is particularly useful because many generic monad functions make sense here, monad transformers can be used and the monadic design allows to simulate probabilistic games in an elegant manner.

We have the same problem like making Data.Set an instance of Monad, see http://www.randomhacks.net/articles/2007/03/15/data-set-monad-haskell-macros

If you need efficiency, you should remove redundant elements by norm. norm converts to Map and back internally and you can hope that the compiler fuses the lists with the intermediate Map structure.

The defined monad is equivalent to WriterT (Product prob) [] a. See http://www.randomhacks.net/articles/2007/02/21/refactoring-probability-distributions.

Constructors

Cons 

Fields

decons :: [(a, prob)]
 

Instances

Fractional prob => C prob (T prob) 
Num prob => Monad (T prob) 
Functor (T prob) 
Num prob => Applicative (T prob) 
(Num prob, Ord prob, Random prob) => C (T prob) 
Eq (T prob a)

We would like to have an equality test of type

(==) :: T prob a -> T prob a -> T prob Bool

that is consistent with the Num instance. We would certainly define

x==y = norm (liftM2 (==) x y)   .

However the Eq class enforces the type

T prob a -> T prob a -> Bool    .

We could implement this as check for equal distributions. This would be inconsistent with the Num instance because it compares entire distributions, not only individual outcomes. Thus we provide this function as equal.

I would prefer to omit the Eq instance completely, but unfortunately the Num instance requires Eq as superclass.

(Num prob, Ord prob, Ord a, Fractional a) => Fractional (T prob a) 
(Num prob, Ord prob, Ord a, Num a) => Num (T prob a) 
(Num prob, Ord prob, Show prob, Ord a, Show a) => Show (T prob a) 
(ToFloat prob, Expected a) => Expected (T prob a) 

certainly :: Num prob => a -> T prob a Source

errorMargin :: RealFloat prob => prob Source

approx :: (RealFloat prob, Ord a) => T prob a -> T prob a -> Bool Source

Check whether two distributions are equal when neglecting rounding errors. We do not want to put this into an Eq instance, since it is not exact equivalence and it seems to be too easy to mix it up with liftM2 (==) x y.

Auxiliary functions for constructing and working with distributions

lift :: Num prob => ([(a, prob)] -> [(a, prob)]) -> T prob a -> T prob a Source

size :: T prob a -> Int Source

check :: (RealFloat prob, Show prob) => T prob a -> T prob a Source

cons :: (RealFloat prob, Show prob) => [(a, prob)] -> T prob a Source

can fail because of rounding errors, better use fromFreqs

sumP :: Num prob => [(a, prob)] -> prob Source

sortP :: Ord prob => [(a, prob)] -> [(a, prob)] Source

sortPDesc :: Ord prob => [(a, prob)] -> [(a, prob)] Source

sortElem :: Ord a => [(a, prob)] -> [(a, prob)] Source

Normalization = grouping

norm :: (Num prob, Ord a) => T prob a -> T prob a Source

norm' :: (Num prob, Ord a) => [(a, prob)] -> [(a, prob)] Source

norm'' :: (Num prob, Ord a) => [(a, prob)] -> [(a, prob)] Source

pretty :: (Ord a, Show a, Num prob, Ord prob) => (prob -> String) -> T prob a -> String Source

pretty printing

(//%) :: (Ord a, Show a) => T Rational a -> () -> IO () infix 0 Source

equal :: (Num prob, Eq prob, Ord a) => T prob a -> T prob a -> Bool Source

Spread: functions to convert a list of values into a distribution

type Spread prob a = [a] -> T prob a Source

distribution generators

choose :: Num prob => prob -> a -> a -> T prob a Source

enum :: Fractional prob => [Int] -> Spread prob a Source

relative :: Fractional prob => [prob] -> Spread prob a Source

Give a list of frequencies, they do not need to sum up to 1.

shape :: Fractional prob => (prob -> prob) -> Spread prob a Source

linear :: Fractional prob => Spread prob a Source

uniform :: Fractional prob => Spread prob a Source

negExp :: Floating prob => Spread prob a Source

normal :: Floating prob => Spread prob a Source

extract :: T prob a -> [a] Source

extracting and mapping the domain of a distribution

map :: (Num prob, Ord b) => (a -> b) -> T prob a -> T prob b Source

fmap with normalization

unfold :: (Num prob, Ord a) => T prob (T prob a) -> T prob a Source

unfold a distribution of distributions into one distribution, this is join with normalization.

cond Source

Arguments

:: Num prob 
=> T prob Bool 
-> T prob a

True

-> T prob a

False

-> T prob a 

conditional distribution

truth :: Num prob => T prob Bool -> prob Source

(?=<<) :: Fractional prob => (a -> Bool) -> T prob a -> T prob a infixr 1 Source

conditional probability, identical to filter

(>>=?) :: Fractional prob => T prob a -> (a -> Bool) -> T prob a infixl 1 Source

filter in infix form. Can be considered an additional monadic combinator, which can be used where you would want guard otherwise.

data Select a Source

filtering distributions

Constructors

Case a 
Other 

Instances

Eq a => Eq (Select a) 
Ord a => Ord (Select a) 
Show a => Show (Select a) 

above :: (Num prob, Ord prob, Ord a) => prob -> T prob a -> T prob (Select a) Source

below :: (Num prob, Ord prob, Ord a) => prob -> T prob a -> T prob (Select a) Source

select :: (Num prob, Ord prob, Ord a) => (prob -> Bool) -> T prob a -> T prob (Select a) Source

fromFreqs :: Fractional prob => [(a, prob)] -> T prob a Source

filter :: Fractional prob => (a -> Bool) -> T prob a -> T prob a Source

mapMaybe :: Fractional prob => (a -> Maybe b) -> T prob a -> T prob b Source

selectP :: (Num prob, Ord prob) => T prob a -> prob -> a Source

selecting from distributions

scanP :: (Num prob, Ord prob) => prob -> [(a, prob)] -> a Source

(??) :: Num prob => Event a -> T prob a -> prob infixr 1 Source

expected :: Num a => T a a -> a Source

expectation value

variance :: Num a => T a a -> a Source

statistical analyses

stdDev :: Floating a => T a a -> a Source