final revision to GArrow classes
[ghc-base.git] / Control / Concurrent.hs
index b49f7db..62a30b4 100644 (file)
@@ -1,4 +1,11 @@
+{-# LANGUAGE CPP
+           , ForeignFunctionInterface
+           , MagicHash
+           , UnboxedTuples
+           , ScopedTypeVariables
+  #-}
 {-# OPTIONS_GHC -fno-warn-unused-imports #-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Control.Concurrent
@@ -28,11 +35,17 @@ module Control.Concurrent (
 
         forkIO,
 #ifdef __GLASGOW_HASKELL__
-        forkIOUnmasked,
+        forkIOWithUnmask,
         killThread,
         throwTo,
 #endif
 
+        -- ** Threads with affinity
+        forkOn,
+        forkOnWithUnmask,
+        getNumCapabilities,
+        threadCapability,
+
         -- * Scheduling
 
         -- $conc_scheduling     
@@ -47,7 +60,6 @@ module Control.Concurrent (
         threadDelay,            -- :: Int -> IO ()
         threadWaitRead,         -- :: Int -> IO ()
         threadWaitWrite,        -- :: Int -> IO ()
-        closeFd,                -- :: (Int -> IO ()) -> Int -> IO ()
 #endif
 
         -- * Communication abstractions
@@ -72,7 +84,7 @@ module Control.Concurrent (
         forkOS,
         isCurrentThreadBound,
         runInBoundThread,
-        runInUnboundThread
+        runInUnboundThread,
 #endif
 
         -- * GHC's implementation of concurrency
@@ -91,6 +103,10 @@ module Control.Concurrent (
         -- ** Pre-emption
 
         -- $preemption
+
+        -- * Deprecated functions
+        forkIOUnmasked
+
     ) where
 
 import Prelude
@@ -99,8 +115,7 @@ import Control.Exception.Base as Exception
 
 #ifdef __GLASGOW_HASKELL__
 import GHC.Exception
-import GHC.Conc         ( ThreadId(..), myThreadId, killThread, yield,
-                          threadDelay, forkIO, forkIOUnmasked, childHandler )
+import GHC.Conc hiding (threadWaitRead, threadWaitWrite)
 import qualified GHC.Conc
 import GHC.IO           ( IO(..), unsafeInterleaveIO, unsafeUnmask )
 import GHC.IORef        ( newIORef, readIORef, writeIORef )
@@ -454,7 +469,9 @@ unsafeResult = either Exception.throwIO return
 -- given file descriptor (GHC only).
 --
 -- This will throw an 'IOError' if the file descriptor was closed
--- while this thread was blocked.
+-- while this thread was blocked.  To safely close a file descriptor
+-- that has been used with 'threadWaitRead', use
+-- 'GHC.Conc.closeFdWith'.
 threadWaitRead :: Fd -> IO ()
 threadWaitRead fd
 #ifdef mingw32_HOST_OS
@@ -477,7 +494,9 @@ threadWaitRead fd
 -- given file descriptor (GHC only).
 --
 -- This will throw an 'IOError' if the file descriptor was closed
--- while this thread was blocked.
+-- while this thread was blocked.  To safely close a file descriptor
+-- that has been used with 'threadWaitWrite', use
+-- 'GHC.Conc.closeFdWith'.
 threadWaitWrite :: Fd -> IO ()
 threadWaitWrite fd
 #ifdef mingw32_HOST_OS
@@ -487,24 +506,6 @@ threadWaitWrite fd
   = GHC.Conc.threadWaitWrite fd
 #endif
 
--- | Close a file descriptor in a concurrency-safe way (GHC only).  If
--- you are using 'threadWaitRead' or 'threadWaitWrite' to perform
--- blocking I\/O, you /must/ use this function to close file
--- descriptors, or blocked threads may not be woken.
---
--- Any threads that are blocked on the file descriptor via
--- 'threadWaitRead' or 'threadWaitWrite' will be unblocked by having
--- IO exceptions thrown.
-closeFd :: (Fd -> IO ())        -- ^ Low-level action that performs the real close.
-        -> Fd                   -- ^ File descriptor to close.
-        -> IO ()
-closeFd close fd
-#ifdef mingw32_HOST_OS
-  = close fd
-#else
-  = GHC.Conc.closeFd close fd
-#endif
-
 #ifdef mingw32_HOST_OS
 foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool