LazyPPL

LazyPPL

Haskell library for Bayesian probabilistic programming

Explore Examples

LazyPPL is a Haskell library for Bayesian probabilistic programming. It supports lazy use of probability, and we provide new Metropolis-Hastings algorithms to allow this. LazyPPL is inspired by recent ideas in synthetic probability theory and synthetic measure theory, such as quasi-Borel spaces and Markov categories. Laziness appears to be a good paradigm for non-parametric statistics. LazyPPL is inspired by many other languages, including Church, Anglican, and MonadBayes. Several aspects are now incorporated into MonadBayes (see here).

Linear and piecewise linear regression
Regression

Linear & Piecewise Regression

Start simple with Bayesian linear regression, then extend to piecewise models using a Poisson point process.

Wiener process regression
Stochastic Processes

Wiener Process Regression

Model time series with Wiener process priors for continuous, nowhere-differentiable random functions.

Program induction
Program Induction

Program Induction

Infer arithmetic expressions that explain observed data using probabilistic program induction.

Observed graph for inference
Graph Inference

Graph Inference

Infer parameters and structure of random graphs, such as geometric versus Erdős–Rényi models, from observed adjacency data.

2D physics bumper configuration
Physics

Inference in a Physics Model

Perform Bayesian inference in a 2D physics simulation, inferring bumper configurations so a falling ball lands in a cup.

Two-Monad Architecture

LazyPPL provides two monads:

Simple example

To illustrate the basic usage, here is a very simple first example, that doesn’t use laziness. More advanced examples are in the menu above, and further examples in the GitHub repository.

Extensions and imports for this Literate Haskell file
{-# LANGUAGE ExtendedDefaultRules #-}
module Index where
import LazyPPL
import LazyPPL.Distributions
import Graphics.Matplotlib hiding (density)
import Data.List

Suppose we we know that there are fewer buses on Sundays than on other days. I notice 4 buses in an hour, what is the probability it is a Sunday?

model :: Meas Bool
model = do
  -- Prior belief: it is Sunday with prob. 1/7
  sunday <- sample $ bernoulli (1/7)
  -- I know the rates of buses on the different days:
  let rate = if sunday then 3 else 10
  -- observe 4 buses
  score $ poissonPdf rate 4
  return sunday

We run a Metropolis-Hastings simulation to get a stream of draws from this unnormalized measure. We plot a histogram of the results, which shows the posterior probability that it is Sunday, given that we saw 4 buses.

inference :: IO ()
inference = do
  xws <- mh 1 model
  plotHistogram "images/index-posterior.svg" (map fst $ take 1000 xws)
Posterior probability of Sunday given 4 buses observed
Plotting utilities
plotHistogram :: (Show a , Eq a) => String -> [a] -> IO ()
plotHistogram filename xs = do
  putStrLn $ "Generating " ++ filename ++ "..."
  let categories = nub xs
  let counts = map (\c -> length $ filter (==c) xs) categories
  file filename $ bar (map show categories) $ map (\n -> (fromIntegral n)/(fromIntegral $ length xs)) counts
  putStrLn $ "Done."

main = do {inference}