[Haskell-cafe] Memoization
Marc A. Ziegert
coeus at gmx.de
Sun May 27 13:21:56 EDT 2007
you may want to use a container like Array or Map.
most times i use an Array myself to speed things up like this.
with Map it will either be a bit tricky or you'll need to use an unsafeIO hack.
here are some functions that may help you. my favorites are Array and MapMealey.
- marc
memoizeArrayUnsafe :: (Ix i) => (i,i) -> (i->e) -> (i->e)
memoizeArrayUnsafe r f = (Data.Array.!) $ Data.Array.listArray r $ fmap f $ Data.Ix.range r
memoizeArray :: (Ix i) => (i,i) -> (i->e) -> (i->e)
memoizeArray r f i = if Data.Ix.inRange r i then memoizeArrayUnsafe r f i else f i
data Mealey i o = Mealey { runMealey :: i -> (o,Mealey i o) }
memoizeMapMealey :: (Ord k) => (k->a) -> (Mealey k a)
memoizeMapMealey f = Mealey (fm Data.Map.empty) where
fm m k = case Data.Map.lookup m k of
(Just a) -> (a,Mealey . fm $ m)
Nothing -> let a = f k in (a,Mealey . fm $ Data.Map.insert k a $ m)
memoizeMapST :: (Ord k) => (k->ST s a) -> ST s (k->ST s a)
memoizeMapST f = do
r <- newSTRef (Data.Map.empty)
return $ \k -> do
m <- readSTRef r
case Data.Map.lookup m k of
(Just a) -> return a
Nothing -> do
a <- f k
writeSTRef r $ Data.Map.insert k a m
return a
or with inelegant unsafe hacks you get more elegant interfaces:
memoizeMapUnsafeIO :: (Ord k) => (k->IO a) -> (k->a)
memoizeMapUnsafeIO f = unsafePerformIO $ do
r <- newIORef (Data.Map.empty)
return $ \k -> unsafePerformIO $ do
m <- readIORef r
case Data.Map.lookup m k of
(Just a) -> return a
Nothing -> do
a <- f k
writeIORef r $ Data.Map.insert k a m
return a
memoizeMap :: (Ord k) => (k->a) -> (k->a)
memoizeMap f = memoizeMapUnsafeIO (return . f)
memoizeMap f = runST $ do
f' <- memoizeMapST (return . f)
return $ runST . unsafeIOToST . unsafeSTToIO . f'
Am Sonntag, 27. Mai 2007 04:34 schrieb Mark Engelberg:
> I'd like to write a memoization utility. Ideally, it would look
> something like this:
>
> memoize :: (a->b) -> (a->b)
>
> memoize f gives you back a function that maintains a cache of
> previously computed values, so that subsequent calls with the same
> input will be faster.
>
> I've searched the web for memoization examples in Haskell, and all the
> examples use the trick of storing cached values in a lazy list. This
> only works for certain types of functions, and I'm looking for a more
> general solution.
>
> In other languages, one would maintain the cache in some sort of
> mutable map. Even better, in many languages you can "rebind" the name
> of the function to the memoized version, so recursive functions can be
> memoized without altering the body of the function.
>
> I don't see any elegant way to do this in Haskell, and I'm doubting
> its possible. Can someone prove me wrong?
>
> --Mark
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20070527/a8f5ba48/attachment-0001.bin
More information about the Haskell-Cafe
mailing list