~ubuntu-branches/ubuntu/precise/ghc/precise

« back to all changes in this revision

Viewing changes to libraries/base/Control/Concurrent.hs

  • Committer: Bazaar Package Importer
  • Author(s): Joachim Breitner
  • Date: 2011-01-17 12:49:24 UTC
  • Revision ID: james.westby@ubuntu.com-20110117124924-do1pym1jlf5o636m
Tags: upstream-7.0.1
ImportĀ upstreamĀ versionĀ 7.0.1

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
 
2
-----------------------------------------------------------------------------
 
3
-- |
 
4
-- Module      :  Control.Concurrent
 
5
-- Copyright   :  (c) The University of Glasgow 2001
 
6
-- License     :  BSD-style (see the file libraries/base/LICENSE)
 
7
-- 
 
8
-- Maintainer  :  libraries@haskell.org
 
9
-- Stability   :  experimental
 
10
-- Portability :  non-portable (concurrency)
 
11
--
 
12
-- A common interface to a collection of useful concurrency
 
13
-- abstractions.
 
14
--
 
15
-----------------------------------------------------------------------------
 
16
 
 
17
module Control.Concurrent (
 
18
        -- * Concurrent Haskell
 
19
 
 
20
        -- $conc_intro
 
21
 
 
22
        -- * Basic concurrency operations
 
23
 
 
24
        ThreadId,
 
25
#ifdef __GLASGOW_HASKELL__
 
26
        myThreadId,
 
27
#endif
 
28
 
 
29
        forkIO,
 
30
#ifdef __GLASGOW_HASKELL__
 
31
        forkIOUnmasked,
 
32
        killThread,
 
33
        throwTo,
 
34
#endif
 
35
 
 
36
        -- * Scheduling
 
37
 
 
38
        -- $conc_scheduling     
 
39
        yield,                  -- :: IO ()
 
40
 
 
41
        -- ** Blocking
 
42
 
 
43
        -- $blocking
 
44
 
 
45
#ifdef __GLASGOW_HASKELL__
 
46
        -- ** Waiting
 
47
        threadDelay,            -- :: Int -> IO ()
 
48
        threadWaitRead,         -- :: Int -> IO ()
 
49
        threadWaitWrite,        -- :: Int -> IO ()
 
50
#endif
 
51
 
 
52
        -- * Communication abstractions
 
53
 
 
54
        module Control.Concurrent.MVar,
 
55
        module Control.Concurrent.Chan,
 
56
        module Control.Concurrent.QSem,
 
57
        module Control.Concurrent.QSemN,
 
58
        module Control.Concurrent.SampleVar,
 
59
 
 
60
        -- * Merging of streams
 
61
#ifndef __HUGS__
 
62
        mergeIO,                -- :: [a]   -> [a] -> IO [a]
 
63
        nmergeIO,               -- :: [[a]] -> IO [a]
 
64
#endif
 
65
        -- $merge
 
66
 
 
67
#ifdef __GLASGOW_HASKELL__
 
68
        -- * Bound Threads
 
69
        -- $boundthreads
 
70
        rtsSupportsBoundThreads,
 
71
        forkOS,
 
72
        isCurrentThreadBound,
 
73
        runInBoundThread,
 
74
        runInUnboundThread
 
75
#endif
 
76
 
 
77
        -- * GHC's implementation of concurrency
 
78
 
 
79
        -- |This section describes features specific to GHC's
 
80
        -- implementation of Concurrent Haskell.
 
81
 
 
82
        -- ** Haskell threads and Operating System threads
 
83
 
 
84
        -- $osthreads
 
85
 
 
86
        -- ** Terminating the program
 
87
 
 
88
        -- $termination
 
89
 
 
90
        -- ** Pre-emption
 
91
 
 
92
        -- $preemption
 
93
    ) where
 
94
 
 
95
import Prelude
 
96
 
 
97
import Control.Exception.Base as Exception
 
98
 
 
99
#ifdef __GLASGOW_HASKELL__
 
100
import GHC.Exception
 
101
import GHC.Conc         ( ThreadId(..), myThreadId, killThread, yield,
 
102
                          threadDelay, forkIO, forkIOUnmasked, childHandler )
 
