9707ad049916b2f007067880061176bf72caa176
[ghc-base.git] / GHC / Conc.lhs
1 \begin{code}
2 {-# OPTIONS -fno-implicit-prelude #-}
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.Conc
6 -- Copyright   :  (c) The University of Glasgow, 1994-2002
7 -- License     :  see libraries/base/LICENSE
8 -- 
9 -- Maintainer  :  cvs-ghc@haskell.org
10 -- Stability   :  internal
11 -- Portability :  non-portable (GHC extensions)
12 --
13 -- Basic concurrency stuff.
14 -- 
15 -----------------------------------------------------------------------------
16
17 #include "config.h"
18 module GHC.Conc
19         ( ThreadId(..)
20
21         -- Forking and suchlike
22         , myThreadId    -- :: IO ThreadId
23         , killThread    -- :: ThreadId -> IO ()
24         , throwTo       -- :: ThreadId -> Exception -> IO ()
25         , par           -- :: a -> b -> b
26         , pseq          -- :: a -> b -> b
27         , yield         -- :: IO ()
28         , labelThread   -- :: ThreadId -> String -> IO ()
29         , forkProcessPrim -- :: IO Int
30
31         -- Waiting
32         , threadDelay           -- :: Int -> IO ()
33         , threadWaitRead        -- :: Int -> IO ()
34         , threadWaitWrite       -- :: Int -> IO ()
35
36         -- MVars
37         , MVar          -- abstract
38         , newMVar       -- :: a -> IO (MVar a)
39         , newEmptyMVar  -- :: IO (MVar a)
40         , takeMVar      -- :: MVar a -> IO a
41         , putMVar       -- :: MVar a -> a -> IO ()
42         , tryTakeMVar   -- :: MVar a -> IO (Maybe a)
43         , tryPutMVar    -- :: MVar a -> a -> IO Bool
44         , isEmptyMVar   -- :: MVar a -> IO Bool
45         , addMVarFinalizer -- :: MVar a -> IO () -> IO ()
46
47 #ifdef mingw32_TARGET_OS
48         , asyncRead     -- :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
49         , asyncWrite    -- :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
50
51         , asyncReadBA   -- :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int, Int)
52         , asyncWriteBA  -- :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int, Int)
53 #endif
54         ) where
55
56 import Data.Maybe
57
58 import GHC.Base
59 import GHC.IOBase       ( IO(..), MVar(..), ioException, IOException(..), IOErrorType(..) )
60 import GHC.Num          ( fromInteger, negate )
61 import GHC.Real         ( fromIntegral )
62 import GHC.Base         ( Int(..) )
63 import GHC.Exception    ( Exception(..), AsyncException(..) )
64 import GHC.Pack         ( packCString# )
65 import GHC.Ptr          ( Ptr(..), plusPtr )
66
67 infixr 0 `par`, `pseq`
68 \end{code}
69
70 %************************************************************************
71 %*                                                                      *
72 \subsection{@ThreadId@, @par@, and @fork@}
73 %*                                                                      *
74 %************************************************************************
75
76 \begin{code}
77 data ThreadId = ThreadId ThreadId#
78 -- ToDo: data ThreadId = ThreadId (Weak ThreadId#)
79 -- But since ThreadId# is unlifted, the Weak type must use open
80 -- type variables.
81 {- ^
82 A 'ThreadId' is an abstract type representing a handle to a thread.
83 'ThreadId' is an instance of 'Eq', 'Ord' and 'Show', where
84 the 'Ord' instance implements an arbitrary total ordering over
85 'ThreadId's. The 'Show' instance lets you convert an arbitrary-valued
86 'ThreadId' to string form; showing a 'ThreadId' value is occasionally
87 useful when debugging or diagnosing the behaviour of a concurrent
88 program.
89
90 NOTE: in GHC, if you have a 'ThreadId', you essentially have
91 a pointer to the thread itself.  This means the thread itself can\'t be
92 garbage collected until you drop the 'ThreadId'.
93 This misfeature will hopefully be corrected at a later date.
94 -}
95
96 --forkIO has now been hoisted out into the Concurrent library.
97
98 {- | 'killThread' terminates the given thread (Note: 'killThread' is
99 not implemented in Hugs).  Any work already done by the thread isn\'t
100 lost: the computation is suspended until required by another thread.
101 The memory used by the thread will be garbage collected if it isn\'t
102 referenced from anywhere.  The 'killThread' function is defined in
103 terms of 'throwTo':
104
105 > killThread tid = throwTo tid (AsyncException ThreadKilled)
106
107 -}
108 killThread :: ThreadId -> IO ()
109 killThread tid = throwTo tid (AsyncException ThreadKilled)
110
111 {- | 'throwTo' raises an arbitrary exception in the target thread.
112
113 'throwTo' does not return until the exception has been raised in the
114 target thread.  The calling thread can thus be certain that the target
115 thread has received the exception.  This is a useful property to know
116 when dealing with race conditions: eg. if there are two threads that
117 can kill each other, it is guaranteed that only one of the threads
118 will get to kill the other. -}
119 throwTo :: ThreadId -> Exception -> IO ()
120 throwTo (ThreadId id) ex = IO $ \ s ->
121    case (killThread# id ex s) of s1 -> (# s1, () #)
122
123 -- | Returns the 'ThreadId' of the calling thread.
124 myThreadId :: IO ThreadId
125 myThreadId = IO $ \s ->
126    case (myThreadId# s) of (# s1, id #) -> (# s1, ThreadId id #)
127
128
129 -- |The 'yield' action allows (forces, in a co-operative multitasking
130 -- implementation) a context-switch to any other currently runnable
131 -- threads (if any), and is occasionally useful when implementing
132 -- concurrency abstractions.
133 yield :: IO ()
134 yield = IO $ \s -> 
135    case (yield# s) of s1 -> (# s1, () #)
136
137 {- | 'labelThread' stores a string as identifier for this thread if
138 you built a RTS with debugging support. This identifier will be used in
139 the debugging output to make distinction of different threads easier
140 (otherwise you only have the thread state object\'s address in the heap).
141
142 Other applications like the graphical Concurrent Haskell Debugger
143 (<http://www.informatik.uni-kiel.de/~fhu/chd/>) may choose to overload
144 'labelThread' for their purposes as well.
145 -}
146
147 labelThread :: ThreadId -> String -> IO ()
148 labelThread (ThreadId t) str = IO $ \ s ->
149    let ps  = packCString# str
150        adr = byteArrayContents# ps in
151      case (labelThread# t adr s) of s1 -> (# s1, () #)
152
153 {- | This function is a replacement for "System.Posix.Process.forkProcessAll":
154 This implementation /will stop all other Concurrent Haskell threads/ in the
155 (heavyweight) forked copy.
156 'forkProcessPrim' returns the pid of the child process to the parent, 0 to the
157 child, and a value less than 0 in case of errors. See also:
158 'System.Posix.Process.forkProcess' in package @unix@.
159
160 Without this function, you need excessive and often impractical
161 explicit synchronization using the regular Concurrent Haskell constructs to assure
162 that only the desired thread is running after the fork().
163
164 The stopped threads are /not/ garbage collected! This behaviour may change in
165 future releases.
166
167 NOTE: currently, main threads are not stopped in the child process.
168 To work around this problem, call 'forkProcessPrim' from the main thread. 
169 -}
170
171 -- XXX RTS should know about 'pid_t'.
172
173 forkProcessPrim :: IO Int
174 forkProcessPrim = IO $ \s -> case (forkProcess# s) of (# s1, id #) -> (# s1, (I# id) #)
175
176 --      Nota Bene: 'pseq' used to be 'seq'
177 --                 but 'seq' is now defined in PrelGHC
178 --
179 -- "pseq" is defined a bit weirdly (see below)
180 --
181 -- The reason for the strange "lazy" call is that
182 -- it fools the compiler into thinking that pseq  and par are non-strict in
183 -- their second argument (even if it inlines pseq at the call site).
184 -- If it thinks pseq is strict in "y", then it often evaluates
185 -- "y" before "x", which is totally wrong.  
186
187 {-# INLINE pseq  #-}
188 pseq :: a -> b -> b
189 pseq  x y = x `seq` lazy y
190
191 {-# INLINE par  #-}
192 par :: a -> b -> b
193 par  x y = case (par# x) of { _ -> lazy y }
194 \end{code}
195
196 %************************************************************************
197 %*                                                                      *
198 \subsection[mvars]{M-Structures}
199 %*                                                                      *
200 %************************************************************************
201
202 M-Vars are rendezvous points for concurrent threads.  They begin
203 empty, and any attempt to read an empty M-Var blocks.  When an M-Var
204 is written, a single blocked thread may be freed.  Reading an M-Var
205 toggles its state from full back to empty.  Therefore, any value
206 written to an M-Var may only be read once.  Multiple reads and writes
207 are allowed, but there must be at least one read between any two
208 writes.
209
210 \begin{code}
211 --Defined in IOBase to avoid cycle: data MVar a = MVar (SynchVar# RealWorld a)
212
213 -- |Create an 'MVar' which is initially empty.
214 newEmptyMVar  :: IO (MVar a)
215 newEmptyMVar = IO $ \ s# ->
216     case newMVar# s# of
217          (# s2#, svar# #) -> (# s2#, MVar svar# #)
218
219 -- |Create an 'MVar' which contains the supplied value.
220 newMVar :: a -> IO (MVar a)
221 newMVar value =
222     newEmptyMVar        >>= \ mvar ->
223     putMVar mvar value  >>
224     return mvar
225
226 -- |Return the contents of the 'MVar'.  If the 'MVar' is currently
227 -- empty, 'takeMVar' will wait until it is full.  After a 'takeMVar', 
228 -- the 'MVar' is left empty.
229 -- 
230 -- If several threads are competing to take the same 'MVar', one is chosen
231 -- to continue at random when the 'MVar' becomes full.
232 takeMVar :: MVar a -> IO a
233 takeMVar (MVar mvar#) = IO $ \ s# -> takeMVar# mvar# s#
234
235 -- |Put a value into an 'MVar'.  If the 'MVar' is currently full,
236 -- 'putMVar' will wait until it becomes empty.
237 --
238 -- If several threads are competing to fill the same 'MVar', one is
239 -- chosen to continue at random with the 'MVar' becomes empty.
240 putMVar  :: MVar a -> a -> IO ()
241 putMVar (MVar mvar#) x = IO $ \ s# ->
242     case putMVar# mvar# x s# of
243         s2# -> (# s2#, () #)
244
245 -- |A non-blocking version of 'takeMVar'.  The 'tryTakeMVar' function
246 -- returns immediately, with 'Nothing' if the 'MVar' was empty, or
247 -- @'Just' a@ if the 'MVar' was full with contents @a@.  After 'tryTakeMVar',
248 -- the 'MVar' is left empty.
249 tryTakeMVar :: MVar a -> IO (Maybe a)
250 tryTakeMVar (MVar m) = IO $ \ s ->
251     case tryTakeMVar# m s of
252         (# s, 0#, _ #) -> (# s, Nothing #)      -- MVar is empty
253         (# s, _,  a #) -> (# s, Just a  #)      -- MVar is full
254
255 -- |A non-blocking version of 'putMVar'.  The 'tryPutMVar' function
256 -- attempts to put the value @a@ into the 'MVar', returning 'True' if
257 -- it was successful, or 'False' otherwise.
258 tryPutMVar  :: MVar a -> a -> IO Bool
259 tryPutMVar (MVar mvar#) x = IO $ \ s# ->
260     case tryPutMVar# mvar# x s# of
261         (# s, 0# #) -> (# s, False #)
262         (# s, _  #) -> (# s, True #)
263
264 -- |Check whether a given 'MVar' is empty.
265 --
266 -- Notice that the boolean value returned  is just a snapshot of
267 -- the state of the MVar. By the time you get to react on its result,
268 -- the MVar may have been filled (or emptied) - so be extremely
269 -- careful when using this operation.   Use 'tryTakeMVar' instead if possible.
270 isEmptyMVar :: MVar a -> IO Bool
271 isEmptyMVar (MVar mv#) = IO $ \ s# -> 
272     case isEmptyMVar# mv# s# of
273         (# s2#, flg #) -> (# s2#, not (flg ==# 0#) #)
274
275 -- |Add a finalizer to an 'MVar'.  See "Foreign.ForeignPtr" and
276 -- "System.Mem.Weak" for more about finalizers.
277 addMVarFinalizer :: MVar a -> IO () -> IO ()
278 addMVarFinalizer (MVar m) finalizer = 
279   IO $ \s -> case mkWeak# m () finalizer s of { (# s1, w #) -> (# s1, () #) }
280 \end{code}
281
282
283 %************************************************************************
284 %*                                                                      *
285 \subsection{Thread waiting}
286 %*                                                                      *
287 %************************************************************************
288
289 @threadWaitRead@ delays rescheduling of a thread until input on the
290 specified file descriptor is available for reading (just like select).
291 @threadWaitWrite@ is similar, but for writing on a file descriptor.
292
293 \begin{code}
294 -- |The 'threadDelay' operation will cause the current thread to
295 -- suspend for a given number of microseconds.  Note that the resolution
296 -- used by the Haskell runtime system\'s internal timer together with the
297 -- fact that the thread may take some time to be rescheduled after the
298 -- time has expired, means that the accuracy is more like 1\/50 second.
299 threadDelay :: Int -> IO ()
300
301 -- | Block the current thread until data is available to read on the
302 -- given file descriptor.
303 threadWaitRead :: Int -> IO ()
304
305 -- | Block the current thread until data can be written to the
306 -- given file descriptor.
307 threadWaitWrite :: Int -> IO ()
308
309 threadDelay     (I# ms) = IO $ \s -> case delay# ms s     of s -> (# s, () #)
310 threadWaitRead  (I# fd) = IO $ \s -> case waitRead# fd s  of s -> (# s, () #)
311 threadWaitWrite (I# fd) = IO $ \s -> case waitWrite# fd s of s -> (# s, () #)
312
313 #ifdef mingw32_TARGET_OS
314
315 -- Note: threadDelay, threadWaitRead and threadWaitWrite aren't really functional
316 -- on Win32, but left in there because lib code (still) uses them (the manner
317 -- in which they're used doesn't cause problems on a Win32 platform though.)
318
319 asyncRead :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
320 asyncRead  (I# fd) (I# isSock) (I# len) (Ptr buf) = 
321   IO $ \s -> case asyncRead# fd isSock len buf s  of 
322                (# s, len#, err# #) -> (# s, (I# len#, I# err#) #)
323
324 asyncWrite :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
325 asyncWrite  (I# fd) (I# isSock) (I# len) (Ptr buf) = 
326   IO $ \s -> case asyncWrite# fd isSock len buf s  of 
327                (# s, len#, err# #) -> (# s, (I# len#, I# err#) #)
328
329 -- to aid the use of these primops by the IO Handle implementation,
330 -- provide the following convenience funs:
331
332 -- this better be a pinned byte array!
333 asyncReadBA :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int,Int)
334 asyncReadBA fd isSock len off bufB = 
335   asyncRead fd isSock len ((Ptr (byteArrayContents# (unsafeCoerce# bufB))) `plusPtr` off)
336   
337 asyncWriteBA :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int,Int)
338 asyncWriteBA fd isSock len off bufB = 
339   asyncWrite fd isSock len ((Ptr (byteArrayContents# (unsafeCoerce# bufB))) `plusPtr` off)
340
341 #endif
342 \end{code}