[Haskell-cafe] reactive and <<loop>>
stefan kersten
sk at k-hornz.de
Thu Jun 19 14:08:46 EDT 2008
hi,
i'm having problems with a very simple example using conal elliott's
'reactive' library:
module Main where
import Control.Applicative
import Control.Concurrent
import Control.Monad
import Data.Reactive
import System.Random
main :: IO ()
main = do
(e, snk) <- mkEvent
forkIO $ forever ((getStdRandom random :: IO Double) >>= snk >>
threadDelay 10000)
runE (print `fmap` withPrevE e)
return ()
which starts to output this after a while:
reactive_loop.hs: <<loop>>
this is with ghc 6.8.1 on osx 10.4. any ideas what might be going wrong?
many thanks,
<sk>
More information about the Haskell-Cafe
mailing list