lazyppl-1.0: Lazy Probabilistic Programming Library
Safe HaskellSafe-Inferred
LanguageHaskell2010

LazyPPL

Description

LazyPPL is a library for Bayesian probabilistic programming. It supports lazy use of probability, and we provide new Metropolis-Hastings simulation algorithms to allow this. Laziness appears to be a good paradigm for non-parametric statistics.

Reference paper: Affine Monads and Lazy Structures for Bayesian Programming. POPL 2023.

Illustrations: https://lazyppl-team.github.io.

LazyPPL is inspired by recent ideas in synthetic probability theory and synthetic measure theory, such as quasi-Borel spaces and Markov categories. LazyPPL is inspired by many other languages, including Church, Anglican, and Monad-Bayes. Monad-Bayes now includes a LazyPPL-inspired simulation algorithm.

This module defines

  1. Two monads: Prob (for probability measures) and Meas (for unnormalized measures), with interface uniform, sample, score.
  2. Monte Carlo inference methods produce samples from an unnormalized measure. We provide three inference methods:

    a. mh (Metropolis-Hastings algorithm based on lazily mutating parts of the tree at random).

    b. mhirreducible, which randomly restarts for a properly irreducible Metropolis-Hastings kernel.

    c. wis (simple reference weighted importance sampling)

    See also the SingleSite module for a separate single-site Metropolis-Hastings algorithm via GHC.Exts.Heap and System.IO.Unsafe.

  3. Various useful helpful functions.

A typical usage would be

    import LazyPPL (Prob, Meas, uniform, sample, score, mh, every)

Most of the structure here will not be needed in typical models. We expose more of the structure for more experimental uses.

The Distributions module provides many useful distributions, and further non-parametric distributions are in DirichletP, GP, IBP, and Memoization.

Synopsis

Rose tree type

Our source of randomness will be an infinitely wide and deep lazy rose tree, regarded as initialized with uniform [0,1] choices for each label.

data Tree Source #

A Tree here is a lazy, infinitely wide and infinitely deep rose tree, labelled by Doubles.

Constructors

Tree Double [Tree] 

Monads

newtype Prob a Source #

A probability distribution over a is a function Tree -> a .

We can think of this as the law of a random variable, indexed by the source of randomness, which is Tree.

According to the monad implementation, a program uses up bits of the tree as it runs. The tree being infinitely wide and deep allows for lazy computation.

Constructors

Prob (Tree -> a) 

Instances

Instances details
Applicative Prob Source # 
Instance details

Defined in LazyPPL

Methods

pure :: a -> Prob a #

(<*>) :: Prob (a -> b) -> Prob a -> Prob b #

liftA2 :: (a -> b -> c) -> Prob a -> Prob b -> Prob c #

(*>) :: Prob a -> Prob b -> Prob b #

(<*) :: Prob a -> Prob b -> Prob a #

Functor Prob Source # 
Instance details

Defined in LazyPPL

Methods

fmap :: (a -> b) -> Prob a -> Prob b #

(<$) :: a -> Prob b -> Prob a #

Monad Prob Source #

Sequencing is done by splitting the tree and using different bits for different computations.

This monad structure is strongly inspired by the probability monad of quasi-Borel space.

Instance details

Defined in LazyPPL

Methods

(>>=) :: Prob a -> (a -> Prob b) -> Prob b #

(>>) :: Prob a -> Prob b -> Prob b #

return :: a -> Prob a #

MonadMemo Prob Table Source # 
Instance details

Defined in LazyPPL.Distributions.DirichletP

Methods

memoize :: (Table -> Prob b) -> Prob (Table -> b) Source #

MonadMemo Prob Dish Source # 
Instance details

Defined in LazyPPL.Distributions.IBP

Methods

memoize :: (Dish -> Prob b) -> Prob (Dish -> b) Source #

newtype Meas a Source #

An unnormalized measure is represented by a probability distribution over pairs of a weight and a result.

Constructors

Meas (WriterT (Product (Log Double)) Prob a) 

Instances

Instances details
Applicative Meas Source # 
Instance details

Defined in LazyPPL

Methods

pure :: a -> Meas a #

(<*>) :: Meas (a -> b) -> Meas a -> Meas b #

liftA2 :: (a -> b -> c) -> Meas a -> Meas b -> Meas c #

(*>) :: Meas a -> Meas b -> Meas b #

