probability-0.2.2: Probabilistic Functional Programming

Numeric.Probability.Distribution

Contents

Description

Deterministic and probabilistic values

Synopsis

Events

type Event a = a -> BoolSource

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

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

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 Data.Map and back internally and you can hope that the compiler fuses the lists with the intermediate Map structure.

Constructors

Cons 

Fields

decons :: [(a, prob)]
 

Instances

Fractional prob => C prob (T prob) 
Num prob => Monad (T prob) 
Functor (T prob) 
(Num prob, Ord prob, Random prob) => C (T prob) 
Eq (T prob a) 
(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, Ord a, Show a) => Show (T prob a) 
(ToFloat prob, Expected a) => Expected (T prob a) 

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

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

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 aSource

size :: T prob a -> IntSource

check :: RealFloat prob => T prob a -> T prob aSource

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

can fail because of rounding errors, better use fromFreqs

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

sortP :: 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 aSource

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 -> StringSource

pretty printing

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

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

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

distribution generators

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

enum :: Fractional prob => [Int] -> Spread prob aSource

relative :: Fractional prob => [prob] -> Spread prob aSource

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

shape :: Fractional prob => (prob -> prob) -> Spread prob aSource

linear :: Fractional prob => Spread prob aSource

uniform :: Fractional prob => Spread prob aSource

negExp :: Floating prob => Spread prob aSource

normal :: Floating prob => Spread prob aSource

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 bSource

fmap with normalization

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

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

condSource

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 -> probSource

(?=<<) :: Fractional prob => (a -> Bool) -> T prob a -> T prob aSource

conditional probability, identical to Dist.filter

(>>=?) :: Fractional prob => T prob a -> (a -> Bool) -> T prob aSource

Dist.filter in infix form. Can be considered an additional monadic combinator, which can be used where you would want Control.Monad.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

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

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

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

selecting from distributions

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

(??) :: Num prob => Event a -> T prob a -> probSource

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

expectation value

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

statistical analyses

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