docs: describe the changes to forkIO, and document forkOnIO
[ghc-base.git] / GHC / Conc.lhs
index 7883cd6..498b928 100644 (file)
@@ -28,6 +28,7 @@ module GHC.Conc
        -- * Forking and suchlike
        , forkIO        -- :: IO a -> IO ThreadId
        , forkOnIO      -- :: Int -> IO a -> IO ThreadId
+        , numCapabilities -- :: Int
        , childHandler  -- :: Exception -> IO ()
        , myThreadId    -- :: IO ThreadId
        , killThread    -- :: ThreadId -> IO ()
@@ -79,7 +80,17 @@ module GHC.Conc
        , asyncWriteBA  -- :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int, Int)
 #endif
 
+#ifndef mingw32_HOST_OS
+        , signalHandlerLock
+#endif
+
        , ensureIOManagerIsRunning
+
+#ifdef mingw32_HOST_OS
+        , ConsoleEvent(..)
+        , win32ConsoleHandler
+        , toWin32ConsoleEvent
+#endif
         ) where
 
 import System.Posix.Types
@@ -102,7 +113,11 @@ import GHC.Real            ( fromIntegral, div )
 #ifndef mingw32_HOST_OS
 import GHC.Base                ( Int(..) )
 #endif
-import GHC.Exception    ( catchException, Exception(..), AsyncException(..) )
+#ifdef mingw32_HOST_OS
+import GHC.Read         ( Read )
+import GHC.Enum         ( Enum )
+#endif
+import GHC.Exception
 import GHC.Pack                ( packCString# )
 import GHC.Ptr          ( Ptr(..), plusPtr, FunPtr(..) )
 import GHC.STRef
@@ -171,12 +186,15 @@ instance Ord ThreadId where
    compare = cmpThread
 
 {- |
-This sparks off a new thread to run the 'IO' computation passed as the
+Sparks off a new thread to run the 'IO' computation passed as the
 first argument, and returns the 'ThreadId' of the newly created
 thread.
 
 The new thread will be a lightweight thread; if you want to use a foreign
-library that uses thread-local storage, use 'forkOS' instead.
+library that uses thread-local storage, use 'Control.Concurrent.forkOS' instead.
+
+GHC note: the new thread inherits the /blocked/ state of the parent 
+(see 'Control.Exception.block').
 -}
 forkIO :: IO () -> IO ThreadId
 forkIO action = IO $ \ s -> 
@@ -184,12 +202,36 @@ forkIO action = IO $ \ s ->
  where
   action_plus = catchException action childHandler
 
+{- |
+Like 'forkIO', but lets you specify on which CPU the thread is
+created.  Unlike a `forkIO` thread, a thread created by `forkOnIO`
+will stay on the same CPU for its entire lifetime (`forkIO` threads
+can migrate between CPUs according to the scheduling policy).
+`forkOnIO` is useful for overriding the scheduling policy when you
+know in advance how best to distribute the threads.
+
+The `Int` argument specifies the CPU number; it is interpreted modulo
+'numCapabilities' (note that it actually specifies a capability number
+rather than a CPU number, but to a first approximation the two are
+equivalent).
+-}
 forkOnIO :: Int -> IO () -> IO ThreadId
 forkOnIO (I# cpu) action = IO $ \ s -> 
    case (forkOn# cpu action_plus s) of (# s1, id #) -> (# s1, ThreadId id #)
  where
   action_plus = catchException action childHandler
 
+-- | the value passed to the @+RTS -N@ flag.  This is the number of
+-- Haskell threads that can run truly simultaneously at any given
+-- time, and is typically set to the number of physical CPU cores on
+-- the machine.
+numCapabilities :: Int
+numCapabilities = unsafePerformIO $  do 
+                    n <- peek n_capabilities
+                    return (fromIntegral n)
+
+foreign import ccall "&n_capabilities" n_capabilities :: Ptr CInt
+
 childHandler :: Exception -> IO ()
 childHandler err = catchException (real_handler err) childHandler
 
@@ -234,7 +276,7 @@ until the call has completed.  This is the case regardless of whether
 the call is inside a 'block' or not.
 
 Important note: the behaviour of 'throwTo' differs from that described in
-the paper "Asynchronous exceptions in Haskell" 
+the paper \"Asynchronous exceptions in Haskell\"
 (<http://research.microsoft.com/~simonpj/Papers/asynch-exns.htm>).
 In the paper, 'throwTo' is non-blocking; but the library implementation adopts
 a more synchronous design in which 'throwTo' does not return until the exception
@@ -545,6 +587,15 @@ isEmptyMVar (MVar mv#) = IO $ \ s# ->
 addMVarFinalizer :: MVar a -> IO () -> IO ()
 addMVarFinalizer (MVar m) finalizer = 
   IO $ \s -> case mkWeak# m () finalizer s of { (# s1, w #) -> (# s1, () #) }
+
+withMVar :: MVar a -> (a -> IO b) -> IO b
+withMVar m io = 
+  block $ do
+    a <- takeMVar m
+    b <- catchException (unblock (io a))
+           (\e -> do putMVar m a; throw e)
+    putMVar m a
+    return b
 \end{code}
 
 
@@ -557,7 +608,7 @@ addMVarFinalizer (MVar m) finalizer =
 \begin{code}
 #ifdef mingw32_HOST_OS
 
--- Note: threadDelay, threadWaitRead and threadWaitWrite aren't really functional
+-- Note: threadWaitRead and threadWaitWrite aren't really functional
 -- on Win32, but left in there because lib code (still) uses them (the manner
 -- in which they're used doesn't cause problems on a Win32 platform though.)
 
@@ -805,14 +856,34 @@ service_cont wakeup delays = do
 io_MANAGER_WAKEUP = 0xffffffff :: Word32
 io_MANAGER_DIE    = 0xfffffffe :: Word32
 
-start_console_handler :: Word32 -> IO ()
-start_console_handler r = do                   
-  stableptr <- peek console_handler
-  forkIO $ do io <- deRefStablePtr stableptr; io (fromIntegral r)
-  return ()
+data ConsoleEvent
+ = ControlC
+ | Break
+ | Close
+    -- these are sent to Services only.
+ | Logoff
+ | Shutdown
+ deriving (Eq, Ord, Enum, Show, Read, Typeable)
 
-foreign import ccall "&console_handler" 
-   console_handler :: Ptr (StablePtr (CInt -> IO ()))
+start_console_handler :: Word32 -> IO ()
+start_console_handler r =
+  case toWin32ConsoleEvent r of
+     Just x  -> withMVar win32ConsoleHandler $ \handler -> do
+                    forkIO (handler x)
+                    return ()
+     Nothing -> return ()
+
+toWin32ConsoleEvent ev = 
+   case ev of
+       0 {- CTRL_C_EVENT-}        -> Just ControlC
+       1 {- CTRL_BREAK_EVENT-}    -> Just Break
+       2 {- CTRL_CLOSE_EVENT-}    -> Just Close
+       5 {- CTRL_LOGOFF_EVENT-}   -> Just Logoff
+       6 {- CTRL_SHUTDOWN_EVENT-} -> Just Shutdown
+       _ -> Nothing
+
+win32ConsoleHandler :: MVar (ConsoleEvent -> IO ())
+win32ConsoleHandler = unsafePerformIO (newMVar (error "win32ConsoleHandler"))
 
 stick :: IORef HANDLE
 {-# NOINLINE stick #-}
@@ -858,7 +929,7 @@ foreign import ccall unsafe "readIOManagerEvent" -- in the RTS (ThrIOManager.c)
 foreign import ccall unsafe "sendIOManagerEvent" -- in the RTS (ThrIOManager.c)
   c_sendIOManagerEvent :: Word32 -> IO ()
 
-foreign import ccall unsafe "maperrno"             -- in runProcess.c
+foreign import ccall unsafe "maperrno"             -- in Win32Utils.c
    c_maperrno :: IO ()
 
 foreign import stdcall "WaitForSingleObject"
@@ -946,9 +1017,11 @@ service_loop wakeup readfds writefds ptimeval old_reqs old_delays = do
                 case s of
                  _ | s == io_MANAGER_WAKEUP -> return False
                  _ | s == io_MANAGER_DIE    -> return True
-                 _ -> do handler_tbl <- peek handlers
+                 _ -> withMVar signalHandlerLock $ \_ -> do
+                          handler_tbl <- peek handlers
                          sp <- peekElemOff handler_tbl (fromIntegral s)
-                         forkIO (do io <- deRefStablePtr sp; io)
+                          io <- deRefStablePtr sp
+                         forkIO io
                          return False
 
   if exit then return () else do
@@ -973,6 +1046,12 @@ wakeupIOManager = do
   with io_MANAGER_WAKEUP $ \pbuf -> do 
     c_write (fromIntegral fd) pbuf 1; return ()
 
+-- Lock used to protect concurrent access to signal_handlers.  Symptom of
+-- this race condition is #1922, although that bug was on Windows a similar
+-- bug also exists on Unix.
+signalHandlerLock :: MVar ()
+signalHandlerLock = unsafePerformIO (newMVar ())
+
 foreign import ccall "&signal_handlers" handlers :: Ptr (Ptr (StablePtr (IO ())))
 
 foreign import ccall "setIOManagerPipe"
@@ -1069,16 +1148,28 @@ foreign import ccall safe "select"
            -> IO CInt
 
 foreign import ccall unsafe "hsFD_SETSIZE"
-  fD_SETSIZE :: Fd
+  c_fD_SETSIZE :: CInt
+
+fD_SETSIZE :: Fd
+fD_SETSIZE = fromIntegral c_fD_SETSIZE
 
 foreign import ccall unsafe "hsFD_CLR"
-  fdClr :: Fd -> Ptr CFdSet -> IO ()
+  c_fdClr :: CInt -> Ptr CFdSet -> IO ()
+
+fdClr :: Fd -> Ptr CFdSet -> IO ()
+fdClr (Fd fd) fdset = c_fdClr fd fdset
 
 foreign import ccall unsafe "hsFD_ISSET"
-  fdIsSet :: Fd -> Ptr CFdSet -> IO CInt
+  c_fdIsSet :: CInt -> Ptr CFdSet -> IO CInt
+
+fdIsSet :: Fd -> Ptr CFdSet -> IO CInt
+fdIsSet (Fd fd) fdset = c_fdIsSet fd fdset
 
 foreign import ccall unsafe "hsFD_SET"
-  fdSet :: Fd -> Ptr CFdSet -> IO ()
+  c_fdSet :: CInt -> Ptr CFdSet -> IO ()
+
+fdSet :: Fd -> Ptr CFdSet -> IO ()
+fdSet (Fd fd) fdset = c_fdSet fd fdset
 
 foreign import ccall unsafe "hsFD_ZERO"
   fdZero :: Ptr CFdSet -> IO ()