monad-bayes-1.3.0: A library for probabilistic programming.
Copyright(c) Adam Scibior 2015-2020
LicenseMIT
Maintainerleonhard.markert@tweag.io
Stabilityexperimental
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Bayes.Traced.Static

Description

 
Synopsis

Documentation

data TracedT m a Source #

A tracing monad where only a subset of random choices are traced.

The random choices that are not to be traced should be lifted from the transformed monad.

Constructors

TracedT 

Fields

Instances

Instances details
MonadTrans TracedT Source # 
Instance details

Defined in Control.Monad.Bayes.Traced.Static

Methods

lift :: Monad m => m a -> TracedT m a #

Monad m => Applicative (TracedT m) Source # 
Instance details

Defined in Control.Monad.Bayes.Traced.Static

Methods

pure :: a -> TracedT m a #

(<*>) :: TracedT m (a -> b) -> TracedT m a -> TracedT m b #

liftA2 :: (a -> b -> c) -> TracedT m a -> TracedT m b -> TracedT m c #

(*>) :: TracedT m a -> TracedT m b -> TracedT m b #

(<*) :: TracedT m a -> TracedT m b -> TracedT m a #

Monad m => Functor (TracedT m) Source # 
Instance details

Defined in Control.Monad.Bayes.Traced.Static

Methods

fmap :: (a -> b) -> TracedT m a -> TracedT m b #

(<$) :: a -> TracedT m b -> TracedT m a #

Monad m => Monad (TracedT m) Source # 
Instance details

Defined in Control.Monad.Bayes.Traced.Static

Methods

(>>=) :: TracedT m a -> (a -> TracedT m b) -> TracedT m b #

(>>) :: TracedT m a -> TracedT m b -> TracedT m b #

return :: a -> TracedT m a #

MonadDistribution m => MonadDistribution (TracedT m) Source # 
Instance details

Defined in Control.Monad.Bayes.Traced.Static

MonadFactor m => MonadFactor (TracedT m) Source # 
Instance details

Defined in Control.Monad.Bayes.Traced.Static

Methods

score :: Log Double -> TracedT m () Source #

MonadMeasure m => MonadMeasure (TracedT m) Source # 
Instance details

Defined in Control.Monad.Bayes.Traced.Static

hoist :: (forall x. m x -> m x) -> TracedT m a -> TracedT m a Source #

marginal :: Monad m => TracedT m a -> m a Source #

Discard the trace and supporting infrastructure.

mhStep :: MonadDistribution m => TracedT m a -> TracedT m a Source #

A single step of the Trace Metropolis-Hastings algorithm.

mh :: MonadDistribution m => Int -> TracedT m a -> m [a] Source #

Full run of the Trace Metropolis-Hastings algorithm with a specified number of steps. Newest samples are at the head of the list.

For example:

  • I have forgotten what day it is.
  • There are ten buses per hour in the week and three buses per hour at the weekend.
  • I observe four buses in a given hour.
  • What is the probability that it is the weekend?
>>> :{
 let
   bus = do x <- bernoulli (2/7)
            let rate = if x then 3 else 10
            factor $ poissonPdf rate 4
            return x
   mhRunBusSingleObs = do
     let nSamples = 2
     sampleIOfixed $ unweighted $ mh nSamples bus
 in mhRunBusSingleObs
:}
[True,True,True]

Of course, it will need to be run more than twice to get a reasonable estimate.