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