Calling the callback when event registration fails

Andrew Martin andrew.thaddeus at gmail.com
Thu Feb 7 13:08:45 UTC 2019


Here's the relevant code from GHC's event manager:

modifyFd :: KQueue -> Fd -> E.Event -> E.Event -> IO Bool
modifyFd kq fd oevt nevt = kqueueControl (kqueueFd kq) evs
  where
  evs
    | nevt == mempty = toEvents fd (toFilter oevt) flagDelete noteEOF
    | otherwise = toEvents fd (toFilter nevt) flagAdd noteEOF

modifyFdOnce :: KQueue -> Fd -> E.Event -> IO Bool
modifyFdOnce kq fd evt =
  kqueueControl (kqueueFd kq) (toEvents fd (toFilter evt) (flagAdd .|.
flagOneshot) noteEOF)

kqueueControl :: KQueueFd -> [Event] -> IO Bool
kqueueControl kfd evts =
  withTimeSpec (TimeSpec 0 0) $ \tp ->
    withArrayLen evts $ \evlen evp -> do
      res <- kevent False kfd evp evlen nullPtr 0 tp
      if res == -1
        then do
        err <- getErrno
        case err of
          _ | err == eINTR -> return True
          _ | err == eINVAL -> return False
          _ | err == eNOTSUP -> return False
          _ -> throwErrno "kevent"

And the kevent haskell function just wraps C's kevent function. Here's
FreeBSD's docs on the two relevant error codes:

    [EINVAL] The specified time limit or filter is invalid.

There is no similar documentation for ENOTSUP. I also found this in the
mailing list archive:
https://mail.haskell.org/pipermail/ghc-devs/2013-March/000798.html. It
confirms my suspicions. Immediately calling the callback when event
registration fails leads to undesirable behavior. The caller of
threadWaitRead will think that a file description is ready for a read when
it really isn't, and then whatever buffer-copying uninterruptible FFI call
they perform next will potentially block the runtime. The linked thread
suggests a fix (fallback on select when kqueue doesn't work). What's weird
is that the EPoll backend just throws an exception when it gets an error
like this. Maybe it would be more honest to make the kqueue backend do the
same.

On Wed, Feb 6, 2019 at 8:56 PM Carter Schonwald <carter.schonwald at gmail.com>
wrote:

> under what circumstances would those failure modes happen where the
> process can still run? (if need be, i can help you dig into the *BSD code
> bases if we aren't sure when the  kqueue code would do that)
>
> On Wed, Feb 6, 2019 at 7:10 PM Andrew Martin <andrew.thaddeus at gmail.com>
> wrote:
>
>> Digging through the different backends, it looks like only the kqueue
>> backend is even capable of returning False when modifyFd/modifyFdOnce is
>> called. This happens when kevent returns eINTR or eINVAL. Why do we call
>> the callback here instead of just throwing an error like we do in so many
>> other cases?
>>
>> On Wed, Feb 6, 2019 at 5:44 PM Andrew Martin <andrew.thaddeus at gmail.com>
>> wrote:
>>
>>> In the event manager's registerFd_, we find:
>>>
>>>     registerFd_ :: EventManager -> IOCallback -> Fd -> Event -> Lifetime
>>>                 -> IO (FdKey, Bool)
>>>     registerFd_ mgr@(EventManager{..}) cb !fd !evs lt = do
>>>       ... <- ...
>>>       (modify,ok) <- withMVar (callbackTableVar mgr fd) $ \tbl -> do
>>>         ... <- ...
>>>       -- this simulates behavior of old IO manager:
>>>       -- i.e. just call the callback if the registration fails.
>>>       when (not ok) (cb reg evs)
>>>       return (reg,modify)
>>>
>>> A comment and a question. Comment: registerFd_ is only ever called in
>>> contexts where exceptions are masked, so withMVar is doing some needless
>>> mask/restore. Question: why do we immidiately call the callback if event
>>> registration fails? This means that if event registration fails during
>>> something like `threadWaitRead`, the end result would be that
>>> `threadWaitRead` would just return immidiately. That doesn't seem good.
>>>
>>> --
>>> -Andrew Thaddeus Martin
>>>
>>
>>
>> --
>> -Andrew Thaddeus Martin
>> _______________________________________________
>> Libraries mailing list
>> Libraries at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
>>
>

-- 
-Andrew Thaddeus Martin
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20190207/35e3b1e9/attachment.html>


More information about the Libraries mailing list