add threadCapability :: ThreadId -> IO (Int,Bool)
[ghc-base.git] / GHC / Conc.lhs
1 \begin{code}
2 {-# LANGUAGE CPP, NoImplicitPrelude #-}
3 {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
4 {-# OPTIONS_HADDOCK not-home #-}
5
6 -----------------------------------------------------------------------------
7 -- |
8 -- Module      :  GHC.Conc
9 -- Copyright   :  (c) The University of Glasgow, 1994-2002
10 -- License     :  see libraries/base/LICENSE
11 -- 
12 -- Maintainer  :  cvs-ghc@haskell.org
13 -- Stability   :  internal
14 -- Portability :  non-portable (GHC extensions)
15 --
16 -- Basic concurrency stuff.
17 -- 
18 -----------------------------------------------------------------------------
19
20 -- No: #hide, because bits of this module are exposed by the stm package.
21 -- However, we don't want this module to be the home location for the
22 -- bits it exports, we'd rather have Control.Concurrent and the other
23 -- higher level modules be the home.  Hence:
24
25 #include "Typeable.h"
26
27 -- #not-home
28 module GHC.Conc
29         ( ThreadId(..)
30
31         -- * Forking and suchlike
32         , forkIO        -- :: IO a -> IO ThreadId
33         , forkIOUnmasked
34         , forkOnIO      -- :: Int -> IO a -> IO ThreadId
35         , forkOnIOUnmasked
36         , numCapabilities -- :: Int
37         , getNumCapabilities -- :: IO Int
38         , numSparks       -- :: IO Int
39         , childHandler  -- :: Exception -> IO ()
40         , myThreadId    -- :: IO ThreadId
41         , killThread    -- :: ThreadId -> IO ()
42         , throwTo       -- :: ThreadId -> Exception -> IO ()
43         , par           -- :: a -> b -> b
44         , pseq          -- :: a -> b -> b
45         , runSparks
46         , yield         -- :: IO ()
47         , labelThread   -- :: ThreadId -> String -> IO ()
48
49         , ThreadStatus(..), BlockReason(..)
50         , threadStatus  -- :: ThreadId -> IO ThreadStatus
51         , threadCapability
52
53         -- * Waiting
54         , threadDelay           -- :: Int -> IO ()
55         , registerDelay         -- :: Int -> IO (TVar Bool)
56         , threadWaitRead        -- :: Int -> IO ()
57         , threadWaitWrite       -- :: Int -> IO ()
58         , closeFdWith           -- :: (Fd -> IO ()) -> Fd -> IO ()
59
60         -- * TVars
61         , STM(..)
62         , atomically    -- :: STM a -> IO a
63         , retry         -- :: STM a
64         , orElse        -- :: STM a -> STM a -> STM a
65         , throwSTM      -- :: Exception e => e -> STM a
66         , catchSTM      -- :: Exception e => STM a -> (e -> STM a) -> STM a
67         , alwaysSucceeds -- :: STM a -> STM ()
68         , always        -- :: STM Bool -> STM ()
69         , TVar(..)
70         , newTVar       -- :: a -> STM (TVar a)
71         , newTVarIO     -- :: a -> STM (TVar a)
72         , readTVar      -- :: TVar a -> STM a
73         , readTVarIO    -- :: TVar a -> IO a
74         , writeTVar     -- :: a -> TVar a -> STM ()
75         , unsafeIOToSTM -- :: IO a -> STM a
76
77         -- * Miscellaneous
78         , withMVar
79 #ifdef mingw32_HOST_OS
80         , asyncRead     -- :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
81         , asyncWrite    -- :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
82         , asyncDoProc   -- :: FunPtr (Ptr a -> IO Int) -> Ptr a -> IO Int
83
84         , asyncReadBA   -- :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int, Int)
85         , asyncWriteBA  -- :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int, Int)
86 #endif
87
88 #ifndef mingw32_HOST_OS
89         , Signal, HandlerFun, setHandler, runHandlers
90 #endif
91
92         , ensureIOManagerIsRunning
93
94 #ifdef mingw32_HOST_OS
95         , ConsoleEvent(..)
96         , win32ConsoleHandler
97         , toWin32ConsoleEvent
98 #endif
99         , setUncaughtExceptionHandler      -- :: (Exception -> IO ()) -> IO ()
100         , getUncaughtExceptionHandler      -- :: IO (Exception -> IO ())
101
102         , reportError, reportStackOverflow
103         ) where
104
105 import GHC.Conc.IO
106 import GHC.Conc.Sync
107
108 #ifndef mingw32_HOST_OS
109 import GHC.Conc.Signal
110 #endif
111
112 \end{code}