103
import qualified GHC.Conc
 
104
import GHC.IO           ( IO(..), unsafeInterleaveIO, unsafeUnmask )
 
105
import GHC.IORef        ( newIORef, readIORef, writeIORef )
 
106
import GHC.Base
 
107
 
 
108
import System.Posix.Types ( Fd )
 
109
import Foreign.StablePtr
 
110
import Foreign.C.Types  ( CInt )
 
111
import Control.Monad    ( when )
 
112
 
 
113
#ifdef mingw32_HOST_OS
 
114
import Foreign.C
 
115
import System.IO
 
116
#endif
 
117
#endif
 
118
 
 
119
#ifdef __HUGS__
 
120
import Hugs.ConcBase
 
121
#endif
 
122
 
 
123
import Control.Concurrent.MVar
 
124
import Control.Concurrent.Chan
 
125
import Control.Concurrent.QSem
 
126
import Control.Concurrent.QSemN
 
127
import Control.Concurrent.SampleVar
 
128
 
 
129
#ifdef __HUGS__
 
130
type ThreadId = ()
 
131
#endif
 
132
 
 
133
{- $conc_intro
 
134
 
 
135
The concurrency extension for Haskell is described in the paper
 
136
/Concurrent Haskell/
 
137
<http://www.haskell.org/ghc/docs/papers/concurrent-haskell.ps.gz>.
 
138
 
 
139
Concurrency is \"lightweight\", which means that both thread creation
 
140
and context switching overheads are extremely low.  Scheduling of
 
141
Haskell threads is done internally in the Haskell runtime system, and
 
142
doesn't make use of any operating system-supplied thread packages.
 
143
 
 
144
However, if you want to interact with a foreign library that expects your
 
145
program to use the operating system-supplied thread package, you can do so
 
146
by using 'forkOS' instead of 'forkIO'.
 
147
 
 
148
Haskell threads can communicate via 'MVar's, a kind of synchronised
 
149
mutable variable (see "Control.Concurrent.MVar").  Several common
 
150
concurrency abstractions can be built from 'MVar's, and these are
 
151
provided by the "Control.Concurrent" library.
 
152
In GHC, threads may also communicate via exceptions.
 
153
-}
 
154
 
 
155
{- $conc_scheduling
 
156
 
 
157
    Scheduling may be either pre-emptive or co-operative,
 
158
    depending on the implementation of Concurrent Haskell (see below
 
159
    for information related to specific compilers).  In a co-operative
 
160
    system, context switches only occur when you use one of the
 
161
    primitives defined in this module.  This means that programs such
 
162
    as:
 
163
 
 
164
 
 
165
>   main = forkIO (write 'a') >> write 'b'
 
166
>     where write c = putChar c >> write c
 
167
 
 
168
    will print either @aaaaaaaaaaaaaa...@ or @bbbbbbbbbbbb...@,
 
169
    instead of some random interleaving of @a@s and @b@s.  In
 
170
    practice, cooperative multitasking is sufficient for writing
 
171
    simple graphical user interfaces.  
 
172
-}
 
173
 
 
174
{- $blocking
 
175
Different Haskell implementations have different characteristics with
 
176
regard to which operations block /all/ threads.
 
177
 
 
178
Using GHC without the @-threaded@ option, all foreign calls will block
 
179
all other Haskell threads in the system, although I\/O operations will
 
180
not.  With the @-threaded@ option, only foreign calls with the @unsafe@
 
181
attribute will block all other threads.
 
182
 
 
183
Using Hugs, all I\/O operations and foreign calls will block all other
 
184
Haskell threads.
 
185
-}
 
186
 
 
187
#ifndef __HUGS__
 
188
max_buff_size :: Int
 
189
max_buff_size = 1
 
190
 
 
191
mergeIO :: [a] -> [a] -> IO [a]
 
192
nmergeIO :: [[a]] -> IO [a]
 
193
 
 
194
-- $merge
 
195
-- The 'mergeIO' and 'nmergeIO' functions fork one thread for each
 
196
-- input list that concurrently evaluates that list; the results are
 
197
-- merged into a single output list.  
 
198
--
 
