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