module Control.Concurrent.Futures.Example02 where import qualified Control.Concurrent.Futures.Chan as Chan import qualified Control.Concurrent.Futures.Futures as Futures import Control.Concurrent -- local finals oneSecond = 1000000 -------------------------------------------------------------------------------- -- | Producer Consumer Example for channels using 'Futures.withFuturesDo'. channelExampleF :: IO () channelExampleF = Futures.withFuturesDo channelExample -- | Producer Consumer Example for channels. channelExample :: IO () channelExample = do putStrLn $ "Producer-Consumer example with channels" channel <- Chan.newChan Control.Concurrent.forkIO $ (produce 10 channel) Control.Concurrent.forkIO $ (consume channel) Control.Concurrent.threadDelay $ 10 * oneSecond consume :: (Show a) => Chan.Chan a -> IO b consume chan = do putStrLn $ "Trying to read..." val <- Chan.readChan chan putStrLn $ "read new value: " ++ show val --Control.Concurrent.threadDelay oneSecond consume chan produce :: (Num a) => a -> Chan.Chan a -> IO () produce n chan = do case n of 0 -> Chan.writeChan chan n otherwise -> do Chan.writeChan chan n Control.Concurrent.threadDelay oneSecond produce (n-1) chan