monad-bayes-0.1.0.0: A library for probabilistic programming.

Copyright(c) Adam Scibior 2015-2020
LicenseMIT
Maintainerleonhard.markert@tweag.io
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Bayes.Population

Description

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

Synopsis

Documentation

data Population m a Source #

A collection of weighted samples, or particles.

Instances
MonadTrans Population Source # 
Instance details

Defined in Control.Monad.Bayes.Population

Methods

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

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

Defined in Control.Monad.Bayes.Population

Methods

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

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

return :: a -> Population m a #

fail :: String -> Population m a #

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

Defined in Control.Monad.Bayes.Population

Methods

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

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

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

Defined in Control.Monad.Bayes.Population

Methods

pure :: a -> Population m a #

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

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

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

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

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

Defined in Control.Monad.Bayes.Population

Methods

liftIO :: IO a -> Population m a #

MonadSample m => MonadInfer (Population m) Source # 
Instance details

Defined in Control.Monad.Bayes.Population

Monad m => MonadCond (Population m) Source # 
Instance details

Defined in Control.Monad.Bayes.Population

Methods

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

MonadSample m => MonadSample (Population m) Source # 
Instance details

Defined in Control.Monad.Bayes.Population

runPopulation :: Functor m => Population m a -> m [(a, Log Double)] Source #

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

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

Explicit representation of the weighted sample.

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

Initialize Population with a concrete weighted sample.

spawn :: Monad m => Int -> Population 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.

resampleMultinomial :: MonadSample m => Population m a -> Population m a Source #

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

resampleSystematic :: MonadSample m => Population m a -> Population m a Source #

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

extractEvidence :: Monad m => Population m a -> Population (Weighted m) a Source #

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

pushEvidence :: MonadCond m => Population m a -> Population m a Source #

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

proper :: MonadSample m => Population m a -> Weighted 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 => Population m a -> m (Log Double) Source #

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

collapse :: MonadInfer m => Population 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.

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

Applies a random transformation to a population.

normalize :: Monad m => Population m a -> Population m a Source #

Normalizes the weights in the population so that their sum is 1. This transformation introduces bias.

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

Population average of a function, computed using unnormalized weights.

flatten :: Monad m => Population (Population m) a -> Population m a Source #

Combine a population of populations into a single population.

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

Applies a transformation to the inner monad.