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

Mcmc

Description

Creation date: Tue May 5 18:01:15 2020.

For an introduction to Markov chain Monte Carlo (MCMC) samplers and update mechanisms using the Metropolis-Hastings-Green algorithm, please see Geyer, C. J., (2011), Introduction to Markov Chain Monte Carlo, In Handbook of Markov Chain Monte Carlo (pp. 45), CRC press.

This library focusses on classical Markov chain Monte Carlo algorithms such as the Metropolis-Hastings-Green (MHG) [1] algorithm, or population methods involving parallel chains such as the Metropolic-coupled Markov chain Monte Carlo [2] algorithm. In particular, sequential Monte Carlo [3] algorithms following a moving posterior distribution are not provided. Recently, Hamiltonian Monte Carlo (HMC) proposals have been added [4]. HMC proposals can be used with automatic differentiation. HMC proposals with automatic differentiation are quite slow for complicated prior or likelihood functions, but they are incredibly useful when specialized MHG proposals are not readily available.

An MCMC sampler can be run with mcmc, for example using the Metropolis-Hastings-Green algorithm mhg.

Usually, it is best to start with an example:

The import of this module alone should cover most use cases.

[1] Geyer, C. J. (2011), Introduction to markov chain monte carlo, In Handbook of Markov Chain Monte Carlo (pp. 45), CRC press.

[2] Geyer, C. J. (1991), Markov chain monte carlo maximum likelihood, Computing Science and Statistics, Proceedings of the 23rd Symposium on the Interface.

[3] Sequential monte carlo methods in practice (2001), Editors: Arnaud Doucet, Nando de Freitas, and Neil Gordon, Springer New York.

[4] Review by Betancourt and notes: Betancourt, M., A conceptual introduction to Hamiltonian Monte Carlo, arXiv, 1701–02434 (2017).

Synopsis

Proposals

A Proposal is an instruction about how to advance a given Markov chain so that it possibly reaches a new state. That is, Proposals specify how the chain traverses the state space. As far as this MCMC library is concerned, Proposals are considered to be /elementary updates/ in that they cannot be decomposed into smaller updates.

Proposals can be combined to form composite updates, a technique often referred to as composition. On the other hand, mixing (used in the sense of mixture models) is the random choice of a Proposal (or a composition of Proposals) from a given set.

The composition and mixture of Proposals allows specification of nearly all MCMC algorithms involving a single chain (i.e., population methods such as particle filters are excluded). In particular, Gibbs samplers of all sorts can be specified using this procedure. For reference, please see the short encyclopedia of MCMC methods.

This library enables composition and mixture of Proposals via the Cycle data type. Essentially, a Cycle is a set of Proposals. The chain advances after the completion of each Cycle, which is called an iteration, and the iteration counter is increased by one.

The Proposals in a Cycle can be executed in the given order or in a random sequence which allows, for example, specification of a fixed scan Gibbs sampler, or a random sequence scan Gibbs sampler, respectively. See Order.

Notes: - It is important that the given Cycle enables traversal of the complete state space. Otherwise, the Markov chain will not converge to the correct stationary posterior distribution. - Be careful when assigning proposals because acceptance ratios may have to be amended using Jacobians. Please see an example involving a pair of numbers.

Proposals are named according to what they do, i.e., how they change the state of a Markov chain, and not according to the intrinsically used probability distributions. For example, slideSymmetric is a sliding proposal. Under the hood, it uses the normal distribution with mean zero and given variance. The sampled variate is added to the current value of the variable (hence, the name slide). The same nomenclature is used by RevBayes [4]. The probability distributions and intrinsic properties of a specific proposal are specified in detail in the documentation.

The other method, which is used intrinsically, is more systematic, but also a little bit more complicated: we separate between the proposal distribution and how the state is affected. And here, I am referring to the operator (addition, multiplication, any other binary operator). For example, the sliding proposal with mean m, standard deviation s, and tuning parameter t is implemented as

slide :: Double -> Double -> Double -> PFunction Double
slide m s t =
  genericContinuous (normalDistr m (s * t)) (+) (Just negate) Nothing

