[Haskell-cafe] Memoization-question

Bulat Ziganshin bulat.ziganshin at gmail.com
Thu Dec 11 15:11:56 EST 2008


Hello Daniel,

Thursday, December 11, 2008, 11:09:46 PM, you wrote:

you is almost right. but ghc don't share results of function calls
despite their type. it just assumes that value of any type may use a
lot of memory even if this type is trivial :)

example when automatic sharing is very bad idea is:

main = print (sum[1..10^10] + sum[1..10^10])

> Am Donnerstag, 11. Dezember 2008 16:18 schrieb Mattias Bengtsson:
>> The program below computes (f 27) almost instantly but if i replace the
>> definition of (f n) below with (f n = f (n - 1) * f (n -1)) then it
>> takes around 12s to terminate. I realize this is because the original
>> version caches results and only has to calculate, for example, (f 25)
>> once instead of (i guess) four times.
>> There is probably a good reason why this isn't caught by the compiler.
>> But I'm interested in why. Anyone care to explain?
>>
>> > main = print (f 27)
>> >
>> > f 0 = 1
>> > f n = let f' = f (n-1)
>> >       in f' * f'
>>
>> (compiled with ghc --make -O2)
>>
>> Mattias
>>

> Not an expert, so I may be wrong.
> The way you wrote your function, you made it clear to the compiler that you
> want sharing, so it shares.
> With

> g 0 = 1
> g n = g (n-1)*g (n-1)

> it doesn't, because the type of g is Num t => t -> t, and you might call it
> with whatever weird Num type, for which sharing might be a bad idea (okay,
> for this specific function I don't see how I would define a Num type where
> sharing would be bad).
> If you give g a signature like
g :: Int ->> Int,
> the compiler knows that sharing is a good idea and does it (cool thing aside:
> with
> module Main where

> f 0 = 1
> f n = let a = f (n-1) in a*a

> main = do
>     print (f 27)
>     print (g 30)

> g 0 = 1
> g n = g (n-1)*g (n-1)

> main still runs instantaneously, but g n takes exponential time at the ghci
> prompt. That's because in main the argument of g is defaulted to Integer, so
> it's shared.)
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


-- 
Best regards,
 Bulat                            mailto:Bulat.Ziganshin at gmail.com



More information about the Haskell-Cafe mailing list