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