[Haskell-cafe] Re: Asynchronous exception wormholes kill modularity

Bas van Dijk v.dijk.bas at gmail.com
Fri Apr 9 06:19:19 EDT 2010


On Fri, Apr 9, 2010 at 10:40 AM, Bertram Felgenhauer
<bertram.felgenhauer at googlemail.com> wrote:
> How does forkIO fit into the picture? That's one point where reasonable
> code may want to unblock all exceptions unconditionally - for example to
> allow the thread to be killed later.
>
>    timeout t io = block $ do
>        result <- newEmptyMVar
>        tid <- forkIO $ unblock (io >>= putMVar result)
>        threadDelay t `onException` killThread tid
>        killThread tid
>        tryTakeMVar result

The System.Timeout.timeout function is indeed problematic:

http://haskell.org/ghc/docs/latest/html/libraries/base-4.2.0.0/System-Timeout.html

To quote the documentation:

"...The design of this combinator was guided by the objective that
timeout n f  should behave exactly the same as f as long as f doesn't
time out..."

and

"...It also possible for f to receive exceptions thrown to it by
another thread..."

They seem to contradict each other because when 'f' has asynchronous
exceptions blocked 'timeout n f' should also have asynchronous
exceptions blocked because it should behave the same, however the
latter says that 'f' may always receive asynchronous exceptions.

Of course for the timeout function to work correctly 'f' should be
able to receive asynchronous exceptions otherwise it won't terminate
when the Timeout exception is asynchronously thrown to it:

timeout :: Int -> IO a -> IO (Maybe a)
timeout n f
    | n <  0    = fmap Just f
    | n == 0    = return Nothing
    | otherwise = do
        pid <- myThreadId
        ex  <- fmap Timeout newUnique
        handleJust (\e -> if e == ex then Just () else Nothing)
                   (\_ -> return Nothing)
                   (bracket (forkIO (threadDelay n >> throwTo pid ex))
                            (killThread)
                            (\_ -> fmap Just f))

now when we rewrite 'bracket', using 'mask' so that it's not an
asynchronous exception wormhole anymore, and we apply timeout to a
computation in a thread that has asynchronous exceptions blocked the
computation won't actually timeout because it won't be able the
receive the Timeout exception.

I think we just have to live with this and explain it clearly in the
documentation of timeout that you should not call it in a masked
thread.

regards,

Bas


More information about the Haskell-Cafe mailing list