Skip to content

Commit

Permalink
Simplify SMC2 instances
Browse files Browse the repository at this point in the history
  • Loading branch information
turion committed May 17, 2023
1 parent 8596ad1 commit 6321c33
Showing 1 changed file with 2 additions and 8 deletions.
10 changes: 2 additions & 8 deletions src/Control/Monad/Bayes/Inference/SMC2.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ module Control.Monad.Bayes.Inference.SMC2
where

import Control.Monad.Bayes.Class
( MonadDistribution (random),
( MonadDistribution,
MonadFactor (..),
MonadMeasure,
)
Expand All @@ -35,20 +35,14 @@ import Numeric.Log (Log)

-- | Helper monad transformer for preprocessing the model for 'smc2'.
newtype SMC2 m a = SMC2 (Sequential (Traced (Population m)) a)
deriving newtype (Functor, Applicative, Monad)
deriving newtype (Functor, Applicative, Monad, MonadDistribution, MonadFactor)

setup :: SMC2 m a -> Sequential (Traced (Population m)) a
setup (SMC2 m) = m

instance MonadTrans SMC2 where
lift = SMC2 . lift . lift . lift

instance MonadDistribution m => MonadDistribution (SMC2 m) where
random = lift random

instance Monad m => MonadFactor (SMC2 m) where
score = SMC2 . score

instance MonadDistribution m => MonadMeasure (SMC2 m)

-- | Sequential Monte Carlo squared.
Expand Down

0 comments on commit 6321c33

Please sign in to comment.