mcmc-0.7.0.1: Sample from a posterior using Markov chain Monte Carlo
Copyright2021 Dominik Schrempf
LicenseGPL-3.0-or-later
Maintainerdominik.schrempf@gmail.com
Stabilityunstable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Mcmc.Proposal

Description

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

Synopsis

Proposals

newtype PName Source #

Proposal name.

Constructors

PName 

Fields

Instances

Instances details
Eq PName Source # 
Instance details

Defined in Mcmc.Proposal

Methods

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

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

Ord PName Source # 
Instance details

Defined in Mcmc.Proposal

Methods

compare :: PName -> PName -> Ordering #

(<) :: PName -> PName -> Bool #

(<=) :: PName -> PName -> Bool #

(>) :: PName -> PName -> Bool #

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

max :: PName -> PName -> PName #

min :: PName -> PName -> PName #

Show PName Source # 
Instance details

Defined in Mcmc.Proposal

Methods

showsPrec :: Int -> PName -> ShowS #

show :: PName -> String #

showList :: [PName] -> ShowS #

Semigroup PName Source # 
Instance details

Defined in Mcmc.Proposal

Methods

(<>) :: PName -> PName -> PName #

sconcat :: NonEmpty PName -> PName #

stimes :: Integral b => b -> PName -> PName #

Monoid PName Source # 
Instance details

Defined in Mcmc.Proposal

Methods

mempty :: PName #

mappend :: PName -> PName -> PName #

mconcat :: [PName] -> PName #

data PWeight Source #

The positive weight determines how often a Proposal is executed per iteration of the Markov chain. Abstract data type; for construction, see pWeight.

Instances

Instances details
Eq PWeight Source # 
Instance details

Defined in Mcmc.Proposal

Methods

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

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

Ord PWeight Source # 
Instance details

Defined in Mcmc.Proposal

Show PWeight Source # 
Instance details

Defined in Mcmc.Proposal

pWeight :: Int -> PWeight Source #

Check if the weight is positive.

Call error if weight is zero or negative.

data PDimension Source #

Proposal dimension.

The number of affected, independent parameters.

The dimension is used to calculate the optimal acceptance rate, and does not have to be exact.

Usually, the optimal acceptance rate of low dimensional proposals is higher than for high dimensional ones. However, this is not always true (see below).

Further, optimal acceptance rates are still subject to controversies. To my knowledge, research has focused on random walk proposals with multivariate normal distributions of dimension d. In this case, the following acceptance rates are desired:

  • one dimension: 0.44 (numerical results);
  • five and more dimensions: 0.234 (numerical results);
  • infinite dimensions: 0.234 (theorem for specific target distributions).

See Handbook of Markov chain Monte Carlo, chapter 4.

Of course, many proposals may not be classical random walk proposals. For example, the beta proposal on a simplex (beta) samples one new variable of the simplex from a beta distribution while rescaling all other variables. What is the dimension of this proposal? Here, the dimension is set to 2. The reason is that if the dimension of the simplex is 2, two variables are changed. If the dimension of the simplex is high, one variable is changed substantially, while all others are changed marginally.

Further, if a proposal changes a number of variables in the same way (and not independently like in a random walk proposal), the dimension of the proposal is set to the number of variables changed.

Moreover, proposals of unknown dimension are assumed to have high dimension, and the optimal acceptance rate 0.234 is used.

Finally, special proposals may have completely different desired acceptance rates. For example. the Hamiltonian Monte Carlo proposal (see Mcmc.Proposal.Hamiltonian.hmc) has a desired acceptance rate of 0.65. Specific acceptance rates can be set with PSpecial.

Constructors

PDimension Int 
PDimensionUnknown 
PSpecial Int Double

Provide dimension (Int) and desired acceptance rate (Double).

data PSpeed Source #

Rough indication whether a proposal is fast or slow.

Useful during burn in. Slow proposals are not executed during fast auto tuning periods.

See BurnInSettings.

Constructors

PFast 
PSlow 

Instances

Instances details
Eq PSpeed Source # 
Instance details

Defined in Mcmc.Proposal

Methods

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

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

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 Markov kernel).

A Proposal may be tuneable in that it contains information about how to enlarge or shrink the proposal size to decrease or increase the acceptance rate.

Predefined proposals are provided. To create custom proposals, one may use the convenience function createProposal.

Constructors

Proposal 

Fields

Instances

Instances details
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 #

type KernelRatio = Log Double Source #

Ratio of the proposal kernels.

For unbiased, volume preserving proposals, the values is 1.0.

For biased proposals, the kernel ratio is qYX / qXY, where qAB is the probability density to move from A to B.

data PResult a Source #

Proposal result.

Constructors

ForceAccept !a

Accept the new value regardless of the prior, likelihood or Jacobian.

ForceReject

Reject the proposal regardless of the prior, likelihood or Jacobian.

Propose !a !KernelRatio !Jacobian

Propose a new value.

