Re: [Haskell-cafe] Troubles understanding memoization in SOE

Thanks Paul & Paul for the answers. I'll certainly read the paper Paul Liu reported. I just deleted 100 lines of text which explained my problem in more detail, and while I was explaining it, I answered it myself. Typical. I thought the lambda function that memo1 returns would be called over and over again, and instead of reevaluating the stream from the beginning, it would just return the stream since it is in the cache, but actually it just gets called twice in recursive situations: the first time it evaluates y = f x, stores the thunk in the cache, and returns the thunk, the second time it finds the same thunk in the cache, and then computation of the rest of the stream continues without consulting the cache anymore right? From my clumsy explanation you can see that I'm still thinking too imperative, too eager. Haskell is more lazy than I am, which is an incredible achievement :-) It would really help if I could see the lazy computation; do you think this kind of memo code is traceable using HAT? I'll guess I'll have to check out arrows / yampa again. A year ago I did not understand a single thing in those papers, but I should try it again now I read the SOE book :-) Thanks a lot, Peter

Peter Verswyvelen wrote:
I thought the lambda function that memo1 returns would be called over and over again, and instead of reevaluating the stream from the beginning, it would just return the stream since it is in the cache, but actually it just gets called twice in recursive situations: the first time it evaluates y = f x, stores the thunk in the cache, and returns the thunk, the second time it finds the same thunk in the cache, and then computation of the rest of the stream continues without consulting the cache anymore right?
Actually the function may be called more than twice -- but each time after the first, it uses the cached value instead of recomputing it. Even in a non-recursive situation, such as "x + x", this saves some computation. The recursive situation just make it worse.
From my clumsy explanation you can see that I'm still thinking too imperative, too eager. Haskell is more lazy than I am, which is an incredible achievement :-)
The confusing thing here is that it is a combination of functional and imperative -- the functional evaluation is happening lazily, but the unsafe stuff causes some imperative side effects, namely the updating of the cache.
It would really help if I could see the lazy computation; do you think this kind of memo code is traceable using HAT?
I don't know -- I've never used HAT!
I'll guess I'll have to check out arrows / yampa again. A year ago I did not understand a single thing in those papers, but I should try it again now I read the SOE book :-)
Ok, good luck. -Paul

Hello Paul,
Actually the function may be called more than twice -- but each time after the first, it uses the cached value instead of recomputing it.
Yes, I got confused, since I first thought that the lambda returned from memo would be called at each "frame" (aka time sample). I made some test code with traces to really make sure I understand what is going on. The standalone code below takes 3 elements of a generated stream, and prints {write:{process:0}0}{read:0}{read:0}[0,{process:1}3,{process:2}6] Where "write" means writing to the cache, "process" means computing a value of the stream, "read" means reading from cache. So once it has computed the head of the stream "[0,", it does not call back into the memo function, and I thought it would, silly me. This is of course obvious for you guys, but for me, this took quite some time to figure out, although I now realize, it is just laziness at work. I think the unsafePerformIO made my mind transcent into the strict imperative world again. Thanks a lot for the help, it's very satisfying to fit another piece of the puzzle :) Peter {-# OPTIONS_GHC -fglasgow-exts #-} import Data.IORef import System.IO.Unsafe import GHC.Prim --------------------------------------------------------------------- -- A bit of ugly test code to figure out memoization in SOE type TimeStamp = Int data Behavior a = Behavior ([TimeStamp] -> [a]) (Behavior fx) `plus` (Behavior fy) = Behavior(\ts -> aux (fx ts) (fy ts)) where aux (x:xs) (y:ys) = x+y:aux xs ys f :: Behavior Int f = fb `plus` fb `plus` fb where fb = Behavior (memo1 aux) where aux (t:ts) = process t:aux ts process t = trace "process" t t test :: Int -> [Int] test n = let Behavior fb = f in take n (fb [0..]) main = print $ test 3 --------------------------------------------------------------------- trace tag a b = unsafePerformIO $ do putStr $ "{"++tag++":"++(show a)++"}" return b -- Works on GHC only unsafePtrEq x y = case reallyUnsafePtrEquality# x y of 1# -> True _ -> False memo1 :: ([Int]->[Int]) -> ([Int]->[Int]) memo1 f = unsafePerformIO $ do cache <- newIORef [] return $ \x -> unsafePerformIO $ do vals <- readIORef cache case x `inCache` vals of Nothing -> do let y = f x trace "write" (head y) $ writeIORef cache [(x,y)] return y Just y -> do trace "read" (head y) $ 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 -----Original Message----- From: Paul Hudak [mailto:paul.hudak@yale.edu] Sent: Tuesday, September 25, 2007 2:45 PM To: Peter Verswyvelen Cc: Haskell-Cafe; Paul Liu; paul.hudak@yale.edu Subject: Re: [Haskell-cafe] Troubles understanding memoization in SOE Peter Verswyvelen wrote:
I thought the lambda function that memo1 returns would be called over and over again, and instead of reevaluating the stream from the beginning, it would just return the stream since it is in the cache, but actually it just gets called twice in recursive situations: the first time it evaluates y = f x, stores the thunk in the cache, and returns the thunk, the second time it finds the same thunk in the cache, and then computation of the rest of the stream continues without consulting the cache anymore right?
Actually the function may be called more than twice -- but each time after the first, it uses the cached value instead of recomputing it. Even in a non-recursive situation, such as "x + x", this saves some computation. The recursive situation just make it worse.
From my clumsy explanation you can see that I'm still thinking too imperative, too eager. Haskell is more lazy than I am, which is an incredible achievement :-)
It would really help if I could see the lazy computation; do you think
The confusing thing here is that it is a combination of functional and imperative -- the functional evaluation is happening lazily, but the unsafe stuff causes some imperative side effects, namely the updating of the cache. this kind of memo code is traceable using HAT?
I don't know -- I've never used HAT!
I'll guess I'll have to check out arrows / yampa again. A year ago I did not understand a single thing in those papers, but I should try it again now I read the SOE book :-)
Ok, good luck. -Paul
participants (2)
-
Paul Hudak
-
Peter Verswyvelen