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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/9574057311c61a8c572e80839a8af0ab19ce0ae8

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

commit 9574057311c61a8c572e80839a8af0ab19ce0ae8
Author: Ian Lynagh <[email protected]>
Date:   Mon Jul 16 00:20:23 2012 +0100

    Remove a workaround for building with old GHCs

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

 GHC/Event/Control.hs |   12 ++----------
 1 files changed, 2 insertions(+), 10 deletions(-)

diff --git a/GHC/Event/Control.hs b/GHC/Event/Control.hs
index ab0636b..cd5641a 100644
--- a/GHC/Event/Control.hs
+++ b/GHC/Event/Control.hs
@@ -77,14 +77,6 @@ wakeupReadFd = controlEventFd
 {-# INLINE wakeupReadFd #-}
 #endif
 
-setNonBlock :: CInt -> IO ()
-setNonBlock fd =
-#if __GLASGOW_HASKELL__ >= 611
-  setNonBlockingFD fd True
-#else
-  setNonBlockingFD fd
-#endif
-
 -- | Create the structure (usually a pipe) used for waking up the IO
 -- manager thread from another thread.
 newControl :: IO Control
@@ -95,7 +87,7 @@ newControl = allocaArray 2 $ \fds -> do
         wr <- peekElemOff fds 1
         -- The write end must be non-blocking, since we may need to
         -- poke the event manager from a signal handler.
-        setNonBlock wr
+        setNonBlockingFD wr True
         setCloseOnExec rd
         setCloseOnExec wr
         return (rd, wr)
@@ -103,7 +95,7 @@ newControl = allocaArray 2 $ \fds -> do
   c_setIOManagerControlFd ctrl_wr
 #if defined(HAVE_EVENTFD)
   ev <- throwErrnoIfMinus1 "eventfd" $ c_eventfd 0 0
-  setNonBlock ev
+  setNonBlockingFD ev True
   setCloseOnExec ev
   c_setIOManagerWakeupFd ev
 #else



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to