199
-- Note: Hugs does not provide these functions, since they require
 
200
-- preemptive multitasking.
 
201
 
 
202
mergeIO ls rs
 
203
 = newEmptyMVar                >>= \ tail_node ->
 
204
   newMVar tail_node           >>= \ tail_list ->
 
205
   newQSem max_buff_size       >>= \ e ->
 
206
   newMVar 2                   >>= \ branches_running ->
 
207
   let
 
208
    buff = (tail_list,e)
 
209
   in
 
210
    forkIO (suckIO branches_running buff ls) >>
 
211
    forkIO (suckIO branches_running buff rs) >>
 
212
    takeMVar tail_node  >>= \ val ->
 
213
    signalQSem e        >>
 
214
    return val
 
215
 
 
216
type Buffer a
 
217
 = (MVar (MVar [a]), QSem)
 
218
 
 
219
suckIO :: MVar Int -> Buffer a -> [a] -> IO ()
 
220
 
 
221
suckIO branches_running buff@(tail_list,e) vs
 
222
 = case vs of
 
223
        [] -> takeMVar branches_running >>= \ val ->
 
224
              if val == 1 then
 
225
                 takeMVar tail_list     >>= \ node ->
 
226
                 putMVar node []        >>
 
227
                 putMVar tail_list node
 
228
              else
 
229
                 putMVar branches_running (val-1)
 
230
        (x:xs) ->
 
231
                waitQSem e                       >>
 
232
                takeMVar tail_list               >>= \ node ->
 
233
                newEmptyMVar                     >>= \ next_node ->
 
234
                unsafeInterleaveIO (
 
235
                        takeMVar next_node  >>= \ y ->
 
236
                        signalQSem e        >>
 
237
                        return y)                >>= \ next_node_val ->
 
238
                putMVar node (x:next_node_val)   >>
 
239
                putMVar tail_list next_node      >>
 
240
                suckIO branches_running buff xs
 
241
 
 
242
nmergeIO lss
 
243
 = let
 
244
    len = length lss
 
245
   in
 
246
    newEmptyMVar          >>= \ tail_node ->
 
247
    newMVar tail_node     >>= \ tail_list ->
 
248
    newQSem max_buff_size >>= \ e ->
 
249
    newMVar len           >>= \ branches_running ->
 
250
    let
 
251
     buff = (tail_list,e)
 
252
    in
 
253
    mapIO (\ x -> forkIO (suckIO branches_running buff x)) lss >>
 
254
    takeMVar tail_node  >>= \ val ->
 
255
    signalQSem e        >>
 
256
    return val
 
257
  where
 
258
    mapIO f xs = sequence (map f xs)
 
259
#endif /* __HUGS__ */
 
260
 
 
261
#ifdef __GLASGOW_HASKELL__
 
262
-- ---------------------------------------------------------------------------
 
263
-- Bound Threads
 
264
 
 
265
{- $boundthreads
 
266
   #boundthreads#
 
267
 
 
268
Support for multiple operating system threads and bound threads as described
 
269
below is currently only available in the GHC runtime system if you use the
 
270
/-threaded/ option when linking.
 
271
 
 
272
Other Haskell systems do not currently support multiple operating system threads.
 
273
 
 
274
A bound thread is a haskell thread that is /bound/ to an operating system
 
275
thread. While the bound thread is still scheduled by the Haskell run-time
 
276
system, the operating system thread takes care of all the foreign calls made
 
277
by the bound thread.
 
278
 
 
279
To a foreign library, the bound thread will look exactly like an ordinary
 
280
operating system thread created using OS functions like @pthread_create@
 
281
or @CreateThread@.
 
282
 
 
283
Bound threads can be created using the 'forkOS' function below. All foreign
 
284
exported functions are run in a bound thread (bound to the OS thread that
 
285
called the function). Also, the @main@ action of every Haskell program is
 
286
run in a bound thread.
 
287
 
 
288
Why do we need this? Because if a foreign library is called from a thread
 
289
created using 'forkIO', it won't have access to any /thread-local state/ - 
 
290
state variables that have specific values for each OS thread
 
291
(see POSIX's @pthread_key_create@ or Win32's @TlsAlloc@). Therefore, some
 
292
libraries (OpenGL, for example) will not work from a thread created using
 
293
'forkIO'. They work fine in threads created using 'forkOS' or when called
 
294
from @main@ or from a @foreign export@.
 
295
 
 
296
In terms of performance, 'forkOS' (aka bound) threads are much more
 
297
expensive than 'forkIO' (aka unbound) threads, because a 'forkOS'
 
298
thread is tied to a particular OS thread, whereas a 'forkIO' thread
 
299
can be run by any OS thread.  Context-switching between a 'forkOS'
 
300
thread and a 'forkIO' thread is many times more expensive than between
 
301
two 'forkIO' threads.
 
302
 
 
303
Note in particular that the main program thread (the thread running
 
304
@Main.main@) is always a bound thread, so for good concurrency
 
305
performance you should ensure that the main thread is not doing
 
306
repeated communication with other threads in the system.  Typically
 
307
this means forking subthreads to do the work using 'forkIO', and
 
308
waiting for the results in the main thread.
 
309
 
 
310
-}
 
