monad-memo-0.1.0: Memoization monad transformer

Portabilitynon-portable (multi-param classes, functional dependencies)
Stabilityexperimental
Maintainereduard.sergeev@gmail.com

Control.Monad.Memo

Contents

Description

Computation type:
Monadic computations with support for memoization.

Defines monadic interface MonadMemo for memoization and simple implementation MemoT (based on Data.Map)

Synopsis

MonadMemo class

class Monad m => MonadMemo k v m | m -> k, m -> v whereSource

Methods

memo :: (k -> m v) -> k -> m vSource

Instances

MonadMemo k [v] m => MonadMemo k v (ListT m) 
MonadCache k (Maybe v) m => MonadMemo k v (MaybeT m) 
MonadCache k v m => MonadMemo k v (IdentityT m) 
MonadCache (s, k) v m => MonadMemo k v (StateT s m) 
MonadCache (s, k) v m => MonadMemo k v (StateT s m) 
(Monoid w, MonadCache k (v, w) m) => MonadMemo k v (WriterT w m) 
(Monoid w, MonadCache k (v, w) m) => MonadMemo k v (WriterT w m) 
MonadCache (r, k) v m => MonadMemo k v (ReaderT r m) 
(Error e, MonadCache k (Either e v) m) => MonadMemo k v (ErrorT e m) 
MonadCache k v m => MonadMemo k v (ContT r m) 
(Monad m, Ord k) => MonadMemo k v (MemoT k v m) 

The Memo monad

type Memo k v = MemoT k v IdentitySource

runMemo :: Memo k v a -> Map k v -> (a, Map k v)Source

evalMemo :: Memo k v a -> Map k v -> aSource

startRunMemo :: Memo k v a -> (a, Map k v)Source

The MemoT monad transformer

newtype MemoT k v m a Source

Constructors

MemoT 

Fields

toStateT :: StateT (Map k v) m a
 

Instances

(Monad m, Ord k) => MonadMemo k v (MemoT k v m) 
(Monad m, Ord k) => MonadCache k v (MemoT k v m) 
MonadTrans (MemoT k v) 
Monad m => Monad (MemoT k v m) 
Functor m => Functor (MemoT k v m) 
MonadFix m => MonadFix (MemoT k v m) 
MonadPlus m => MonadPlus (MemoT k v m) 
(Functor m, Monad m) => Applicative (MemoT k v m) 
(Functor m, MonadPlus m) => Alternative (MemoT k v m) 
MonadIO m => MonadIO (MemoT k v m) 

runMemoT :: MemoT k v m a -> Map k v -> m (a, Map k v)Source

evalMemoT :: Monad m => MemoT k v m a -> Map k v -> m aSource

startRunMemoT :: MemoT k v m a -> m (a, Map k v)Source

startEvalMemoT :: Monad m => MemoT k v m a -> m aSource

Memoization cache level access functions

memoln :: (MonadCache k2 v m1, Monad m1, Monad m2) => (forall a. m1 a -> m2 a) -> (k1 -> k2) -> (k1 -> m2 v) -> k1 -> m2 vSource

memol0 :: (MonadCache k v m, Monad m) => (k -> m v) -> k -> m vSource

Uses current monad's memoization cache

memol1 :: (MonadTrans t1, MonadCache k v m, Monad (t1 m)) => (k -> t1 m v) -> k -> t1 m vSource

Uses the 1st transformer in stack for memoization cache

memol2 :: (MonadTrans t1, MonadTrans t2, MonadCache k v m, Monad (t2 m), Monad (t1 (t2 m))) => (k -> t1 (t2 m) v) -> k -> t1 (t2 m) vSource

Uses the 2nd transformer in stack for memoization cache

memol3 :: (MonadTrans t1, MonadTrans t2, MonadTrans t3, MonadCache k v m, Monad (t3 m), Monad (t2 (t3 m)), Monad (t1 (t2 (t3 m)))) => (k -> t1 (t2 (t3 m)) v) -> k -> t1 (t2 (t3 m)) vSource

Uses the 3rd transformer in stack for memoization cache

memol4 :: (MonadTrans t1, MonadTrans t2, MonadTrans t3, MonadTrans t4, MonadCache k v m, Monad (t4 m), Monad (t3 (t4 m)), Monad (t2 (t3 (t4 m))), Monad (t1 (t2 (t3 (t4 m))))) => (k -> t1 (t2 (t3 (t4 m))) v) -> k -> t1 (t2 (t3 (t4 m))) vSource

Uses the 4th transformer in stack for memoization cache

Example 1: Fibonacci numbers

Memoization can be specified whenever monadic computation is taking place. Including recursive definition. Classic example: Fibonacci number function: Here is simple non-monadic definition of it

fib :: (Num n) => n -> n
fib 0 = 0
fib 1 = 1
fib n = fib (n-1) + fib (n-2)

To use Memo monad we need to convert it into monadic form:

fibm :: (Num n, Monad m) => n -> m n
fibm 0 = return 0
fibm 1 = return 1
fibm n = do
  n1 <- fibm (n-1)
  n2 <- fibm (n-2)
  return (n1+n2)

Then we can specify which computation we want to memoize with memo (both recursive calls to (n-1) and (n-2)):

fibm :: (Num n, Ord n) => n -> Memo n n n
fibm 0 = return 0
fibm 1 = return 1
fibm n = do
  n1 <- fibm `memo` (n-1)
  n2 <- fibm `memo` (n-2)
  return (n1+n2)

NB: Ord is required since internaly Memo implementation uses Data.Map to store and lookup memoized values

Then it can be run with startEvalMemo

startEvalMemo . fibm $ 5

Example 2: Mutualy recursive definition with memoization

In order to use memoization for both mutually recursive function we need to use nested MemoT monad transformers (one for each cache). Let's extend our Fibonacci function with meaningless extra function boo which in turn uses fibm2.

Memoization cache type for fibm2 (caches Integer -> Integer) will be:

type MemoFib = MemoT Integer Integer

While cache for boo (Double -> String):

type MemoBoo = MemoT Double String

Stacking them together gives us te overall type for our combined memoization monad:

type MemoFB = MemoFib (MemoBoo Identity)
boo :: Double -> MemoFB String
boo 0 = "boo: 0" `trace` return ""
boo n = ("boo: " ++ show n) `trace` do
  n1 <- boo `memol1` (n-1)         -- uses next in stack transformer (memol_1_): MemoBoo is nested in MemoFib
  f <- fibm2 `memol0` floor (n-1)  -- uses current transformer (memol_0_): MemoFib
  return (show n ++ show f)
fibm2 :: Integer -> MemoFB Integer 
fibm2 0 = "fib: 0" `trace` return 0
fibm2 1 = "fib: 1" `trace` return 1
fibm2 n = ("fib: " ++ show n) `trace` do
  l <- boo `memol1` fromInteger n  -- as in 'boo' we need to use 1st nested transformer here
  f1 <- fibm2 `memol0` (n-1)       -- as in 'boo' we need to use 1st nested transformer here
  f2 <- fibm2 `memol0` (n-2)       --
  return (f1 + f2 + floor (read l))
evalFibM2 = startEvalMemo . startEvalMemoT . fibm2

Example 3: Combining Memo with other transformers

Being transformer, MemoT can be used with other monads and transformers:

With Writer:

fibmw 0 = return 0
fibmw 1 = return 1
fibmw n = do
  f1 <- fibmw `memo` (n-1)
  f2 <- fibmw `memo` (n-2)
  tell $ show n
  return (f1+f2)
evalFibmw = startEvalMemo . runWriterT . fibmw