1# monad-memo
2[![Build Status](https://github.com/EduardSergeev/monad-memo/workflows/master/badge.svg)](https://github.com/EduardSergeev/monad-memo/actions?query=workflow%3Amaster+branch%3Amaster)
3[![Test Coverage](https://coveralls.io/repos/github/EduardSergeev/monad-memo/badge.svg)](https://coveralls.io/github/EduardSergeev/monad-memo)
4[![Hackage](https://img.shields.io/hackage/v/monad-memo.svg)](https://hackage.haskell.org/package/monad-memo)
5
6## Purpose
7This package provides a convenient mechanism for adding memoization to Haskell monadic functions.
8
9## Memoization
10Memoization is a well known way to speed up function evaluation by caching previously calculated results and reusing them whenever a memoized function is needed to be evaluated with the same arguments again.
11It is usually associated with dynamic programming techiques.
12
13## Overview
14Even though it is possible to manually add memoization to the code which would benefit from it, this ad-hoc approach has usual ad-hoc drawbacks: code pollution, bugs, resistance to changes.
15This package however encapsulates the underlying plumbing behind its simple monadic interface `MonadMemo` with a single combinator `memo` which, when applied to monadic function, turns it into "memoized" one.
16
17The package offers various implementation of `MonadMemo` (which differs in terms of performance and requirements) and it is possible to choose/change the implementation without affecting the main function code.
18The range of supported implementations "out of box" is limited by the range of containers provided by the standard packages installed by [Haskel Platform](http://www.haskell.org/platform/):
19from default pure "fit them all" [Data.Map](http://hackage.haskell.org/packages/archive/containers/latest/doc/html/Data-Map.html) to very fast but limiting [vector](http://hackage.haskell.org/packages/archive/vector/latest/doc/html/Data-Vector-Generic-Mutable.html).
20It is also possible to plug-in a custom container (from a third-party library) and run existing monadic code with it.
21
22The default implementation of `MonadMemo` is also [monad transformer](http://en.wikibooks.org/wiki/Haskell/Monad_transformers) so it can be "mixed" with other monads.
23The package also provides the "memoized" versions of most standard monads found in [mtl](http://hackage.haskell.org/package/mtl).
24
25## Example of usage
26
27A clasic example of function which greatelly benefits from memoization is a recursively defined Fibonacci number function.
28A plain version of this function can be written in the following way:
29```haskell
30fib :: Integer -> Integer
31fib 0 = 0
32fib 1 = 1
33fib n = fib (n-1) + fib (n-2)
34```
35which is very inefficient (impractical for `n>40`).
36
37We can rewrite this definition as a monad:
38```haskell
39fibm :: Monad m => Integer -> m Integer
40fibm 0 = return 0
41fibm 1 = return 1
42fibm n = do
43  f1 <- fibm (n-1)
44  f2 <- fibm (n-2)
45  return (f1+f2)
46```
47and even run it with `Identity` monad with identical inefficiency:
48```haskell
49evalFibmId :: Integer -> Integer
50evalFibmId = runIdentity . fibm
51```
52
53But all we need to do to make this function "computable" for reasonable argument is to add memoization for both recursive branches with `memo` combinator:
54```haskell
55fibm :: (MonadMemo Integer Integer m) => Integer -> m Integer
56fibm 0 = return 0
57fibm 1 = return 1
58fibm n = do
59  f1 <- memo fibm (n-1)
60  f2 <- memo fibm (n-2)
61  return (f1+f2)
62```
63then, to evaluate it with default `Data.Map` based memoization cache we use the following "eval*" function:
64```haskell
65evalFibm :: Integer -> Integer
66evalFibm = startEvalMemo . fibm
67```
68Now the range of the arguments it can handle is limited only by `Integer` computation complexity and stack memory limit.
69
70## More Examples
71
72### Slightly more complicated recursive function
73Well known [Ackerman function](http://en.wikipedia.org/wiki/Ackermann_function) is a two arguments function.
74To memoize two argument function `for2` combinator can be used, giving the following generic code:
75
76```haskell
77ackm :: (Num n, Ord n, MonadMemo (n, n) n m) => n -> n -> m n
78ackm 0 n = return (n+1)
79ackm m 0 = for2 memo ackm (m-1) 1
80ackm m n = do
81  n1 <- for2 memo ackm m (n-1)    -- 'for2' adapts 'memo' for 2-argument 'ackm'
82  for2 memo ackm (m-1) n1
83
84evalAckm :: (Num n, Ord n) => n -> n -> n
85evalAckm n m = startEvalMemo $ ackm n m
86```
87
88### Mutually recursive function memoization
89This example is taken from paper ["Monadic Memoization Mixins" by Daniel Brown and William R. Cook](http://www.cs.utexas.edu/~wcook/Drafts/2006/MemoMixins.pdf)
90
91Given the following mutually recursive function definitions:
92
93```haskell
94-- 'f' depends on 'g'
95f :: Int -> (Int,String)
96f 0 = (1,"+")
97f (n+1)	=(g(n,fst(f n)),"-" ++ snd(f n))
98
99-- 'g' depends on 'f'
100g :: (Int, Int) -> Int
101g (0, m)  = m + 1
102g (n+1,m) = fst(f n)-g(n,m)
103```
104
105How can we memoize both functions?
106
107Lets try to just add [memo](http://hackage.haskell.org/packages/archive/monad-memo/latest/doc/html/Control-Monad-Memo.html#v:memo) for both functions:
108
109```haskell
110-- WRONG: Will NOT compile!
111fm 0 = return (1,"+")
112fm (n+1) = do
113  fn <- memo fm n
114  gn <- memo gm (n , fst fn)
115  return (gn , "-" ++ snd fn)
116
117gm (0,m) = return (m+1)
118gm (n+1,m) = do
119  fn <- memo fm n
120  gn <- memo gm (n,m)
121  return $ fst fn - gn
122```
123
124GHC complains:
125
126    "Occurs check: cannot construct the infinite type: t = (t, v)
127         Expected type: t
128
129         Inferred type: (t, v)"
130
131which is understandable since we are trying to use the same cache for storing "key-value" pairs of the functions of different types (`fm :: Int -> m (Int,String)` and `gm :: (Int, Int) -> m Int`).
132Obviously, to cache both function we will need _two_ caches (even if the types of the functions were identical, it's not very good idea to share the same cache).
133And this is precisely what we have to do - use two memoization caches! The way to achieve it is to use _two_ [MemoT](http://hackage.haskell.org/packages/archive/monad-memo/latest/doc/html/Control-Monad-Memo.html#t:MemoT) monad transformers one nested in another:
134
135```haskell
136-- Memo-cache for 'fm'
137type MemoF = MemoT Int (Int,String)
138-- Memo-cache for 'gm'
139type MemoG = MemoT (Int,Int) Int
140
141-- | Combined stack of caches (transformers)
142-- Stacks two 'MemoT' transformers in one monad to be used in both 'gm' and 'fm' monadic functions
143type MemoFG = MemoF (MemoG Identity)
144```
145
146NB As usually with Haskell it isn't necessary to specify types here (or restrict them to [MemoT](http://hackage.haskell.org/packages/archive/monad-memo/latest/doc/html/Control-Monad-Memo.html#t:MemoT) combinations for the given example).
147
148Then, a little bit of complication, since we use _two_ caches now (one from the current [monad transformer](http://en.wikibooks.org/wiki/Haskell/Monad_transformers) and another from the next, nested in the current) we need to use *memol_X_* set of functions: [memol0](http://hackage.haskell.org/packages/archive/monad-memo/latest/doc/html/Control-Monad-Memo.html#v:memol0), [memol1](http://hackage.haskell.org/packages/archive/monad-memo/latest/doc/html/Control-Monad-Memo.html#v:memol1) etc. Where _X_ specifies "sequential number" of the transformer in stack for a given cache (starting from the current). Here we use the current (0) and the next (1) for `fm` and `gm` respectively:
149
150```haskell
151fm :: Int -> MemoFG (Int,String)
152fm 0 = return (1,"+")
153fm (n+1) = do
154  fn <- memol0 fm n
155  gn <- memol1 gm (n , fst fn)
156  return (gn , "-" ++ snd fn)
157
158gm :: (Int,Int) -> MemoFG Int
159gm (0,m) = return (m+1)
160gm (n+1,m) = do
161  fn <- memol0 fm n
162  gn <- memol1 gm (n,m)
163  return $ fst fn - gn
164
165evalAll = startEvalMemo . startEvalMemoT
166
167-- | Function to run 'fm' computation
168evalFm :: Int -> (Int, String)
169evalFm = evalAll . fm
170
171-- | Function to run 'gm' computation
172evalGm :: (Int,Int) -> Int
173evalGm = evalAll . gm
174```
175
176In fact we can also define 'gm' function in curried form:
177
178```haskell
179fm2 :: Int -> MemoFG (Int,String)
180fm2 0 = return (1,"+")
181fm2 n = do
182  fn <- memol0 fm2 (n-1)
183  gn <- for2 memol1 gm2 (n-1) (fst fn)
184  return (gn , "-" ++ snd fn)
185
186-- 2-argument function now
187gm2 :: Int -> Int -> MemoFG Int
188gm2 0 m = return (m+1)
189gm2 n m = do
190  fn <- memol0 fm2 (n-1)
191  gn <- for2 memol1 gm2 (n-1) m   -- 'for2' adapts 'memol1' for 2-argument gm2
192  return $ fst fn - gn
193
194evalFm2 :: Int -> (Int, String)
195evalFm2 = evalAll . fm2
196
197evalGm2 :: Int -> Int -> Int
198evalGm2 n m = evalAll $ gm2 n m
199```
200
201### Combining MemoT with other monads
202Being monad transformer, memoization monad can be combined with most of existing monads.
203Here we mix it with [MonadWriter](http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Monad-Writer-Class.html#t:MonadWriter):
204
205```haskell
206fibmw :: (Num n, MonadWriter String m, MonadMemo n n m) => n -> m n
207fibmw 0 = tell "0" >> return 0
208fibmw 1 = tell "1" >> return 1
209fibmw n = do
210  f1 <- memo fibmw (n-1)
211  f2 <- memo fibmw (n-2)
212  tell $ show n
213  return (f1+f2)
214
215-- To run combined monad we need to sequence both 'run' functions:
216evalFibmw :: Integer -> (Integer, String)
217evalFibmw = startEvalMemo . runWriterT . fibmw
218
219res = evalFibmw 6  -- > produces (8,"1021310241021351021310246")
220```
221
222## Custom pure cache container
223From monad-memo [version 0.3.0](http://hackage.haskell.org/package/monad-memo-0.3.0) it is possible to replace default [Data.Map](http://hackage.haskell.org/packages/archive/containers/latest/doc/html/Data-Map.html) with another (more efficient?) implementation of internal cache-container
224as long as there is an instance of [Data.MapLike](http://hackage.haskell.org/packages/archive/monad-memo/0.3.0/doc/html/Data-MapLike.html) defined for this container.
225The package currently defines these instances for [Data.Map](http://hackage.haskell.org/packages/archive/containers/latest/doc/html/Data-Map.html) and [Data.IntMap](http://hackage.haskell.org/packages/archive/containers/latest/doc/html/Data-IntMap.html) only.
226
227For instance, should we decide to use [unordered-containers](http://hackage.haskell.org/package/unordered-containers) all we need to do is to define the following instance for our container:
228
229```haskell
230import Data.Hashable
231import qualified Data.HashMap.Strict as H
232
233instance (Eq k, Hashable k) => MapLike (H.HashMap k v) k v where
234    lookup = H.lookup
235    add = H.insert
236```
237
238then we just need to use `(``evalMemoState``H.empty)` instead of `startEvalMemo` and our memoized function will be evaluated using `Hashmap` as an internal container hosted in [MemoState](http://hackage.haskell.org/packages/archive/monad-memo/latest/doc/html/Control-Monad-Trans-Memo-State.html#t:MemoState).
239There is usually no need to do any modification to the memoized function itself.
240
241## Mutable arrays and vectors as MonadCache
242
243### Array-based memoization cache
244[version 0.4.0](http://hackage.haskell.org/package/monad-memo-0.4.0) adds [ArrayCache](http://hackage.haskell.org/packages/archive/monad-memo/0.4.0/doc/html/Control-Monad-Memo-Array.html): a new [MonadCache](http://hackage.haskell.org/packages/archive/monad-memo/0.4.0/doc/html/Control-Monad-Memo-Class.html#t:MonadCache) implementation based on mutable arrays (inside [IO](http://hackage.haskell.org/packages/archive/base/latest/doc/html/System-IO.html#t:IO) or [ST s](http://hackage.haskell.org/packages/archive/base/latest/doc/html/Control-Monad-ST.html) monad). The main benefit of this `MonadCache` is its performance: it can be an order of magnitude faser than standard `Data.Map`-based cache. This is due to the fact that arrays have `O(1)` lookup time and in-place mutable arrays also have `O(1)` for updates (i.e. the cache `add` operation).
245
246Unfortunatelly you cannot always use this `MonadCache` due to array's natural limitations:
247
248* The key must be an instance of [Ix](http://hackage.haskell.org/packages/archive/base/latest/doc/html/Data-Ix.html#t:Ix) typeclass
249* The bounds of the array must be known (and specified) beforehand and array cannot be resized
250* Array is a continious space of values, so if the key distribution is wide and sparse the memory will be wasted (or array may not even fit into memory)
251
252But if the nature of your memoized function permits the usage of `ArrayCache` you can make your code much more faster by simply switching from Map-based `MonadCache` to `ArrayCache` especially if the value type of your function can be "unboxed" (i.e. it is one of primitive types like `Int` or `Double`). "Unboxed" values are packed in unboxed arrays `UArray` which offer even faster execution and are the most efficient in terms of memory usage.
253Normally you don't have to modify your monadic function definition to run `ArrayCache`-based memoization: just use appropriate `eval*` or `run*` function. For instance our canonical `fibm` function:
254
255```haskell
256fibm 0 = return 0
257fibm 1 = return 1
258fibm n = do
259  n1 <- memo fibm (n-1)
260  n2 <- memo fibm (n-2)
261  return (n1+n2)
262```
263
264can be run using `ST` array of `Integers` with the following function:
265
266```haskell
267evalFibmSTA :: Integer -> Integer
268evalFibmSTA n = runST $ evalArrayMemo (fibm n) (0,n)
269```
270here the `(0,n)` argument defines the bounds of cache array.
271Is it equally easy to use unboxed version of the array, but `Integer` cannot be unboxed (it isn't primitive type), so lets just use `Double` for our function result:
272
273```haskell
274evalFibmSTUA :: Integer -> Double
275evalFibmSTUA n = runST $ evalUArrayMemo (fibm n) (0,n)
276```
277
278Instead of `ST` you can use `IO` monad:
279
280```haskell
281evalFibmIOA :: Integer -> IO Integer
282evalFibmIOA n = evalArrayMemo (fibm n) (0,n)
283
284evalFibmIOUA :: Integer -> IO Double
285evalFibmIOUA n = evalUArrayMemo (fibm n) (0,n)
286```
287
288### Vector-based memoization cache
289For even better performance use [VectorCache](http://hackage.haskell.org/packages/archive/monad-memo/0.4.0/doc/html/Control-Monad-Memo-Vector.html) and its flavours ([unsafe version](http://hackage.haskell.org/packages/archive/monad-memo/0.4.0/doc/html/Control-Monad-Memo-Vector-Unsafe.html) and [dynamically expandable version](http://hackage.haskell.org/packages/archive/monad-memo/0.4.0/doc/html/Control-Monad-Memo-Vector-Expandable.html)) which are all based on very fast [vector](http://hackage.haskell.org/package/vector) library.
290
291Note however that this `MonadCache` is even more limiting that `ArrayCache` since `vector` supports only `Int` as an index.
292
293The usage is very similar to `ArrayCache`, but instead of range we need to specify the length of the vector:
294```haskell
295evalFibmSTV :: Int -> Integer
296evalFibmSTV n = runST $ evalVectorMemo (fibm n) n
297
298evalFibmIOUV :: Int -> IO Double
299evalFibmIOUV n = evalUVectorMemo (fibm n) n
300```
301Use "Expandable" version to avoid specifying length parameter:
302```haskell
303import qualified Control.Monad.Memo.Vector.Expandable as VE
304
305evalFibmSTVE :: Int -> Integer
306evalFibmSTVE n = runST $ VE.startEvalVectorMemo (fibm n)
307```
308
309## Performance of different `MonadCache`'s:
310
311The difference in performance for different `MonadCache`'s with Fibonacci function is demonstrated by [this criterion test](benchmark/Main.hs).
312The test runs memoized Fibonacci function using the following caches:
313 * default Map-based
314 * State-based with Data.IntMap
315 * array and unboxed array based (Array and UArray)
316 * vector, unsafe vector and expandable vector (both boxed and unboxed vectors)
317
318![summary](benchmark/results/fib_memo.png)
319
320Full report can be [found here](http://htmlpreview.github.com/?https://github.com/EduardSergeev/monad-memo/blob/dev/benchmark/results/fib_memo.html).
321
322
323## Custom mutable cache
324
325It is also possible to use a mutable container as a `MonadCache` not defined here.
326For example if we wish to use mutable hash-table from [hashtables package](http://hackage.haskell.org/package/hashtables) we can do so with the following code:
327```haskell
328{-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances, FlexibleInstances #-}
329
330import Data.Hashable
331import Control.Monad.ST
332import Control.Monad.Memo
333import Control.Monad.Trans.Memo.ReaderCache
334import qualified Data.HashTable.ST.Basic as H
335
336newtype Container s k v = Container { toTable :: H.HashTable s k v }
337
338type Cache s k v = ReaderCache (Container s k v)
339
340instance (Eq k, Hashable k) => MonadMemo k v (Cache s k v (ST s)) where
341        {-# INLINE memo #-}
342        memo f k = do
343          c <- container
344          e <- lift $ H.lookup (toTable c) k
345          if isNothing e
346            then do
347              v <- f k
348              lift $ H.insert (toTable c) k v
349              return v
350            else return (fromJust e)
351
352{-# INLINE fib1 #-}
353fibm 0 = return 0
354fibm 1 = return 1
355fibm n = do
356  f1 <- memo fibm (n-1)
357  f2 <- memo fibm (n-2)
358  return (f1+f2)
359
360evalFib :: Int -> Int
361evalFib n = runST $ do
362   c <- H.new
363   evalReaderCache (fibm n) (Container c)
364```
365
366
367## References
368* http://www.haskell.org/haskellwiki/Memoization
369* ["Monadic Memoization Mixins" by Daniel Brown and William R. Cook](http://www.cs.utexas.edu/~wcook/Drafts/2006/MemoMixins.pdf)
370* [data-memocombinators](http://hackage.haskell.org/packages/archive/data-memocombinators/latest/doc/html/Data-MemoCombinators.html)
371* ["Fun with Type Functions" by Oleg Kiselyov, Ken Shan, and Simon Peyton Jones (see 3.1 - "Type-directed memoization")](http://research.microsoft.com/~simonpj/papers/assoc-types/fun-with-type-funs/typefun.pdf)
372