[commit: base] : preventing warnings. (411db2e)
Johan Tibell
johan.tibell at gmail.com
Tue Feb 12 07:51:08 CET 2013
Repository : ssh://darcs.haskell.org//srv/darcs/packages/base
On branch :
http://hackage.haskell.org/trac/ghc/changeset/411db2e961fd638a606f094ba8fe52d43b35aae9
>---------------------------------------------------------------
commit 411db2e961fd638a606f094ba8fe52d43b35aae9
Author: Kazu Yamamoto <kazu at iij.ad.jp>
Date: Wed Dec 26 15:45:52 2012 +0900
preventing warnings.
Conflicts:
GHC/Event/Manager.hs
>---------------------------------------------------------------
GHC/Event/Control.hs | 1 -
GHC/Event/Manager.hs | 7 +++----
GHC/Event/TimerManager.hs | 5 ++---
3 files changed, 5 insertions(+), 8 deletions(-)
diff --git a/GHC/Event/Control.hs b/GHC/Event/Control.hs
index 3f9f9ed..457d853 100644
--- a/GHC/Event/Control.hs
+++ b/GHC/Event/Control.hs
@@ -47,7 +47,6 @@ import System.Posix.Internals (c_close, c_pipe, c_read, c_write,
import System.Posix.Types (Fd)
#if defined(HAVE_EVENTFD)
-import Data.Word (Word64)
import Foreign.C.Error (throwErrnoIfMinus1)
import Foreign.C.Types (CULong(..))
#else
diff --git a/GHC/Event/Manager.hs b/GHC/Event/Manager.hs
index 45bf648..f6ba9b2 100644
--- a/GHC/Event/Manager.hs
+++ b/GHC/Event/Manager.hs
@@ -51,7 +51,7 @@ module GHC.Event.Manager
import Control.Concurrent.MVar (MVar, modifyMVar, newMVar, readMVar, putMVar,
tryPutMVar, takeMVar)
import Control.Exception (onException)
-import Control.Monad ((=<<), forM_, liftM, sequence_, when, replicateM, void)
+import Control.Monad ((=<<), forM_, liftM, when, replicateM, void)
import Data.IORef (IORef, atomicModifyIORef, mkWeakIORef, newIORef, readIORef,
writeIORef)
import Data.Maybe (Maybe(..))
@@ -300,11 +300,10 @@ registerFd mgr cb fd evs = do
-- | Wake up the event manager.
wakeManager :: EventManager -> IO ()
-wakeManager mgr =
#if defined(HAVE_EPOLL) || defined(HAVE_KQUEUE)
- return ()
+wakeManager _ = return ()
#else
- sendWakeup (emControl mgr)
+wakeManager mgr = sendWakeup (emControl mgr)
#endif
eventsOf :: [FdData] -> Event
diff --git a/GHC/Event/TimerManager.hs b/GHC/Event/TimerManager.hs
index 49b0d6c..dd55355 100644
--- a/GHC/Event/TimerManager.hs
+++ b/GHC/Event/TimerManager.hs
@@ -51,8 +51,7 @@ import GHC.Real ((/), fromIntegral )
import GHC.Show (Show(..))
import GHC.Event.Clock (getMonotonicTime)
import GHC.Event.Control
-import GHC.Event.Internal (Backend, Event, evtClose, evtRead, evtWrite,
- Timeout(..))
+import GHC.Event.Internal (Backend, Event, evtRead, Timeout(..))
import GHC.Event.Unique (Unique, UniqueSource, newSource, newUnique)
import System.Posix.Types (Fd)
@@ -206,7 +205,7 @@ loop mgr at TimerManager{..} = do
step :: TimerManager -> TimeoutQueue -> IO (Bool, TimeoutQueue)
step mgr at TimerManager{..} tq = do
(timeout, q') <- mkTimeout tq
- I.poll emBackend (Just timeout) (handleControlEvent mgr)
+ _ <- I.poll emBackend (Just timeout) (handleControlEvent mgr)
state <- readIORef emState
state `seq` return (state == Running, q')
where
More information about the ghc-commits
mailing list