In order to calculate the Metropolis-Hastings-Green ratio, we need to know the ratio of the backward to forward kernels (the KernelRatio or the probability masses or probability densities) and the Jacobian.

Note: The Jacobian should be part of the KernelRatio. However, it is more declarative to have them separate. Like so, we are constantly reminded: Is the Jacobian modifier different from 1.0?

Instances

Instances details
Eq a => Eq (PResult a) Source # 
Instance details

Defined in Mcmc.Proposal

Methods

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

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

Show a => Show (PResult a) Source # 
Instance details

Defined in Mcmc.Proposal

Methods

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

show :: PResult a -> String #

showList :: [PResult a] -> ShowS #

type Jacobian = Log Double Source #

Absolute value of the determinant of the Jacobian matrix.

type JacobianFunction a = JacobianFunctionG a Double Source #

Function calculating the Jacobian.

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

Lift a proposal from one data type to another.

Assume the Jacobian is 1.0.

For example:

scaleFirstEntryOfTuple = _1 @~ scale

See also liftProposalWith.

liftProposalWith :: JacobianFunction b -> Lens' b a -> Proposal a -> Proposal b Source #

Lift a proposal from one data type to another.

A function to calculate the Jacobian has to be provided. If the Jabobian is 1.0, use liftProposal.

For further reference, please see the example Pair.

type PFunction a = a -> IOGenM StdGen -> IO (PResult a, Maybe AcceptanceCounts) Source #

Simple proposal function without tuning information.

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

Maybe report acceptance counts internal to the proposal (e.g., used by proposals based on Hamiltonian dynamics).

createProposal Source #

Arguments

:: PDescription

Description of the proposal type and parameters.

-> (TuningParameter -> PFunction a)

Function creating a simple proposal function for a given tuning parameter.

-> PSpeed

Speed.

-> PDimension

Dimension.

-> PName

Name.

-> PWeight

Weight.

-> Tune

Activate tuning?

-> Proposal a 

Create a proposal with a single tuning parameter.

Proposals with auxiliary tuning parameters have to be created manually. See Tuner for more information, and Hamiltonian for an example.

Tuners

data Tuner a Source #

Required information to tune Proposals.

Constructors

Tuner 

Fields

data Tune Source #

Tune proposal?

Constructors

Tune 
NoTune 

Instances

Instances details
Eq Tune Source # 
Instance details

Defined in Mcmc.Proposal

Methods

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

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

Show Tune Source # 
Instance details

Defined in Mcmc.Proposal

Methods

showsPrec :: Int -> Tune -> ShowS #

show :: Tune -> String #

showList :: [Tune] -> ShowS #

type TuningParameter = Double Source #

Tuning parameter.

The larger the tuning parameter, the larger the proposal and the lower the expected acceptance rate; and vice versa.

data TuningType Source #

The last tuning step may be special.

type TuningFunction a Source #

Arguments

 = TuningType 
-> PDimension 
-> AcceptanceRate

Acceptance rate of last tuning period.

-> Maybe (Vector a)

Trace of last tuning period. Only available when requested by proposal.

-> (TuningParameter, AuxiliaryTuningParameters) 
-> (TuningParameter, AuxiliaryTuningParameters) 

Compute new tuning parameters.

type AuxiliaryTuningParameters = Vector TuningParameter Source #

Auxiliary tuning parameters.

Auxiliary tuning parameters are not shown in proposal summaries.

Vector may be empty.

tuningFunction :: TuningFunction a Source #

Default tuning function.

The default tuning function only uses the acceptance rate. In particular, it does not handle auxiliary tuning parameters and ignores the actual samples attained during the last tuning period.

tuningFunctionWithAux Source #

Arguments

:: (TuningType -> Vector a -> AuxiliaryTuningParameters -> AuxiliaryTuningParameters)

Auxiliary tuning function.

-> TuningFunction a 

Also tune auxiliary tuning parameters.

tuningFunctionOnlyAux Source #

Arguments

:: (TuningType -> Vector a -> AuxiliaryTuningParameters -> AuxiliaryTuningParameters)

Auxiliary tuning function.

-> TuningFunction a 

Only tune auxiliary tuning parameters.

tuningParameterMin :: TuningParameter Source #

Minimal tuning parameter; subject to change.

tuningParameterMax :: TuningParameter Source #

Maximal tuning parameter; subject to change.

tuneWithTuningParameters :: TuningParameter -> AuxiliaryTuningParameters -> Proposal a -> Either String (Proposal a) Source #

Tune a Proposal.

The size of the proposal is proportional to the tuning parameter which has positive lower and upper boundaries of tuningParameterMin and tuningParameterMax, respectively.

Auxiliary tuning parameters may also be used by the Tuner of the proposal.

Return Left if:

  • the Proposal is not tuneable;
  • the auxiliary tuning parameters are invalid.

Used by fromSavedChain.

Output

proposalHeader :: ByteString Source #

Header of proposal summaries.