module Numeric.Probability.Example.Bayesian where
import qualified Numeric.Probability.Distribution as Dist
import qualified Numeric.Probability.Transition as Trans
import qualified Numeric.Probability.Monad as MonadExt
import Numeric.Probability.Distribution ((??), (?=<<), )
type Probability = Rational
type Dist a = Dist.T Probability a
type State a = [a]
type PState a = Dist (State a)
type STrans a = State a -> PState a
type SPred a = a -> State a -> Bool
event :: Probability -> a -> STrans a
event p e0 = Trans.maybe p (e0:)
happens :: Eq a => SPred a
happens = elem
network :: [STrans a] -> PState a
network = flip MonadExt.compose []
source :: Probability -> a -> STrans a
source = event
bin :: Eq a =>
a -> a -> Probability -> Probability -> Probability -> Probability ->
a -> STrans a
bin x y a b c d z s | elem x s && elem y s = event a z s
| elem x s = event b z s
| elem y s = event c z s
| otherwise = event d z s
data Nodes = A | B | E deriving (Eq,Ord,Show)
g :: PState Nodes
g = network [source 0.1 A,
source 0.2 B,
bin A B 1 1 0.5 0 E]
e, aE, bE :: Probability
e = happens E ?? g
aE = happens A ?? happens E ?=<< g
bE = happens B ?? happens E ?=<< g