declarative-0.5.4: DIY Markov Chains.
Copyright(c) 2015 Jared Tobin
LicenseMIT
MaintainerJared Tobin <jared@jtobin.ca>
Stabilityunstable
Portabilityghc
Safe HaskellNone
LanguageHaskell2010

Numeric.MCMC.Anneal

Description

Transition operators can easily be tweaked to operate over an annealed parameter space, which can be useful when sampling from bumpy landscapes with isolated modes.

This library exports a single anneal function that allows one to run a declarative-compatible transition operator over a space that has been annealed to a specified temperature.

import Numeric.MCMC

annealingTransition = do
  anneal 0.70 (metropolis 1)
  anneal 0.05 (metropolis 1)
  anneal 0.05 (metropolis 1)
  anneal 0.70 (metropolis 1)
  metropolis 1

These annealed operators can then just be used like any other:

himmelblau :: Target [Double]
himmelblau = Target lHimmelblau Nothing where
  lHimmelblau :: [Double] -> Double
  lHimmelblau [x0, x1] =
    (-1) * ((x0 * x0 + x1 - 11) ^ 2 + (x0 + x1 * x1 - 7) ^ 2)

main :: IO ()
main = withSystemRandom . asGenIO $
  mcmc 10000 [0, 0] annealingTransition himmelblau
Synopsis

Documentation

anneal :: (Monad m, Functor f) => Double -> Transition m (Chain (f Double) b) -> Transition m (Chain (f Double) b) Source #

An annealing transformer.

When executed, the supplied transition operator will execute over the parameter space annealed to the supplied inverse temperature.

let annealedTransition = anneal 0.30 (slice 0.5)