19 Jun
                
                    2008
                
            
            
                19 Jun
                
                '08
                
            
            
            
        
    
                2:08 p.m.
            
        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>
        6347
        
      
          Age (days ago)
        
      
        6347
        
    
          Last active (days ago)
        
        
        
        0 comments
    
    
        
        1 participants
    
    
    
    
    
    
    
    
    participants (1)
- 
                
stefan kersten