declarative-0.1.0.1: DIY Markov Chains.

Copyright(c) 2015 Jared Tobin
LicenseMIT
MaintainerJared Tobin <jared@jtobin.ca>
Stabilityunstable
Portabilityghc
Safe HaskellNone
LanguageHaskell2010

Numeric.MCMC

Contents

Description

This module presents a simple combinator language for Markov transition operators that are useful in MCMC.

Any transition operators sharing the same stationary distribution and obeying the Markov and reversibility properties can be combined in a couple of ways, such that the resulting operator preserves the stationary distribution and desirable properties amenable for MCMC.

We can deterministically concatenate operators end-to-end, or sample from a collection of them according to some probability distribution. See Geyer, 2005 for details.

The result is a simple grammar for building composite, property-preserving transition operators from existing ones:

transition ::= primitive transition
             | concatT transition transition
             | sampleT transition transition

In addition to the above, this module provides a number of combinators for building composite transition operators. It re-exports a number of production-quality transition operators from the mighty-metropolis, speedy-slice, and hasty-hamiltonian libraries.

Markov chains can then be run over arbitrary Targets using whatever transition operator is desired.

import Numeric.MCMC
import Data.Sampling.Types

target :: [Double] -> Double
target [x0, x1] = negate (5  *(x1 - x0 ^ 2) ^ 2 + 0.05 * (1 - x0) ^ 2)

rosenbrock :: Target [Double]
rosenbrock = Target target Nothing

transition :: Transition IO (Chain [Double] b)
transition =
  concatT
    (sampleT (metropolis 0.5) (metropolis 1.0))
    (sampleT (slice 2.0) (slice 3.0))

main :: IO ()
main = withSystemRandom . asGenIO $ mcmc 10000 [0, 0] rosenbrock transition

See the attached test suite for other examples.

Synopsis

Documentation

concatT :: Monad m => Transition m a -> Transition m a -> Transition m a Source

Deterministically concat transition operators together.

concatAllT :: Monad m => [Transition m a] -> Transition m a Source

Deterministically concat a list of transition operators together.

sampleT :: PrimMonad m => Transition m a -> Transition m a -> Transition m a Source

Probabilistically concat transition operators together.

sampleAllT :: PrimMonad m => [Transition m a] -> Transition m a Source

Probabilistically concat transition operators together via a uniform distribution.

bernoulliT :: PrimMonad m => Double -> Transition m a -> Transition m a -> Transition m a Source

Probabilistically concat transition operators together using a Bernoulli distribution with the supplied success probability.

This is just a generalization of sampleT.

frequency :: PrimMonad m => [(Int, Transition m a)] -> Transition m a Source

Probabilistically concat transition operators together using the supplied frequency distribution.

This function is more-or-less an exact copy of frequency, except here applied to transition operators.

mcmc :: (Show (t a), FoldableWithIndex (Index (t a)) t, Ixed (t a), Num (IxValue (t a)), Variate (IxValue (t a))) => Int -> t a -> Transition IO (Chain (t a) b) -> Target (t a) -> Gen RealWorld -> IO () Source

Trace n iterations of a Markov chain and stream them to stdout.

>>> withSystemRandom . asGenIO $ mcmc 3 [0, 0] (metropolis 0.5) rosenbrock
-0.48939312153007863,0.13290702689491818
1.4541485365128892e-2,-0.4859905564050404
0.22487398491619448,-0.29769783186855125

Re-exported

metropolis :: (Traversable f, PrimMonad m) => Double -> Transition m (Chain (f Double) b)

A generic Metropolis transition operator.

hamiltonian :: (Num (IxValue (t Double)), Traversable t, FunctorWithIndex (Index (t Double)) t, Ixed (t Double), PrimMonad m, (~) * (IxValue (t Double)) Double) => Double -> Int -> Transition m (Chain (t Double) b)

A Hamiltonian transition operator.

slice :: (PrimMonad m, FoldableWithIndex (Index (t a)) t, Ixed (t a), Num (IxValue (t a)), Variate (IxValue (t a))) => IxValue (t a) -> Transition m (Chain (t a) b)

A slice sampling transition operator.

create :: PrimMonad m => m (Gen (PrimState m))

Create a generator for variates using a fixed seed.

createSystemRandom :: IO GenIO

Seed a PRNG with data from the system's fast source of pseudo-random numbers. All the caveats of withSystemRandom apply here as well.

withSystemRandom :: PrimBase m => (Gen (PrimState m) -> m a) -> IO a

Seed a PRNG with data from the system's fast source of pseudo-random numbers ("/dev/urandom" on Unix-like systems), then run the given action.

This is a somewhat expensive function, and is intended to be called only occasionally (e.g. once per thread). You should use the Gen it creates to generate many random numbers.

Note: on Windows, this code does not yet use the native Cryptographic API as a source of random numbers (it uses the system clock instead). As a result, the sequences it generates may not be highly independent.

asGenIO :: (GenIO -> IO a) -> GenIO -> IO a

Constrain the type of an action to run in the IO monad.