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