
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

On Sat, 22 Sep 2007, 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
Hm, why the unsafePerformIO hacks? It should be possible without: http://www.haskell.org/haskellwiki/Memoization

I don't know, "me newbie, you expert" ;-) I just pasted the code from the SOE website. But note that it is using pointers to the infinite lists to avoid comparing them by content (which wouldn't work, since they're infinite), so it has to use unsafePerformIO no? 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 But what I don't understand is that I guess this code memoizes the full list, while it should just memoize the tail that is still reachable through the garbage collector? Or maybe that is what a "pointer to list" is? Some kind of weak pointer / stable name that points to the tail of the list that is still needed for evaluation? Hard stuff for a newbie, but I got to understand how it works, so I can fit one more piece of the growing Haskell puzzle :) Peter -----Original Message----- From: Henning Thielemann [mailto:lemming@henning-thielemann.de] Sent: Monday, September 24, 2007 1:44 PM To: Peter Verswyvelen Cc: Haskell-Cafe Subject: Re: [Haskell-cafe] Troubles understanding memoization in SOE On Sat, 22 Sep 2007, 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
Hm, why the unsafePerformIO hacks? It should be possible without: http://www.haskell.org/haskellwiki/Memoization

If you read the memo1 function carefully you'll notice that the cache
always contains just one pair. It's coincident that just memo-ing one
last function application is enough for the SOE examples. You could,
for example, make it memo-ing last two or more results.
The reason for this memoization hack in SOE is complicated.
Recursively defined signals using switch will have time/space leak if
not for the memoization, which itself is complicated that one can't
simply use a shared list to achieve it. Hence the hack using unsafe
operation.
The loss of sharing of function application results is fundementally
rooted in the call-by-need evaluation strategy, which, unlike optimal
evaluation, doesn't share the reduction of "virtual redex"es.
There are a number of ways to get around this problem, and memoization
is one of them. By re-structuring the code, or choosing different data
structures, one could also avoid such problems. The evolution of FRP
into Yampa/Arrow is a good example, where no memoization is needed.
We recently wrote a paper about the leak problem. The draft is at
http://www.cs.yale.edu/~hl293/download/leak.pdf. Comments are welcome!
Regards
Paul Liu
On 9/24/07, bf3@telenet.be
I don't know, "me newbie, you expert" ;-) I just pasted the code from the SOE website.
But note that it is using pointers to the infinite lists to avoid comparing them by content (which wouldn't work, since they're infinite), so it has to use unsafePerformIO no?
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
But what I don't understand is that I guess this code memoizes the full list, while it should just memoize the tail that is still reachable through the garbage collector? Or maybe that is what a "pointer to list" is? Some kind of weak pointer / stable name that points to the tail of the list that is still needed for evaluation? Hard stuff for a newbie, but I got to understand how it works, so I can fit one more piece of the growing Haskell puzzle :)
Peter
-----Original Message----- From: Henning Thielemann [mailto:lemming@henning-thielemann.de] Sent: Monday, September 24, 2007 1:44 PM To: Peter Verswyvelen Cc: Haskell-Cafe Subject: Re: [Haskell-cafe] Troubles understanding memoization in SOE
On Sat, 22 Sep 2007, 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
Hm, why the unsafePerformIO hacks? It should be possible without: http://www.haskell.org/haskellwiki/Memoization
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

We recently wrote a paper about the leak problem. The draft is at http://www.cs.yale.edu/~hl293/download/leak.pdf. Comments are welcome! Interesting. Now that I know the "basic Haskell" stuff these arrows make much more sense. However, they look *very* similar to a visual
Paul L wrote: programming language and IDE my former colleagues and I developed for doing realtime particle effects on videogame consoles. This language contained special constructs to avoid space/time leaks, like a dedicated "feedback loop". I hope I won't come to the conclusion that after one year learning the cool lazy functional programming language Haskell (which I want to use for making simple videogames in a clean way for teaching), I got back from where I started :-) Of course that will not be the case, I'm really learning a lot. Even if it turns out Haskell is not really suitable for games, I will have learned a lot. However it is very important for my goal that the code looks very concise and clean, and having to chase hidden space/time leaks would ruin the elegance. A minor detail in your paper: on page 7, you represent *(d) sf1 &&& sf2 *as a big box taking one input and producing two outputs. The input is internally split using a Y. This does not seem consistent with the other boxes (e.g. *first *or *loop *internally) that show two arrows for an incoming/outgoing pair, so I would say the outer box of &&& would also have two inputs and two outputs. Best regards, Peter Verswyvelen