This specification is more involved. Especially since we need to know the probability of jumping back, and so we need to know the inverse operator negate. However, it also allows specification of new proposals with great ease.

[4] Höhna, S., Landis, M. J., Heath, T. A., Boussau, B., Lartillot, N., Moore, B. R., Huelsenbeck, J. P., …, Revbayes: bayesian phylogenetic inference using graphical models and an interactive model-specification language, Systematic Biology, 65(4), 726–736 (2016). http://dx.doi.org/10.1093/sysbio/syw021

newtype PName Source #

Proposal name.

Constructors

PName 

Fields

Instances

Instances details
Monoid PName Source # 
Instance details

Defined in Mcmc.Proposal

Methods

mempty :: PName #

mappend :: PName -> PName -> PName #

mconcat :: [PName] -> PName #

Semigroup PName Source # 
Instance details

Defined in Mcmc.Proposal

Methods

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

sconcat :: NonEmpty PName -> PName #

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

Show PName Source # 
Instance details

Defined in Mcmc.Proposal

Methods

showsPrec :: Int -> PName -> ShowS #

show :: PName -> String #

showList :: [PName] -> ShowS #

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 #

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
Show PWeight Source # 
Instance details

Defined in Mcmc.Proposal

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

pWeight :: Int -> PWeight Source #

Check if the weight is positive.

Call error if weight is zero or negative.

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.

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 #

(@~) :: 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.

data Tune Source #

Tune proposal?

Constructors

Tune 
NoTune 

Instances

Instances details
Show Tune Source # 
Instance details

Defined in Mcmc.Proposal

Methods

showsPrec :: Int -> Tune -> ShowS #

show :: Tune -> String #

showList :: [Tune] -> ShowS #

Eq Tune Source # 
Instance details

Defined in Mcmc.Proposal

Methods

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

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

scale :: Shape Double -> Scale Double -> PName -> PWeight -> Tune -> Proposal Double Source #

Multiplicative proposal.

The gamma distribution is used to sample the multiplier. Therefore, this and all derived proposals are log-additive in that they do not change the sign of the state. Further, the value zero is never proposed when having a strictly positive value.

Consider using slide to allow proposition of values having opposite sign.

scaleUnbiased :: Shape Double -> PName -> PWeight -> Tune -> Proposal Double Source #

See scale.

The scale of the gamma distribution is set to (shape)^{-1}, so that the mean of the gamma distribution is 1.0.

scaleContrarily :: Shape Double -> Scale Double -> PName -> PWeight -> Tune -> Proposal (Double, Double) Source #

See scale.

The two values are scaled contrarily so that their product stays constant. Contrary proposals are useful when parameters are confounded.

scaleBactrian :: SpikeParameter -> StandardDeviation Double -> PName -> PWeight -> Tune -> Proposal Double Source #

Multiplicative proposal with kernel similar to the silhouette of a Bactrian camel.

See scale, and slideBactrian.

slide :: Mean Double -> StandardDeviation Double -> PName -> PWeight -> Tune -> Proposal Double Source #

Additive proposal.

A normal distribution is used to sample the addend.

slideSymmetric :: StandardDeviation Double -> PName -> PWeight -> Tune -> Proposal Double Source #

See slide.

Use a normal distribution with mean zero. This proposal is fast, because the Metropolis-Hastings-Green ratio does not include calculation of the forwards and backwards kernels.

slideUniformSymmetric :: Size -> PName -> PWeight -> Tune -> Proposal Double Source #

See slide.

Use a uniformly distributed kernel with mean zero. This proposal is fast, because the Metropolis-Hastings-Green ratio does not include calculation of the forwards and backwards kernels.

slideContrarily :: Mean Double -> StandardDeviation Double -> PName -> PWeight -> Tune -> Proposal (Double, Double) Source #

See slide.

Use a normally distributed kernel.

The two values are slid contrarily so that their sum stays constant. Contrary proposals are useful when parameters are confounded.

slideBactrian :: SpikeParameter -> StandardDeviation Double -> PName -> PWeight -> Tune -> Proposal Double Source #

