Copyright | (c) Adam Scibior 2015-2020 |
---|---|
License | MIT |
Maintainer | leonhard.markert@tweag.io |
Stability | experimental |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module defines MonadMeasure
, which can be used to represent any probabilistic program,
such as the following:
import Control.Monad (when) import Control.Monad.Bayes.Class model :: MonadMeasure m => m Bool model = do rain <- bernoulli 0.3 sprinkler <- bernoulli $ if rain then 0.1 else 0.4 let wetProb = case (rain, sprinkler) of (True, True) -> 0.98 (True, False) -> 0.80 (False, True) -> 0.90 (False, False) -> 0.00 score wetProb return rain
Synopsis
- class Monad m => MonadDistribution m
- random :: MonadDistribution m => m Double
- uniform :: MonadDistribution m => Double -> Double -> m Double
- normal :: MonadDistribution m => Double -> Double -> m Double
- gamma :: MonadDistribution m => Double -> Double -> m Double
- beta :: MonadDistribution m => Double -> Double -> m Double
- bernoulli :: MonadDistribution m => Double -> m Bool
- categorical :: (MonadDistribution m, Vector v Double) => v Double -> m Int
- logCategorical :: (MonadDistribution m, Vector v (Log Double), Vector v Double) => v (Log Double) -> m Int
- uniformD :: MonadDistribution m => [a] -> m a
- geometric :: MonadDistribution m => Double -> m Int
- poisson :: MonadDistribution m => Double -> m Int
- dirichlet :: (MonadDistribution m, Vector v Double) => v Double -> m (v Double)
- class Monad m => MonadFactor m
- score :: MonadFactor m => Log Double -> m ()
- factor :: MonadFactor m => Log Double -> m ()
- condition :: MonadFactor m => Bool -> m ()
- class (MonadDistribution m, MonadFactor m) => MonadMeasure m
- discrete :: (DiscreteDistr d, MonadDistribution m) => d -> m Int
- normalPdf :: Double -> Double -> Double -> Log Double
- data Bayesian m z o = Bayesian {
- prior :: m z
- generative :: z -> m o
- likelihood :: z -> o -> Log Double
- poissonPdf :: Double -> Integer -> Log Double
- posterior :: (MonadMeasure m, Foldable f, Functor f) => Bayesian m z o -> f o -> m z
- priorPredictive :: Monad m => Bayesian m a b -> m b
- posteriorPredictive :: (MonadMeasure m, Foldable f, Functor f) => Bayesian m a b -> f b -> m b
- independent :: Applicative m => Int -> m a -> m [a]
- mvNormal :: MonadDistribution m => Vector Double -> Matrix Double -> m (Vector Double)
- type Histogram = Histogram BinD Double
- histogram :: Int -> [(Double, Log Double)] -> Histogram
- histogramToList :: Histogram -> [(Double, Double)]
- type Distribution a = forall m. MonadDistribution m => m a
- type Measure a = forall m. MonadMeasure m => m a
- type Kernel a b = forall m. MonadMeasure m => a -> m b
- newtype Log a = Exp {
- ln :: a
Documentation
class Monad m => MonadDistribution m Source #
Monads that can draw random variables.
Instances
:: MonadDistribution m | |
=> m Double | \(\sim \mathcal{U}(0, 1)\) |
Draw from a uniform distribution.
:: MonadDistribution m | |
=> Double | lower bound a |
-> Double | upper bound b |
-> m Double | \(\sim \mathcal{U}(a, b)\). |
Draw from a uniform distribution.
:: MonadDistribution m | |
=> Double | mean μ |
-> Double | standard deviation σ |
-> m Double | \(\sim \mathcal{N}(\mu, \sigma^2)\) |
Draw from a normal distribution.
:: MonadDistribution m | |
=> Double | shape k |
-> Double | scale θ |
-> m Double | \(\sim \Gamma(k, \theta)\) |
Draw from a gamma distribution.
:: MonadDistribution m | |
=> Double | shape α |
-> Double | shape β |
-> m Double | \(\sim \mathrm{Beta}(\alpha, \beta)\) |
Draw from a beta distribution.
:: MonadDistribution m | |
=> Double | probability p |
-> m Bool | \(\sim \mathrm{B}(1, p)\) |
Draw from a Bernoulli distribution.
:: (MonadDistribution m, Vector v Double) | |
=> v Double | event probabilities |
-> m Int | outcome category |
Draw from a categorical distribution.
:: (MonadDistribution m, Vector v (Log Double), Vector v Double) | |
=> v (Log Double) | event probabilities |
-> m Int | outcome category |
Draw from a categorical distribution in the log domain.
:: MonadDistribution m | |
=> [a] | observable outcomes |
-> m a | \(\sim \mathcal{U}\{\mathrm{xs}\}\) |
Draw from a discrete uniform distribution.
:: MonadDistribution m | |
=> Double | success rate p |
-> m Int | \(\sim\) number of failed Bernoulli trials with success probability p before first success |
Draw from a geometric distribution.
:: MonadDistribution m | |
=> Double | parameter λ |
-> m Int | \(\sim \mathrm{Pois}(\lambda)\) |
Draw from a Poisson distribution.
:: (MonadDistribution m, Vector v Double) | |
=> v Double | concentration parameters |
-> m (v Double) | \(\sim \mathrm{Dir}(\mathrm{as})\) |
Draw from a Dirichlet distribution.
class Monad m => MonadFactor m Source #
Monads that can score different execution paths.
Instances
MonadFactor Enumerator Source # | |
Defined in Control.Monad.Bayes.Enumerator | |
Monad m => MonadFactor (SMC2 m) Source # | |
Monad m => MonadFactor (Population m) Source # | |
Defined in Control.Monad.Bayes.Population | |
MonadFactor m => MonadFactor (Sequential m) Source # | |
Defined in Control.Monad.Bayes.Sequential.Coroutine | |
MonadFactor m => MonadFactor (Traced m) Source # | |
MonadFactor m => MonadFactor (Traced m) Source # | |
MonadFactor m => MonadFactor (Traced m) Source # | |
Monad m => MonadFactor (Weighted m) Source # | |
MonadFactor m => MonadFactor (ListT m) Source # | |
MonadFactor m => MonadFactor (ExceptT e m) Source # | |
MonadFactor m => MonadFactor (IdentityT m) Source # | |
MonadFactor m => MonadFactor (ReaderT r m) Source # | |
MonadFactor m => MonadFactor (StateT s m) Source # | |
(Monoid w, MonadFactor m) => MonadFactor (WriterT w m) Source # | |
MonadFactor m => MonadFactor (ContT r m) Source # | |
:: MonadFactor m | |
=> Log Double | likelihood of the execution path |
-> m () |
Record a likelihood.
:: MonadFactor m | |
=> Log Double | likelihood of the execution path |
-> m () |
Synonym for score
.
condition :: MonadFactor m => Bool -> m () Source #
Hard conditioning.
class (MonadDistribution m, MonadFactor m) => MonadMeasure m Source #
Monads that support both sampling and scoring.
Instances
discrete :: (DiscreteDistr d, MonadDistribution m) => d -> m Int Source #
Draw from a discrete distributions using the probability mass function.
:: Double | mean μ |
-> Double | standard deviation σ |
-> Double | sample x |
-> Log Double | relative likelihood of observing sample x in \(\mathcal{N}(\mu, \sigma^2)\) |
Probability density function of the normal distribution.
a useful datatype for expressing bayesian models
Bayesian | |
|
priorPredictive :: Monad m => Bayesian m a b -> m b Source #
posteriorPredictive :: (MonadMeasure m, Foldable f, Functor f) => Bayesian m a b -> f b -> m b Source #
independent :: Applicative m => Int -> m a -> m [a] Source #
mvNormal :: MonadDistribution m => Vector Double -> Matrix Double -> m (Vector Double) Source #
multivariate normal
type Distribution a = forall m. MonadDistribution m => m a Source #
synonym for pretty type signatures, but note that (A -> Distribution B) won't work as intended: for that, use Kernel Also note that the use of RankNTypes means performance may take a hit: really the main point of these signatures is didactic
type Measure a = forall m. MonadMeasure m => m a Source #
type Kernel a b = forall m. MonadMeasure m => a -> m b Source #
Log
-domain Float
and Double
values.
Instances
Foldable Log | |
Defined in Numeric.Log 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 # elem :: Eq a => a -> Log a -> Bool # maximum :: Ord a => Log a -> a # | |
Eq1 Log | |
Traversable Log | |
Applicative Log | |
Functor Log | |
Monad Log | |
Serial1 Log | |
Defined in Numeric.Log serializeWith :: MonadPut m => (a -> m ()) -> Log a -> m () # deserializeWith :: MonadGet m => m a -> m (Log a) # | |
Comonad Log | |
ComonadApply Log | |
Distributive Log | |
Foldable1 Log | |
Defined in Numeric.Log 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 # 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 | |
Defined in Numeric.Log | |
Apply Log | |
Bind Log | |
Extend Log | |
Traversable1 Log | |
(RealFloat a, Unbox a) => Vector Vector (Log a) | |
Defined in Numeric.Log basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Log a) -> m (Vector (Log a)) # basicUnsafeThaw :: PrimMonad m => Vector (Log a) -> m (Mutable Vector (PrimState m) (Log a)) # basicLength :: Vector (Log a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Log a) -> Vector (Log a) # basicUnsafeIndexM :: Monad m => Vector (Log a) -> Int -> m (Log a) # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Log a) -> Vector (Log a) -> m () # | |
Unbox a => MVector MVector (Log a) | |
Defined in Numeric.Log 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 :: PrimMonad m => Int -> m (MVector (PrimState m) (Log a)) # basicInitialize :: PrimMonad m => MVector (PrimState m) (Log a) -> m () # basicUnsafeReplicate :: PrimMonad m => Int -> Log a -> m (MVector (PrimState m) (Log a)) # basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Log a) -> Int -> m (Log a) # basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Log a) -> Int -> Log a -> m () # basicClear :: PrimMonad m => MVector (PrimState m) (Log a) -> m () # basicSet :: PrimMonad m => MVector (PrimState m) (Log a) -> Log a -> m () # basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Log a) -> MVector (PrimState m) (Log a) -> m () # basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Log a) -> MVector (PrimState m) (Log a) -> m () # basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Log a) -> Int -> m (MVector (PrimState m) (Log a)) # | |
Data a => Data (Log a) | |
Defined in Numeric.Log 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) # 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) | |
RealFloat a => Monoid (Log a) | |
RealFloat a => Semigroup (Log a) | |
(RealFloat a, Enum a) => Enum (Log a) | |
RealFloat a => Floating (Log a) | |
Generic (Log a) | |
RealFloat a => Num (Log a) | |
(Floating a, Read a) => Read (Log a) | |
RealFloat a => Fractional (Log a) | |
(RealFloat a, Ord a) => Real (Log a) | |
Defined in Numeric.Log toRational :: Log a -> Rational # | |
RealFloat a => RealFrac (Log a) | |
(Floating a, Show a) => Show (Log a) | |
Binary a => Binary (Log a) | |
Serial a => Serial (Log a) | |
Defined in Numeric.Log | |
Serialize a => Serialize (Log a) | |
NFData a => NFData (Log a) | |
Defined in Numeric.Log | |
Eq a => Eq (Log a) | |
Ord a => Ord (Log a) | |
Hashable a => Hashable (Log a) | |
Defined in Numeric.Log | |
(RealFloat a, Unbox a) => Unbox (Log a) | |
Defined in Numeric.Log | |
newtype MVector s (Log a) | |
Defined in Numeric.Log | |
type Rep (Log a) | |
Defined in Numeric.Log | |
newtype Vector (Log a) | |
Defined in Numeric.Log |