Difference between revisions of "Memoization"

From HaskellWiki
Jump to navigation Jump to search
(distinction between recursive and non-recursive case)
(separate section for NaturalTree)
Line 3: Line 3:
 
'''Memoization''' is a technique for storing values of a function instead of recomputing them each time the function is called.
 
'''Memoization''' is a technique for storing values of a function instead of recomputing them each time the function is called.
   
== Memoization of arbitrary functions ==
+
== Memoization without recursion ==
 
You need type classes to get a reasonable type for the function you want
 
   
  +
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 <hask>Memoizable</hask>.
 
<haskell>
 
<haskell>
 
memoize :: Memoizable a => (a->b) -> (a->b)
 
memoize :: Memoizable a => (a->b) -> (a->b)
Line 12: Line 14:
   
 
Now, how to implement something like this? Of course, one needs a finite
 
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 that stores values <hask>b</hask> for keys of type <hask>a</hask>.
map can be constructed recursively based on the structure of a:
+
It turns out that such a map can be constructed recursively based on the structure of <hask>a</hask>:
 
 
<haskell>
 
<haskell>
 
Map () b := b
 
Map () b := b
Line 21: Line 22:
 
</haskell>
 
</haskell>
   
Here, Map a b is the type of a finite map from keys a to values b. Its
+
Here, <hask>Map a b</hask> is the type of a finite map from keys <hask>a</hask> to values <hask>b</hask>.
construction is based on the following laws for functions
+
Its construction is based on the following laws for functions
 
 
<haskell>
 
<haskell>
 
() -> b =~= b
 
() -> b =~= b
Line 35: Line 35:
 
* R. Hinze: [http://www.informatik.uni-bonn.de/~ralf/publications.html#J4 Generalizing generalized tries]
 
* R. Hinze: [http://www.informatik.uni-bonn.de/~ralf/publications.html#J4 Generalizing generalized tries]
   
== Memoization of recursively defined functions ==
+
== Memoization with recursion ==
   
 
Things become more complicated if the function is recursively defined
 
Things become more complicated if the function is recursively defined
Line 63: Line 63:
   
   
== Memoizing fix point operator ==
+
=== Memoizing fix point operator ===
   
 
You can factor out the memoizing trick to a function, the memoizing fix point operator,
 
You can factor out the memoizing trick to a function, the memoizing fix point operator,
Line 96: Line 96:
 
</haskell>
 
</haskell>
   
  +
== Efficient tree data structure for maps from Int to somewhere ==
Here we use a special tree as memoizing data structure.
 
  +
 
Here we present a special tree data type which is useful as memoizing data structure e.g. for the Fibonacci function.
 
<haskell>
 
<haskell>
memoFix :: ((Int -> Integer) -> (Int -> Integer)) -> (Int -> Integer)
+
memoizeInt :: (Int -> a) -> (Int -> a)
 
memoizeInt f = (fmap f (naturals 1 0) !!!)
memoFix f =
 
let memo = fmap (f mf) (naturals 1 0)
 
mf = (memo !!!)
 
in mf
 
 
</haskell>
 
</haskell>
   
 
A data structure with a node corresponding to each natural number to use as a memo.
 
A data structure with a node corresponding to each natural number to use as a memo.
 
 
<haskell>
 
<haskell>
 
data NaturalTree a = Node a (NaturalTree a) (NaturalTree a)
 
data NaturalTree a = Node a (NaturalTree a) (NaturalTree a)

Revision as of 21:53, 5 August 2007


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) x (a' -> b) -- = case analysis
  (a x 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 shall used 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 =
   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 ;-)

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


See also