[Haskell-cafe] memoization

Andreas Abel andreas.abel at ifi.lmu.de
Wed Jul 24 10:06:59 CEST 2013


Sorry I screwed up.  The following is indeed memoizing:

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

Here, the eta-expansion does not matter.  But as you say, memoized_fib 
below is not memoizing, since x is in scope in the where clauses, even 
though they do not mention it.  Thus, for each x we get "new" 
definitions of fibs and fib.  Yet, this is only true for -O0.

For -O1 and greater, ghc seems to see that x is not mentioned in the 
where clauses and apparently lifts them out.  Thus, for -O1.. 
memoized_fib is also memoizing.  (I ran it, this time ;-) !)

Cheers,
Andreas

On 22.07.13 11:43 PM, Tom Ellis wrote:
> On Mon, Jul 22, 2013 at 04:16:19PM +0200, Andreas Abel wrote:
>> 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.

I meant to write

   "Then, eta-expansions do not matter."

(In general, they do matter.)

> But this is *not* memoized (run it and see!).  The "eta-expansions" do
> indeed matter (although I don't think they are truly eta-expasions because
> of the desugaring of the where to a let).
>
> What matters is not the let binding, but where the let binding occurs in
> relation to the lambda.  There's no compiler magic here, just operational
> semantics.
>
> Tom
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

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