You're correct in pointing out that f uses memoization inside of
itself to cache the intermediate values that it commutes, but those
values don't get shared between invocations of f; thus, if you call f
with the same value of n several times then the memo table might get
reconstructed redundantly. (However, there are other strategies for
memoization that are persistent across calls.)
Cheers,
Greg
On 7/8/10 9:59 PM, Michael Mossey wrote:
Thanks, okay the next question is: how does the memoization work? Each
call to memo seems to construct a new array, if the same f(n) is
encountered several times in the recursive branching, it would be
computed several times. Am I wrong?
Thanks,
Mike
Gregory Crosswhite wrote:
On 7/8/10 9:17 PM, Michael Mossey wrote:
Daniel Fischer wrote:
If f has the appropriate type and the base case is f 0 = 0,
module Memo where
import Data.Array
f :: (Integral a, Ord a, Ix a) => a -> a
f n = memo ! n
where
memo = array (0,n) $ (0,0) : [(i, max i (memo!(i
`quot` 2) + memo!(i `quot` 3) + memo!(i `quot`
4))) | i <- [1 .. n]]
is wasteful regarding space, but it calculates only the needed
values and very simple.
Can someone explain to a beginner like me why this calculates only
the needed values? The list comprehension draws from 1..n so I don't
understand why all those values wouldn't be computed.
The second pair of each element of the list will remain unevaluated
until demanded --- it's the beauty of being a lazy language. :-)
Put another way, although it might look like the list contains values
(and technically it does due to referential transparency), at a lower
level what it actually contains are pairs such that the second
element is represented not by number but rather by a function that
can be called to obtain its value.
Cheers,
Greg
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe