[Haskell-cafe] memoization

Andreas Abel andreas.abel at ifi.lmu.de
Mon Jul 22 16:16:19 CEST 2013


On 22.07.2013 09:52, Chris Wong wrote:
>> 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)
>>
>
> [.. snipped ..]
>
>> Could someone explain the technical details of why this works? Why is "map
>> fib [0 ..]" not recalculated every time I call memoized_fib?
>
> A binding is memoized if, ignoring everything after the equals sign,
> it looks like a constant.
>
> In other words, these are memoized:
>
>      x = 2
>
>      Just x = blah
>
>      (x, y) = blah
>
>      f = \x -> x + 1
>      -- f = ...
>
> and these are not:
>
>      f x = x + 1
>
>      f (Just x, y) = x + y
>
> If you remove the right-hand side of memoized_fib, you get:
>
>      memoized_fib = ...
>
> This looks like a constant. So the value (map fib [0..] !!) is memoized.
>
> If you change that line to
>
>      memoized_fib x = map fib [0..] !! x
>
> GHC no longer memoizes it, and it runs much more slowly.

True, but the essential thing to be memoized is not memoized_fib, which 
is a function, but the subexpression

   map fib [0..]

which is an infinite list, i.e., a value.

The rule must be like "in

   let x = e

if e is purely applicative, then its subexpressions are memoized."
For instance, the following is also not memoizing:

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

In general, I would not trust such compiler magic, but just let-bind 
anything I want memoized myself:

memoized_fib :: Int -> Integer
memoized_fib x = fibs !! x
     where fibs  = map fib [0..]   -- lazily computed infinite list
           fib 0 = 0
           fib 1 = 1
           fib n = memoized_fib (n-2) + memoized_fib (n-1)

The eta-expansions do not matter.

Cheers,
Andreas

-- 
Andreas Abel  <><      Du bist der geliebte Mensch.

Theoretical Computer Science, University of Munich
Oettingenstr. 67, D-80538 Munich, GERMANY

andreas.abel at ifi.lmu.de
http://www2.tcs.ifi.lmu.de/~abel/




More information about the Haskell-Cafe mailing list