> ..until further notice, just assume "broken".

Useful to know.  I shall postpone its use in critical projects.

BTW, s/joinMaybes/justE works quickly, in minimal CPU and memory.  Forgot about that function.  Curious that the operational semantics have become so odd though; I'm used to denotational ones being off -- late updates and so forth -- but I haven't come across quite that level of resource consumption in reactive code before.

Freddie

2009/6/10 Svein Ove Aas <svein.ove@aas.no>
2009/6/10 Freddie Manners <f.manners@gmail.com>:
> This is a silly example.  Console lines "b = x" update the value of b; "c =
> y" likewise; lines starting "a" cause the current value of a to be printed.
>
> module Main
>    where
>
> import FRP.Reactive
> import FRP.Reactive.LegacyAdapters
> import Data.List
> import Control.Monad
> import Control.Concurrent
> import Control.Applicative
>
> parseEvent :: String -> Event String -> Event Integer
> parseEvent s = fmap read . joinMaybes . fmap (stripPrefix s)
>
> main :: IO ()
> main = do
>       cl    <- makeClock
>       (s,e) <- makeEvent cl
>       forkIO . forever $ getLine >>= s
>       let b = stepper 0 $ parseEvent "b =" e
>       let c = stepper 0 $ parseEvent "c =" e
>       let p = parseEvent "a" e
>       let a = liftA2 (+) b c -- the only interesting line
>
>       adaptE . fmap print $ snapshot_ a p
>
> So yes, this does use explicit concurrency because "feeding" the reactive
> events (with getLine) and printing the answers must happen in different
> threads.
>
> Interestingly, this fairly simple program gobbles CPU and RAM on
> reactive-0.11, as well as running with a bit of a lag.  Could joinMaybes be
> to blame?  I don't know how happy the Monad instance of Event is these days.
>
"Fundamentally broken" about covers it.

Well, to be specific, joinE is broken, and looks hard to fix.
The Monoid instance for Event is also broken, but I think only when
all Events involved are finite.

Further, I was trying to fix it, but GHC is broken.

I'd also like to note that LegacyAdapters is broken. I've got a fix
for the broken bits, which happens to break everything else. Blocked
on another GHC bug, though.

..until further notice, just assume "broken".

--
Svein Ove Aas