
data World = World { ... }
wave1 :: Behavior World
wave2 :: Behavior World
worldB = wave1 `switcher` fmap (const wave2) (whenE (zeroCreeps wave1)
Oops. The list's spam-filter tossed this note.
---------- Forwarded message ----------
From: Alexander Foremny
where pollE = atTimes [1..]
zeroCreeps :: Behavior World -> Behavior Bool
When running worldB from main I can see the program's memory usage increasing and everything becomes very unresponsive. It seems as if whenE is accumalating all the occurences of the event. The problem seems to boil down to snapshot having the same behavior.
snapshot (pure False) (atTimes [1..])
This piece of code uses very much memory either. Is this due to reactive being broken (I read that somewhere) or is my solution just no solution at all? I am using ghc 6.12.1 with reactive 0.11.5 and reactive-glut 0.1.9. Regards Alexander Foremny

Hi, On Tue, August 24, 2010 10:14, Alexander Foremny wrote:
When running worldB from main I can see the program's memory usage increasing and everything becomes very unresponsive. It seems as if whenE is accumalating all the occurences of the event. The problem seems to boil down to snapshot having the same behavior.
snapshot (pure False) (atTimes [1..])
This piece of code uses very much memory either. Is this due to reactive being broken (I read that somewhere) or is my solution just no solution at all?
I am using ghc 6.12.1 with reactive 0.11.5 and reactive-glut 0.1.9.
Shameless plug alert... I've attached my Haskell debugger hades http://control.monad.st/ to the following testcase: import Control.Applicative import FRP.Reactive import FRP.Reactive.LegacyAdapters foo = snapshot_ (pure (putStrLn "Hi")) (atTimes [0.001,0.002..]) main = adaptE foo >> adaptE foo Curious as to what is being retained, I did some poking around in the heap. Here's what I've found: [... snip looking through backtrace ...]
liftIO . putStr =<< prettyPrint 140513828164552 $1 = foo/s2fC pointers 140513828164552 [Ptr (RemotePtr 8279928),Ptr (RemotePtr 8324640)] liftIO . putStr =<< prettyPrint 8279928 $1 = (,) (Imp $134 (exactNB/smWn $138 $133 $134)) (Stepper $141 ((,) (Imp $140 (exactNB/smWn $138 $139 $140)) (Stepper $141 ((,) (Imp $143 (exactNB/smWn $138 $142 $143)) (Stepper $141 ((,) (Imp $145 (exactNB/smWn $138 $144 $145)) (Stepper $141 ((,) (Imp $147 (exactNB/smWn $138 $146 $147)) (Stepper $141 ((,) (Imp $149 (exactNB/smWn $138 $148 $149)) (Stepper $141 ((,) (Imp $151 (exactNB/smWn $138 $150 $151)) (Stepper $141 ((,) (Imp $153 (exactNB/smWn $138 $152 $153)) ([...snip...] [...] $133 = 1.0e-3 $134 = (NoBound $133) $135 = 'H' $136 = (FileHandle $80 $81) $137 = (hPutStr1 $120 ((,) NoBuffering $121) $122 (hPutStr2 $123 $124) (hPutStr_$s$wa1 $127 $126) (hPutStr_$s$wa $127 $128)) $138 = (
$2 (amb2 (forkIO2 (childHandler1 $24 $25 $26 $27 ($Lr3Ktlvl23 $23))) $31 (catches1 $31) (finally1 $31) ((Handler $32 writeWord64OffPtr1/r1uF):((Handler $131 writeWord64OffPtr1/r1uJ):((Handler (<dict for Exception> $53 $54 ($LrXBa7 $52) $57) (<instance field ShowNonTermination2>/r1uL)):((Handler $132 $Lr1yylvl1/r1uP):((Handler (<dict for Exception> $75 $76 ($LrXVa12 $74) $79) ($Lr1yylvl1/r1uR (writeWord64OffPtr1/r1uD $136 $123 $137 $129 '"':$130))):$9))))) (SomeException $131 BothBottom) (SomeException $132 DontBother))) $139 = 2.0e-3 $140 = (NoBound $139) $141 = (main8 $123 $135:$50:$9 $136 $137) $142 = 3.0e-3 $143 = (NoBound $142) $144 = 4.0e-3 $145 = (NoBound $144) $146 = 5.0e-3 $147 = (NoBound $146) $148 = 6.0e-3 $149 = (NoBound $148) $150 = 7.0e-3 $151 = (NoBound $150) $152 = 8.0e-3 $153 = (NoBound $152)
So (obviously in retrospect), foo is retaining an object of this form:
(Imp (exactNB/smWn (NoBound 1.0e-3)), Stepper main8
(Imp (exactNB/smWn (NoBound 2.0e-3)), Stepper main8 (..., ...)))
Here, main8 looks to be the (putStrLn "Hi") computation.
A slight tweak to the code should sort this out:
foo () = snapshot_ (pure (putStrLn "Hi")) (atTimes [0.001,0.002..])
main = adaptE (foo ()) >> adaptE (foo ())
Now I no longer see the space leak. In hades, I can't even find a
reference to foo (presumably it got inlined out of existence). The event's
list now looks like this (start from $209):
$195 = 25.91600000000869
$196 = (NoBound $195)
$209 = listEG/sigh $210 $211
$210 = (Imp $196 (exactNB/smWn $216 $195 $196))
$211 = <instance field FunctorEventG_fmap>/siFL (withTimeE1 $212) $213
$212 = exactNB1
$213 = listEG/sigh $210 (Stepper () $214)
$214 = <worker for untilE>/sgyB $215 (<worker for untilE>/sfAZ $228 (Imp
$227 (atTimes3 $216)))
$215 = foldr/s2p1 (atTimes1 $216) $217
$216 = (

Richard,
Wow and wow!
I'm going to learn about hades.
- Conal
On Wed, Aug 25, 2010 at 8:26 AM, Richard Smith
Hi,
On Tue, August 24, 2010 10:14, Alexander Foremny wrote:
When running worldB from main I can see the program's memory usage increasing and everything becomes very unresponsive. It seems as if whenE is accumalating all the occurences of the event. The problem seems to boil down to snapshot having the same behavior.
snapshot (pure False) (atTimes [1..])
This piece of code uses very much memory either. Is this due to reactive being broken (I read that somewhere) or is my solution just no solution at all?
I am using ghc 6.12.1 with reactive 0.11.5 and reactive-glut 0.1.9.
Shameless plug alert...
I've attached my Haskell debugger hades http://control.monad.st/ to the following testcase:
import Control.Applicative import FRP.Reactive import FRP.Reactive.LegacyAdapters
foo = snapshot_ (pure (putStrLn "Hi")) (atTimes [0.001,0.002..]) main = adaptE foo >> adaptE foo
Curious as to what is being retained, I did some poking around in the heap. Here's what I've found:
[... snip looking through backtrace ...]
liftIO . putStr =<< prettyPrint 140513828164552 $1 = foo/s2fC pointers 140513828164552 [Ptr (RemotePtr 8279928),Ptr (RemotePtr 8324640)] liftIO . putStr =<< prettyPrint 8279928 $1 = (,) (Imp $134 (exactNB/smWn $138 $133 $134)) (Stepper $141 ((,) (Imp $140 (exactNB/smWn $138 $139 $140)) (Stepper $141 ((,) (Imp $143 (exactNB/smWn $138 $142 $143)) (Stepper $141 ((,) (Imp $145 (exactNB/smWn $138 $144 $145)) (Stepper $141 ((,) (Imp $147 (exactNB/smWn $138 $146 $147)) (Stepper $141 ((,) (Imp $149 (exactNB/smWn $138 $148 $149)) (Stepper $141 ((,) (Imp $151 (exactNB/smWn $138 $150 $151)) (Stepper $141 ((,) (Imp $153 (exactNB/smWn $138 $152 $153)) ([...snip...] [...] $133 = 1.0e-3 $134 = (NoBound $133) $135 = 'H' $136 = (FileHandle $80 $81) $137 = (hPutStr1 $120 ((,) NoBuffering $121) $122 (hPutStr2 $123 $124) (hPutStr_$s$wa1 $127 $126) (hPutStr_$s$wa $127 $128)) $138 = (
$2 (amb2 (forkIO2 (childHandler1 $24 $25 $26 $27 ($Lr3Ktlvl23 $23))) $31 (catches1 $31) (finally1 $31) ((Handler $32 writeWord64OffPtr1/r1uF):((Handler $131 writeWord64OffPtr1/r1uJ):((Handler (<dict for Exception> $53 $54 ($LrXBa7 $52) $57) (<instance field ShowNonTermination2>/r1uL)):((Handler $132 $Lr1yylvl1/r1uP):((Handler (<dict for Exception> $75 $76 ($LrXVa12 $74) $79) ($Lr1yylvl1/r1uR (writeWord64OffPtr1/r1uD $136 $123 $137 $129 '"':$130))):$9))))) (SomeException $131 BothBottom) (SomeException $132 DontBother))) $139 = 2.0e-3 $140 = (NoBound $139) $141 = (main8 $123 $135:$50:$9 $136 $137) $142 = 3.0e-3 $143 = (NoBound $142) $144 = 4.0e-3 $145 = (NoBound $144) $146 = 5.0e-3 $147 = (NoBound $146) $148 = 6.0e-3 $149 = (NoBound $148) $150 = 7.0e-3 $151 = (NoBound $150) $152 = 8.0e-3 $153 = (NoBound $152) So (obviously in retrospect), foo is retaining an object of this form:
(Imp (exactNB/smWn (NoBound 1.0e-3)), Stepper main8 (Imp (exactNB/smWn (NoBound 2.0e-3)), Stepper main8 (..., ...)))
Here, main8 looks to be the (putStrLn "Hi") computation.
A slight tweak to the code should sort this out:
foo () = snapshot_ (pure (putStrLn "Hi")) (atTimes [0.001,0.002..]) main = adaptE (foo ()) >> adaptE (foo ())
Now I no longer see the space leak. In hades, I can't even find a reference to foo (presumably it got inlined out of existence). The event's list now looks like this (start from $209):
$195 = 25.91600000000869 $196 = (NoBound $195) $209 = listEG/sigh $210 $211 $210 = (Imp $196 (exactNB/smWn $216 $195 $196)) $211 = <instance field FunctorEventG_fmap>/siFL (withTimeE1 $212) $213 $212 = exactNB1 $213 = listEG/sigh $210 (Stepper () $214) $214 = <worker for untilE>/sgyB $215 (<worker for untilE>/sfAZ $228 (Imp $227 (atTimes3 $216))) $215 = foldr/s2p1 (atTimes1 $216) $217 $216 = (
$204 $201) $217 = /s8ah $195 25.91700000000869 $218 $219 ( /s3ts $218 $219) $218 = plusDouble $219 = minusDouble I hope this gives you enough insight to be able to fix your code!
Regards, Richard Smith
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive
participants (2)
-
Conal Elliott
-
Richard Smith