[commit: ghc] master: Revert "event manager: Don't worry if attempt to wake dead manager fails" (436aa7a)

git at git.haskell.org git at git.haskell.org
Wed Jan 11 04:41:23 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/436aa7aaf1b30f19ece6c610e357cb678612de8a/ghc

>---------------------------------------------------------------

commit 436aa7aaf1b30f19ece6c610e357cb678612de8a
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Tue Jan 10 23:40:33 2017 -0500

    Revert "event manager: Don't worry if attempt to wake dead manager fails"
    
    This broke the OS X build.
    
    This reverts commit 6de7613604216f65fae92d8066a078bf9cd3c088.


>---------------------------------------------------------------

436aa7aaf1b30f19ece6c610e357cb678612de8a
 libraries/base/GHC/Event/Control.hs | 28 +++++-----------------------
 1 file changed, 5 insertions(+), 23 deletions(-)

diff --git a/libraries/base/GHC/Event/Control.hs b/libraries/base/GHC/Event/Control.hs
index 83950c2..0b0f558 100644
--- a/libraries/base/GHC/Event/Control.hs
+++ b/libraries/base/GHC/Event/Control.hs
@@ -30,12 +30,11 @@ module GHC.Event.Control
 
 import Foreign.ForeignPtr (ForeignPtr)
 import GHC.Base
-import GHC.IORef
 import GHC.Conc.Signal (Signal)
 import GHC.Real (fromIntegral)
 import GHC.Show (Show)
 import GHC.Word (Word8)
-import Foreign.C.Error (throwErrnoIfMinus1_, throwErrno, getErrno, eBADF)
+import Foreign.C.Error (throwErrnoIfMinus1_)
 import Foreign.C.Types (CInt(..), CSize(..))
 import Foreign.ForeignPtr (mallocForeignPtrBytes, withForeignPtr)
 import Foreign.Marshal (alloca, allocaBytes)
@@ -70,9 +69,7 @@ data Control = W {
     , wakeupWriteFd  :: {-# UNPACK #-} !Fd
 #endif
     , didRegisterWakeupFd :: !Bool
-      -- | Have this Control's fds been cleaned up?
-    , controlIsDead  :: !(IORef Bool)
-    }
+    } deriving (Show)
 
 #if defined(HAVE_EVENTFD)
 wakeupReadFd :: Control -> Fd
@@ -104,7 +101,6 @@ newControl shouldRegister = allocaArray 2 $ \fds -> do
   (wake_rd, wake_wr) <- createPipe
   when shouldRegister $ c_setIOManagerWakeupFd wake_wr
 #endif
-  isDead <- newIORef False
   return W { controlReadFd  = fromIntegral ctrl_rd
            , controlWriteFd = fromIntegral ctrl_wr
 #if defined(HAVE_EVENTFD)
@@ -114,7 +110,6 @@ newControl shouldRegister = allocaArray 2 $ \fds -> do
            , wakeupWriteFd  = fromIntegral wake_wr
 #endif
            , didRegisterWakeupFd = shouldRegister
-           , controlIsDead  = isDead
            }
 
 -- | Close the control structure used by the IO manager thread.
@@ -124,7 +119,6 @@ newControl shouldRegister = allocaArray 2 $ \fds -> do
 -- file after it has been closed.
 closeControl :: Control -> IO ()
 closeControl w = do
-  atomicModifyIORef (controlIsDead w) (\_ -> (True, ()))
   _ <- c_close . fromIntegral . controlReadFd $ w
   _ <- c_close . fromIntegral . controlWriteFd $ w
   when (didRegisterWakeupFd w) $ c_setIOManagerWakeupFd (-1)
@@ -178,21 +172,9 @@ readControlMessage ctrl fd
 
 sendWakeup :: Control -> IO ()
 #if defined(HAVE_EVENTFD)
-sendWakeup c = do
-  n <- c_eventfd_write (fromIntegral (controlEventFd c)) 1
-  case n of
-    0     -> return ()
-    _     -> do errno <- getErrno
-                -- Check that Control is still alive if we failed, since it's
-                -- possible that someone cleaned up the fds behind our backs and
-                -- consequently eventfd_write failed with EBADF. If it is dead
-                -- then just swallow the error since we are shutting down
-                -- anyways. Otherwise we will see failures during shutdown from
-                -- setnumcapabilities001 (#12038)
-                isDead <- readIORef (controlIsDead c)
-                if isDead && errno == eBADF
-                  then return ()
-                  else throwErrno "sendWakeup"
+sendWakeup c =
+  throwErrnoIfMinus1_ "sendWakeup" $
+  c_eventfd_write (fromIntegral (controlEventFd c)) 1
 #else
 sendWakeup c = do
   n <- sendMessage (wakeupWriteFd c) CMsgWakeup



More information about the ghc-commits mailing list