[Haskell-cafe] Asynchronous exception wormholes kill modularity

Matthew Brecknell matthew at brecknell.net
Fri Mar 26 01:02:50 EDT 2010


Hi Bas,

Bas van Dijk wrote: 
> block $ do ...
>            modifyMVar_ m f
>            ...
> 
> >From a quick glanse at this code it looks like asynchronous exceptions
> can't be thrown to this transaction because we block them. However the
> unblock in modifyMVar_ opens an asynchronous exception "wormhole"
> right into our blocked computation. This destroys modularity.
> 
> We can solve it by introducing two handy functions 'blockedApply' and
> 'blockedApply2' and wrapping each of the operations in them:
> 
> > blockedApply :: IO a -> (IO a -> IO b) -> IO b
> > blockedApply a f = do
> >   b <- blocked
> >   if b
> >     then f a
> >     else block $ f $ unblock a
> 
> > blockedApply2 :: (c -> IO a) -> ((c -> IO a) -> IO b) -> IO b
> > blockedApply2 g f = do
> >   b <- blocked
> >   if b
> >     then f g
> >     else block $ f $ unblock . g

I think it might be slightly more complicated than that. Any call to
takeMVar or putMVar introduces it's own little wormhole, if it can't be
serviced immediately, regardless of the mask-state of the thread. This
is documented here (under interruptible operations):

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Exception.html#13

And is confirmed by a simple test (with GHC 6.10.4 on Linux):

import Prelude hiding(catch)
import Control.Concurrent
import Control.Exception

main = do
  chan <- newEmptyMVar
  done <- newEmptyMVar
  kill <- block $ forkIO $ do
    (takeMVar chan >>= putMVar done)
      `onException` putMVar done "Exception received during takeMVar"
  forkIO $ do
    killThread kill
    threadDelay 2000000
    putMVar chan "No exception received during takeMVar"
  takeMVar done >>= putStrLn

So we currently have: (1) a state in which asynchronous exceptions are
propagated when execution blocks on an interruptible operation, and are
deferred otherwise; and (2) a state in which asynchronous exceptions are
not deferred.

I agree with the documentation that (1) is at least sometimes necessary,
but it might also have the same negative effect on modularity that you
describe.

So do we need a third state (3) in which asynchronous exceptions are
deferred, even if execution blocks on a takeMVar or putMVar? If so, is
the choice between (1) and (3) always localised, as in the example in
the above documentation? Or is that choice also subject to modularity
concerns?

Regards,
Matthew





More information about the Haskell-Cafe mailing list