Memoization

From HaskellWiki
Revision as of 16:24, 25 April 2014 by Flupp (talk | contribs) (→‎Memoization with recursion: typographic fixes (<hask> → <code>))
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.


Memoization is a technique for storing values of a function instead of recomputing them each time the function is called.

Memoization without recursion

You can just write a memoization function using a data structure that is suitable for your application. We don't go into the details of this case. If you want a general solution for several types, you need a type class, say Memoizable.

memoize :: Memoizable a => (a->b) -> (a->b)

Now, how to implement something like this? Of course, one needs a finite map that stores values b for keys of type a. It turns out that such a map can be constructed recursively based on the structure of a:

  Map ()            b  := b
  Map (Either a a') b  := (Map a b, Map a' b)
  Map (a,a')        b  := Map a (Map a' b)

Here, Map a b is the type of a finite map from keys a to values b. Its construction is based on the following laws for functions

        () -> b  =~=  b
  (a + a') -> b  =~=  (a -> b) × (a' -> b) -- = case analysis
  (a × a') -> b  =~=  a -> (a' -> b)       -- = currying

For further and detailed explanations, see

Memoization with recursion

Things become more complicated if the function is recursively defined and it should use memoized calls to itself. A classic example is the recursive computation of Fibonacci numbers.

The naive implementation of Fibonacci numbers without memoization is horribly slow. Try slow_fib 30, not too much higher than that and it hangs.

slow_fib :: Int -> Integer
slow_fib 0 = 0
slow_fib 1 = 1
slow_fib n = slow_fib (n-2) + slow_fib (n-1)

The memoized version is much faster. Try memoized_fib 10000.

memoized_fib :: Int -> Integer
memoized_fib = (map fib [0 ..] !!)
   where fib 0 = 0
         fib 1 = 1
         fib n = memoized_fib (n-2) + memoized_fib (n-1)


Memoizing fix point operator

You can factor out the memoizing trick to a function, the memoizing fix point operator, which we will call memoFix here.

fib :: (Int -> Integer) -> Int -> Integer
fib f 0 = 1
fib f 1 = 1
fib f n = f (n-1) + f (n-2)

fibonacci :: Int -> Integer
fibonacci = memoFix fib

I suppose if you want to "put it in a library", you should just put fib in, and allow the user to call memoFix fib to make a new version when necessary. This allows the user e.g. to define the data structure used for memoization.

The memoising fixpoint operator works by putting the result of the first call of the function for each natural number into a data structure and using that value for subsequent calls ;-)

In general it is

memoFix :: ((a -> b) -> (a -> b)) -> a -> b
memoFix f =
   let mf = memoize (f mf) in mf

Efficient tree data structure for maps from Int to somewhere

Here we present a special tree data type (data-inttrie) which is useful as memoizing data structure e.g. for the Fibonacci function.

memoizeInt :: (Int -> a) -> (Int -> a)
memoizeInt f = (fmap f (naturals 1 0) !!!)

A data structure with a node corresponding to each natural number to use as a memo.

data NaturalTree a = Node a (NaturalTree a) (NaturalTree a)

Map the nodes to the naturals in this order:

     0
   1   2
  3 5 4 6
 7  ...

Look up the node for a particular number

Node a tl tr !!! 0 = a 
Node a tl tr !!! n =
   if odd n
     then tl !!! top
     else tr !!! (top-1)
        where top = n `div` 2

We surely want to be able to map on these things...

instance Functor NaturalTree where
   fmap f (Node a tl tr) = Node (f a) (fmap f tl) (fmap f tr)

If only so that we can write cute, but inefficient things like the below, which is just a NaturalTree such that naturals!!!n == n:

naturals = Node 0  (fmap ((+1).(*2)) naturals) (fmap ((*2).(+1)) naturals)

The following is probably more efficient (and, having arguments won't hang around at top level, I think) -- have I put more $!s than necessary?

naturals r n =
   Node n
     ((naturals $! r2) $! (n+r))
     ((naturals $! r2) $! (n+r2))
        where r2 = 2*r

Memoising CAFS

Note: This is migrated from the old wiki.

Memoising constructor functions gives you HashConsing, and you can sometimes use MemoisingCafs (constant applicative forms) to implement that.

The MemoisingCafs idiom also supports recursion.

Consider, for example:

wonderous :: Integer -> Integer
wonderous 1 = 0
wonderous x
  | even x    = 1 + wonderous (x `div` 2)
  | otherwise = 1 + wonderous (3*x+1)

This function is not at all understood by mathematicians and has a surprisingly complex recursion pattern, so if you need to call it many times with different values, optimising it would not be easy.

However, we can memoise some of the domain using an array CAF:

wonderous2 :: Integer -> Integer
wonderous2 x
  | x <= maxMemo = memoArray ! x
  | otherwise    = wonderous2' x
  where
        maxMemo = 100
        memoArray = array (1,maxMemo)
                        [ (x, wonderous2' x) | x <- [1..maxMemo] ]
  
        wonderous2' 1 = 0
        wonderous2' x
          | even x    = 1 + wonderous2 (x `div` 2)
          | otherwise = 1 + wonderous2' (3*x+1)

When using this pattern in your own code, note carefully when to call the memoised version (wonderous2 in the above example) and when not to. In general, the partially memoised version (wonderous2' in the above example) should call the memoised version if it needs to perform a recursive call. However, in this instance, we only memoize for small values of x, so the branch of the recursion that passes a larger argument need not bother checking the memo table. (This does slow the array initialization, however.) Thanks to lazy evaluation, we can even memoise an infinite domain, though we lose constant time lookup. This data structure is O(log N):

type MemoTable a = [(Integer, BinTree a)]
data BinTree a = Leaf a | Node Integer (BinTree a) (BinTree a)
 
wonderous3 :: Integer -> Integer
wonderous3 x
  = searchMemoTable x memoTable
  where
        memoTable :: MemoTable Integer
        memoTable = buildMemoTable 1 5

        buildMemoTable n i
            = (nextn, buildMemoTable' n i) : buildMemoTable nextn (i+1)
            where
                nextn = n + 2^i

                buildMemoTable' base 0
                    = Leaf (wonderous3' base)
                buildMemoTable' base i
                    = Node (base + midSize)
                           (buildMemoTable' base (i-1))
                           (buildMemoTable' (base + midSize) (i-1))
                    where
                        midSize = 2 ^ (i-1)
 
        searchMemoTable x ((x',tree):ms)
            | x < x'    = searchMemoTree x tree
            | otherwise = searchMemoTable x ms

        searchMemoTree x (Leaf y) = y
        searchMemoTree x (Node mid l r)
            | x < mid   = searchMemoTree x l
            | otherwise = searchMemoTree x r
 
        wonderous3' 1 = 0
        wonderous3' x
          | even x    = 1 + wonderous3 (x `div` 2)
          | otherwise = 1 + wonderous3 (3*x+1)

Naturally, these techniques can be combined, say, by using a fast CAF data structure for the most common part of the domain and an infinite CAF data structure for the rest.

-- AndrewBromage

Memoizing polymorphic functions

What about memoizing polymorphic functions defined with polymorphic recursion? How can such functions be memoized? The caching data structures used in memoization typically handle only one type of argument at a time. For instance, one can have finite maps of differing types, but each concrete finite map holds just one type of key and one type of value.

See the discussion on Memoizing polymorphic functions, part one and part two, as well as Memoizing polymorphic functions via unmemoization.

See also