[Haskell-beginners] MVar blocked or not?
Dean Herington
heringtonlacey at mindspring.com
Sat Jan 16 22:16:41 EST 2010
At 4:08 PM +0000 1/15/10, Adrian Adshead wrote:
>Hi everyone,
>
>I have a beginer question on using MVar.
>
>In the simple case I am getting what I expect...
>
>
>***CODE***
>module Main ( main ) where
>
>import Control.Concurrent
>import System.IO
>
>main = do
> mv <- newEmptyMVar
> putMVar mv 'a'
> threadDelay (5 * 10^6)
> putMVar mv 'b'
> threadDelay (5 * 10^6)
>***/CODE***
>
>
>Output after the first 5 second delay is :-
>
>Demo.exe: thread blocked indefinitely
>
>
>
>It even works as expected when there is a reading thread
>
>***CODE***
>module Main ( main ) where
>
>import Control.Concurrent
>import Control.Monad
>import System.IO
>
>main = do
> mv <- newEmptyMVar
> forkIO (readMV mv)
> putMVar mv 'a'
> threadDelay (5 * 10^6)
> putMVar mv 'b'
> threadDelay (5 * 10^6)
>
>readMV mv = forever $ do
> ch <- takeMVar mv
> putChar ch >> hFlush stdout
>***/CODE***
>
>Output including expected delays :-
>ab
>
>
>
>Then it starts to act unexpectedly
>
>***CODE***
>module Main ( main ) where
>
>import Control.Concurrent
>import Control.Monad
>import System.IO
>
>main = do
> mv <- newEmptyMVar
> forkIO (readMV mv)
> putMVar mv 'a'
> threadDelay (5 * 10^6)
> putMVar mv 'b'
> threadDelay (5 * 10^6)
>
>readMV mv = forever $ do
> ch <- modifyMVar mv modMV
> putChar ch >> hFlush stdout
> threadDelay (9*10^5)
>
>modMV 'a' = return ('c','a')
>modMV 'c' = return ('a','c')
>modMV x = return (x,x)
>***/CODE***
>
>Output is :-
>acacac
>
>
>The problem is that the output stops after 5 seconds
>and the program exits after 10 seconds. But why?
>
>Questions:-
>
>1. Why does the output stop? (Shouldn't the reader thread
>continue even if the main thread blocks on the second putMVar?)
>
>2. Why does it exit? (Shouldn't it be blocked at the second
>putMVar? The readMV thread now only modifies the MVar so it
>should never be empty)
>
>3. Is there a race condition using modifyMVar while there
>is another thread blocked in a putMVar? (I am assuming the
>second putMVar succeeded, but where did the 'b' go?)
>
>Many thanks for any help
>
>Adrian.
I believe the explanation is that modifyMVar simply wraps takeMVar
and putMVar around your modification action. It does not perform
these two "atomically", contrary to what you seem to be expecting.
Hence, the main thread is able to fill the MVar with 'b' in the short
time the readMV thread leaves the MVar empty while doing its
modifyMVar. This blocks the readMV thread (1.), allowing the main
thread to proceed (2.) and ultimately exit. The 'b' went into the
MVar, but the readMV thread never saw it, because it was waiting in
vain to put back the 'a' it last withdrew.
Dean
More information about the Beginners
mailing list