[project @ 2003-02-21 05:34:12 by sof]
[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         , forkProcess   -- :: IO (Maybe Int)
31
32         -- Waiting
33         , threadDelay           -- :: Int -> IO ()
34         , threadWaitRead        -- :: Int -> IO ()
35         , threadWaitWrite       -- :: Int -> IO ()
36
37         -- MVars
38         , MVar          -- abstract
39         , newMVar       -- :: a -> IO (MVar a)
40         , newEmptyMVar  -- :: IO (MVar a)
41         , takeMVar      -- :: MVar a -> IO a
42         , putMVar       -- :: MVar a -> a -> IO ()
43         , tryTakeMVar   -- :: MVar a -> IO (Maybe a)
44         , tryPutMVar    -- :: MVar a -> a -> IO Bool
45         , isEmptyMVar   -- :: MVar a -> IO Bool
46         , addMVarFinalizer -- :: MVar a -> IO () -> IO ()
47
48 #ifdef mingw32_TARGET_OS
49         , asyncRead     -- :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
50         , asyncWrite    -- :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
51
52         , asyncReadBA   -- :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int, Int)
53         , asyncWriteBA  -- :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int, Int)
54 #endif
55         ) where
56
57 import Data.Maybe
58
59 import GHC.Base
60 import GHC.IOBase       ( IO(..), MVar(..), ioException, IOException(..), IOErrorType(..) )
61 import GHC.Num          ( fromInteger, negate )
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 "Posix.forkProcess": This implementation
154 /will stop all other Concurrent Haskell threads/ in the (heavyweight) forked copy.
155 'forkProcessPrim' returns the pid of the child process to the parent, 0 to the child,
156 and a value less than 0 in case of errors. See also: 'forkProcess'.
157
158 Without this function, you need excessive and often impractical
159 explicit synchronization using the regular Concurrent Haskell constructs to assure
160 that only the desired thread is running after the fork().
161
162 The stopped threads are /not/ garbage collected! This behaviour may change in
163 future releases.
164 -}
165
166 forkProcessPrim :: IO Int
167 forkProcessPrim = IO $ \s -> case (forkProcess# s) of (# s1, id #) -> (# s1, (I# id) #)
168
169 {- | 'forkProcess' is a wrapper around 'forkProcessPrim' similar to the one found in
170 "Posix.forkProcess" which returns a Maybe-type. The child receives @Nothing@, the
171 parent @Just (pid::Int)@. In case of an error, an exception is thrown.
172 -}
173
174 forkProcess :: IO (Maybe Int)
175 forkProcess = do
176   pid <- forkProcessPrim
177   case pid of
178     -1 -> ioException (IOError Nothing      -- stolen from hslibs/posix/PosixUtil
179                               SystemError
180                               "forkProcess"
181                               ""
182                               Nothing)
183     0  -> return Nothing
184     _  -> return (Just pid)
185
186 --      Nota Bene: 'pseq' used to be 'seq'
187 --                 but 'seq' is now defined in PrelGHC
188 --
189 -- "pseq" is defined a bit weirdly (see below)
190 --
191 -- The reason for the strange "lazy" call is that
192 -- it fools the compiler into thinking that pseq  and par are non-strict in
193 -- their second argument (even if it inlines pseq at the call site).
194 -- If it thinks pseq is strict in "y", then it often evaluates
195 -- "y" before "x", which is totally wrong.  
196
197 {-# INLINE pseq  #-}
198 pseq :: a -> b -> b
199 pseq  x y = x `seq` lazy y
200
201 {-# INLINE par  #-}
202 par :: a -> b -> b
203 par  x y = case (par# x) of { _ -> lazy y }
204 \end{code}
205
206 %************************************************************************
207 %*                                                                      *
208 \subsection[mvars]{M-Structures}
209 %*                                                                      *
210 %************************************************************************
211
212 M-Vars are rendezvous points for concurrent threads.  They begin
213 empty, and any attempt to read an empty M-Var blocks.  When an M-Var
214 is written, a single blocked thread may be freed.  Reading an M-Var
215 toggles its state from full back to empty.  Therefore, any value
216 written to an M-Var may only be read once.  Multiple reads and writes
217 are allowed, but there must be at least one read between any two
218 writes.
219
220 \begin{code}
221 --Defined in IOBase to avoid cycle: data MVar a = MVar (SynchVar# RealWorld a)
222
223 -- |Create an 'MVar' which is initially empty.
224 newEmptyMVar  :: IO (MVar a)
225 newEmptyMVar = IO $ \ s# ->
226     case newMVar# s# of
227          (# s2#, svar# #) -> (# s2#, MVar svar# #)
228
229 -- |Create an 'MVar' which contains the supplied value.
230 newMVar :: a -> IO (MVar a)
231 newMVar value =
232     newEmptyMVar        >>= \ mvar ->
233     putMVar mvar value  >>
234     return mvar
235
236 -- |Return the contents of the 'MVar'.  If the 'MVar' is currently
237 -- empty, 'takeMVar' will wait until it is full.  After a 'takeMVar', 
238 -- the 'MVar' is left empty.
239 -- 
240 -- If several threads are competing to take the same 'MVar', one is chosen
241 -- to continue at random when the 'MVar' becomes full.
242 takeMVar :: MVar a -> IO a
243 takeMVar (MVar mvar#) = IO $ \ s# -> takeMVar# mvar# s#
244
245 -- |Put a value into an 'MVar'.  If the 'MVar' is currently full,
246 -- 'putMVar' will wait until it becomes empty.
247 --
248 -- If several threads are competing to fill the same 'MVar', one is
249 -- chosen to continue at random with the 'MVar' becomes empty.
250 putMVar  :: MVar a -> a -> IO ()
251 putMVar (MVar mvar#) x = IO $ \ s# ->
252     case putMVar# mvar# x s# of
253         s2# -> (# s2#, () #)
254
255 -- |A non-blocking version of 'takeMVar'.  The 'tryTakeMVar' function
256 -- returns immediately, with 'Nothing' if the 'MVar' was empty, or
257 -- @'Just' a@ if the 'MVar' was full with contents @a@.  After 'tryTakeMVar',
258 -- the 'MVar' is left empty.
259 tryTakeMVar :: MVar a -> IO (Maybe a)
260 tryTakeMVar (MVar m) = IO $ \ s ->
261     case tryTakeMVar# m s of
262         (# s, 0#, _ #) -> (# s, Nothing #)      -- MVar is empty
263         (# s, _,  a #) -> (# s, Just a  #)      -- MVar is full
264
265 -- |A non-blocking version of 'putMVar'.  The 'tryPutMVar' function
266 -- attempts to put the value @a@ into the 'MVar', returning 'True' if
267 -- it was successful, or 'False' otherwise.
268 tryPutMVar  :: MVar a -> a -> IO Bool
269 tryPutMVar (MVar mvar#) x = IO $ \ s# ->
270     case tryPutMVar# mvar# x s# of
271         (# s, 0# #) -> (# s, False #)
272         (# s, _  #) -> (# s, True #)
273
274 -- |Check whether a given 'MVar' is empty.
275 --
276 -- Notice that the boolean value returned  is just a snapshot of
277 -- the state of the MVar. By the time you get to react on its result,
278 -- the MVar may have been filled (or emptied) - so be extremely
279 -- careful when using this operation.   Use 'tryTakeMVar' instead if possible.
280 isEmptyMVar :: MVar a -> IO Bool
281 isEmptyMVar (MVar mv#) = IO $ \ s# -> 
282     case isEmptyMVar# mv# s# of
283         (# s2#, flg #) -> (# s2#, not (flg ==# 0#) #)
284
285 -- |Add a finalizer to an 'MVar'.  See "Foreign.ForeignPtr" and
286 -- "System.Mem.Weak" for more about finalizers.
287 addMVarFinalizer :: MVar a -> IO () -> IO ()
288 addMVarFinalizer (MVar m) finalizer = 
289   IO $ \s -> case mkWeak# m () finalizer s of { (# s1, w #) -> (# s1, () #) }
290 \end{code}
291
292
293 %************************************************************************
294 %*                                                                      *
295 \subsection{Thread waiting}
296 %*                                                                      *
297 %************************************************************************
298
299 @threadWaitRead@ delays rescheduling of a thread until input on the
300 specified file descriptor is available for reading (just like select).
301 @threadWaitWrite@ is similar, but for writing on a file descriptor.
302
303 \begin{code}
304 -- |The 'threadDelay' operation will cause the current thread to
305 -- suspend for a given number of microseconds.  Note that the resolution
306 -- used by the Haskell runtime system\'s internal timer together with the
307 -- fact that the thread may take some time to be rescheduled after the
308 -- time has expired, means that the accuracy is more like 1\/50 second.
309 threadDelay :: Int -> IO ()
310
311 -- | Block the current thread until data is available to read on the
312 -- given file descriptor.
313 threadWaitRead :: Int -> IO ()
314
315 -- | Block the current thread until data can be written to the
316 -- given file descriptor.
317 threadWaitWrite :: Int -> IO ()
318
319 threadDelay     (I# ms) = IO $ \s -> case delay# ms s     of s -> (# s, () #)
320 threadWaitRead  (I# fd) = IO $ \s -> case waitRead# fd s  of s -> (# s, () #)
321 threadWaitWrite (I# fd) = IO $ \s -> case waitWrite# fd s of s -> (# s, () #)
322
323 #ifdef mingw32_TARGET_OS
324
325 -- Note: threadDelay, threadWaitRead and threadWaitWrite aren't really functional
326 -- on Win32, but left in there because lib code (still) uses them (the manner
327 -- in which they're used doesn't cause problems on a Win32 platform though.)
328
329 asyncRead :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
330 asyncRead  (I# fd) (I# isSock) (I# len) (Ptr buf) = 
331   IO $ \s -> case asyncRead# fd isSock len buf s  of 
332                (# s, len#, err# #) -> (# s, (I# len#, I# err#) #)
333
334 asyncWrite :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
335 asyncWrite  (I# fd) (I# isSock) (I# len) (Ptr buf) = 
336   IO $ \s -> case asyncWrite# fd isSock len buf s  of 
337                (# s, len#, err# #) -> (# s, (I# len#, I# err#) #)
338
339 -- to aid the use of these primops by the IO Handle implementation,
340 -- provide the following convenience funs:
341
342 -- this better be a pinned byte array!
343 asyncReadBA :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int,Int)
344 asyncReadBA fd isSock len off bufB = 
345   asyncRead fd isSock len ((Ptr (byteArrayContents# (unsafeCoerce# bufB))) `plusPtr` off)
346   
347 asyncWriteBA :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int,Int)
348 asyncWriteBA fd isSock len off bufB = 
349   asyncWrite fd isSock len ((Ptr (byteArrayContents# (unsafeCoerce# bufB))) `plusPtr` off)
350
351 #endif
352 \end{code}