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