[Haskell-cafe] Memoization

Sebastian Sylvan sebastian.sylvan at gmail.com
Fri Oct 7 13:09:37 EDT 2005


On 10/7/05, Gerd M <gerd_m1977 at hotmail.com> wrote:
> Hello,
> I'm trying to use Data.Map to memoize computations. Unfortunately this
> didn't improve the runtime of f at all, so there must be something wrong
> with my implementation. Thanks in advance!
>
> f 1 s     (HMM s0 _   sts)  =  s ??? sts s0
> f t s hmm = memory hmm Map.! (t,s)
>
> memory hmm@(HMM s0 sss sts)
>             = Map.fromList [ ((t,s),f' t s hmm) | t <- [1..100], s <- sss,
> s/=s0 ]
>
> f' 1 s     (HMM s0 _   sts)  =  s ??? sts s0
> f' t s hmm@(HMM s0 sss sts)
>         = sum [ (memory hmm)Map.!(t-1,s') * (s ??? sts s')  | s' <- sss, s'
> /= s0 ]
>

I would use an array, which has O(1) lookup...
Instead of changing your code, I'll give a bit more well-known example
(partially because I'm in a bit of a rush :-)). Here's a fib function
memoized for the first 100 n (using a general approach with arrays,
instead of the zipWith thing)

import Data.Array

fib 0 = 1
fib 1 = 1
fib n | n <= 100 = fibarr!n
      | otherwise = fib' n

fibarr = listArray (2,100) [ fib' x | x <- [2..100]]
fib' n = fib (n-1) + fib (n-2)

The array is lazy in its elements (but not its indices) so the array
of 100 fibs won't actually be computed until you request a fib (then
all fibs < n will be computed).
So basically, define an array which contains the value of the function
at each entry, make sure you use the array in defining these elements
if your function is recursive (top-level, it doesn't change the
correctness but if you define it in a local scope your implementation
probably won't save the entries in the array between calls which kinda
ruins the point of memoization!).


/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862


More information about the Haskell-Cafe mailing list