Digging around with the commented query -- that a "pure (string)" is getting delayed -- I've hit a rather fundamental problem: it seems Event doesn't obey the Monad laws. I don't know whether this is a known issue or whether I'm being plain stupid, but this:--
module Main
where
import FRP.Reactive
import FRP.Reactive.LegacyAdapters
import Control.Concurrent
import Control.Applicative
import Control.Monad
import Data.Monoid
import Data.Maybe
main = do
clock <- makeClock
(sink, evnt) <- makeEvent clock
forkIO . sequence_ $ repeat (getLine >>= sink)
adaptE . fmap putStrLn $ (pure "A Line!" `mappend` evnt)
-- adaptE . fmap putStrLn $ (pure "A Line!" `mappend` (evnt >>= return))
and the same with the penultimate line commented instead of the last, appear to have different behaviours: in the version shown, "A Line!" is printed when the program starts; and in the other, this is delayed until after the first line is read (but before it is printed).
Should this happen?
Freddie Manners
Hi
As part of studying the Reactive library, I have created a simple game.
The object of the game is to guess a number.
As I am a newbie with respect to FRP, I assume that my game could have
been implemented more elegantly. Comments are most welcome.
The game can be found here
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=3037#a3037 and it is
attached.
Greetings,
Mads Lindstrøm
_______________________________________________
Reactive mailing list
Reactive@haskell.org
http://www.haskell.org/mailman/listinfo/reactive