Additive symmetric proposal with kernel similar to the silhouette of a Bactrian camel.

The Bactrian kernel is a mixture of two symmetrically arranged normal distributions. The spike parameter \(m \in (0, 1)\) loosely determines the standard deviations of the individual humps while the second parameter \(s > 0\) refers to the standard deviation of the complete Bactrian kernel.

See https://www.ncbi.nlm.nih.gov/pmc/articles/PMC3845170/.

Cycles

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.

No proposals with the same name and description are allowed in a Cycle, so that they can be uniquely identified.

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

Create a Cycle from a list of Proposals; use RandomO, but see setOrder.

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

Instances details
Show Order Source # 
Instance details

Defined in Mcmc.Cycle

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

Eq Order Source # 
Instance details

Defined in Mcmc.Cycle

Methods

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

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

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

Set the order of Proposals in a Cycle.

Settings

Monitors

A Monitor describes which part of the Markov chain should be logged and where. Monitor files can directly be loaded into established MCMC analysis tools working with tab separated tables (for example, Tracer).

There are three different Monitor types:

MonitorStdOut
Log to standard output.
MonitorFile
Log to a file.
MonitorBatch
Log summary statistics such as the mean of the last states to a file.

data Monitor a Source #

A Monitor observing the chain.

A Monitor describes which part of the Markov chain should be logged and where. Further, they allow output of summary statistics per iteration in a flexible way.

Constructors

Monitor (MonitorStdOut a) [MonitorFile a] [MonitorBatch a] 

data MonitorStdOut a Source #

Monitor to standard output; construct with monitorStdOut.

monitorStdOut :: [MonitorParameter a] -> Period -> MonitorStdOut a Source #

Monitor to standard output.

data MonitorFile a Source #

Monitor to a file; constructed with monitorFile.

monitorFile Source #

Arguments

:: String

Name; used as part of the file name.

-> [MonitorParameter a] 
-> Period 
-> MonitorFile a 

Monitor parameters to a file.

data MonitorBatch a Source #

Batch monitor to a file.

Calculate summary statistics over the last given number of iterations (batch size). Construct with monitorBatch.

monitorBatch Source #

Arguments

:: String

Name; used as part of the file name.

-> [MonitorParameterBatch a] 
-> BatchSize 
-> MonitorBatch a 

Batch monitor parameters to a file, see MonitorBatch.

simpleMonitor :: Period -> Monitor a Source #

Only monitor prior, likelihood and posterior functions with given period. Do not monitor parameters.

Priors, likelihoods, Jacobians, and posteriors

module Mcmc.Prior

Run MCMC samplers

mcmc :: Algorithm a => Settings -> a -> IO a Source #

Run an MCMC algorithm with given settings.

mcmcContinue :: Algorithm a => Iterations -> Settings -> a -> IO a Source #

Continue an MCMC algorithm for the given number of iterations.

Currently, it is only possible to continue MCMC algorithms that have completed successfully. This restriction is necessary, because for parallel chains, it is hardly possible to ensure all chains are synchronized when the process is killed or fails.

See:

See also settingsLoad, mhgLoad, and mc3Load.

Algorithms

Marginal likelihood calculation

Types used in statistics

Useful re-exports

newtype Log a #

Log-domain Float and Double values.

Constructors

Exp 

Fields

Instances

Instances details
Foldable Log 
Instance details

Defined in Numeric.Log

Methods

fold :: Monoid m => Log m -> m #

foldMap :: Monoid m => (a -> m) -> Log a -> m #

foldMap' :: Monoid m => (a -> m) -> Log a -> m #

foldr :: (a -> b -> b) -> b -> Log a -> b #

foldr' :: (a -> b -> b) -> b -> Log a -> b #

foldl :: (b -> a -> b) -> b -> Log a -> b #

foldl' :: (b -> a -> b) -> b -> Log a -> b #

foldr1 :: (a -> a -> a) -> Log a -> a #

foldl1 :: (a -> a -> a) -> Log a -> a #

toList :: Log a -> [a] #

null :: Log a -> Bool #

length :: Log a -> Int #

elem :: Eq a => a -> Log a -> Bool #

