Memoization

From HaskellWiki
Revision as of 21:27, 5 August 2007 by Lemming (talk | contribs) (more links to Haskell Cafe)
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.

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 =
   let fib 0 = 0
       fib 1 = 1
       fib n = memoized_fib (n-2) + memoized_fib (n-1)
   in  (map fib [0 ..] !!)


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 ;-)

memoFix :: ((Int -> Integer) -> (Int -> Integer)) -> (Int -> Integer)
memoFix f = mf
   where memo = fmap (f mf) (naturals 1 0)
         mf = (memo !!!)

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


See also