Skip to content

Commit

Permalink
Applicative Population transformer
Browse files Browse the repository at this point in the history
  • Loading branch information
turion committed Jan 3, 2024
1 parent 4035c9a commit 084862f
Show file tree
Hide file tree
Showing 4 changed files with 44 additions and 24 deletions.
1 change: 1 addition & 0 deletions monad-bayes.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -101,6 +101,7 @@ library
Control.Monad.Bayes.Inference.TUI
Control.Monad.Bayes.Integrator
Control.Monad.Bayes.Population
Control.Monad.Bayes.Population.Applicative
Control.Monad.Bayes.Sampler.Lazy
Control.Monad.Bayes.Sampler.Strict
Control.Monad.Bayes.Sequential.Coroutine
Expand Down
21 changes: 3 additions & 18 deletions src/Control/Applicative/List.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,7 @@ module Control.Applicative.List where

-- base
import Control.Applicative
-- transformers
import Control.Monad.Trans.Writer.Strict
import Data.Functor.Compose
-- log-domain
import Numeric.Log (Log)

-- * Applicative ListT

Expand All @@ -17,22 +13,11 @@ import Numeric.Log (Log)
newtype ListT m a = ListT {getListT :: Compose m [] a}
deriving newtype (Functor, Applicative, Alternative)

listT :: m [a] -> ListT m a
listT = ListT . Compose

lift :: (Functor m) => m a -> ListT m a
lift = ListT . Compose . fmap pure

runListT :: ListT m a -> m [a]
runListT = getCompose . getListT

-- * Applicative Population transformer

-- WriterT has to be used instead of WeightedT,
-- since WeightedT uses StateT under the hood,
-- which requires a Monad (ListT m) constraint.
newtype PopulationT m a = PopulationT {getPopulationT :: WriterT (Log Double) (ListT m) a}
deriving newtype (Functor, Applicative, Alternative)

runPopulationT :: PopulationT m a -> m [(a, Log Double)]
runPopulationT = runListT . runWriterT . getPopulationT

fromWeightedList :: m [(a, Log Double)] -> PopulationT m a
fromWeightedList = PopulationT . WriterT . ListT . Compose
17 changes: 11 additions & 6 deletions src/Control/Monad/Bayes/Population.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,6 @@ module Control.Monad.Bayes.Population
where

import Control.Applicative (Alternative)
import Control.Applicative.List qualified as ApplicativeListT
import Control.Arrow (second)
import Control.Monad (MonadPlus, replicateM)
import Control.Monad.Bayes.Class
Expand All @@ -49,6 +48,7 @@ import Control.Monad.Bayes.Class
MonadMeasure,
factor,
)
import Control.Monad.Bayes.Population.Applicative qualified as Applicative
import Control.Monad.Bayes.Weighted
( WeightedT,
applyWeight,
Expand All @@ -70,6 +70,11 @@ import Numeric.Log qualified as Log
import Prelude hiding (all, sum)

-- | A collection of weighted samples, or particles.
--
-- This monad transformer is internally represented as a free monad,
-- which means that each layer of its computation contains a collection of weighted samples.
-- These can be flattened with 'flatten',
-- but the result is not a monad anymore.
newtype PopulationT m a = PopulationT {getPopulationT :: WeightedT (FreeT [] m) a}
deriving newtype (Functor, Applicative, Alternative, Monad, MonadIO, MonadPlus, MonadDistribution, MonadFactor, MonadMeasure)

Expand Down Expand Up @@ -278,12 +283,12 @@ hoist ::
PopulationT n a
hoist f = PopulationT . Weighted.hoist (hoistFreeT f) . getPopulationT

-- | Flatten all layers of the free structure
flatten :: (Monad m) => PopulationT m a -> ApplicativeListT.PopulationT m a
flatten = ApplicativeListT.fromWeightedList . runPopulationT
-- | Flatten all layers of the free structure.
flatten :: (Monad m) => PopulationT m a -> Applicative.PopulationT m a
flatten = Applicative.fromWeightedList . runPopulationT

-- | Create a population from a single layer of branching computations.
--
-- Similar to 'fromWeightedListT'.
single :: (Monad m) => ApplicativeListT.PopulationT m a -> PopulationT m a
single = fromWeightedList . ApplicativeListT.runPopulationT
single :: (Monad m) => Applicative.PopulationT m a -> PopulationT m a
single = fromWeightedList . Applicative.runPopulationT
29 changes: 29 additions & 0 deletions src/Control/Monad/Bayes/Population/Applicative.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,29 @@
-- | 'PopulationT' turns a single sample into a collection of weighted samples.
--
-- This module contains an _'Applicative'_ transformer corresponding to the Population monad transformer from the article.
-- It is based on the old-fashioned 'ListT', which is not a valid monad transformer, but a valid applicative transformer.
-- The corresponding monad transformer is contained in 'Control.Monad.Bayes.Population'.
-- One can convert from the monad transformer to the applicative transformer by 'flatten'ing.
module Control.Monad.Bayes.Population.Applicative where

import Control.Applicative
import Control.Applicative.List
import Control.Monad.Trans.Writer.Strict
import Data.Functor.Compose
import Numeric.Log (Log)

-- * Applicative Population transformer

-- WriterT has to be used instead of WeightedT,
-- since WeightedT uses StateT under the hood,
-- which requires a Monad (ListT m) constraint.

-- | A collection of weighted samples, or particles.
newtype PopulationT m a = PopulationT {getPopulationT :: WriterT (Log Double) (ListT m) a}
deriving newtype (Functor, Applicative, Alternative)

runPopulationT :: PopulationT m a -> m [(a, Log Double)]
runPopulationT = runListT . runWriterT . getPopulationT

fromWeightedList :: m [(a, Log Double)] -> PopulationT m a
fromWeightedList = PopulationT . WriterT . listT

0 comments on commit 084862f

Please sign in to comment.