On Wed, 26 Sep 2007, Peter Verswyvelen wrote:
I hope I won't come to the conclusion that after one year learning the cool lazy functional programming language Haskell (which I want to use for making simple videogames in a clean way for teaching),
I haven't tested it, but know of the existence of "Haskell in Space": http://www.informatik.uni-bremen.de/~cxl/lehre/pi3.ws01/asteroids/

That looks nice, but HGL does not work on Windows anymore does it? Thanks, Peter -----Original Message----- From: Henning Thielemann [mailto:lemming@henning-thielemann.de] Sent: Wednesday, September 26, 2007 11:44 AM To: Peter Verswyvelen Cc: Haskell-Cafe Subject: Re: [Haskell-cafe] Troubles understanding memoization in SOE On Wed, 26 Sep 2007, Peter Verswyvelen wrote:
I hope I won't come to the conclusion that after one year learning the cool lazy functional programming language Haskell (which I want to use for making simple videogames in a clean way for teaching),
I haven't tested it, but know of the existence of "Haskell in Space": http://www.informatik.uni-bremen.de/~cxl/lehre/pi3.ws01/asteroids/

Henning Thielemann wrote:
On Wed, 26 Sep 2007, Peter Verswyvelen wrote:
I hope I won't come to the conclusion that after one year learning the cool lazy functional programming language Haskell (which I want to use for making simple videogames in a clean way for teaching), I haven't tested it, but know of the existence of "Haskell in Space": http://www.informatik.uni-bremen.de/~cxl/lehre/pi3.ws01/asteroids/
Also see these two: http://www.haskell.org/haskellwiki/Frag http://haskell.org/yale/papers/haskell-workshop03/index.html -Paul

Thanks for the nice feedback. I think I know enough to tackle these papers now, although I'm sure it will take a while ;) For a really simple and easy approach that only uses basic Haskell, http://www.geocities.jp/takascience/haskell/monadius_en.html This is a remake of the Konami game that was the cause of my videogame "addiction" :) Cheers, Peter -----Original Message----- From: Paul Hudak [mailto:paul.hudak@yale.edu] Sent: Wednesday, September 26, 2007 2:39 PM To: Peter Verswyvelen Cc: Henning Thielemann; Haskell-Cafe; paul.hudak@yale.edu Subject: Re: [Haskell-cafe] Troubles understanding memoization in SOE Henning Thielemann wrote:
On Wed, 26 Sep 2007, Peter Verswyvelen wrote:
I hope I won't come to the conclusion that after one year learning the cool lazy functional programming language Haskell (which I want to use for making simple videogames in a clean way for teaching), I haven't tested it, but know of the existence of "Haskell in Space": http://www.informatik.uni-bremen.de/~cxl/lehre/pi3.ws01/asteroids/
Also see these two: http://www.haskell.org/haskellwiki/Frag http://haskell.org/yale/papers/haskell-workshop03/index.html -Paul

paul.hudak:
Henning Thielemann wrote:
On Wed, 26 Sep 2007, Peter Verswyvelen wrote:
I hope I won't come to the conclusion that after one year learning the cool lazy functional programming language Haskell (which I want to use for making simple videogames in a clean way for teaching), I haven't tested it, but know of the existence of "Haskell in Space": http://www.informatik.uni-bremen.de/~cxl/lehre/pi3.ws01/asteroids/
Also see these two:
http://www.haskell.org/haskellwiki/Frag http://haskell.org/yale/papers/haskell-workshop03/index.html
And don't forget these three games that got mentioned during the week. Octane Mech: http://berlinbrowndev.blogspot.com/2007/09/octane-mech-opengl-haskell-based-... OpenGL Tetris: http://myawesomeblag.blogspot.com/2007/03/opengl-tetris-in-haskell.html Games in Haskell video: http://www.londonhug.net/2007/09/21/games-in-haskell-video-now-available/

On Wed, 26 Sep 2007, Don Stewart wrote:
And don't forget these three games that got mentioned during the week.
Octane Mech: http://berlinbrowndev.blogspot.com/2007/09/octane-mech-opengl-haskell-based-...
OpenGL Tetris: http://myawesomeblag.blogspot.com/2007/03/opengl-tetris-in-haskell.html
Games in Haskell video: http://www.londonhug.net/2007/09/21/games-in-haskell-video-now-available/
Would be great, if announcements were more formalized and could be automatically added to the Wiki or some automated overview for non-Hackage packages. http://haskell.org/haskellwiki/Applications_and_libraries/Games

