Interruptible exception wormholes kill modularity

Edward Z. Yang ezyang at mit.edu
Sat Jul 2 04:49:55 UTC 2016


In 2010, in the thread "Asynchronous exception wormholes kill modularity" [1],
Bas van Dijk observed that 'unblock :: IO a -> IO a' broke modularity,
as the sequence of calls 'block . block . unblock $ io' would result in
'io' being run with asynchronous exceptions unblocked, despite the outer
'block' "expecting" that asynchronous exceptions cannot be thrown.

I would like to make two claims:

    1. The new mask/restore interface is insufficient to "solve"
    this modularity problem, as *interruptible* operations can
    still be used to catch asynchronous exceptions.

    2. Thus, we should provide an unblock combinator which
    can be used to catch asynchronous exceptions from a 'mask'
    (though not an 'uninterruptibleMask')--though it is
    doubtful if anyone should ever use 'mask' in the first
    place.

Claim 1: Here is some code which reimplements 'unblock':

    import Control.Exception
    import Control.Concurrent
    import Control.Concurrent.MVar

    unblock :: IO a -> IO a
    unblock io = do
        m <- newEmptyMVar
        _ <- forkIO (io >>= putMVar m)
        takeMVar m

The main idea is that 'takeMVar' is an interruptible operation:
when it blocks, the thread can now receive asynchronous exceptions.
In general, a thread can unmask exceptions by blocking.  Here
is a simple test-case:

    main = do
        let x = 10000000 -- Just do a bit of work
        tid <- myThreadId
        forkIO $ (threadDelay 10000 >> killThread tid)
        r <- mask $ \restore -> do
            -- restore $ do
            -- unblock $ do
                -- do something non-blocking
                evaluate (f x [])
        -- If the exception is delivered in a timely manner,
        -- shouldn't get here.
        print r

    f 0 r = r
    f n r = f (n-1) (n:r)

With both restore and unblock commented, the ThreadKilled
exception is delayed; uncommenting either restore or unblock
causes the exception to be delivered.

This admonition does not apply to uninterruptibleMask, for
which there are no interruptible exceptions.

Claim 2:  Thus, I come to the conclusion that we were wrong
to remove 'unblock', and that it is no worse than the
ability for interruptible actions to catch asynchronous
exceptions.

You could very well argue that interruptible actions are a design flaw.
Then you should use 'uninterruptibleMask' instead, which effectively
removes the concept of interruptibility--and is thus modular.  Indeed,
Eyal Lotem proposed [2] that 'bracket' should instead use
'uninterruptibleMask', for precisely the reason that it is too easy to
reenable asynchronous exceptions in 'mask'.  But assuming that
interruptible masks are a good idea (Simon Marlow has defended them
as "a way avoid reasoning about asynchronous exceptions except
at specific points, i.e., where you might block"), there should
be an 'unblock' for this type of mask.

It should be said that the absence of 'unblock' for
'uninterruptibleMask' only implies that a passed in IO action (e.g., the
cleanup action in bracket) does not have access to the exceptions thrown
to the current thread; it doesn't actually guarantee uninterruptibility,
since the passed in IO action could always raise a normal exception.
Haskell's type system is not up to the task of enforcing such
invariants.

Cheers,
Edward

[1]
https://mail.haskell.org/pipermail/libraries/2010-March/013310.html
https://mail.haskell.org/pipermail/libraries/2010-April/013420.html

[2]
https://mail.haskell.org/pipermail/libraries/2014-September/023675.html

P.S. You were CC'ed to this mail because you participated in the original
"Asynchronous exception wormholes kill modularity" discussion.

P.P.S. I have some speculations about using uninterruptibleMask more
frequently: it seems to me that there ought to be a variant of
uninterruptibleMask that immediately raises an exception if
the "uninterruptible" action blocks.  This would probably of
great assistance of noticing and eliminating blocking in
uninterruptible code.


More information about the ghc-devs mailing list