Another space leak question

Srineet srineet@email.com
Mon, 2 Jul 2001 17:28:38 +0530


Thanks, but oops, that doesn't solve my real problem. Ok, let me stop trying
to simplify and put the relevanty parts of my original code. Will lead to a
longer mail.

With a space leak:
------------------

This is what I had earlier.

I have a type called PTState which is,
> type PTState  = (PTBitmaps, Randoms, Helicopters)
"Randoms" is a type synonym for [Int]. "PTBitmaps" is not so relevant here,
neither is Helicopters.

And this used to be the main loop (you can skip the first three lines, the
main part is "loop").
mainLoop  = do
   w <- openWindowEx "Paratrooper 1" Nothing (Just (wWidth, wHeight))
DoubleBuffered (Just 100)
   bmps <- loadPTBitmaps       --load bmp files
   rs   <- randomRsIO (1, 20)  -- random numbers
   let loop st = do
       getWindowTick w
       let (ns, gs)    = step st;
           g   =   foldr overGraphic emptyGraphic gs
           in
           do setGraphic w g; loop  ns
   loop (initState bmps rs)

Btw, I am using the hugs graphics library here. I'll just give the type of
some functions:
mainLoop:: IO()
step    :: PTState->PTState    -- this is like updating the state and
passing it back to  "loop" again.
randomRsIO::[Int]    is supposed to return a lazily evaluated infinite list
of random numbers.
setGraphic   :: Window -> Graphic -> IO()    -- just draws a "graphic" on
screen.
initState    :: PTBitmaps -> Randoms -> PTState -- just initializes the
state.

No Space Leak:
-----------------
Now I removed the randoms from PTState: and started passing it as a separate
parameter to "loop" and "step":

So the new PTState is just (PTBitmaps, Helicopters)

> main' = do
>   w <- openWindowEx "Paratrooper 1" Nothing (Just (wWidth, wHeight))
DoubleBuffered (Just 100)
>   bmps <- loadPTBitmaps       --load bmp files
>   rs   <- randomRsIO (1, 20)  -- random numbers
>   loop w rs (initState bmps)

> loop w rs st  = do
>   getWindowTick w
>   let (ns, gs)    = step st (take numHelicopters rs);
>       g   =   foldr overGraphic emptyGraphic gs
>       in
>       do  setGraphic w g; loop w (drop numHelicopters rs) ns

Why did the space leak go away?

- Srineet.

More info:
In the earlier version I used to use the following function to extract
random numbers from the state:
> stGetRandoms  :: Int -> PTState -> (Randoms, PTState)
> stGetRandoms num (bmps, rs, hcs)  = (take num rs, (bmps, drop num rs,
hcs))




----- Original Message -----
From: <kahl@heraklit.informatik.unibw-muenchen.de>
To: <srineet@email.com>
Cc: <haskell-cafe@haskell.org>
Sent: Monday, July 02, 2001 3:44 PM
Subject: Re: Another space leak question


>
> "Srineet" <srineet@email.com> writes:
>
>
>  >     Now [main2] continues forever, but doesn't cause hugs to run out of
>  > heap.What' the reason that, while both [main1] and [main2] run forever,
the
>  > first causes hugs to run out of heap while second doesn't.
>
> referring to the following program (slightly adapted for compatibility
with
> HOPS/MHA):
>
> > step1 :: [Int] -> Int -> Int
> > step1 (x:xs) n = step1 xs (n+x)
>
> > main1 :: Int
> > main1 = step1 (repeat 1) 1
>
> > step2 :: [Int] -> Int -> Int
> > step2 (x:xs) n | n == 0    = 0
> >                | otherwise = step2 xs (n+x)
>
> > main2 :: Int
> > main2 = step2 (repeat 1) 1
>
> The reason is that the addition in step1 is deferred lazily,
> since its result is never needed.
> Therefore, unreduced additions accumulate.
>
> In contrast, the result of the addition in step2 is needed
> for comparison in ``n == 0'' --- this forces evaluation of n.
>
>
> I have produced two animations (hold down the space bar in ghostview
> to get the effect ;-), available at:
>
> http://ist.unibw-muenchen.de/kahl/MHA/Srineet_main1.ps.gz
> http://ist.unibw-muenchen.de/kahl/MHA/Srineet_main2.ps.gz
>
> A remedy might be to force sequentialisation:
>
> > step1' (x:xs) n = let n' = n+x in n' `seq` step1 xs n'
>
>
> Hope that helps!
>
>
> Wolfram
>
>
> http://ist.unibw-muenchen.de/kahl/
> http://ist.unibw-muenchen.de/kahl/HOPS/
>