maximum :: Ord a => Log a -> a #

minimum :: Ord a => Log a -> a #

sum :: Num a => Log a -> a #

product :: Num a => Log a -> a #

Eq1 Log 
Instance details

Defined in Numeric.Log

Methods

liftEq :: (a -> b -> Bool) -> Log a -> Log b -> Bool #

Traversable Log 
Instance details

Defined in Numeric.Log

Methods

traverse :: Applicative f => (a -> f b) -> Log a -> f (Log b) #

sequenceA :: Applicative f => Log (f a) -> f (Log a) #

mapM :: Monad m => (a -> m b) -> Log a -> m (Log b) #

sequence :: Monad m => Log (m a) -> m (Log a) #

Applicative Log 
Instance details

Defined in Numeric.Log

Methods

pure :: a -> Log a #

(<*>) :: Log (a -> b) -> Log a -> Log b #

liftA2 :: (a -> b -> c) -> Log a -> Log b -> Log c #

(*>) :: Log a -> Log b -> Log b #

(<*) :: Log a -> Log b -> Log a #

Functor Log 
Instance details

Defined in Numeric.Log

Methods

fmap :: (a -> b) -> Log a -> Log b #

(<$) :: a -> Log b -> Log a #

Monad Log 
Instance details

Defined in Numeric.Log

Methods

(>>=) :: Log a -> (a -> Log b) -> Log b #

(>>) :: Log a -> Log b -> Log b #

return :: a -> Log a #

Serial1 Log 
Instance details

Defined in Numeric.Log

Methods

serializeWith :: MonadPut m => (a -> m ()) -> Log a -> m () #

deserializeWith :: MonadGet m => m a -> m (Log a) #

Comonad Log 
Instance details

Defined in Numeric.Log

Methods

extract :: Log a -> a #

duplicate :: Log a -> Log (Log a) #

extend :: (Log a -> b) -> Log a -> Log b #

ComonadApply Log 
Instance details

Defined in Numeric.Log

Methods

(<@>) :: Log (a -> b) -> Log a -> Log b #

(@>) :: Log a -> Log b -> Log b #

(<@) :: Log a -> Log b -> Log a #

Distributive Log 
Instance details

Defined in Numeric.Log

Methods

distribute :: Functor f => f (Log a) -> Log (f a) #

collect :: Functor f => (a -> Log b) -> f a -> Log (f b) #

distributeM :: Monad m => m (Log a) -> Log (m a) #

collectM :: Monad m => (a -> Log b) -> m a -> Log (m b) #

Foldable1 Log 
Instance details

Defined in Numeric.Log

Methods

fold1 :: Semigroup m => Log m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Log a -> m #

foldMap1' :: Semigroup m => (a -> m) -> Log a -> m #

toNonEmpty :: Log a -> NonEmpty a #

maximum :: Ord a => Log a -> a #

minimum :: Ord a => Log a -> a #

head :: Log a -> a #

last :: Log a -> a #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> Log a -> b #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> Log a -> b #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> Log a -> b #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> Log a -> b #

Hashable1 Log 
Instance details

Defined in Numeric.Log

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Log a -> Int #

Apply Log 
Instance details

Defined in Numeric.Log

Methods

(<.>) :: Log (a -> b) -> Log a -> Log b #

(.>) :: Log a -> Log b -> Log b #

(<.) :: Log a -> Log b -> Log a #

liftF2 :: (a -> b -> c) -> Log a -> Log b -> Log c #

Bind Log 
Instance details

Defined in Numeric.Log

Methods

(>>-) :: Log a -> (a -> Log b) -> Log b #

join :: Log (Log a) -> Log a #

Extend Log 
Instance details

Defined in Numeric.Log

Methods

duplicated :: Log a -> Log (Log a) #

extended :: (Log a -> b) -> Log a -> Log b #

Traversable1 Log 
Instance details

Defined in Numeric.Log

Methods

traverse1 :: Apply f => (a -> f b) -> Log a -> f (Log b) #

sequence1 :: Apply f => Log (f b) -> f (Log b) #

