| Copyright | (c) Dominik Schrempf 2020 |
|---|---|
| License | GPL-3.0-or-later |
| Maintainer | dominik.schrempf@gmail.com |
| Stability | unstable |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Mcmc.Proposal
Contents
Description
Creation date: Wed May 20 13:42:53 2020.
Synopsis
- data Proposal a = Proposal {}
- (@~) :: Lens' b a -> Proposal a -> Proposal b
- newtype ProposalSimple a = ProposalSimple {}
- data Tuner a
- createProposal :: String -> Int -> (Double -> ProposalSimple a) -> Bool -> Proposal a
- tune :: Double -> Proposal a -> Maybe (Proposal a)
- data Order
- data Cycle a
- fromList :: [Proposal a] -> Cycle a
- setOrder :: Order -> Cycle a -> Cycle a
- getNCycles :: Cycle a -> Int -> GenIO -> IO [[Proposal a]]
- tuneCycle :: Map (Proposal a) Double -> Cycle a -> Cycle a
- autotuneCycle :: Acceptance (Proposal a) -> Cycle a -> Cycle a
- summarizeCycle :: Acceptance (Proposal a) -> Cycle a -> Text
- data Acceptance k
- emptyA :: Ord k => [k] -> Acceptance k
- pushA :: (Ord k, Show k) => k -> Bool -> Acceptance k -> Acceptance k
- resetA :: Ord k => Acceptance k -> Acceptance k
- transformKeysA :: (Ord k1, Ord k2) => [k1] -> [k2] -> Acceptance k1 -> Acceptance k2
- acceptanceRatios :: Acceptance k -> Map k Double
Proposal
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 # | |
| Ord (Proposal a) Source # | |
| Show (Proposal a) Source # | |
(@~) :: 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.
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.
Cycle
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 |
| SequentialO | The |
| RandomReversibleO | Similar to |
| SequentialReversibleO | Similar to |
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.
getNCycles :: Cycle a -> Int -> GenIO -> IO [[Proposal a]] Source #
Replicate Proposals according to their weights and possibly shuffle them.
autotuneCycle :: Acceptance (Proposal a) -> Cycle a -> Cycle a Source #
summarizeCycle :: Acceptance (Proposal a) -> Cycle a -> Text Source #
Acceptance
data Acceptance k Source #
For each key k, store the number of accepted and rejected proposals.
Instances
| ToJSONKey k => ToJSON (Acceptance k) Source # | |
Defined in Mcmc.Proposal Methods toJSON :: Acceptance k -> Value # toEncoding :: Acceptance k -> Encoding # toJSONList :: [Acceptance k] -> Value # toEncodingList :: [Acceptance k] -> Encoding # | |
| (Ord k, FromJSONKey k) => FromJSON (Acceptance k) Source # | |
Defined in Mcmc.Proposal Methods parseJSON :: Value -> Parser (Acceptance k) # parseJSONList :: Value -> Parser [Acceptance k] # | |
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.