d1b6875e66285ebcd132e2f0ac69d16949eac690
[ghc-base.git] / Control / Concurrent.hs
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                 bracket (newStablePtr action_plus)
410                         freeStablePtr
411                         (\cEntry -> forkOS_entry_reimported cEntry >> readIORef ref) >>=
412                   unsafeResult
413     | otherwise = failNonThreaded
414
415 {- | 
416 Run the 'IO' computation passed as the first argument. If the calling thread
417 is /bound/, an unbound thread is created temporarily using 'forkIO'.
418 @runInBoundThread@ doesn't finish until the 'IO' computation finishes.
419
420 Use this function /only/ in the rare case that you have actually observed a
421 performance loss due to the use of bound threads. A program that
422 doesn't need it's main thread to be bound and makes /heavy/ use of concurrency
423 (e.g. a web server), might want to wrap it's @main@ action in
424 @runInUnboundThread@.
425
426 Note that exceptions which are thrown to the current thread are thrown in turn
427 to the thread that is executing the given computation. This ensures there's
428 always a way of killing the forked thread.
429 -}
430 runInUnboundThread :: IO a -> IO a
431
432 runInUnboundThread action = do
433   bound <- isCurrentThreadBound
434   if bound
435     then do
436       mv <- newEmptyMVar
437       mask $ \restore -> do
438         tid <- forkIO $ Exception.try (restore action) >>= putMVar mv
439         let wait = takeMVar mv `Exception.catch` \(e :: SomeException) ->
440                      Exception.throwTo tid e >> wait
441         wait >>= unsafeResult
442     else action
443
444 unsafeResult :: Either SomeException a -> IO a
445 unsafeResult = either Exception.throwIO return
446 #endif /* __GLASGOW_HASKELL__ */
447
448 #ifdef __GLASGOW_HASKELL__
449 -- ---------------------------------------------------------------------------
450 -- threadWaitRead/threadWaitWrite
451
452 -- | Block the current thread until data is available to read on the
453 -- given file descriptor (GHC only).
454 --
455 -- This will throw an 'IOError' if the file descriptor was closed
456 -- while this thread was blocked.  To safely close a file descriptor
457 -- that has been used with 'threadWaitRead', use
458 -- 'GHC.Conc.closeFdWith'.
459 threadWaitRead :: Fd -> IO ()
460 threadWaitRead fd
461 #ifdef mingw32_HOST_OS
462   -- we have no IO manager implementing threadWaitRead on Windows.
463   -- fdReady does the right thing, but we have to call it in a
464   -- separate thread, otherwise threadWaitRead won't be interruptible,
465   -- and this only works with -threaded.
466   | threaded  = withThread (waitFd fd 0)
467   | otherwise = case fd of
468                   0 -> do _ <- hWaitForInput stdin (-1)
469                           return ()
470                         -- hWaitForInput does work properly, but we can only
471                         -- do this for stdin since we know its FD.
472                   _ -> error "threadWaitRead requires -threaded on Windows, or use System.IO.hWaitForInput"
473 #else
474   = GHC.Conc.threadWaitRead fd
475 #endif
476
477 -- | Block the current thread until data can be written to the
478 -- given file descriptor (GHC only).
479 --
480 -- This will throw an 'IOError' if the file descriptor was closed
481 -- while this thread was blocked.  To safely close a file descriptor
482 -- that has been used with 'threadWaitWrite', use
483 -- 'GHC.Conc.closeFdWith'.
484 threadWaitWrite :: Fd -> IO ()
485 threadWaitWrite fd
486 #ifdef mingw32_HOST_OS
487   | threaded  = withThread (waitFd fd 1)
488   | otherwise = error "threadWaitWrite requires -threaded on Windows"
489 #else
490   = GHC.Conc.threadWaitWrite fd
491 #endif
492
493 #ifdef mingw32_HOST_OS
494 foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool
495
496 withThread :: IO a -> IO a
497 withThread io = do
498   m <- newEmptyMVar
499   _ <- mask_ $ forkIO $ try io >>= putMVar m
500   x <- takeMVar m
501   case x of
502     Right a -> return a
503     Left e  -> throwIO (e :: IOException)
504
505 waitFd :: Fd -> CInt -> IO ()
506 waitFd fd write = do
507    throwErrnoIfMinus1_ "fdReady" $
508         fdReady (fromIntegral fd) write iNFINITE 0
509
510 iNFINITE :: CInt
511 iNFINITE = 0xFFFFFFFF -- urgh
512
513 foreign import ccall safe "fdReady"
514   fdReady :: CInt -> CInt -> CInt -> CInt -> IO CInt
515 #endif
516
517 -- ---------------------------------------------------------------------------
518 -- More docs
519
520 {- $osthreads
521
522       #osthreads# In GHC, threads created by 'forkIO' are lightweight threads, and
523       are managed entirely by the GHC runtime.  Typically Haskell
524       threads are an order of magnitude or two more efficient (in
525       terms of both time and space) than operating system threads.
526
527       The downside of having lightweight threads is that only one can
528       run at a time, so if one thread blocks in a foreign call, for
529       example, the other threads cannot continue.  The GHC runtime
530       works around this by making use of full OS threads where
531       necessary.  When the program is built with the @-threaded@
532       option (to link against the multithreaded version of the
533       runtime), a thread making a @safe@ foreign call will not block
534       the other threads in the system; another OS thread will take
535       over running Haskell threads until the original call returns.
536       The runtime maintains a pool of these /worker/ threads so that
537       multiple Haskell threads can be involved in external calls
538       simultaneously.
539
540       The "System.IO" library manages multiplexing in its own way.  On
541       Windows systems it uses @safe@ foreign calls to ensure that
542       threads doing I\/O operations don't block the whole runtime,
543       whereas on Unix systems all the currently blocked I\/O requests
544       are managed by a single thread (the /IO manager thread/) using
545       @select@.
546
547       The runtime will run a Haskell thread using any of the available
548       worker OS threads.  If you need control over which particular OS
549       thread is used to run a given Haskell thread, perhaps because
550       you need to call a foreign library that uses OS-thread-local
551       state, then you need bound threads (see "Control.Concurrent#boundthreads").
552
553       If you don't use the @-threaded@ option, then the runtime does
554       not make use of multiple OS threads.  Foreign calls will block
555       all other running Haskell threads until the call returns.  The
556       "System.IO" library still does multiplexing, so there can be multiple
557       threads doing I\/O, and this is handled internally by the runtime using
558       @select@.
559 -}
560
561 {- $termination
562
563       In a standalone GHC program, only the main thread is
564       required to terminate in order for the process to terminate.
565       Thus all other forked threads will simply terminate at the same
566       time as the main thread (the terminology for this kind of
567       behaviour is \"daemonic threads\").
568
569       If you want the program to wait for child threads to
570       finish before exiting, you need to program this yourself.  A
571       simple mechanism is to have each child thread write to an
572       'MVar' when it completes, and have the main
573       thread wait on all the 'MVar's before
574       exiting:
575
576 >   myForkIO :: IO () -> IO (MVar ())
577 >   myForkIO io = do
578 >     mvar <- newEmptyMVar
579 >     forkIO (io `finally` putMVar mvar ())
580 >     return mvar
581
582       Note that we use 'finally' from the
583       "Control.Exception" module to make sure that the
584       'MVar' is written to even if the thread dies or
585       is killed for some reason.
586
587       A better method is to keep a global list of all child
588       threads which we should wait for at the end of the program:
589
590 >    children :: MVar [MVar ()]
591 >    children = unsafePerformIO (newMVar [])
592 >    
593 >    waitForChildren :: IO ()
594 >    waitForChildren = do
595 >      cs <- takeMVar children
596 >      case cs of
597 >        []   -> return ()
598 >        m:ms -> do
599 >           putMVar children ms
600 >           takeMVar m
601 >           waitForChildren
602 >
603 >    forkChild :: IO () -> IO ThreadId
604 >    forkChild io = do
605 >        mvar <- newEmptyMVar
606 >        childs <- takeMVar children
607 >        putMVar children (mvar:childs)
608 >        forkIO (io `finally` putMVar mvar ())
609 >
610 >     main =
611 >       later waitForChildren $
612 >       ...
613
614       The main thread principle also applies to calls to Haskell from
615       outside, using @foreign export@.  When the @foreign export@ed
616       function is invoked, it starts a new main thread, and it returns
617       when this main thread terminates.  If the call causes new
618       threads to be forked, they may remain in the system after the
619       @foreign export@ed function has returned.
620 -}
621
622 {- $preemption
623
624       GHC implements pre-emptive multitasking: the execution of
625       threads are interleaved in a random fashion.  More specifically,
626       a thread may be pre-empted whenever it allocates some memory,
627       which unfortunately means that tight loops which do no
628       allocation tend to lock out other threads (this only seems to
629       happen with pathological benchmark-style code, however).
630
631       The rescheduling timer runs on a 20ms granularity by
632       default, but this may be altered using the
633       @-i\<n\>@ RTS option.  After a rescheduling
634       \"tick\" the running thread is pre-empted as soon as
635       possible.
636
637       One final note: the
638       @aaaa@ @bbbb@ example may not
639       work too well on GHC (see Scheduling, above), due
640       to the locking on a 'System.IO.Handle'.  Only one thread
641       may hold the lock on a 'System.IO.Handle' at any one
642       time, so if a reschedule happens while a thread is holding the
643       lock, the other thread won't be able to run.  The upshot is that
644       the switch from @aaaa@ to
645       @bbbbb@ happens infrequently.  It can be
646       improved by lowering the reschedule tick period.  We also have a
647       patch that causes a reschedule whenever a thread waiting on a
648       lock is woken up, but haven't found it to be useful for anything
649       other than this example :-)
650 -}
651 #endif /* __GLASGOW_HASKELL__ */