Skip to content

Commit 084862f

Browse files
committed
Applicative Population transformer
1 parent 4035c9a commit 084862f

File tree

4 files changed

+44
-24
lines changed

4 files changed

+44
-24
lines changed

monad-bayes.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -101,6 +101,7 @@ library
101101
Control.Monad.Bayes.Inference.TUI
102102
Control.Monad.Bayes.Integrator
103103
Control.Monad.Bayes.Population
104+
Control.Monad.Bayes.Population.Applicative
104105
Control.Monad.Bayes.Sampler.Lazy
105106
Control.Monad.Bayes.Sampler.Strict
106107
Control.Monad.Bayes.Sequential.Coroutine

src/Control/Applicative/List.hs

Lines changed: 3 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -4,11 +4,7 @@ module Control.Applicative.List where
44

55
-- base
66
import Control.Applicative
7-
-- transformers
8-
import Control.Monad.Trans.Writer.Strict
97
import Data.Functor.Compose
10-
-- log-domain
11-
import Numeric.Log (Log)
128

139
-- * Applicative ListT
1410

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

16+
listT :: m [a] -> ListT m a
17+
listT = ListT . Compose
18+
2019
lift :: (Functor m) => m a -> ListT m a
2120
lift = ListT . Compose . fmap pure
2221

2322
runListT :: ListT m a -> m [a]
2423
runListT = getCompose . getListT
25-
26-
-- * Applicative Population transformer
27-
28-
-- WriterT has to be used instead of WeightedT,
29-
-- since WeightedT uses StateT under the hood,
30-
-- which requires a Monad (ListT m) constraint.
31-
newtype PopulationT m a = PopulationT {getPopulationT :: WriterT (Log Double) (ListT m) a}
32-
deriving newtype (Functor, Applicative, Alternative)
33-
34-
runPopulationT :: PopulationT m a -> m [(a, Log Double)]
35-
runPopulationT = runListT . runWriterT . getPopulationT
36-
37-
fromWeightedList :: m [(a, Log Double)] -> PopulationT m a
38-
fromWeightedList = PopulationT . WriterT . ListT . Compose

src/Control/Monad/Bayes/Population.hs

Lines changed: 11 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,6 @@ module Control.Monad.Bayes.Population
4040
where
4141

4242
import Control.Applicative (Alternative)
43-
import Control.Applicative.List qualified as ApplicativeListT
4443
import Control.Arrow (second)
4544
import Control.Monad (MonadPlus, replicateM)
4645
import Control.Monad.Bayes.Class
@@ -49,6 +48,7 @@ import Control.Monad.Bayes.Class
4948
MonadMeasure,
5049
factor,
5150
)
51+
import Control.Monad.Bayes.Population.Applicative qualified as Applicative
5252
import Control.Monad.Bayes.Weighted
5353
( WeightedT,
5454
applyWeight,
@@ -70,6 +70,11 @@ import Numeric.Log qualified as Log
7070
import Prelude hiding (all, sum)
7171

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

@@ -278,12 +283,12 @@ hoist ::
278283
PopulationT n a
279284
hoist f = PopulationT . Weighted.hoist (hoistFreeT f) . getPopulationT
280285

281-
-- | Flatten all layers of the free structure
282-
flatten :: (Monad m) => PopulationT m a -> ApplicativeListT.PopulationT m a
283-
flatten = ApplicativeListT.fromWeightedList . runPopulationT
286+
-- | Flatten all layers of the free structure.
287+
flatten :: (Monad m) => PopulationT m a -> Applicative.PopulationT m a
288+
flatten = Applicative.fromWeightedList . runPopulationT
284289

285290
-- | Create a population from a single layer of branching computations.
286291
--
287292
-- Similar to 'fromWeightedListT'.
288-
single :: (Monad m) => ApplicativeListT.PopulationT m a -> PopulationT m a
289-
single = fromWeightedList . ApplicativeListT.runPopulationT
293+
single :: (Monad m) => Applicative.PopulationT m a -> PopulationT m a
294+
single = fromWeightedList . Applicative.runPopulationT
Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,29 @@
1+
-- | 'PopulationT' turns a single sample into a collection of weighted samples.
2+
--
3+
-- This module contains an _'Applicative'_ transformer corresponding to the Population monad transformer from the article.
4+
-- It is based on the old-fashioned 'ListT', which is not a valid monad transformer, but a valid applicative transformer.
5+
-- The corresponding monad transformer is contained in 'Control.Monad.Bayes.Population'.
6+
-- One can convert from the monad transformer to the applicative transformer by 'flatten'ing.
7+
module Control.Monad.Bayes.Population.Applicative where
8+
9+
import Control.Applicative
10+
import Control.Applicative.List
11+
import Control.Monad.Trans.Writer.Strict
12+
import Data.Functor.Compose
13+
import Numeric.Log (Log)
14+
15+
-- * Applicative Population transformer
16+
17+
-- WriterT has to be used instead of WeightedT,
18+
-- since WeightedT uses StateT under the hood,
19+
-- which requires a Monad (ListT m) constraint.
20+
21+
-- | A collection of weighted samples, or particles.
22+
newtype PopulationT m a = PopulationT {getPopulationT :: WriterT (Log Double) (ListT m) a}
23+
deriving newtype (Functor, Applicative, Alternative)
24+
25+
runPopulationT :: PopulationT m a -> m [(a, Log Double)]
26+
runPopulationT = runListT . runWriterT . getPopulationT
27+
28+
fromWeightedList :: m [(a, Log Double)] -> PopulationT m a
29+
fromWeightedList = PopulationT . WriterT . listT

0 commit comments

Comments
 (0)