[Haskell-cafe] Race Condition in threads

mukesh tiwari mukeshtiwari.iiitm at gmail.com
Tue Dec 18 19:28:45 CET 2012


Hi Serguey
Thank you for reply. I tried with IORef but I am missing a  function which
modify it.

In this case every thread just write value 10 to variable n.
incr_count :: MVar () -> IORef Int  -> IO ()
incr_count m n = ( forM_ [ 1 .. 10000 ] $ \_ -> writeIORef n 10  ) >>
putMVar m ()


main :: IO ()
main = do
      count <- newIORef 0
      list <- forM [1..10] $ \_ -> newEmptyMVar
      forM_ list $ \var -> forkIO . incr_count var $ count
      forM_ list $ \var ->  takeMVar var
      val <- readIORef count
      print val


ghci>:t atomicModifyIORef
atomicModifyIORef :: IORef a -> (a -> (a, b)) -> IO b
ghci>:t readIORef
readIORef :: IORef a -> IO a
ghci>:t writeIORef
writeIORef :: IORef a -> a -> IO ()

I have atomicModifyIORef but it puts it into IO. I am missing some thing
like this
ghci>:t modifyMVar_
modifyMVar_ :: MVar a -> (a -> IO a) -> IO ()

modifyIORef_:: IORef a -> ( a -> IO a ) -> IO ()

Mukesh Tiwari


On Tue, Dec 18, 2012 at 11:50 PM, Serguey Zefirov <sergueyz at gmail.com>wrote:

> 2012/12/18 mukesh tiwari <mukeshtiwari.iiitm at gmail.com>:
> > Hello All
> > I have two questions.
> > 1. I wrote this code to create 10  simultaneous threads. Could some one
> > please tell me if this is correct or not ?
> >
> > incr_count :: MVar () -> MVar Int -> IO ()
> > incr_count m n = ( forM_ [ 1..10000 ] $ \_ -> modifyMVar_ n ( return . (
> +
> > 10 ) ) ) >> putMVar m ()
> >
> > main :: IO()
> > main = do
> >       count <- newMVar 0
> >       list <- forM [1..10] $ \_ -> newEmptyMVar
> >       forM_ list $ \var -> forkIO . incr_count var $ count
> >       forM_ list $ \var ->  takeMVar var
> >       val <- takeMVar count
> >       print val
>
> It is pretty much correct (some comments would be nice, though).
>
>
> > 2. I am trying to create  race condition which makes the variable in
> > inconsistent state. Could some one please tell me how to achieve this ? I
> > look at IORef but it does not have function like modifyMVar_.
>
> MVars are "atomic" in the sense that they have empty state and mutator
> can wait until variable will have a value. So you have to operate with
> something else, either IORef or with readMVar instead of takeMVar or
> modifyMVar_.
>
> > Mukesh Tiwari
> >
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20121218/e367ca7a/attachment.htm>


More information about the Haskell-Cafe mailing list