8df665e37cae5166202a7cd46ebac4a89ef1d8c8
[ghc-base.git] / Control / Concurrent.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Control.Concurrent
4 -- Copyright   :  (c) The University of Glasgow 2001
5 -- License     :  BSD-style (see the file libraries/base/LICENSE)
6 -- 
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  experimental
9 -- Portability :  non-portable (concurrency)
10 --
11 -- A common interface to a collection of useful concurrency
12 -- abstractions.
13 --
14 -----------------------------------------------------------------------------
15
16 module Control.Concurrent (
17         -- * Concurrent Haskell
18
19         -- $conc_intro
20
21         -- * Basic concurrency operations
22
23         ThreadId,
24 #ifdef __GLASGOW_HASKELL__
25         myThreadId,
26 #endif
27
28         forkIO,
29 #ifdef __GLASGOW_HASKELL__
30         killThread,
31         throwTo,
32 #endif
33
34         -- * Scheduling
35
36         -- $conc_scheduling     
37         yield,                  -- :: IO ()
38
39         -- ** Blocking
40         
41         -- $blocking
42
43 #ifdef __GLASGOW_HASKELL__
44         -- ** Waiting
45         threadDelay,            -- :: Int -> IO ()
46         threadWaitRead,         -- :: Int -> IO ()
47         threadWaitWrite,        -- :: Int -> IO ()
48 #endif
49
50         -- * Communication abstractions
51
52         module Control.Concurrent.MVar,
53         module Control.Concurrent.Chan,
54         module Control.Concurrent.QSem,
55         module Control.Concurrent.QSemN,
56         module Control.Concurrent.SampleVar,
57
58         -- * Merging of streams
59 #ifndef __HUGS__
60         mergeIO,                -- :: [a]   -> [a] -> IO [a]
61         nmergeIO,               -- :: [[a]] -> IO [a]
62 #endif
63         -- $merge
64
65 #ifdef __GLASGOW_HASKELL__
66         -- * Bound Threads
67         -- $boundthreads
68         rtsSupportsBoundThreads,
69         forkOS,
70         isCurrentThreadBound,
71         runInBoundThread,
72         runInUnboundThread
73 #endif
74
75         -- * GHC's implementation of concurrency
76
77         -- |This section describes features specific to GHC's
78         -- implementation of Concurrent Haskell.
79         
80         -- ** Terminating the program
81
82         -- $termination
83
84         -- ** Pre-emption
85
86         -- $preemption
87     ) where
88
89 import Prelude
90
91 import Control.Exception as Exception
92
93 #ifdef __GLASGOW_HASKELL__
94 import GHC.Conc         ( ThreadId(..), myThreadId, killThread, yield,
95                           threadDelay, threadWaitRead, threadWaitWrite )
96 import GHC.TopHandler   ( reportStackOverflow, reportError )
97 import GHC.IOBase       ( IO(..) )
98 import GHC.IOBase       ( unsafeInterleaveIO )
99 import GHC.IOBase   ( newIORef, readIORef, writeIORef )
100 import GHC.Base
101
102 import Foreign.StablePtr
103 import Foreign.C.Types  ( CInt )
104 import Control.Monad    ( when )
105 #endif
106
107 #ifdef __HUGS__
108 import Hugs.ConcBase
109 #endif
110
111 import Control.Concurrent.MVar
112 import Control.Concurrent.Chan
113 import Control.Concurrent.QSem
114 import Control.Concurrent.QSemN
115 import Control.Concurrent.SampleVar
116
117 #ifdef __HUGS__
118 type ThreadId = ()
119 #endif
120
121 {- $conc_intro
122
123 The concurrency extension for Haskell is described in the paper
124 /Concurrent Haskell/
125 <http://www.haskell.org/ghc/docs/papers/concurrent-haskell.ps.gz>.
126
127 Concurrency is \"lightweight\", which means that both thread creation
128 and context switching overheads are extremely low.  Scheduling of
129 Haskell threads is done internally in the Haskell runtime system, and
130 doesn't make use of any operating system-supplied thread packages.
131
132 However, if you want to interact with a foreign library that expects your
133 program to use the operating system-supplied thread package, you can do so
134 by using 'forkOS' instead of 'forkIO'.
135
136 Haskell threads can communicate via 'MVar's, a kind of synchronised
137 mutable variable (see "Control.Concurrent.MVar").  Several common
138 concurrency abstractions can be built from 'MVar's, and these are
139 provided by the "Control.Concurrent" library.
140 In GHC, threads may also communicate via exceptions.
141 -}
142
143 {- $conc_scheduling
144
145     Scheduling may be either pre-emptive or co-operative,
146     depending on the implementation of Concurrent Haskell (see below
147     for information related to specific compilers).  In a co-operative
148     system, context switches only occur when you use one of the
149     primitives defined in this module.  This means that programs such
150     as:
151
152
153 >   main = forkIO (write 'a') >> write 'b'
154 >     where write c = putChar c >> write c
155
156     will print either @aaaaaaaaaaaaaa...@ or @bbbbbbbbbbbb...@,
157     instead of some random interleaving of @a@s and @b@s.  In
158     practice, cooperative multitasking is sufficient for writing
159     simple graphical user interfaces.  
160 -}
161
162 {- $blocking
163 Calling a foreign C procedure (such as @getchar@) that blocks waiting
164 for input will block /all/ threads, unless the @threadsafe@ attribute
165 is used on the foreign call (and your compiler \/ operating system
166 supports it).  GHC's I\/O system uses non-blocking I\/O internally to
167 implement thread-friendly I\/O, so calling standard Haskell I\/O
168 functions blocks only the thread making the call.
169 -}
170
171 -- Thread Ids, specifically the instances of Eq and Ord for these things.
172 -- The ThreadId type itself is defined in std/PrelConc.lhs.
173
174 -- Rather than define a new primitve, we use a little helper function
175 -- cmp_thread in the RTS.
176
177 #ifdef __GLASGOW_HASKELL__
178 id2TSO :: ThreadId -> ThreadId#
179 id2TSO (ThreadId t) = t
180
181 foreign import ccall unsafe "cmp_thread" cmp_thread :: ThreadId# -> ThreadId# -> Int
182 -- Returns -1, 0, 1
183
184 cmpThread :: ThreadId -> ThreadId -> Ordering
185 cmpThread t1 t2 = 
186    case cmp_thread (id2TSO t1) (id2TSO t2) of
187       -1 -> LT
188       0  -> EQ
189       _  -> GT -- must be 1
190
191 instance Eq ThreadId where
192    t1 == t2 = 
193       case t1 `cmpThread` t2 of
194          EQ -> True
195          _  -> False
196
197 instance Ord ThreadId where
198    compare = cmpThread
199
200 foreign import ccall unsafe "rts_getThreadId" getThreadId :: ThreadId# -> Int
201
202 instance Show ThreadId where
203    showsPrec d t = 
204         showString "ThreadId " . 
205         showsPrec d (getThreadId (id2TSO t))
206
207 {- |
208 This sparks off a new thread to run the 'IO' computation passed as the
209 first argument, and returns the 'ThreadId' of the newly created
210 thread.
211
212 The new thread will be a lightweight thread; if you want to use a foreign
213 library that uses thread-local storage, use 'forkOS' instead.
214 -}
215 forkIO :: IO () -> IO ThreadId
216 forkIO action = IO $ \ s -> 
217    case (fork# action_plus s) of (# s1, id #) -> (# s1, ThreadId id #)
218  where
219   action_plus = Exception.catch action childHandler
220
221 childHandler :: Exception -> IO ()
222 childHandler err = Exception.catch (real_handler err) childHandler
223
224 real_handler :: Exception -> IO ()
225 real_handler ex =
226   case ex of
227         -- ignore thread GC and killThread exceptions:
228         BlockedOnDeadMVar            -> return ()
229         BlockedIndefinitely          -> return ()
230         AsyncException ThreadKilled  -> return ()
231
232         -- report all others:
233         AsyncException StackOverflow -> reportStackOverflow
234         other       -> reportError other
235
236 #endif /* __GLASGOW_HASKELL__ */
237
238 #ifndef __HUGS__
239 max_buff_size :: Int
240 max_buff_size = 1
241
242 mergeIO :: [a] -> [a] -> IO [a]
243 nmergeIO :: [[a]] -> IO [a]
244
245 -- $merge
246 -- The 'mergeIO' and 'nmergeIO' functions fork one thread for each
247 -- input list that concurrently evaluates that list; the results are
248 -- merged into a single output list.  
249 --
250 -- Note: Hugs does not provide these functions, since they require
251 -- preemptive multitasking.
252
253 mergeIO ls rs
254  = newEmptyMVar                >>= \ tail_node ->
255    newMVar tail_node           >>= \ tail_list ->
256    newQSem max_buff_size       >>= \ e ->
257    newMVar 2                   >>= \ branches_running ->
258    let
259     buff = (tail_list,e)
260    in
261     forkIO (suckIO branches_running buff ls) >>
262     forkIO (suckIO branches_running buff rs) >>
263     takeMVar tail_node  >>= \ val ->
264     signalQSem e        >>
265     return val
266
267 type Buffer a 
268  = (MVar (MVar [a]), QSem)
269
270 suckIO :: MVar Int -> Buffer a -> [a] -> IO ()
271
272 suckIO branches_running buff@(tail_list,e) vs
273  = case vs of
274         [] -> takeMVar branches_running >>= \ val ->
275               if val == 1 then
276                  takeMVar tail_list     >>= \ node ->
277                  putMVar node []        >>
278                  putMVar tail_list node
279               else      
280                  putMVar branches_running (val-1)
281         (x:xs) ->
282                 waitQSem e                       >>
283                 takeMVar tail_list               >>= \ node ->
284                 newEmptyMVar                     >>= \ next_node ->
285                 unsafeInterleaveIO (
286                         takeMVar next_node  >>= \ y ->
287                         signalQSem e        >>
288                         return y)                >>= \ next_node_val ->
289                 putMVar node (x:next_node_val)   >>
290                 putMVar tail_list next_node      >>
291                 suckIO branches_running buff xs
292
293 nmergeIO lss
294  = let
295     len = length lss
296    in
297     newEmptyMVar          >>= \ tail_node ->
298     newMVar tail_node     >>= \ tail_list ->
299     newQSem max_buff_size >>= \ e ->
300     newMVar len           >>= \ branches_running ->
301     let
302      buff = (tail_list,e)
303     in
304     mapIO (\ x -> forkIO (suckIO branches_running buff x)) lss >>
305     takeMVar tail_node  >>= \ val ->
306     signalQSem e        >>
307     return val
308   where
309     mapIO f xs = sequence (map f xs)
310 #endif /* __HUGS__ */
311
312 #ifdef __GLASGOW_HASKELL__
313 -- ---------------------------------------------------------------------------
314 -- Bound Threads
315
316 {- $boundthreads
317
318 Support for multiple operating system threads and bound threads as described
319 below is currently only available in the GHC runtime system if you use the
320 /-threaded/ option when linking.
321
322 Other Haskell systems do not currently support multiple operating system threads.
323
324 A bound thread is a haskell thread that is /bound/ to an operating system
325 thread. While the bound thread is still scheduled by the Haskell run-time
326 system, the operating system thread takes care of all the foreign calls made
327 by the bound thread.
328
329 To a foreign library, the bound thread will look exactly like an ordinary
330 operating system thread created using OS functions like @pthread_create@
331 or @CreateThread@.
332
333 Bound threads can be created using the 'forkOS' function below. All foreign
334 exported functions are run in a bound thread (bound to the OS thread that
335 called the function). Also, the @main@ action of every Haskell program is
336 run in a bound thread.
337
338 Why do we need this? Because if a foreign library is called from a thread
339 created using 'forkIO', it won't have access to any /thread-local state/ - 
340 state variables that have specific values for each OS thread
341 (see POSIX's @pthread_key_create@ or Win32's @TlsAlloc@). Therefore, some
342 libraries (OpenGL, for example) will not work from a thread created using
343 'forkIO'. They work fine in threads created using 'forkOS' or when called
344 from @main@ or from a @foreign export@.
345 -}
346
347 -- | 'True' if bound threads are supported.
348 -- If @rtsSupportsBoundThreads@ is 'False', 'isCurrentThreadBound'
349 -- will always return 'False' and both 'forkOS' and 'runInBoundThread' will
350 -- fail.
351 foreign import ccall rtsSupportsBoundThreads :: Bool
352
353
354 {- |
355 Like 'forkIO', this sparks off a new thread to run the 'IO' computation passed as the
356 first argument, and returns the 'ThreadId' of the newly created
357 thread.
358
359 However, @forkOS@ uses operating system-supplied multithreading support to create
360 a new operating system thread. The new thread is /bound/, which means that
361 all foreign calls made by the 'IO' computation are guaranteed to be executed
362 in this new operating system thread; also, the operating system thread is not
363 used for any other foreign calls.
364
365 This means that you can use all kinds of foreign libraries from this thread 
366 (even those that rely on thread-local state), without the limitations of 'forkIO'.
367 -}
368 forkOS :: IO () -> IO ThreadId
369
370 foreign export ccall forkOS_entry
371     :: StablePtr (IO ()) -> IO ()
372
373 foreign import ccall "forkOS_entry" forkOS_entry_reimported
374     :: StablePtr (IO ()) -> IO ()
375
376 forkOS_entry stableAction = do
377         action <- deRefStablePtr stableAction
378         action
379
380 foreign import ccall forkOS_createThread
381     :: StablePtr (IO ()) -> IO CInt
382
383 failNonThreaded = fail $ "RTS doesn't support multiple OS threads "
384                        ++"(use ghc -threaded when linking)"
385     
386 forkOS action 
387     | rtsSupportsBoundThreads = do
388         mv <- newEmptyMVar
389         let action_plus = Exception.catch action childHandler
390         entry <- newStablePtr (myThreadId >>= putMVar mv >> action_plus)
391         err <- forkOS_createThread entry
392         when (err /= 0) $ fail "Cannot create OS thread."
393         tid <- takeMVar mv
394         freeStablePtr entry
395         return tid
396     | otherwise = failNonThreaded
397
398 -- | Returns 'True' if the calling thread is /bound/, that is, if it is
399 -- safe to use foreign libraries that rely on thread-local state from the
400 -- calling thread.
401 isCurrentThreadBound :: IO Bool
402 isCurrentThreadBound = IO $ \ s# -> 
403     case isCurrentThreadBound# s# of
404         (# s2#, flg #) -> (# s2#, not (flg ==# 0#) #)
405
406
407 {- | 
408 Run the 'IO' computation passed as the first argument. If the calling thread
409 is not /bound/, a bound thread is created temporarily. @runInBoundThread@
410 doesn't finish until the 'IO' computation finishes.
411
412 You can wrap a series of foreign function calls that rely on thread-local state
413 with @runInBoundThread@ so that you can use them without knowing whether the
414 current thread is /bound/.
415 -}
416 runInBoundThread :: IO a -> IO a
417
418 runInBoundThread action
419     | rtsSupportsBoundThreads = do
420         bound <- isCurrentThreadBound
421         if bound
422             then action
423             else do
424                 ref <- newIORef undefined
425                 let action_plus = Exception.try action >>= writeIORef ref
426                 resultOrException <- 
427                     bracket (newStablePtr action_plus)
428                             freeStablePtr
429                             (\cEntry -> forkOS_entry_reimported cEntry >> readIORef ref)
430                 case resultOrException of
431                     Left exception -> Exception.throw exception
432                     Right result -> return result
433     | otherwise = failNonThreaded
434
435 {- | 
436 Run the 'IO' computation passed as the first argument. If the calling thread
437 is /bound/, an unbound thread is created temporarily using 'forkIO'.
438 @runInBoundThread@ doesn't finish until the 'IO' computation finishes.
439
440 Use this function /only/ in the rare case that you have actually observed a
441 performance loss due to the use of bound threads. A program that
442 doesn't need it's main thread to be bound and makes /heavy/ use of concurrency
443 (e.g. a web server), might want to wrap it's @main@ action in
444 @runInUnboundThread@.
445 -}
446 runInUnboundThread :: IO a -> IO a
447
448 runInUnboundThread action = do
449     bound <- isCurrentThreadBound
450     if bound
451         then do
452             mv <- newEmptyMVar
453             forkIO (Exception.try action >>= putMVar mv)
454             takeMVar mv >>= \either -> case either of
455                 Left exception -> Exception.throw exception
456                 Right result -> return result
457         else action
458         
459 #endif /* __GLASGOW_HASKELL__ */
460
461 -- ---------------------------------------------------------------------------
462 -- More docs
463
464 {- $termination
465
466       In a standalone GHC program, only the main thread is
467       required to terminate in order for the process to terminate.
468       Thus all other forked threads will simply terminate at the same
469       time as the main thread (the terminology for this kind of
470       behaviour is \"daemonic threads\").
471
472       If you want the program to wait for child threads to
473       finish before exiting, you need to program this yourself.  A
474       simple mechanism is to have each child thread write to an
475       'MVar' when it completes, and have the main
476       thread wait on all the 'MVar's before
477       exiting:
478
479 >   myForkIO :: IO () -> IO (MVar ())
480 >   myForkIO io = do
481 >     mvar <- newEmptyMVar
482 >     forkIO (io `finally` putMVar mvar ())
483 >     return mvar
484
485       Note that we use 'finally' from the
486       "Control.Exception" module to make sure that the
487       'MVar' is written to even if the thread dies or
488       is killed for some reason.
489
490       A better method is to keep a global list of all child
491       threads which we should wait for at the end of the program:
492
493 >    children :: MVar [MVar ()]
494 >    children = unsafePerformIO (newMVar [])
495 >    
496 >    waitForChildren :: IO ()
497 >    waitForChildren = do
498 >      cs <- takeMVar children
499 >      case cs of
500 >        []   -> return ()
501 >        m:ms -> do
502 >           putMVar children ms
503 >           takeMVar m
504 >           waitForChildren
505 >    
506 >    forkChild :: IO () -> IO ()
507 >    forkChild io = do
508 >        mvar <- newEmptyMVar
509 >        childs <- takeMVar children
510 >        putMVar children (mvar:childs)
511 >        forkIO (io `finally` putMVar mvar ())
512 >
513 >     main =
514 >       later waitForChildren $
515 >       ...
516
517       The main thread principle also applies to calls to Haskell from
518       outside, using @foreign export@.  When the @foreign export@ed
519       function is invoked, it starts a new main thread, and it returns
520       when this main thread terminates.  If the call causes new
521       threads to be forked, they may remain in the system after the
522       @foreign export@ed function has returned.
523 -}
524
525 {- $preemption
526
527       GHC implements pre-emptive multitasking: the execution of
528       threads are interleaved in a random fashion.  More specifically,
529       a thread may be pre-empted whenever it allocates some memory,
530       which unfortunately means that tight loops which do no
531       allocation tend to lock out other threads (this only seems to
532       happen with pathological benchmark-style code, however).
533
534       The rescheduling timer runs on a 20ms granularity by
535       default, but this may be altered using the
536       @-i\<n\>@ RTS option.  After a rescheduling
537       \"tick\" the running thread is pre-empted as soon as
538       possible.
539
540       One final note: the
541       @aaaa@ @bbbb@ example may not
542       work too well on GHC (see Scheduling, above), due
543       to the locking on a 'System.IO.Handle'.  Only one thread
544       may hold the lock on a 'System.IO.Handle' at any one
545       time, so if a reschedule happens while a thread is holding the
546       lock, the other thread won't be able to run.  The upshot is that
547       the switch from @aaaa@ to
548       @bbbbb@ happens infrequently.  It can be
549       improved by lowering the reschedule tick period.  We also have a
550       patch that causes a reschedule whenever a thread waiting on a
551       lock is woken up, but haven't found it to be useful for anything
552       other than this example :-)
553 -}