Peter Verswyvelen wrote:
Paul L wrote: A minor detail in your paper: on page 7, you represent *(d) sf1 &&& sf2 *as a big box taking one input and producing two outputs. The input is internally split using a Y. This does not seem consistent with the other boxes (e.g. *first *or *loop *internally) that show two arrows for an incoming/outgoing pair, so I would say the outer box of &&& would also have two inputs and two outputs.
But look at the type of &&&: (&&&) :: Arrow a => a b c -> a b c' -> a b (c, c') or, perhaps more readable, (&&&) :: Arrow (~>) => (b ~> c) -> (b ~> c') -> (b ~> (c, c')) As you can see, the resulting arrow of type (b ~> (c, c')) really has only one input and produces a pair, i.e. two outputs. Internally it must duplicate the b input somehow and apply it to both input arrows, exactly as the box shows. Bertram

Gee you are right, how embarrasing. I mistakenly read the signature of *** just above &&&, which is (***) :: Arrow a ⇒ a b c → a b’ c’ → a (b,b’) (c,c’) Now just to me sure I get it right, *** results in an arrow that has two inputs (b,b') and two outputs (c,c')?
(&&&) :: Arrow (~>) => (b ~> c) -> (b ~> c') -> (b ~> (c, c'))
Hey that’s a nice trick, and it is valid Haskell :) Peter -----Original Message----- From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell. org] On Behalf Of Bertram Felgenhauer Sent: Wednesday, September 26, 2007 2:06 PM To: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Troubles understanding memoization in SOE Peter Verswyvelen wrote:
Paul L wrote: A minor detail in your paper: on page 7, you represent *(d) sf1 &&& sf2 *as a big box taking one input and producing two outputs. The input is internally split using a Y. This does not seem consistent with the other boxes (e.g. *first *or *loop *internally) that show two arrows for an incoming/outgoing pair, so I would say the outer box of &&& would also have two inputs and two outputs.
But look at the type of &&&: (&&&) :: Arrow a => a b c -> a b c' -> a b (c, c') or, perhaps more readable, (&&&) :: Arrow (~>) => (b ~> c) -> (b ~> c') -> (b ~> (c, c')) As you can see, the resulting arrow of type (b ~> (c, c')) really has only one input and produces a pair, i.e. two outputs. Internally it must duplicate the b input somehow and apply it to both input arrows, exactly as the box shows. Bertram _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Paul L wrote:
We recently wrote a paper about the leak problem. The draft is at http://www.cs.yale.edu/~hl293/download/leak.pdf. Comments are welcome! I'm trying to understand the following in this paper:
(A) repeat x = x : repeat x or, in lambdas: (B) repeat = λx → x : repeat x This requires O(n) space. But we can achieve O(1) space by writing instead: (C) repeat = λx → let xs = x : xs in xs Let me see if I understand this correctly. Since I'm an imperative programmer, I'll try a bit of C++ here. struct Cell : Value { Value* head; Value* tail; }; So in (A) and (B), a Cell c1 is allocated, and c1->head would be a pointer to x, and c1->tail would be a pointer to a newly allocated Cell c2, etc etc, hence O(n) space complexity In (C) however, a Cell xs is allocated, and xs->head is also a pointer to x, but xs->tail is a pointer the cell xs again, creating one circular data structure, hence O(1) space complexity. Is this more or less correct? I'm also trying to figure out how the "fixed point combinator" works, so the fix f = f (fix f), and it's effect on space/time complexity. Any good tutorials on that one? Or is this the one http://haskell.org/haskellwiki/Recursive_function_theory. Looks a bit scary at first sight ;-) Thanks again, Peter

Peter Verswyvelen wrote:
Let me see if I understand this correctly. Since I'm an imperative programmer, I'll try a bit of C++ here.
struct Cell : Value { Value* head; Value* tail; };
So in (A) and (B), a Cell c1 is allocated, and c1->head would be a pointer to x, and c1->tail would be a pointer to a newly allocated Cell c2, etc etc, hence O(n) space complexity In (C) however, a Cell xs is allocated, and xs->head is also a pointer to x, but xs->tail is a pointer the cell xs again, creating one circular data structure, hence O(1) space complexity.
Is this more or less correct?
yes.. I don't think you meant to both derive Cell from Value and have a "head" pointer. Otherwise it's an excellent analogy (ignoring how _unevaluated_ thunks are represented, because without those -- with strict list evaluation -- O(n) repeat has to be O(infinity) ).
I'm also trying to figure out how the "fixed point combinator" works, so the fix f = f (fix f), and it's effect on space/time complexity.
or fix f = let x = f x in x which may have different complexity properties? I don't know... Imagine inlining `fix`, if you have a better intuition for explicit (co)recursion than for `fix`. Oh wait, only my definition can be fully inlined, not yours. Isaac

Peter Verswyvelen wrote:
Paul L wrote:
We recently wrote a paper about the leak problem. The draft is at http://www.cs.yale.edu/~hl293/download/leak.pdf. Comments are welcome! I'm trying to understand the following in this paper:
(A) repeat x = x : repeat x or, in lambdas: (B) repeat = λx → x : repeat x This requires O(n) space. But we can achieve O(1) space by writing instead: (C) repeat = λx → let xs = x : xs in xs
Let me see if I understand this correctly. Since I'm an imperative programmer, I'll try a bit of C++ here.
struct Cell : Value { Value* head; Value* tail; };
So in (A) and (B), a Cell c1 is allocated, and c1->head would be a pointer to x, and c1->tail would be a pointer to a newly allocated Cell c2, etc etc, hence O(n) space complexity In (C) however, a Cell xs is allocated, and xs->head is also a pointer to x, but xs->tail is a pointer the cell xs again, creating one circular data structure, hence O(1) space complexity.
Is this more or less correct?
Yes. Also I believe (A) and (B) are the same as repeat = fix (\ f -> (\ x -> x : f x ) ) While (C) is repeat = \x -> fix (\ me -> x : me ) or repeat x = fix (\me -> x : me )
I'm also trying to figure out how the "fixed point combinator" works, so the fix f = f (fix f), and it's effect on space/time complexity. Any good tutorials on that one? Or is this the one http://haskell.org/haskellwiki/Recursive_function_theory. Looks a bit scary at first sight ;-)
Thanks again, Peter
A good way to think about 'fix' is that it lets us write a definition that talks about the thing that we are defining. This is very common in Haskell, since every recursive definition or mutually recursive set of definitions talks about itself. (Every Haskell let is a bit like Scheme's letrec). This is also common in C++ and Java when an object "talks about" itself while it is being constructed. Warning: It is easy for a programming mistake to create a dependency loop (or "black hole") when using 'fix' improperly. This is similar to a C++/Java object calling itself during construction when it is in only a partially constructed state and causing an error. Now take the definition from GHC's base package, currently in http://darcs.haskell.org/packages/base/Data/Function.hs
-- | @'fix' f@ is the least fixed point of the function @f@, -- i.e. the least defined @x@ such that @f x = x@. fix :: (a -> a) -> a fix f = let x = f x in x
Consider the type of fix, namely (a->a)->a. Note that is not the same as a->a->a which is actually a->(a->a). For (A) and (B) the type 'a' is the type of 'f' which is a function. If repeat :: q -> [q] then 'a' is 'q->[q]' and the fix is of type ( (q->[q]) -> (q->[q]) ) -> (q->[q]) For (C) the type 'a' is the type of 'me' which is a list, and the fix is of type ( [q] -> [q] ) -> [q] Expand (C) step by step: -- Rename x to be q to avoid name collisions repeat = \q -> fix (\me -> q : me ) -- Now substitute the definition of fix using f = (\me -> q : me) repeat = \q -> let x = (\me -> q : me) x in x -- Apply the function with me replaced by x repeat = \q -> let x = q : x in x Optionally convert to pointful notation repeat q = let x = q : x in x And these are your definition (C) Expand (A) or (B) step by step: Rename x to q to avoid name collision later repeat = fix (\ f -> (\ q -> q : f q ) ) Expand definition of fix replacing f with (\ f -> (\ q -> q : f q ) ) repeat = let x = (\ f -> (\ q -> q : f q ) ) x in x Apply the function replacing f with x repeat = let x = (\ q -> q : x q ) ) in x Simplify by noting that 'x' and 'repeat' name the same thing repeat = (\q -> q : repeat q) Optionally convert to pointful notation repeat q = q : repeat q -- Chris

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
participants (9)
-
Bertram Felgenhauer
-
bf3@telenet.be
-
ChrisK
-
Don Stewart
-
Henning Thielemann
-
Isaac Dupree
-
Paul Hudak
-
Paul L
-
Peter Verswyvelen