311
 
 
312
-- | 'True' if bound threads are supported.
 
313
-- If @rtsSupportsBoundThreads@ is 'False', 'isCurrentThreadBound'
 
314
-- will always return 'False' and both 'forkOS' and 'runInBoundThread' will
 
315
-- fail.
 
316
foreign import ccall rtsSupportsBoundThreads :: Bool
 
317
 
 
318
 
 
319
{- | 
 
320
Like 'forkIO', this sparks off a new thread to run the 'IO'
 
321
computation passed as the first argument, and returns the 'ThreadId'
 
322
of the newly created thread.
 
323
 
 
324
However, 'forkOS' creates a /bound/ thread, which is necessary if you
 
325
need to call foreign (non-Haskell) libraries that make use of
 
326
thread-local state, such as OpenGL (see "Control.Concurrent#boundthreads").
 
327
 
 
328
Using 'forkOS' instead of 'forkIO' makes no difference at all to the
 
329
scheduling behaviour of the Haskell runtime system.  It is a common
 
330
misconception that you need to use 'forkOS' instead of 'forkIO' to
 
331
avoid blocking all the Haskell threads when making a foreign call;
 
332
this isn't the case.  To allow foreign calls to be made without
 
333
blocking all the Haskell threads (with GHC), it is only necessary to
 
334
use the @-threaded@ option when linking your program, and to make sure
 
335
the foreign import is not marked @unsafe@.
 
336
-}
 
337
 
 
338
forkOS :: IO () -> IO ThreadId
 
339
 
 
340
foreign export ccall forkOS_entry
 
341
    :: StablePtr (IO ()) -> IO ()
 
342
 
 
343
foreign import ccall "forkOS_entry" forkOS_entry_reimported
 
344
    :: StablePtr (IO ()) -> IO ()
 
345
 
 
346
forkOS_entry :: StablePtr (IO ()) -> IO ()
 
347
forkOS_entry stableAction = do
 
348
        action <- deRefStablePtr stableAction
 
349
        action
 
350
 
 
351
foreign import ccall forkOS_createThread
 
352
    :: StablePtr (IO ()) -> IO CInt
 
353
 
 
354
failNonThreaded :: IO a
 
355
failNonThreaded = fail $ "RTS doesn't support multiple OS threads "
 
356
                       ++"(use ghc -threaded when linking)"
 
357
 
 
358
forkOS action0
 
359
    | rtsSupportsBoundThreads = do
 
360
        mv <- newEmptyMVar
 
361
        b <- Exception.getMaskingState
 
362
        let
 
363
            -- async exceptions are masked in the child if they are masked
 
