Fix #4514 - IO manager deadlock
[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         closeFd,                -- :: (Int -> IO ()) -> Int -> IO ()
51 #endif
52
53         -- * Communication abstractions
54
55         module Control.Concurrent.MVar,
56         module Control.Concurrent.Chan,
57         module Control.Concurrent.QSem,
58         module Control.Concurrent.QSemN,
59         module Control.Concurrent.SampleVar,
60
61         -- * Merging of streams
62 #ifndef __HUGS__
63         mergeIO,                -- :: [a]   -> [a] -> IO [a]
64         nmergeIO,               -- :: [[a]] -> IO [a]
65 #endif
66         -- $merge
67
68 #ifdef __GLASGOW_HASKELL__
69         -- * Bound Threads
70         -- $boundthreads
71         rtsSupportsBoundThreads,
72         forkOS,
73         isCurrentThreadBound,
74         runInBoundThread,
75         runInUnboundThread
76 #endif
77
78         -- * GHC's implementation of concurrency
79
80         -- |This section describes features specific to GHC's
81         -- implementation of Concurrent Haskell.
82
83         -- ** Haskell threads and Operating System threads
84
85         -- $osthreads
86
87         -- ** Terminating the program
88
89         -- $termination
90
91         -- ** Pre-emption
92
93         -- $preemption
94     ) where
95
96 import Prelude
97
98 import Control.Exception.Base as Exception
99
100 #ifdef __GLASGOW_HASKELL__
101 import GHC.Exception
102 import GHC.Conc         ( ThreadId(..), myThreadId, killThread, yield,
103                           threadDelay, forkIO, forkIOUnmasked, childHandler )
104 import qualified GHC.Conc
105 import GHC.IO           ( IO(..), unsafeInterleaveIO, unsafeUnmask )
106 import GHC.IORef        ( newIORef, readIORef, writeIORef )
107 import GHC.Base
108
109 import System.Posix.Types ( Fd )
110 import Foreign.StablePtr
111 import Foreign.C.Types  ( CInt )
112 import Control.Monad    ( when )
113
114 #ifdef mingw32_HOST_OS
115 import Foreign.C
116 import System.IO
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 In terms of performance, 'forkOS' (aka bound) threads are much more
298 expensive than 'forkIO' (aka unbound) threads, because a 'forkOS'
299 thread is tied to a particular OS thread, whereas a 'forkIO' thread
300 can be run by any OS thread.  Context-switching between a 'forkOS'
301 thread and a 'forkIO' thread is many times more expensive than between
302 two 'forkIO' threads.
303
304 Note in particular that the main program thread (the thread running
305 @Main.main@) is always a bound thread, so for good concurrency
306 performance you should ensure that the main thread is not doing
307 repeated communication with other threads in the system.  Typically
308 this means forking subthreads to do the work using 'forkIO', and
309 waiting for the results in the main thread.
310
311 -}
312
313 -- | 'True' if bound threads are supported.
314 -- If @rtsSupportsBoundThreads@ is 'False', 'isCurrentThreadBound'
315 -- will always return 'False' and both 'forkOS' and 'runInBoundThread' will
316 -- fail.
317 foreign import ccall rtsSupportsBoundThreads :: Bool
318
319
320 {- | 
321 Like 'forkIO', this sparks off a new thread to run the 'IO'
322 computation passed as the first argument, and returns the 'ThreadId'
323 of the newly created thread.
324
325 However, 'forkOS' creates a /bound/ thread, which is necessary if you
326 need to call foreign (non-Haskell) libraries that make use of
327 thread-local state, such as OpenGL (see "Control.Concurrent#boundthreads").
328
329 Using 'forkOS' instead of 'forkIO' makes no difference at all to the
330 scheduling behaviour of the Haskell runtime system.  It is a common
331 misconception that you need to use 'forkOS' instead of 'forkIO' to
332 avoid blocking all the Haskell threads when making a foreign call;
333 this isn't the case.  To allow foreign calls to be made without
334 blocking all the Haskell threads (with GHC), it is only necessary to
335 use the @-threaded@ option when linking your program, and to make sure
336 the foreign import is not marked @unsafe@.
337 -}
338
339 forkOS :: IO () -> IO ThreadId
340
341 foreign export ccall forkOS_entry
342     :: StablePtr (IO ()) -> IO ()
343
344 foreign import ccall "forkOS_entry" forkOS_entry_reimported
345     :: StablePtr (IO ()) -> IO ()
346
347 forkOS_entry :: StablePtr (IO ()) -> IO ()
348 forkOS_entry stableAction = do
349         action <- deRefStablePtr stableAction
350         action
351
352 foreign import ccall forkOS_createThread
353     :: StablePtr (IO ()) -> IO CInt
354
355 failNonThreaded :: IO a
356 failNonThreaded = fail $ "RTS doesn't support multiple OS threads "
357                        ++"(use ghc -threaded when linking)"
358
359 forkOS action0
360     | rtsSupportsBoundThreads = do
361         mv <- newEmptyMVar
362         b <- Exception.getMaskingState
363         let
364             -- async exceptions are masked in the child if they are masked
365             -- in the parent, as for forkIO (see #1048). forkOS_createThread
366             -- creates a thread with exceptions masked by default.
367             action1 = case b of
368                         Unmasked -> unsafeUnmask action0
369                         MaskedInterruptible -> action0
370                         MaskedUninterruptible -> uninterruptibleMask_ action0
371
372             action_plus = Exception.catch action1 childHandler
373
374         entry <- newStablePtr (myThreadId >>= putMVar mv >> action_plus)
375         err <- forkOS_createThread entry
376         when (err /= 0) $ fail "Cannot create OS thread."
377         tid <- takeMVar mv
378         freeStablePtr entry
379         return tid
380     | otherwise = failNonThreaded
381
382 -- | Returns 'True' if the calling thread is /bound/, that is, if it is
383 -- safe to use foreign libraries that rely on thread-local state from the
384 -- calling thread.
385 isCurrentThreadBound :: IO Bool
386 isCurrentThreadBound = IO $ \ s# ->
387     case isCurrentThreadBound# s# of
388         (# s2#, flg #) -> (# s2#, not (flg ==# 0#) #)
389
390
391 {- | 
392 Run the 'IO' computation passed as the first argument. If the calling thread
393 is not /bound/, a bound thread is created temporarily. @runInBoundThread@
394 doesn't finish until the 'IO' computation finishes.
395
396 You can wrap a series of foreign function calls that rely on thread-local state
397 with @runInBoundThread@ so that you can use them without knowing whether the
398 current thread is /bound/.
399 -}
400 runInBoundThread :: IO a -> IO a
401
402 runInBoundThread action
403     | rtsSupportsBoundThreads = do
404         bound <- isCurrentThreadBound
405         if bound
406             then action
407             else do
408                 ref <- newIORef undefined
409                 let action_plus = Exception.try action >>= writeIORef ref
410                 bracket (newStablePtr action_plus)
411                         freeStablePtr
412                         (\cEntry -> forkOS_entry_reimported cEntry >> readIORef ref) >>=
413                   unsafeResult
414     | otherwise = failNonThreaded
415
416 {- | 
417 Run the 'IO' computation passed as the first argument. If the calling thread
418 is /bound/, an unbound thread is created temporarily using 'forkIO'.
419 @runInBoundThread@ doesn't finish until the 'IO' computation finishes.
420
421 Use this function /only/ in the rare case that you have actually observed a
422 performance loss due to the use of bound threads. A program that
423 doesn't need it's main thread to be bound and makes /heavy/ use of concurrency
424 (e.g. a web server), might want to wrap it's @main@ action in
425 @runInUnboundThread@.
426
427 Note that exceptions which are thrown to the current thread are thrown in turn
428 to the thread that is executing the given computation. This ensures there's
429 always a way of killing the forked thread.
430 -}
431 runInUnboundThread :: IO a -> IO a
432
433 runInUnboundThread action = do
434   bound <- isCurrentThreadBound
435   if bound
436     then do
437       mv <- newEmptyMVar
438       mask $ \restore -> do
439         tid <- forkIO $ Exception.try (restore action) >>= putMVar mv
440         let wait = takeMVar mv `Exception.catch` \(e :: SomeException) ->
441                      Exception.throwTo tid e >> wait
442         wait >>= unsafeResult
443     else action
444
445 unsafeResult :: Either SomeException a -> IO a
446 unsafeResult = either Exception.throwIO return
447 #endif /* __GLASGOW_HASKELL__ */
448
449 #ifdef __GLASGOW_HASKELL__
450 -- ---------------------------------------------------------------------------
451 -- threadWaitRead/threadWaitWrite
452
453 -- | Block the current thread until data is available to read on the
454 -- given file descriptor (GHC only).
455 --
456 -- This will throw an 'IOError' if the file descriptor was closed
457 -- while this thread was blocked.
458 threadWaitRead :: Fd -> IO ()
459 threadWaitRead fd
460 #ifdef mingw32_HOST_OS
461   -- we have no IO manager implementing threadWaitRead on Windows.
462   -- fdReady does the right thing, but we have to call it in a
463   -- separate thread, otherwise threadWaitRead won't be interruptible,
464   -- and this only works with -threaded.
465   | threaded  = withThread (waitFd fd 0)
466   | otherwise = case fd of
467                   0 -> do _ <- hWaitForInput stdin (-1)
468                           return ()
469                         -- hWaitForInput does work properly, but we can only
470                         -- do this for stdin since we know its FD.
471                   _ -> error "threadWaitRead requires -threaded on Windows, or use System.IO.hWaitForInput"
472 #else
473   = GHC.Conc.threadWaitRead fd
474 #endif
475
476 -- | Block the current thread until data can be written to the
477 -- given file descriptor (GHC only).
478 --
479 -- This will throw an 'IOError' if the file descriptor was closed
480 -- while this thread was blocked.
481 threadWaitWrite :: Fd -> IO ()
482 threadWaitWrite fd
483 #ifdef mingw32_HOST_OS
484   | threaded  = withThread (waitFd fd 1)
485   | otherwise = error "threadWaitWrite requires -threaded on Windows"
486 #else
487   = GHC.Conc.threadWaitWrite fd
488 #endif
489
490 -- | Close a file descriptor in a concurrency-safe way (GHC only).  If
491 -- you are using 'threadWaitRead' or 'threadWaitWrite' to perform
492 -- blocking I\/O, you /must/ use this function to close file
493 -- descriptors, or blocked threads may not be woken.
494 --
495 -- Any threads that are blocked on the file descriptor via
496 -- 'threadWaitRead' or 'threadWaitWrite' will be unblocked by having
497 -- IO exceptions thrown.
498 closeFd :: (Fd -> IO ())        -- ^ Low-level action that performs the real close.
499         -> Fd                   -- ^ File descriptor to close.
500         -> IO ()
501 closeFd close fd
502 #ifdef mingw32_HOST_OS
503   = close fd
504 #else
505   = GHC.Conc.closeFd close fd
506 #endif
507
508 #ifdef mingw32_HOST_OS
509 foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool
510
511 withThread :: IO a -> IO a
512 withThread io = do
513   m <- newEmptyMVar
514   _ <- mask_ $ forkIO $ try io >>= putMVar m
515   x <- takeMVar m
516   case x of
517     Right a -> return a
518     Left e  -> throwIO (e :: IOException)
519
520 waitFd :: Fd -> CInt -> IO ()
521 waitFd fd write = do
522    throwErrnoIfMinus1_ "fdReady" $
523         fdReady (fromIntegral fd) write iNFINITE 0
524
525 iNFINITE :: CInt
526 iNFINITE = 0xFFFFFFFF -- urgh
527
528 foreign import ccall safe "fdReady"
529   fdReady :: CInt -> CInt -> CInt -> CInt -> IO CInt
530 #endif
531
532 -- ---------------------------------------------------------------------------
533 -- More docs
534
535 {- $osthreads
536
537       #osthreads# In GHC, threads created by 'forkIO' are lightweight threads, and
538       are managed entirely by the GHC runtime.  Typically Haskell
539       threads are an order of magnitude or two more efficient (in
540       terms of both time and space) than operating system threads.
541
542       The downside of having lightweight threads is that only one can
543       run at a time, so if one thread blocks in a foreign call, for
544       example, the other threads cannot continue.  The GHC runtime
545       works around this by making use of full OS threads where
546       necessary.  When the program is built with the @-threaded@
547       option (to link against the multithreaded version of the
548       runtime), a thread making a @safe@ foreign call will not block
549       the other threads in the system; another OS thread will take
550       over running Haskell threads until the original call returns.
551       The runtime maintains a pool of these /worker/ threads so that
552       multiple Haskell threads can be involved in external calls
553       simultaneously.
554
555       The "System.IO" library manages multiplexing in its own way.  On
556       Windows systems it uses @safe@ foreign calls to ensure that
557       threads doing I\/O operations don't block the whole runtime,
558       whereas on Unix systems all the currently blocked I\/O requests
559       are managed by a single thread (the /IO manager thread/) using
560       @select@.
561
562       The runtime will run a Haskell thread using any of the available
563       worker OS threads.  If you need control over which particular OS
564       thread is used to run a given Haskell thread, perhaps because
565       you need to call a foreign library that uses OS-thread-local
566       state, then you need bound threads (see "Control.Concurrent#boundthreads").
567
568       If you don't use the @-threaded@ option, then the runtime does
569       not make use of multiple OS threads.  Foreign calls will block
570       all other running Haskell threads until the call returns.  The
571       "System.IO" library still does multiplexing, so there can be multiple
572       threads doing I\/O, and this is handled internally by the runtime using
573       @select@.
574 -}
575
576 {- $termination
577
578       In a standalone GHC program, only the main thread is
579       required to terminate in order for the process to terminate.
580       Thus all other forked threads will simply terminate at the same
581       time as the main thread (the terminology for this kind of
582       behaviour is \"daemonic threads\").
583
584       If you want the program to wait for child threads to
585       finish before exiting, you need to program this yourself.  A
586       simple mechanism is to have each child thread write to an
587       'MVar' when it completes, and have the main
588       thread wait on all the 'MVar's before
589       exiting:
590
591 >   myForkIO :: IO () -> IO (MVar ())
592 >   myForkIO io = do
593 >     mvar <- newEmptyMVar
594 >     forkIO (io `finally` putMVar mvar ())
595 >     return mvar
596
597       Note that we use 'finally' from the
598       "Control.Exception" module to make sure that the
599       'MVar' is written to even if the thread dies or
600       is killed for some reason.
601
602       A better method is to keep a global list of all child
603       threads which we should wait for at the end of the program:
604
605 >    children :: MVar [MVar ()]
606 >    children = unsafePerformIO (newMVar [])
607 >    
608 >    waitForChildren :: IO ()
609 >    waitForChildren = do
610 >      cs <- takeMVar children
611 >      case cs of
612 >        []   -> return ()
613 >        m:ms -> do
614 >           putMVar children ms
615 >           takeMVar m
616 >           waitForChildren
617 >
618 >    forkChild :: IO () -> IO ThreadId
619 >    forkChild io = do
620 >        mvar <- newEmptyMVar
621 >        childs <- takeMVar children
622 >        putMVar children (mvar:childs)
623 >        forkIO (io `finally` putMVar mvar ())
624 >
625 >     main =
626 >       later waitForChildren $
627 >       ...
628
629       The main thread principle also applies to calls to Haskell from
630       outside, using @foreign export@.  When the @foreign export@ed
631       function is invoked, it starts a new main thread, and it returns
632       when this main thread terminates.  If the call causes new
633       threads to be forked, they may remain in the system after the
634       @foreign export@ed function has returned.
635 -}
636
637 {- $preemption
638
639       GHC implements pre-emptive multitasking: the execution of
640       threads are interleaved in a random fashion.  More specifically,
641       a thread may be pre-empted whenever it allocates some memory,
642       which unfortunately means that tight loops which do no
643       allocation tend to lock out other threads (this only seems to
644       happen with pathological benchmark-style code, however).
645
646       The rescheduling timer runs on a 20ms granularity by
647       default, but this may be altered using the
648       @-i\<n\>@ RTS option.  After a rescheduling
649       \"tick\" the running thread is pre-empted as soon as
650       possible.
651
652       One final note: the
653       @aaaa@ @bbbb@ example may not
654       work too well on GHC (see Scheduling, above), due
655       to the locking on a 'System.IO.Handle'.  Only one thread
656       may hold the lock on a 'System.IO.Handle' at any one
657       time, so if a reschedule happens while a thread is holding the
658       lock, the other thread won't be able to run.  The upshot is that
659       the switch from @aaaa@ to
660       @bbbbb@ happens infrequently.  It can be
661       improved by lowering the reschedule tick period.  We also have a
662       patch that causes a reschedule whenever a thread waiting on a
663       lock is woken up, but haven't found it to be useful for anything
664       other than this example :-)
665 -}
666 #endif /* __GLASGOW_HASKELL__ */