probability-0.1: Computations with discrete random variables

Probability

Contents

Synopsis

Auxiliary definitions

Events

type Event a = a -> BoolSource

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

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

Probabilities

newtype Probability Source

Constructors

P ProbRep 

Instances

roundRel :: RealFrac a => Int -> a -> aSource

Monad composition

(>@>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m cSource

binary composition

sequ :: Monad m => [a -> m a] -> a -> m aSource

composition of a list of monadic functions

Deterministic and probabilistic values

Distributions

newtype Dist a Source

probability disribution

Constructors

D 

Fields

unD :: [(a, ProbRep)]
 

Instances

Monad Dist 
Functor Dist 
MonadPlus Dist 
Sim Dist 
Iterate Dist 
(Ord a, Eq a) => Eq (Dist a) 
(Ord a, Show a) => Show (Dist a) 
Expected a => Expected (Dist a) 

Auxiliary functions for constructing and working with distributions

onD :: ([(a, ProbRep)] -> [(a, ProbRep)]) -> Dist a -> Dist aSource

mkD :: [(a, ProbRep)] -> Dist aSource

sortP :: [(a, ProbRep)] -> [(a, ProbRep)]Source

Normalization = grouping

normBy :: Ord a => (a -> a -> Bool) -> Dist a -> Dist aSource

accumBy :: Num b => (a -> a -> Bool) -> [(a, b)] -> [(a, b)]Source

norm :: Ord a => Dist a -> Dist aSource

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

Operations on distributions

joinWith :: (a -> b -> c) -> Dist a -> Dist b -> Dist cSource

product of independent distributions, identical to Monad.liftM2

prod :: Dist a -> Dist b -> Dist (a, b)Source

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

type Spread a = [a] -> Dist aSource

distribution generators

choose :: ProbRep -> a -> a -> Dist aSource

extract :: Dist a -> [a]Source

extracting and mapping the domain of a distribution

mapD :: (a -> b) -> Dist a -> Dist bSource

unfoldD :: Dist (Dist a) -> Dist aSource

unfold a distribution of distributions into one distribution

cond :: Dist Bool -> Dist a -> Dist a -> Dist aSource

conditional distribution

(|||) :: Dist a -> Event a -> Dist aSource

conditional probability

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 :: Ord a => ProbRep -> Dist a -> Dist (Select a)Source

scale :: [(a, ProbRep)] -> Dist aSource

filterD :: (a -> Bool) -> Dist a -> Dist aSource

selectP :: Dist a -> ProbRep -> aSource

selecting from distributions

scanP :: ProbRep -> [(a, ProbRep)] -> aSource

class ToFloat a whereSource

Methods

toFloat :: a -> FloatSource

class Expected a whereSource

Methods

expected :: a -> FloatSource

variance :: Expected a => Dist a -> FloatSource

statistical analyses

Randomized values

R random value

type R a = IO aSource

Random values

printR :: Show a => R a -> R ()Source

pick :: Dist a -> R aSource

RDist random distribution

type RDist a = R (Dist a)Source

Randomized distributions

Deterministic and probabilistic generators

Transitions

type Change a = a -> aSource

deterministic generator

type Trans a = a -> Dist aSource

probabilistic generator

mapT :: Change a -> Trans a -> Trans aSource

Spreading changes into transitions

type SpreadC a = [Change a] -> Trans aSource

functions to convert a list of changes into a transition

liftC :: Spread a -> [Change a] -> Trans aSource

enumT :: [ProbRep] -> [Change a] -> Trans aSource

Spreading transitions into transitions

type SpreadT a = [Trans a] -> Trans aSource

functions to convert a list of transitions into a transition

liftT :: Spread (Trans a) -> [Trans a] -> Trans aSource

enumTT :: [ProbRep] -> [Trans a] -> Trans aSource

Randomized generators

Randomized changes

type RChange a = a -> R aSource

random change

Randomized transitions

type RTrans a = a -> RDist aSource

random transition

type ApproxDist a = R [a]Source

rDist :: Ord a => [R a] -> RDist aSource

rDist converts a list of randomly generated values into a distribution by taking equal weights for all values

Iteration and simulation

class Iterate c whereSource

Naming convention:

  • * takes n :: Int and a generator and iterates the generator n times
  • . produces a single result
  • .. produces a trace
  • ~ takes k :: Int [and n :: Int] and a generator and simulates the [n-fold repetition of the] generator k times

There are the following functions:

  • n *. t iterates t and produces a distribution
  • n *.. t iterates t and produces a trace
  • k ~. t simulates t and produces a distribution
  • (k,n) ~*. t simulates the n-fold repetition of t and produces a distribution
  • (k,n) ~.. t simulates the n-fold repetition of t and produces a trace

Iteration captures three iteration strategies: iter builds an n-fold composition of a (randomized) transition while and until implement conditional repetitions

The class Iterate allows the overloading of iteration for different kinds of generators, namely transitions and random changes:

  • Trans   a = a -> Dist a    ==>   c = Dist
  • RChange a = a -> R a       ==>   c = R = IO

Methods

(*.) :: Int -> (a -> c a) -> a -> c aSource

while :: (a -> Bool) -> (a -> c a) -> a -> c aSource

until :: (a -> Bool) -> (a -> c a) -> a -> c aSource

Instances

class Sim c whereSource

Simulation means to repeat a random chage many times and to accumulate all results into a distribution. Therefore, simulation can be regarded as an approximation of distributions through randomization.

The Sim class allows the overloading of simulation for different kinds of generators, namely transitions and random changes:

  • Trans   a = a -> Dist a   ==>   c = Dist
  • RChange a = a -> R a      ==>   c = R = IO

Methods

(~.) :: Ord a => Int -> (a -> c a) -> RTrans aSource

returns the final randomized transition

(~..) :: Ord a => (Int, Int) -> (a -> c a) -> RExpand aSource

returns the whole trace

(~*.) :: Ord a => (Int, Int) -> (a -> c a) -> RTrans aSource

Instances

Tracing

type Trace a = [a]Source

type Space a = Trace (Dist a)Source

type Walk a = a -> Trace aSource

type Expand a = a -> Space aSource

(>>:) :: Trans a -> Expand a -> Expand aSource

(>>:) composes the result of a transition with a space (transition is composed on the left)

(a -> m a) -> (a -> [m a]) -> (a -> [m a])

walk :: Int -> Change a -> Walk aSource

walk is a bounded version of the predefined function iterate

(*..) :: Int -> Trans a -> Expand aSource

(*..) is identical to (*.), but returns the list of all intermediate distributions

type RTrace a = R (Trace a)Source

type RSpace a = R (Space a)Source

type RWalk a = a -> RTrace aSource

type RExpand a = a -> RSpace aSource

rWalk :: Int -> RChange a -> RWalk aSource

rWalk computes a list of values by randomly selecting one value from a distribution in each step.

mergeTraces :: Ord a => [RTrace a] -> RSpace aSource

mergeTraces converts a list of RTraces into a list of randomized distributions, i.e., an RSpace, by creating a randomized distribution for each list position across all traces