364
            -- in the parent, as for forkIO (see #1048). forkOS_createThread
 
365
            -- creates a thread with exceptions masked by default.
 
366
            action1 = case b of
 
367
                        Unmasked -> unsafeUnmask action0
 
368
                        MaskedInterruptible -> action0
 
369
                        MaskedUninterruptible -> uninterruptibleMask_ action0
 
370
 
 
371
            action_plus = Exception.catch action1 childHandler
 
372
 
 
373
        entry <- newStablePtr (myThreadId >>= putMVar mv >> action_plus)
 
374
        err <- forkOS_createThread entry
 
375
        when (err /= 0) $ fail "Cannot create OS thread."
 
376
        tid <- takeMVar mv
 
377
        freeStablePtr entry
 
378
        return tid
 
379
    | otherwise = failNonThreaded
 
380
 
 
381
-- | Returns 'True' if the calling thread is /bound/, that is, if it is
 
382
-- safe to use foreign libraries that rely on thread-local state from the
 
383
-- calling thread.
 
384
isCurrentThreadBound :: IO Bool
 
385
isCurrentThreadBound = IO $ \ s# ->
 
386
    case isCurrentThreadBound# s# of
 
387
        (# s2#, flg #) -> (# s2#, not (flg ==# 0#) #)
 
388
 
 
389
 
 
390
{- | 
 
391
Run the 'IO' computation passed as the first argument. If the calling thread
 
392
is not /bound/, a bound thread is created temporarily. @runInBoundThread@
 
393
doesn't finish until the 'IO' computation finishes.
 
394
 
 
395
You can wrap a series of foreign function calls that rely on thread-local state
 
396
with @runInBoundThread@ so that you can use them without knowing whether the
 
397
current thread is /bound/.
 
398
-}
 
399
runInBoundThread :: IO a -> IO a
 
400
 
 
401
runInBoundThread action
 
402
    | rtsSupportsBoundThreads = do
 
403
        bound <- isCurrentThreadBound
 
404
        if bound
 
405
            then action
 
406
            else do
 
407
                ref <- newIORef undefined
 
408
                let action_plus = Exception.try action >>= writeIORef ref
 
409
                resultOrException <-
 
410
                    bracket (newStablePtr action_plus)
 
411
                            freeStablePtr
 
412
                            (\cEntry -> forkOS_entry_reimported cEntry >> readIORef ref)
 
413
                case resultOrException of
 
414
                    Left exception -> Exception.throw (exception :: SomeException)
 
415
                    Right result -> return result
 
416
    | otherwise = failNonThreaded
 
417
 
 
418
{- | 
 
419
Run the 'IO' computation passed as the first argument. If the calling thread
 
420
is /bound/, an unbound thread is created temporarily using 'forkIO'.
 
421
@runInBoundThread@ doesn't finish until the 'IO' computation finishes.
 
422
 
 
423
Use this function /only/ in the rare case that you have actually observed a
 
424
performance loss due to the use of bound threads. A program that
 
425
doesn't need it's main thread to be bound and makes /heavy/ use of concurrency
 
426
(e.g. a web server), might want to wrap it's @main@ action in
 
427
@runInUnboundThread@.
 
428
-}
 
429
runInUnboundThread :: IO a -> IO a
 
430
 
 
431
runInUnboundThread action = do
 
432
    bound <- isCurrentThreadBound
 
433
    if bound
 
434
        then do
 
435
            mv <- newEmptyMVar
 
436
            b <- blocked
 
437
            _ <- mask $ \restore -> forkIO $
 
438
              Exception.try (if b then action else restore action) >>=
 
439
              putMVar mv
 
440
            takeMVar mv >>= \ei -> case ei of
 
441
                Left exception -> Exception.throw (exception :: SomeException)
 
442
                Right result -> return result
 
443
        else action
 
444
 
 
445
#endif /* __GLASGOW_HASKELL__ */
 
446
 
 
447
#ifdef __GLASGOW_HASKELL__
 
448
-- ---------------------------------------------------------------------------
 
449
-- threadWaitRead/threadWaitWrite
 
450
 
 
451
-- | Block the current thread until data is available to read on the
 
452
-- given file descriptor (GHC only).
 
453
threadWaitRead :: Fd -> IO ()
 
454
threadWaitRead fd
 
455
#ifdef mingw32_HOST_OS
 
456
  -- we have no IO manager implementing threadWaitRead on Windows.
 
457
  -- fdReady does the right thing, but we have to call it in a
 
458
  -- separate thread, otherwise threadWaitRead won't be interruptible,
 
459
  -- and this only works with -threaded.
 
460
  | threaded  = withThread (waitFd fd 0)
 
461
  | otherwise = case fd of
 
462
                  0 -> do _ <- hWaitForInput stdin (-1)
 
463
                          return ()
 
464
                        -- hWaitForInput does work properly, but we can only
 
465
                        -- do this for stdin since we know its FD.
 
466
                  _ -> error "threadWaitRead requires -threaded on Windows, or use System.IO.hWaitForInput"
 
467
#else
 
468
  = GHC.Conc.threadWaitRead fd
 
469
#endif
 
470
 
 
471
-- | Block the current thread until data can be written to the
 
472
-- given file descriptor (GHC only).
 
473
threadWaitWrite :: Fd -> IO ()
 
474
threadWaitWrite fd
 
475
#ifdef mingw32_HOST_OS
 
476
  | threaded  = withThread (waitFd fd 1)
 
477
  | otherwise = error "threadWaitWrite requires -threaded on Windows"
 
478
#else
 
479
  = GHC.Conc.threadWaitWrite fd
 
480
#endif
 
481
 
 
482
#ifdef mingw32_HOST_OS
 
483
foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool
 
484
 
 
485
withThread :: IO a -> IO a
 
486
withThread io = do
 
487
  m <- newEmptyMVar
 
488
  _ <- mask_ $ forkIO $ try io >>= putMVar m
 
489
  x <- takeMVar m
 
490
  case x of
 
491
    Right a -> return a
 
492
    Left e  -> throwIO (e :: IOException)
 
493
 
 
494
waitFd :: Fd -> CInt -> IO ()
 
495
waitFd fd write = do
 
496
   throwErrnoIfMinus1_ "fdReady" $
 
497
        fdReady (fromIntegral fd) write (fromIntegral iNFINITE) 0
 
498
 
 
499
iNFINITE :: CInt
 
500
iNFINITE = 0xFFFFFFFF -- urgh
 
501
 
 
502
foreign import ccall safe "fdReady"
 
503
  fdReady :: CInt -> CInt -> CInt -> CInt -> IO CInt
 
504
#endif
 
505
 
 
506
-- ---------------------------------------------------------------------------
 
507
-- More docs
 
508
 
 
509
{- $osthreads
 
510
 
 
511
      #osthreads# In GHC, threads created by 'forkIO' are lightweight threads, and
 
512
      are managed entirely by the GHC runtime.  Typically Haskell
 
513
      threads are an order of magnitude or two more efficient (in
 
514
      terms of both time and space) than operating system threads.
 
515
 
 
516
      The downside of having lightweight threads is that only one can
 
517
      run at a time, so if one thread blocks in a foreign call, for
 
518
      example, the other threads cannot continue.  The GHC runtime
 
519
      works around this by making use of full OS threads where
 
520
      necessary.  When the program is built with the @-threaded@
 
521
      option (to link against the multithreaded version of the
 
522
      runtime), a thread making a @safe@ foreign call will not block
 
523
      the other threads in the system; another OS thread will take
 
524
      over running Haskell threads until the original call returns.
 
525
      The runtime maintains a pool of these /worker/ threads so that
 
526
      multiple Haskell threads can be involved in external calls
 
527
      simultaneously.
 
528
 
 
529
      The "System.IO" library manages multiplexing in its own way.  On
 
530
      Windows systems it uses @safe@ foreign calls to ensure that
 
531
      threads doing I\/O operations don't block the whole runtime,
 
532
      whereas on Unix systems all the currently blocked I\/O requests
 
533
      are managed by a single thread (the /IO manager thread/) using
 
534
      @select@.
 
535
 
 
536
      The runtime will run a Haskell thread using any of the available
 
537
      worker OS threads.  If you need control over which particular OS
 
538
      thread is used to run a given Haskell thread, perhaps because
 
539
      you need to call a foreign library that uses OS-thread-local
 
540
      state, then you need bound threads (see "Control.Concurrent#boundthreads").
 
541
 
 
542
      If you don't use the @-threaded@ option, then the runtime does
 
543
      not make use of multiple OS threads.  Foreign calls will block
 
544
      all other running Haskell threads until the call returns.  The
 
545
      "System.IO" library still does multiplexing, so there can be multiple
 
546
      threads doing I\/O, and this is handled internally by the runtime using
 
547
      @select@.
 
548
-}
 
549
 
 
550
{- $termination
 
551
 
 
552
      In a standalone GHC program, only the main thread is
 
553
      required to terminate in order for the process to terminate.
 
554
      Thus all other forked threads will simply terminate at the same
 
555
      time as the main thread (the terminology for this kind of
 
556
      behaviour is \"daemonic threads\").
 
557
 
 
558
      If you want the program to wait for child threads to
 
559
      finish before exiting, you need to program this yourself.  A
 
560
      simple mechanism is to have each child thread write to an
 
561
      'MVar' when it completes, and have the main
 
562
      thread wait on all the 'MVar's before
 
563
      exiting:
 
564
 
 
565
>   myForkIO :: IO () -> IO (MVar ())
 
566
>   myForkIO io = do
 
567
>     mvar <- newEmptyMVar
 
568
>     forkIO (io `finally` putMVar mvar ())
 
569
>     return mvar
 
570
 
 
571
      Note that we use 'finally' from the
 
572
      "Control.Exception" module to make sure that the
 
573
      'MVar' is written to even if the thread dies or
 
574
      is killed for some reason.
 
575
 
 
576
      A better method is to keep a global list of all child
 
577
      threads which we should wait for at the end of the program:
 
578
 
 
579
>    children :: MVar [MVar ()]
 
580
>    children = unsafePerformIO (newMVar [])
 
581
>    
 
582
>    waitForChildren :: IO ()
 
583
>    waitForChildren = do
 
584
>      cs <- takeMVar children
 
585
>      case cs of
 
586
>        []   -> return ()
 
587
>        m:ms -> do
 
588
>           putMVar children ms
 
589
>           takeMVar m
 
590
>           waitForChildren
 
591
>
 
592
>    forkChild :: IO () -> IO ThreadId
 
593
>    forkChild io = do
 
594
>        mvar <- newEmptyMVar
 
595
>        childs <- takeMVar children
 
596
>        putMVar children (mvar:childs)
 
597
>        forkIO (io `finally` putMVar mvar ())
 
598
>
 
599
>     main =
 
600
>       later waitForChildren $
 
601
>       ...
 
602
 
 
603
      The main thread principle also applies to calls to Haskell from
 
604
      outside, using @foreign export@.  When the @foreign export@ed
 
605
      function is invoked, it starts a new main thread, and it returns
 
606
      when this main thread terminates.  If the call causes new
 
607
      threads to be forked, they may remain in the system after the
 
608
      @foreign export@ed function has returned.
 
609
-}
 
610
 
 
611
{- $preemption
 
612
 
 
613
      GHC implements pre-emptive multitasking: the execution of
 
614
      threads are interleaved in a random fashion.  More specifically,
 
615
      a thread may be pre-empted whenever it allocates some memory,
 
616
      which unfortunately means that tight loops which do no
 
617
      allocation tend to lock out other threads (this only seems to
 
618
      happen with pathological benchmark-style code, however).
 
619
 
 
620
      The rescheduling timer runs on a 20ms granularity by
 
621
      default, but this may be altered using the
 
622
      @-i\<n\>@ RTS option.  After a rescheduling
 
623
      \"tick\" the running thread is pre-empted as soon as
 
624
      possible.
 
625
 
 
626
      One final note: the
 
627
      @aaaa@ @bbbb@ example may not
 
628
      work too well on GHC (see Scheduling, above), due
 
629
      to the locking on a 'System.IO.Handle'.  Only one thread
 
630
      may hold the lock on a 'System.IO.Handle' at any one
 
631
      time, so if a reschedule happens while a thread is holding the
 
632
      lock, the other thread won't be able to run.  The upshot is that
 
633
      the switch from @aaaa@ to
 
634
      @bbbbb@ happens infrequently.  It can be
 
635
      improved by lowering the reschedule tick period.  We also have a
 
636
      patch that causes a reschedule whenever a thread waiting on a
 
637
      lock is woken up, but haven't found it to be useful for anything
 
638
      other than this example :-)
 
639
-}
 
640
#endif /* __GLASGOW_HASKELL__ */