Understanding behavior of BlockedIndefinitelyOnMVar exception

Brandon Simmons brandon.m.simmons at gmail.com
Mon Jul 25 00:56:12 CEST 2011


I'm trying to really understand how the BlockedIndefinitelyOnMVar
exception works in concurrent code as I would like to rely on it as a
useful runtime signal in a concurrency library I'm working on.

Here is some code illustrating a function restoring an abandoned lock
in a single-threaded program and works as I would expect:

-------- START CODE --------
module Main
    where

import Control.Concurrent
import Control.Exception

-- This raises the exception only once and the lock is successfully restored:
main1 = do
    lock <- newMVar ()
    lockPrint "good1" lock
    badLockPrint "bad" lock
    -- exception is raised and lock is restored here:
    lockPrint "good2" lock
    -- no exception raised:
    lockPrint "good3" lock
    readMVar lock

lockPrint :: String -> MVar () -> IO ()
lockPrint name v =
    do e <- try $ takeMVar v :: IO (Either BlockedIndefinitelyOnMVar ())
       -- either print exception, or print name:
       either print (const $ putStrLn name) e
   `finally`  putMVar v ()

-- perhaps simulates an operation that died before it could return a lock:
badLockPrint :: String -> MVar () -> IO ()
badLockPrint s v = do
    takeMVar v
    putStrLn s
    -- Forgot to return the lock here!:
-------- END CODE --------


Now here is a variation of 'main' that forks the operations:


-------- START CODE --------
main0 = do
    lock <- newMVar ()
    forkIO $ lockPrint "good1" lock

    threadDelay 1000000
    forkIO $ badLockPrint "bad" lock

    -- these both raise blocked indefinitely exception
    threadDelay 1000000
    forkIO $ lockPrint "good2" lock
    threadDelay 1000000
    forkIO $ lockPrint "good3" lock

    threadDelay 1000000
-------- END CODE --------


What I think I've learned here is that the BlockedIndefinitelyOnMVar
exception is raised in all the blocked threads "at once" as it were.
That despite the fact that the handler code in 'lockPrint' restores
the lock for successive threads.

This would also seem to imply that putMVar's in an exception handler
don't stop the runtime from raising the BlockedIndefinitelyOnMVar. But
that doesn't really seem right.

Can anyone comment on the two conclusions above?

FWIW, this was an interesting related thread:
http://comments.gmane.org/gmane.comp.lang.haskell.glasgow.user/18667

Thanks,
Brandon Simmons
http://coder.bsimmons.name



More information about the Glasgow-haskell-users mailing list