mcmc-0.2.1: Sample from a posterior using Markov chain Monte Carlo

Copyright(c) Dominik Schrempf 2020
LicenseGPL-3.0-or-later
Maintainerdominik.schrempf@gmail.com
Stabilityunstable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Mcmc.Proposal

Contents

Description

Creation date: Wed May 20 13:42:53 2020.

Synopsis

Proposal

data Proposal a Source #

A Proposal is an instruction about how the Markov chain will traverse the state space a. Essentially, it is a probability mass or probability density conditioned on the current state (i.e., a kernel).

A Proposal may be tuneable in that it contains information about how to enlarge or shrink the step size to tune the acceptance ratio.

Constructors

Proposal 

Fields

Instances
Eq (Proposal a) Source # 
Instance details

Defined in Mcmc.Proposal

Methods

(==) :: Proposal a -> Proposal a -> Bool #

(/=) :: Proposal a -> Proposal a -> Bool #

Ord (Proposal a) Source # 
Instance details

Defined in Mcmc.Proposal

Methods

compare :: Proposal a -> Proposal a -> Ordering #

(<) :: Proposal a -> Proposal a -> Bool #

(<=) :: Proposal a -> Proposal a -> Bool #

(>) :: Proposal a -> Proposal a -> Bool #

(>=) :: Proposal a -> Proposal a -> Bool #

max :: Proposal a -> Proposal a -> Proposal a #

min :: Proposal a -> Proposal a -> Proposal a #

Show (Proposal a) Source # 
Instance details

Defined in Mcmc.Proposal

Methods

showsPrec :: Int -> Proposal a -> ShowS #

show :: Proposal a -> String #

showList :: [Proposal a] -> ShowS #

(@~) :: Lens' b a -> Proposal a -> Proposal b Source #

Convert a proposal from one data type to another using a lens.

For example:

scaleFirstEntryOfTuple = scale >>> _1

newtype ProposalSimple a Source #

Simple proposal without tuning information.

Instruction about randomly moving from the current state to a new state, given some source of randomness.

In order to calculate the Metropolis-Hastings ratio, we need to know the ratio of the backward to forward kernels (i.e., the probability masses or probability densities). For unbiased proposals, this ratio is 1.0.

Constructors

ProposalSimple 

Fields

data Tuner a Source #

Tune the acceptance ratio of a Proposal; see tune, or autotuneCycle.

createProposal Source #

Arguments

:: String

Name.

-> Int

Weight.

-> (Double -> ProposalSimple a)

Function creating a simple proposal for a given tuning parameter. The larger the tuning parameter, the larger the proposal (and the lower the expected acceptance ratio), and vice versa.

-> Bool

Activate tuning?

-> Proposal a 

Create a possibly tuneable proposal.

tune :: Double -> Proposal a -> Maybe (Proposal a) Source #

Tune a Proposal. Return Nothing if Proposal is not tuneable. If the parameter dt is larger than 1.0, the Proposal is enlarged, if 0<dt<1.0, it is shrunk. Negative tuning parameters are not allowed.

Cycle

data Order Source #

Define the order in which Proposals are executed in a Cycle. The total number of Proposals per Cycle may differ between Orders (e.g., compare RandomO and RandomReversibleO).

Constructors

RandomO

Shuffle the Proposals in the Cycle. The Proposals are replicated according to their weights and executed in random order. If a Proposal has weight w, it is executed exactly w times per iteration.

SequentialO

The Proposals are executed sequentially, in the order they appear in the Cycle. Proposals with weight w>1 are repeated immediately w times (and not appended to the end of the list).

RandomReversibleO

Similar to RandomO. However, a reversed copy of the list of shuffled Proposals is appended such that the resulting Markov chain is reversible. Note: the total number of Proposals executed per cycle is twice the number of RandomO.

SequentialReversibleO

Similar to SequentialO. However, a reversed copy of the list of sequentially ordered Proposals is appended such that the resulting Markov chain is reversible.

Instances
Eq Order Source # 
Instance details

Defined in Mcmc.Proposal

Methods

(==) :: Order -> Order -> Bool #

(/=) :: Order -> Order -> Bool #

Show Order Source # 
Instance details

Defined in Mcmc.Proposal

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

Default Order Source # 
Instance details

Defined in Mcmc.Proposal

Methods

def :: Order #

data Cycle a Source #

In brief, a Cycle is a list of proposals. The state of the Markov chain will be logged only after all Proposals in the Cycle have been completed, and the iteration counter will be increased by one. The order in which the Proposals are executed is specified by Order. The default is RandomO.

Proposals must have unique names, so that they can be identified.

fromList :: [Proposal a] -> Cycle a Source #

Create a Cycle from a list of Proposals.

setOrder :: Order -> Cycle a -> Cycle a Source #

Set the order of Proposals in a Cycle.

getNCycles :: Cycle a -> Int -> GenIO -> IO [[Proposal a]] Source #

Replicate Proposals according to their weights and possibly shuffle them.

tuneCycle :: Map (Proposal a) Double -> Cycle a -> Cycle a Source #

Tune Proposals in the Cycle. See tune.

autotuneCycle :: Acceptance (Proposal a) -> Cycle a -> Cycle a Source #

Calculate acceptance ratios and auto tune the Proposals in the Cycle. For now, a Proposal is enlarged when the acceptance ratio is above 0.44, and shrunk otherwise. Do not change Proposals that are not tuneable.

summarizeCycle :: Acceptance (Proposal a) -> Cycle a -> ByteString Source #

Summarize the Proposals in the Cycle. Also report acceptance ratios.

Acceptance

data Acceptance k Source #

For each key k, store the number of accepted and rejected proposals.

Instances
ToJSONKey k => ToJSON (Acceptance k) Source # 
Instance details

Defined in Mcmc.Proposal

(Ord k, FromJSONKey k) => FromJSON (Acceptance k) Source # 
Instance details

Defined in Mcmc.Proposal

emptyA :: Ord k => [k] -> Acceptance k Source #

In the beginning there was the Word.

Initialize an empty storage of accepted/rejected values.

pushA :: (Ord k, Show k) => k -> Bool -> Acceptance k -> Acceptance k Source #

For key k, prepend an accepted (True) or rejected (False) proposal.

resetA :: Ord k => Acceptance k -> Acceptance k Source #

Reset acceptance storage.

transformKeysA :: (Ord k1, Ord k2) => [k1] -> [k2] -> Acceptance k1 -> Acceptance k2 Source #

Transform keys using the given lists. Keys not provided will not be present in the new Acceptance variable.

acceptanceRatios :: Acceptance k -> Map k Double Source #

Acceptance ratios for all proposals.