Asynchronous exceptions in threadWait

Michael Walker mike at barrucadu.co.uk
Thu Jan 17 22:58:08 UTC 2019


So, something like this?

    threadWait :: Event -> Fd -> IO ()
    threadWait evt fd = do
      (m, mgr, reg) <- mask_ $ do
        m <- newEmptyMVar
        mgr <- getSystemEventManager_
        reg <- registerFd mgr (\_ e -> putMVar m e) fd evt M.OneShot
        pure (m, mgr, reg)
      evt' <- takeMVar m `onException` unregisterFd_ mgr reg
      if evt' `eventIs` evtClose
        then ioError $ errnoToIOError "threadWait" eBADF Nothing Nothing
        else return ()

I'm not sure this is semantically equivalent.

GHC can pre-empt a thread whenever it allocates memory, and I assume
it can deliver exceptions at that granularity too.  So if
`onException` allocates memory before the exception handler is set up,
then an exception could possibly be delivered in that brief window,
which would result in `unregisterFd_ mgr reg` never being called, and
an exception being raised in the caller of `threadWait`.

On Thu, 17 Jan 2019 at 22:43, Andrew Martin <andrew.thaddeus at gmail.com> wrote:
>
> Thanks. That makes sense. So, in the code I’m looking at, since takeMVar is the last effectful thing that happens, there is no semantic difference between having mask_ extend all the way down to the bottom of the block (as it currently does) and cutting it off right before the line involving takeMVar?
>
> Sent from my iPhone
>
> On Jan 17, 2019, at 5:23 PM, Michael Walker <mike at barrucadu.co.uk> wrote:
>
> >> Although the entire function has asynchronous exceptions masked, the call to takeMVar uses onException to deal with the possibility of an exception. According to the docs in Control.Concurrent, takeMVar can throw exceptions. But my understand (which may be wrong) is that the only exception this could throw would be something like BlockedIndefinitelyOnMVar, which I don't believe can happen here.
> >
> > That's not quite right.  The mask_ function blocks asynchronous
> > exceptions from being delivered to the thread while it's not
> > "interruptible".  Most blocking functions, such as takeMVar, make the
> > thread interruptible while they're blocked.  So any asynchronous
> > exception (such as ThreadKilled) could be delivered to the thread if
> > it blocks in the takeMVar.
> >
> > --
> > Michael Walker (http://www.barrucadu.co.uk)



-- 
Michael Walker (http://www.barrucadu.co.uk)


More information about the Libraries mailing list