(RealFloat a, Unbox a) => Vector Vector (Log a) 
Instance details

Defined in Numeric.Log

Methods

basicUnsafeFreeze :: Mutable Vector s (Log a) -> ST s (Vector (Log a)) #

basicUnsafeThaw :: Vector (Log a) -> ST s (Mutable Vector s (Log a)) #

basicLength :: Vector (Log a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Log a) -> Vector (Log a) #

basicUnsafeIndexM :: Vector (Log a) -> Int -> Box (Log a) #

basicUnsafeCopy :: Mutable Vector s (Log a) -> Vector (Log a) -> ST s () #

elemseq :: Vector (Log a) -> Log a -> b -> b #

Unbox a => MVector MVector (Log a) 
Instance details

Defined in Numeric.Log

Methods

basicLength :: MVector s (Log a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Log a) -> MVector s (Log a) #

basicOverlaps :: MVector s (Log a) -> MVector s (Log a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (Log a)) #

basicInitialize :: MVector s (Log a) -> ST s () #

basicUnsafeReplicate :: Int -> Log a -> ST s (MVector s (Log a)) #

basicUnsafeRead :: MVector s (Log a) -> Int -> ST s (Log a) #

basicUnsafeWrite :: MVector s (Log a) -> Int -> Log a -> ST s () #

basicClear :: MVector s (Log a) -> ST s () #

basicSet :: MVector s (Log a) -> Log a -> ST s () #

basicUnsafeCopy :: MVector s (Log a) -> MVector s (Log a) -> ST s () #

basicUnsafeMove :: MVector s (Log a) -> MVector s (Log a) -> ST s () #

basicUnsafeGrow :: MVector s (Log a) -> Int -> ST s (MVector s (Log a)) #

Data a => Data (Log a) 
Instance details

Defined in Numeric.Log

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Log a -> c (Log a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Log a) #

toConstr :: Log a -> Constr #

dataTypeOf :: Log a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Log a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Log a)) #

