[Haskell-cafe] memoization using unsafePerformIO
Jan Christiansen
jac at informatik.uni-kiel.de
Tue Jun 23 09:23:38 EDT 2009
Hi,
I have tried to implement a memo function using stable names and weak
pointers like it is presented in the paper "stretching the storage
manager". There is an abstract datatype SNMap a b which implements a
map that maps values of type StableName a to values of type b. The map
is located in an IORef.
{-# NOINLINE memo #-}
memo :: (a -> b) -> a -> b
memo f =
unsafePerformIO (do
tref <- newSNMap
return (applyWeak f tref))
{-# NOINLINE applyWeak #-}
applyWeak :: (a -> b) -> SNMap a (Weak b) -> a -> b
applyWeak f tbl arg =
unsafePerformIO (do
sn <- makeStableName arg
lkp <- lookupSNMap tbl sn
case lkp of
Nothing -> not_found sn
Just weak -> do
val <- deRefWeak weak
case val of
Just result -> return result
Nothing -> not_found sn)
where
not_found sn = do
let res = f arg
weak <- mkWeak arg res Nothing
insertSNMap tbl sn weak
return res
Using this memo function I have implemented a fibonacci function like
it is defined in the paper.
fib :: Int -> Int
fib = memo ufib
ufib :: Int -> Int
ufib 0 = 1
ufib 1 = 1
ufib n = fib (n-1) + fib (n-2)
When I compile this program with 6.10.3 fib yields the correct results
up to 18 but for 19 it detects a loop.
Can anybody give me a hint how I can avoid this behaviour (and still
use unsafePerformIO ; ) )?
Cheers, Jan
More information about the Haskell-Cafe
mailing list