(<*) :: Meas a -> Meas b -> Meas a #

Functor Meas Source # 
Instance details

Defined in LazyPPL

Methods

fmap :: (a -> b) -> Meas a -> Meas b #

(<$) :: a -> Meas b -> Meas a #

Monad Meas Source # 
Instance details

Defined in LazyPPL

Methods

(>>=) :: Meas a -> (a -> Meas b) -> Meas b #

(>>) :: Meas a -> Meas b -> Meas b #

return :: a -> Meas a #

Basic interface

There are three building blocks for measures: uniform for probability measures; sample and score for unnormalized measures. Combined with the monad structure, these give all s-finite measures.

uniform :: Prob Double Source #

A uniform sample is a building block for probability distributions.

This is implemented by getting the label at the head of the tree and discarding the rest.

sample :: Prob a -> Meas a Source #

Regard a probability measure as an unnormalized measure.

score :: Double -> Meas () Source #

A one point measure with a given score (or weight, or mass, or likelihood), which should be a positive real number.

A score of 0 describes impossibility. To avoid numeric issues, we encode it as exp(-300) instead.

Monte Carlo simulation

The Meas type describes unnormalized measures. Monte Carlo simulation allows us to sample from an unnormalized measure. Our main Monte Carlo simulator is mh.

mh Source #

Arguments

:: forall a. Double

The chance p of changing any site

-> Meas a

The unnormalized measure to sample from

-> IO [(a, Product (Log Double))]

Returns a stream of (result,weight) pairs

Produce a stream of samples, using Metropolis Hastings simulation.

The weights are also returned. Often the weights can be discarded, but sometimes we may search for a sample of maximum score.

The algorithm works as follows.

At each step, we randomly change some sites (nodes in the tree). We then accept or reject these proposed changes, using a probability that is determined by the weight of the measure at the new tree. If rejected, we repeat the previous sample.

This kernel is related to the one introduced by Wingate, Stuhlmuller, Goodman, AISTATS 2011, but it is different in that it works when the number of sites is unknown. Moreover, since a site is a path through the tree, the address is more informative than a number, which avoids some addressing issues.

When 1/p is roughly the number of used sites, then this will be a bit like "single-site lightweight" MH. If p = 1 then this is "multi-site lightweight" MH.

Tip: if m :: Prob a then use map fst $ (mh 1 $ sample m) to get a stream of samples from a probability distribution without conditioning. -

mhirreducible Source #

Arguments

:: forall a. Double

The chance p of changing any given site

-> Double

The chance q of doing an all-sites change

-> Meas a

The unnormalized measure m to sample from

-> IO [(a, Product (Log Double))]

Returns a stream of (result,weight) pairs

Irreducible form of mh. Takes p like mh, but also q, which is the chance of proposing an all-sites change. Irreducibility means that, asymptotically, the sequence of samples will converge in distribution to the renormalized version of m.

The kernel in mh is not formally irreducible in the usual sense, although it is an open question whether this is a problem for asymptotic convergence in any definable model. In any case, convergence is only asymptotic, and so it can be helpful to use mhirreducible is that in some situations.

Roughly this avoids mh getting stuck in one particular mode, although it is a rather brutal method.

weightedsamples :: forall a. Meas a -> IO [(a, Log Double)] Source #

Runs an unnormalized measure and gets out a stream of (result,weight) pairs.

These are not samples from the renormalized distribution, just plain (result,weight) pairs. This is useful when the distribution is known to be normalized already.

wis Source #

Arguments

:: Int

n, the number of samples to base on

-> Meas a

m, the measure to normalize

-> IO [a]

Returns a stream of samples

Weighted importance sampling first draws n weighted samples, and then samples a stream of results from that, regarded as an empirical distribution. Sometimes called "likelihood weighted importance sampling".

This is a reference implementation. It will not usually be very efficient at all, but may be useful for debugging.

Useful functions

every :: Int -> [a] -> [a] Source #

Useful function which thins out a stream of results, as is common in Markov Chain Monte Carlo simulation.

every n xs returns only the elements at indices that are multiples of n.-

randomTree :: RandomGen g => g -> Tree Source #

Generate a tree with uniform random labels.

This uses split to split a random seed.

runProb :: Prob a -> Tree -> a Source #

runProb runs a probability deterministically, given a source of randomness.