[Haskell-cafe] Barrier implementation
David Roundy
droundy at abridgegame.org
Fri Dec 16 12:24:35 EST 2005
On Fri, Dec 16, 2005 at 05:46:33PM +0100, Peter Eriksen wrote:
> Here's the code:
>
> > module Main where
> >
> > import Control.Concurrent
> > import Control.Concurrent.STM
> > import System.Random
> >
> > worker :: Int -> TVar Int -> IO ()
> > worker id tv = do
> > sleepingTime <- randomRIO (0, 50000)
> > threadDelay sleepingTime
> > putStr $ show id
> > atomically $ barrier tv id
> > worker id tv
You've got the barrier after the putStr, so there's nothing to make the
first ten putStrs be in order. I think you need a non-updating barrier
before the putStr and then an updating function after the putStr (to tell
the next worker that it is free to print).
> barrier :: TVar Int -> Int -> STM ()
> barrier tv id = do
> passed <- readTVar tv
> if (passed `mod` 10 == id)
> then writeTVar tv (passed+1)
> else retry
> move_along :: TVar Int -> Int -> STM ()
> barrier tv id = do passed <- readTVar tv
> writeTVar tv (passed+1)
> worker :: Int -> TVar Int -> IO ()
> worker id tv = do
> sleepingTime <- randomRIO (0, 50000)
> threadDelay sleepingTime
> atomically $ barrier tv id
> putStr $ show id
> atomically $ move_along tv id
> worker id tv
--
David Roundy
More information about the Haskell-Cafe
mailing list