[commit: base] : Avoid conditional compilation in GHC.Event.Manager. (1dbc927)
Johan Tibell
johan.tibell at gmail.com
Tue Feb 12 07:51:12 CET 2013
Repository : ssh://darcs.haskell.org//srv/darcs/packages/base
On branch :
http://hackage.haskell.org/trac/ghc/changeset/1dbc9270f771d06b9398637a986f07e72afaac18
>---------------------------------------------------------------
commit 1dbc9270f771d06b9398637a986f07e72afaac18
Author: Andreas Voellmy <andreas.voellmy at gmail.com>
Date: Fri Jan 4 10:51:00 2013 -0500
Avoid conditional compilation in GHC.Event.Manager.
Use ordinary Bool value to distinguish between backends supporting oneShot mode and eliminate several uses of conditional compilation in favor of ordinary conditional expressions using this Bool value. The benefit of this change is that more of the code compiles on more of the platforms.
>---------------------------------------------------------------
GHC/Event/Manager.hs | 38 +++++++++++++++++++-------------------
1 files changed, 19 insertions(+), 19 deletions(-)
diff --git a/GHC/Event/Manager.hs b/GHC/Event/Manager.hs
index 1f956a1..da0a461 100644
--- a/GHC/Event/Manager.hs
+++ b/GHC/Event/Manager.hs
@@ -130,6 +130,14 @@ hashFd fd = fromIntegral fd `mod` callbackArraySize
callbackTableVar :: EventManager -> Fd -> MVar (IM.IntMap [FdData])
callbackTableVar mgr fd = emFds mgr ! hashFd fd
{-# INLINE callbackTableVar #-}
+
+haveOneShot :: Bool
+{-# INLINE haveOneShot #-}
+#if defined(HAVE_EPOLL) || defined(HAVE_KQUEUE)
+haveOneShot = True
+#else
+haveOneShot = False
+#endif
------------------------------------------------------------------------
-- Creation
@@ -265,15 +273,13 @@ registerFd_ mgr@(EventManager{..}) cb fd evs = do
reg = FdKey fd u
!fdd = FdData reg evs cb
modifyMVar (callbackTableVar mgr fd) $ \oldMap ->
-#if defined(HAVE_EPOLL) || defined(HAVE_KQUEUE)
- if emOneShot
+ if haveOneShot && emOneShot
then case IM.insertWith (++) fd' [fdd] oldMap of
(Nothing, n) -> do I.modifyFdOnce emBackend fd evs
return (n, (reg, False))
(Just prev, n) -> do I.modifyFdOnce emBackend fd (combineEvents evs prev)
return (n, (reg, False))
else
-#endif
let (!newMap, (oldEvs, newEvs)) =
case IM.insertWith (++) fd' [fdd] oldMap of
(Nothing, n) -> (n, (mempty, evs))
@@ -330,12 +336,9 @@ unregisterFd_ mgr@(EventManager{..}) (FdKey fd u) =
(Just prev, newm) -> (newm, pairEvents prev newm fd')
modify = oldEvs /= newEvs
when modify $
-#if defined(HAVE_EPOLL) || defined(HAVE_KQUEUE)
- if emOneShot && newEvs /= mempty
+ if haveOneShot && emOneShot && newEvs /= mempty
then I.modifyFdOnce emBackend fd newEvs
- else
-#endif
- I.modifyFd emBackend fd oldEvs newEvs
+ else I.modifyFd emBackend fd oldEvs newEvs
return (newMap, modify)
-- | Drop a previous file descriptor registration.
@@ -411,21 +414,18 @@ onFdEvent mgr fd evs =
where
-- nothing to rearm.
aux [] _ [] =
-#if defined(HAVE_EPOLL) || defined(HAVE_KQUEUE)
- return (curmap, cbs)
-#else
- do I.modifyFd (emBackend mgr) fd (eventsOf cbs) mempty
- return (curmap, cbs)
-#endif
+ if haveOneShot
+ then return (curmap, cbs)
+ else do I.modifyFd (emBackend mgr) fd (eventsOf cbs) mempty
+ return (curmap, cbs)
+
-- reinsert and rearm; note that we already have the lock on the
-- callback table for this fd, and we deleted above, so we know there
-- is no entry in the table for this fd.
aux [] fdds saved@(_:_) = do
-#if defined(HAVE_EPOLL) || defined(HAVE_KQUEUE)
- I.modifyFdOnce (emBackend mgr) fd $ eventsOf saved
-#else
- I.modifyFd (emBackend mgr) fd (eventsOf cbs) $ eventsOf saved
-#endif
+ if haveOneShot
+ then I.modifyFdOnce (emBackend mgr) fd $ eventsOf saved
+ else I.modifyFd (emBackend mgr) fd (eventsOf cbs) $ eventsOf saved
return (snd $ IM.insertWith (\_ _ -> saved) fd' saved curmap, fdds)
-- continue, saving those callbacks that don't match the event
More information about the ghc-commits
mailing list