[commit: base] master: Use (.&.) instead of mod in GHC.Event.Manager since the modulus is a power of 2. (fec4764)

Johan Tibell johan.tibell at gmail.com
Tue Feb 12 07:51:35 CET 2013


Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/fec4764fc4ad2ecb8c476e1a90976f52051c088d

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

commit fec4764fc4ad2ecb8c476e1a90976f52051c088d
Author: Andreas Voellmy <andreas.voellmy at gmail.com>
Date:   Mon Jan 7 19:44:31 2013 -0500

    Use (.&.) instead of mod in GHC.Event.Manager since the modulus is a power of 2.

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

 GHC/Event/Manager.hs |    6 ++++--
 1 files changed, 4 insertions(+), 2 deletions(-)

diff --git a/GHC/Event/Manager.hs b/GHC/Event/Manager.hs
index da0a461..5c0ac0a 100644
--- a/GHC/Event/Manager.hs
+++ b/GHC/Event/Manager.hs
@@ -52,6 +52,7 @@ import Control.Concurrent.MVar (MVar, modifyMVar, newMVar, readMVar, putMVar,
                                 tryPutMVar, takeMVar)
 import Control.Exception (onException)
 import Control.Monad ((=<<), forM_, liftM, when, replicateM, void)
+import Data.Bits ((.&.))
 import Data.IORef (IORef, atomicModifyIORef, mkWeakIORef, newIORef, readIORef,
                    writeIORef)
 import Data.Maybe (Maybe(..))
@@ -63,7 +64,7 @@ import GHC.Conc.Signal (runHandlers)
 import GHC.Conc.Sync (yield)
 import GHC.List (filter)
 import GHC.Num (Num(..))
-import GHC.Real (fromIntegral, mod)
+import GHC.Real (fromIntegral)
 import GHC.Show (Show(..))
 import GHC.Event.Control
 import GHC.Event.Internal (Backend, Event, evtClose, evtRead, evtWrite,
@@ -120,11 +121,12 @@ data EventManager = EventManager
     , emLock         :: MVar ()
     }
 
+-- must be power of 2
 callbackArraySize :: Int
 callbackArraySize = 32
 
 hashFd :: Fd -> Int
-hashFd fd = fromIntegral fd `mod` callbackArraySize
+hashFd fd = fromIntegral fd .&. (callbackArraySize - 1)
 {-# INLINE hashFd #-}
 
 callbackTableVar :: EventManager -> Fd -> MVar (IM.IntMap [FdData])





More information about the ghc-commits mailing list