[Haskell-cafe] Troubles understanding memoization in SOE

Paul Hudak paul.hudak at yale.edu
Mon Sep 24 20:34:57 EDT 2007


Hi Peter.  Paul Liu replied well to your later email, but I just wanted 
to point out that memoization is not being used here to make the 
recursion work -- lazy evaluation does just fine.  Rather, the 
memoization is being used for what it's normally good for, namely, to 
avoid repeated computation.  In a recursive context having multiple 
references to the recursive variable, this can result in  an exponential 
blow-up that grinds the computation to a halt very quickly.  I suspect 
that when you observed your program getting "stuck" that it was simply 
blowing up so quickly that it /appeared /stuck.

Also, the reason that there is no space leak in the memoization process 
is that, as Paul Liu pointed out, I only save the last value -- that's 
the reason for the IORef.  The last value is sufficient because FAL is 
carefully designed so that it executes each time step completely before 
the next one begins.

Finally, I should point out this is the only place in SOE where I use 
unsafe features in Haskell.  I felt so bad about it that you'll notice 
that I don't even discuss it in the text!  Interestingly, also as Paul 
Liu pointed out, switching to arrows solves the problem, but in a subtle 
way that we only recently realized.  The paper that Paul cited 
(http://www.cs.yale.edu/~hl293/download/leak.pdf) describes this in detail.

I hope this helps,

   -Paul Hudak


Peter Verswyvelen wrote:
> Hi,
>
> in SOE, the following memoization function is implemented:
> memo1 :: (a->b) -> (a->b)
> memo1 f = unsafePerformIO $ do
>   cache <- newIORef []
>   return $ \x -> unsafePerformIO $ do
>               vals <- readIORef cache
>               case x `inCache` vals of
>                 Nothing -> do let y = f x
>                               writeIORef cache [(x,y)] -- ((x,y) : 
> --                                if null vals then [] else [head vals])
>                               return y
>                 Just y  -> do return y
>
> inCache :: a -> [(a,b)] -> Maybe b
> x `inCache` [] = Nothing
> x `inCache` ((x',y'):xys) =
>    if unsafePtrEq x x' then Just y' else x `inCache` xys
>
> This is then used in
>
> type Time = Float
> type UserAction = G.Event
>
> data G.Event
>   = Key Char Bool
>   | Button Point Bool Bool
>   | MouseMove Point
>   | Resize
>   | Closed
>   deriving Show
>
> newtype Behavior a  = Behavior (([Maybe UserAction],[Time]) -> [a])
> newtype Event a  = Event (([Maybe UserAction],[Time]) -> [Maybe a])
>
> Behavior fb `untilB` Event fe =
>   memoB $ Behavior (\uts@(us,ts) -> loop us ts (fe uts) (fb uts))
>     where loop (_:us) (_:ts) ~(e:es) (b:bs) =
>             b : case e of
>                   Nothing             -> loop us ts es bs
>                   Just (Behavior fb') -> fb' (us,ts)
>
> memoB :: Behavior a -> Behavior a
> memoB (Behavior fb) = Behavior (memo1 fb)
>
>
> If I understand it correctly, the memoization is required because 
> otherwise recursive "streams" wouldn't work. For example, in the Pong 
> game example, a ballPositionX stream is generated by integrating a 
> ballVelocityX stream, but the ballVelocityX stream changes sign when 
> the ball hits the left or right walls, and to determine that event, 
> the ballPositionX stream is required. So both streams are mutually 
> recursive, and without memoization, the program would be stuck (at 
> least my own FRP experiments, which don't use memoization yet, gets 
> stuck :-)). Another trick to prevent this, is the "b : case e of" code 
> in untilB, which causes the event to be handled a bit too late, to 
> avoid cyclic interdependencies.
>
> I hope I got that right. Now my questions.
>
> So, the keys (x) and values (y) in (memo1 fb)  are streams (aka 
> infinite lists)? More correctly, memo1 uses a pointer to the head of 
> the list as a key, for fast comparing (as you can't compare infinite 
> lists)? But since both key and value are infinite streams, won't this 
> approach cause a serious space leak because the whole list cannot be 
> reclaimed by the garbage collector? So the full ballPositionX and 
> ballVelocityX streams would remain in memory, until the program exits?
>
> Since this doesn't happen when I run the SOE examples (I guess!), I 
> clearly misunderstand this whole thing. I could explain it when the 
> pointer to the list is actually a pointer to the delayed computation 
> (a "thunk"?) of the tail, but the code doesn't seem to do that.
>
> Thanks for any help, I hope I explained the problem well enough.
>
> Peter Verswyvelen

-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20070924/6ba0e11f/attachment-0001.htm


More information about the Haskell-Cafe mailing list