module Control.Concurrent.Futures.Example07 where import qualified Control.Concurrent.Futures.Barrier as Barrier import qualified Control.Concurrent.Futures.Futures as Futures import Control.Concurrent -- local finals oneSecond = 1000000 -------------------------------------------------------------------------------- -- | Example for barrier using 'Futures.withFuturesDo'. barExampleF :: IO () barExampleF = Futures.withFuturesDo barExample -- | Example for barrier: 4 threads syncinc on the barrier. barExample :: IO () barExample = do putStrLn $ "4 Threads syncing on a barrier. This demo takes a bit time." bar <- Barrier.newBar 4 Control.Concurrent.forkIO $ (doSomething 2 bar) Control.Concurrent.forkIO $ (doSomething 7 bar) Control.Concurrent.forkIO $ (doSomething 10 bar) Control.Concurrent.forkIO $ (doSomething 5 bar) Control.Concurrent.threadDelay $ 10 * oneSecond --doSomething :: Int -> Barrier.Bar a -> IO () doSomething time bar = do Control.Concurrent.threadDelay $ time * oneSecond i <- Control.Concurrent.myThreadId putStrLn $ show i ++ " syncing." Barrier.syncBar bar return ()