gmapT :: (forall b. Data b => b -> b) -> Log a -> Log a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Log a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Log a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Log a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Log a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Log a -> m (Log a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Log a -> m (Log a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Log a -> m (Log a) #

Storable a => Storable (Log a) 
Instance details

Defined in Numeric.Log

Methods

sizeOf :: Log a -> Int #

alignment :: Log a -> Int #

peekElemOff :: Ptr (Log a) -> Int -> IO (Log a) #

pokeElemOff :: Ptr (Log a) -> Int -> Log a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Log a) #

pokeByteOff :: Ptr b -> Int -> Log a -> IO () #

peek :: Ptr (Log a) -> IO (Log a) #

poke :: Ptr (Log a) -> Log a -> IO () #

RealFloat a => Monoid (Log a) 
Instance details

Defined in Numeric.Log

Methods

mempty :: Log a #

mappend :: Log a -> Log a -> Log a #

mconcat :: [Log a] -> Log a #

RealFloat a => Semigroup (Log a) 
Instance details

Defined in Numeric.Log

Methods

(<>) :: Log a -> Log a -> Log a #

sconcat :: NonEmpty (Log a) -> Log a #

stimes :: Integral b => b -> Log a -> Log a #

(RealFloat a, Enum a) => Enum (Log a) 
Instance details

Defined in Numeric.Log

Methods

succ :: Log a -> Log a #

pred :: Log a -> Log a #

toEnum :: Int -> Log a #

fromEnum :: Log a -> Int #

enumFrom :: Log a -> [Log a] #

enumFromThen :: Log a -> Log a -> [Log a] #

enumFromTo :: Log a -> Log a -> [Log a] #

enumFromThenTo :: Log a -> Log a -> Log a -> [Log a] #

RealFloat a => Floating (Log a) 
Instance details

Defined in Numeric.Log

Methods

pi :: Log a #

exp :: Log a -> Log a #

log :: Log a -> Log a #

sqrt :: Log a -> Log a #

(**) :: Log a -> Log a -> Log a #

logBase :: Log a -> Log a -> Log a #

sin :: Log a -> Log a #

cos :: Log a -> Log a #

tan :: Log a -> Log a #

asin :: Log a -> Log a #

acos :: Log a -> Log a #

atan :: Log a -> Log a #

sinh :: Log a -> Log a #

cosh :: Log a -> Log a #

tanh :: Log a -> Log a #

asinh :: Log a -> Log a #

acosh :: Log a -> Log a #

atanh :: Log a -> Log a #

log1p :: Log a -> Log a #

expm1 :: Log a -> Log a #

log1pexp :: Log a -> Log a #

log1mexp :: Log a -> Log a #

Generic (Log a) 
Instance details

Defined in Numeric.Log

Associated Types

type Rep (Log a) :: Type -> Type #

Methods

from :: Log a -> Rep (Log a) x #

to :: Rep (Log a) x -> Log a #

RealFloat a => Num (Log a) 
Instance details

Defined in Numeric.Log

Methods

(+) :: Log a -> Log a -> Log a #

(-) :: Log a -> Log a -> Log a #

(*) :: Log a -> Log a -> Log a #

negate :: Log a -> Log a #

abs :: Log a -> Log a #

signum :: Log a -> Log a #

fromInteger :: Integer -> Log a #

(Floating a, Read a) => Read (Log a) 
Instance details

Defined in Numeric.Log

RealFloat a => Fractional (Log a) 
Instance details

Defined in Numeric.Log

Methods

(/) :: Log a -> Log a -> Log a #

recip :: Log a -> Log a #

fromRational :: Rational -> Log a #

(RealFloat a, Ord a) => Real (Log a) 
Instance details

Defined in Numeric.Log

Methods

toRational :: Log a -> Rational #

RealFloat a => RealFrac (Log a) 
Instance details

Defined in Numeric.Log

Methods

properFraction :: Integral b => Log a -> (b, Log a) #

truncate :: Integral b => Log a -> b #

round :: Integral b => Log a -> b #

ceiling :: Integral b => Log a -> b #

floor :: Integral b => Log a -> b #

(Floating a, Show a) => Show (Log a) 
Instance details

Defined in Numeric.Log

Methods

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

show :: Log a -> String #

showList :: [Log a] -> ShowS #

Binary a => Binary (Log a) 
Instance details

Defined in Numeric.Log

Methods

put :: Log a -> Put #

get :: Get (Log a) #

putList :: [Log a] -> Put #

Serial a => Serial (Log a) 
Instance details

Defined in Numeric.Log

Methods

serialize :: MonadPut m => Log a -> m () #

deserialize :: MonadGet m => m (Log a) #

Serialize a => Serialize (Log a) 
Instance details

Defined in Numeric.Log

Methods

put :: Putter (Log a) #

get :: Get (Log a) #

NFData a => NFData (Log a) 
Instance details

Defined in Numeric.Log

Methods

rnf :: Log a -> () #

Eq a => Eq (Log a) 
Instance details

Defined in Numeric.Log

Methods

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

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

Ord a => Ord (Log a) 
Instance details

Defined in Numeric.Log

Methods

compare :: Log a -> Log a -> Ordering #

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

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

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

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

max :: Log a -> Log a -> Log a #

min :: Log a -> Log a -> Log a #

Hashable a => Hashable (Log a) 
Instance details

Defined in Numeric.Log

Methods

hashWithSalt :: Int -> Log a -> Int #

hash :: Log a -> Int #

(RealFloat a, Unbox a) => Unbox (Log a) 
Instance details

Defined in Numeric.Log

newtype MVector s (Log a) 
Instance details

Defined in Numeric.Log

newtype MVector s (Log a) = MV_Log (MVector s a)
type Rep (Log a) 
Instance details

Defined in Numeric.Log

type Rep (Log a) = D1 ('MetaData "Log" "Numeric.Log" "log-domain-0.13.2-6SGFvld2wRX6cBg4GUXOqb" 'True) (C1 ('MetaCons "Exp" 'PrefixI 'True) (S1 ('MetaSel ('Just "ln") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
newtype Vector (Log a) 
Instance details

Defined in Numeric.Log

newtype Vector (Log a) = V_Log (Vector a)