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.Population

Description

PopulationT turns a single sample into a collection of weighted samples.

Synopsis

Documentation

newtype PopulationT m a Source #

A collection of weighted samples, or particles.

Constructors

PopulationT 

Fields

Instances

Instances details
MonadTrans PopulationT Source # 
Instance details

Defined in Control.Monad.Bayes.Population

Methods

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

MonadIO m => MonadIO (PopulationT m) Source # 
Instance details

Defined in Control.Monad.Bayes.Population

Methods

liftIO :: IO a -> PopulationT m a #

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

Defined in Control.Monad.Bayes.Population

Methods

pure :: a -> PopulationT m a #

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

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

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

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

Functor m => Functor (PopulationT m) Source # 
Instance details

Defined in Control.Monad.Bayes.Population

Methods

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

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

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

Defined in Control.Monad.Bayes.Population

Methods

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

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

return :: a -> PopulationT m a #

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

Defined in Control.Monad.Bayes.Population

Monad m => MonadFactor (PopulationT m) Source # 
Instance details

Defined in Control.Monad.Bayes.Population

Methods

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

MonadDistribution m => MonadMeasure (PopulationT m) Source # 
Instance details

Defined in Control.Monad.Bayes.Population

runPopulationT :: PopulationT m a -> m [(a, Log Double)] Source #

Explicit representation of the weighted sample with weights in the log domain.

explicitPopulation :: Functor m => PopulationT m a -> m [(a, Double)] Source #

Explicit representation of the weighted sample.

fromWeightedList :: Monad m => m [(a, Log Double)] -> PopulationT m a Source #

Initialize PopulationT with a concrete weighted sample.

spawn :: Monad m => Int -> PopulationT m () Source #

Increase the sample size by a given factor. The weights are adjusted such that their sum is preserved. It is therefore safe to use spawn in arbitrary places in the program without introducing bias.

multinomial :: MonadDistribution m => Vector Double -> m [Int] Source #

Multinomial sampler. Sample from \(0, \ldots, n - 1\) \(n\) times drawn at random according to the weights where \(n\) is the length of vector of weights.

resampleMultinomial :: MonadDistribution m => PopulationT m a -> PopulationT m a Source #

Resample the population using the underlying monad and a multinomial resampling scheme. The total weight is preserved.

systematic :: Double -> Vector Double -> [Int] Source #

Systematic sampler. Sample \(n\) values from \((0,1]\) as follows \[ \begin{aligned} u^{(1)} &\sim U\left(0, \frac{1}{n}\right] \\ u^{(i)} &=u^{(1)}+\frac{i-1}{n}, \quad i=2,3, \ldots, n \end{aligned} \] and then pick integers \(m\) according to \[ Q^{(m-1)}<u^{(n)} \leq Q^{(m)} \] where \[ Q^{(m)}=\sum_{k=1}^{m} w^{(k)} \] and \(w^{(k)}\) are the weights. See also Comparison of Resampling Schemes for Particle Filtering.

resampleSystematic :: MonadDistribution m => PopulationT m a -> PopulationT m a Source #

Resample the population using the underlying monad and a systematic resampling scheme. The total weight is preserved.

stratified :: MonadDistribution m => Vector Double -> m [Int] Source #

Stratified sampler.

Sample \(n\) values from \((0,1]\) as follows \[ u^{(i)} \sim U\left(\frac{i-1}{n}, \frac{i}{n}\right], \quad i=1,2, \ldots, n \] and then pick integers \(m\) according to \[ Q^{(m-1)}<u^{(n)} \leq Q^{(m)} \] where \[ Q^{(m)}=\sum_{k=1}^{m} w^{(k)} \] and \(w^{(k)}\) are the weights.

The conditional variance of stratified sampling is always smaller than that of multinomial sampling and it is also unbiased - see Comparison of Resampling Schemes for Particle Filtering.

resampleStratified :: MonadDistribution m => PopulationT m a -> PopulationT m a Source #

Resample the population using the underlying monad and a stratified resampling scheme. The total weight is preserved.

extractEvidence :: Monad m => PopulationT m a -> PopulationT (WeightedT m) a Source #

Separate the sum of weights into the WeightedT transformer. Weights are normalized after this operation.

pushEvidence :: MonadFactor m => PopulationT m a -> PopulationT m a Source #

Push the evidence estimator as a score to the transformed monad. Weights are normalized after this operation.

proper :: MonadDistribution m => PopulationT m a -> WeightedT m a Source #

A properly weighted single sample, that is one picked at random according to the weights, with the sum of all weights.

evidence :: Monad m => PopulationT m a -> m (Log Double) Source #

Model evidence estimator, also known as pseudo-marginal likelihood.

hoist :: Monad n => (forall x. m x -> n x) -> PopulationT m a -> PopulationT n a Source #

Applies a transformation to the inner monad.

collapse :: MonadMeasure m => PopulationT m a -> m a Source #

Picks one point from the population and uses model evidence as a score in the transformed monad. This way a single sample can be selected from a population without introducing bias.

popAvg :: Monad m => (a -> Double) -> PopulationT m a -> m Double Source #

PopulationT average of a function, computed using unnormalized weights.