Hi Dustin,

Sorry about that. There are some serious space leaks no one has figured out yet (afaik). :(

    - Conal

On Tue, Jan 11, 2011 at 3:32 PM, Dustin DeWeese <dustin.deweese@gmail.com> wrote:
I cannot get Reactive to behave.  I am trying to write a simple program that feeds events to a function and prints 'DING!' when it receives an event from the function.  If the function is id or (join . return), it works correctly.  If the function is (>>= return), it consumes all of my RAM and does nothing.

Why?  I've spent several days trying to figure this out.

I am using GHC 6.12.1 for x86_64 Linux.

import FRP.Reactive
import FRP.Reactive.Reactive
import FRP.Reactive.Internal.Reactive
import FRP.Reactive.Internal.Timing
import FRP.Reactive.LegacyAdapters
import Control.Monad
import Control.Concurrent
import Control.Applicative

runEventProcessor :: (Event () -> Event ()) -> IO ()
runEventProcessor f = do
  clk <- makeClock
  (sink, ev) <- makeEvent clk
  forkE (wait clk) . fmap (\_ -> putStrLn "DING!") . f $ ev
  forever $ do getLine -- wait for <ENTER>
               sink ()
               putStrLn "<< button pressed >>"
               threadDelay 100000 -- avoid pressing button too fast

wait clk = sleepPast (cGetTime clk) . exactNB

explodes1 = runEventProcessor (>>= return)
explodes2 = runEventProcessor (join . fmap (Event . pure . pure))
works1 = runEventProcessor (join . return)
works2 = runEventProcessor (fmap id)
works3 = runEventProcessor (join . Event . pure . pure)
-- requires joinE to be exported from FRP.Reactive.PrimReactive
-- works4 = runEventProcessor (joinE . return)


_______________________________________________
Reactive mailing list
Reactive@haskell.org
http://www.haskell.org/mailman/listinfo/reactive