Make threadWaitRead/threadWaitWrite partially useable on Windows
[ghc-base.git] / Control / Concurrent.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Control.Concurrent
4 -- Copyright   :  (c) The University of Glasgow 2001
5 -- License     :  BSD-style (see the file libraries/base/LICENSE)
6 -- 
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  experimental
9 -- Portability :  non-portable (concurrency)
10 --
11 -- A common interface to a collection of useful concurrency
12 -- abstractions.
13 --
14 -----------------------------------------------------------------------------
15
16 module Control.Concurrent (
17         -- * Concurrent Haskell
18
19         -- $conc_intro
20
21         -- * Basic concurrency operations
22
23         ThreadId,
24 #ifdef __GLASGOW_HASKELL__
25         myThreadId,
26 #endif
27
28         forkIO,
29 #ifdef __GLASGOW_HASKELL__
30         killThread,
31         throwTo,
32 #endif
33
34         -- * Scheduling
35
36         -- $conc_scheduling     
37         yield,                  -- :: IO ()
38
39         -- ** Blocking
40
41         -- $blocking
42
43 #ifdef __GLASGOW_HASKELL__
44         -- ** Waiting
45         threadDelay,            -- :: Int -> IO ()
46         threadWaitRead,         -- :: Int -> IO ()
47         threadWaitWrite,        -- :: Int -> IO ()
48 #endif
49
50         -- * Communication abstractions
51
52         module Control.Concurrent.MVar,
53         module Control.Concurrent.Chan,
54         module Control.Concurrent.QSem,
55         module Control.Concurrent.QSemN,
56         module Control.Concurrent.SampleVar,
57
58         -- * Merging of streams
59 #ifndef __HUGS__
60         mergeIO,                -- :: [a]   -> [a] -> IO [a]
61         nmergeIO,               -- :: [[a]] -> IO [a]
62 #endif
63         -- $merge
64
65 #ifdef __GLASGOW_HASKELL__
66         -- * Bound Threads
67         -- $boundthreads
68         rtsSupportsBoundThreads,
69         forkOS,
70         isCurrentThreadBound,
71         runInBoundThread,
72         runInUnboundThread
73 #endif
74
75         -- * GHC's implementation of concurrency
76
77         -- |This section describes features specific to GHC's
78         -- implementation of Concurrent Haskell.
79
80         -- ** Haskell threads and Operating System threads
81
82         -- $osthreads
83
84         -- ** Terminating the program
85
86         -- $termination
87
88         -- ** Pre-emption
89
90         -- $preemption
91     ) where
92
93 import Prelude
94
95 import Control.Exception as Exception
96
97 #ifdef __GLASGOW_HASKELL__
98 import GHC.Conc         ( ThreadId(..), myThreadId, killThread, yield,
99                           threadDelay, forkIO, childHandler )
100 import qualified GHC.Conc
101 import GHC.TopHandler   ( reportStackOverflow, reportError )
102 import GHC.IOBase       ( IO(..) )
103 import GHC.IOBase       ( unsafeInterleaveIO )
104 import GHC.IOBase       ( newIORef, readIORef, writeIORef )
105 import GHC.Base
106
107 import System.Posix.Types ( Fd )
108 import Foreign.StablePtr
109 import Foreign.C.Types  ( CInt )
110 import Control.Monad    ( when )
111
112 #ifdef mingw32_HOST_OS
113 import Foreign.C
114 import System.IO
115 import GHC.Handle
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
297 -- | 'True' if bound threads are supported.
298 -- If @rtsSupportsBoundThreads@ is 'False', 'isCurrentThreadBound'
299 -- will always return 'False' and both 'forkOS' and 'runInBoundThread' will
300 -- fail.
301 foreign import ccall rtsSupportsBoundThreads :: Bool
302
303
304 {- |
305 Like 'forkIO', this sparks off a new thread to run the 'IO' computation passed as the
306 first argument, and returns the 'ThreadId' of the newly created
307 thread.
308
309 However, @forkOS@ uses operating system-supplied multithreading support to create
310 a new operating system thread. The new thread is /bound/, which means that
311 all foreign calls made by the 'IO' computation are guaranteed to be executed
312 in this new operating system thread; also, the operating system thread is not
313 used for any other foreign calls.
314
315 This means that you can use all kinds of foreign libraries from this thread 
316 (even those that rely on thread-local state), without the limitations of 'forkIO'.
317
318 Just to clarify, 'forkOS' is /only/ necessary if you need to associate
319 a Haskell thread with a particular OS thread.  It is not necessary if
320 you only need to make non-blocking foreign calls (see
321 "Control.Concurrent#osthreads").  Neither is it necessary if you want
322 to run threads in parallel on a multiprocessor: threads created with
323 'forkIO' will be shared out amongst the running CPUs (using GHC,
324 @-threaded@, and the @+RTS -N@ runtime option).
325
326 -}
327 forkOS :: IO () -> IO ThreadId
328
329 foreign export ccall forkOS_entry
330     :: StablePtr (IO ()) -> IO ()
331
332 foreign import ccall "forkOS_entry" forkOS_entry_reimported
333     :: StablePtr (IO ()) -> IO ()
334
335 forkOS_entry stableAction = do
336         action <- deRefStablePtr stableAction
337         action
338
339 foreign import ccall forkOS_createThread
340     :: StablePtr (IO ()) -> IO CInt
341
342 failNonThreaded = fail $ "RTS doesn't support multiple OS threads "
343                        ++"(use ghc -threaded when linking)"
344
345 forkOS action
346     | rtsSupportsBoundThreads = do
347         mv <- newEmptyMVar
348         let action_plus = Exception.catch action childHandler
349         entry <- newStablePtr (myThreadId >>= putMVar mv >> action_plus)
350         err <- forkOS_createThread entry
351         when (err /= 0) $ fail "Cannot create OS thread."
352         tid <- takeMVar mv
353         freeStablePtr entry
354         return tid
355     | otherwise = failNonThreaded
356
357 -- | Returns 'True' if the calling thread is /bound/, that is, if it is
358 -- safe to use foreign libraries that rely on thread-local state from the
359 -- calling thread.
360 isCurrentThreadBound :: IO Bool
361 isCurrentThreadBound = IO $ \ s# ->
362     case isCurrentThreadBound# s# of
363         (# s2#, flg #) -> (# s2#, not (flg ==# 0#) #)
364
365
366 {- | 
367 Run the 'IO' computation passed as the first argument. If the calling thread
368 is not /bound/, a bound thread is created temporarily. @runInBoundThread@
369 doesn't finish until the 'IO' computation finishes.
370
371 You can wrap a series of foreign function calls that rely on thread-local state
372 with @runInBoundThread@ so that you can use them without knowing whether the
373 current thread is /bound/.
374 -}
375 runInBoundThread :: IO a -> IO a
376
377 runInBoundThread action
378     | rtsSupportsBoundThreads = do
379         bound <- isCurrentThreadBound
380         if bound
381             then action
382             else do
383                 ref <- newIORef undefined
384                 let action_plus = Exception.try action >>= writeIORef ref
385                 resultOrException <-
386                     bracket (newStablePtr action_plus)
387                             freeStablePtr
388                             (\cEntry -> forkOS_entry_reimported cEntry >> readIORef ref)
389                 case resultOrException of
390                     Left exception -> Exception.throw exception
391                     Right result -> return result
392     | otherwise = failNonThreaded
393
394 {- | 
395 Run the 'IO' computation passed as the first argument. If the calling thread
396 is /bound/, an unbound thread is created temporarily using 'forkIO'.
397 @runInBoundThread@ doesn't finish until the 'IO' computation finishes.
398
399 Use this function /only/ in the rare case that you have actually observed a
400 performance loss due to the use of bound threads. A program that
401 doesn't need it's main thread to be bound and makes /heavy/ use of concurrency
402 (e.g. a web server), might want to wrap it's @main@ action in
403 @runInUnboundThread@.
404 -}
405 runInUnboundThread :: IO a -> IO a
406
407 runInUnboundThread action = do
408     bound <- isCurrentThreadBound
409     if bound
410         then do
411             mv <- newEmptyMVar
412             forkIO (Exception.try action >>= putMVar mv)
413             takeMVar mv >>= \either -> case either of
414                 Left exception -> Exception.throw exception
415                 Right result -> return result
416         else action
417
418 #endif /* __GLASGOW_HASKELL__ */
419
420 -- ---------------------------------------------------------------------------
421 -- threadWaitRead/threadWaitWrite
422
423 -- | Block the current thread until data is available to read on the
424 -- given file descriptor (GHC only).
425 threadWaitRead :: Fd -> IO ()
426 threadWaitRead fd
427 #ifdef mingw32_HOST_OS
428   -- we have no IO manager implementing threadWaitRead on Windows.
429   -- fdReady does the right thing, but we have to call it in a
430   -- separate thread, otherwise threadWaitRead won't be interruptible,
431   -- and this only works with -threaded.
432   | threaded  = withThread (waitFd fd 0)
433   | otherwise = case fd of
434                   0 -> do hWaitForInput stdin (-1); return ()
435                         -- hWaitForInput does work properly, but we can only
436                         -- do this for stdin since we know its FD.
437                   _ -> error "threadWaitRead requires -threaded on Windows, or use System.IO.hWaitForInput"
438 #else
439   = GHC.Conc.threadWaitRead fd
440 #endif
441
442 -- | Block the current thread until data can be written to the
443 -- given file descriptor (GHC only).
444 threadWaitWrite :: Fd -> IO ()
445 threadWaitWrite fd
446 #ifdef mingw32_HOST_OS
447   | threaded  = withThread (waitFd fd 1)
448   | otherwise = error "threadWaitWrite requires -threaded on Windows"
449 #else
450   = GHC.Conc.threadWaitWrite fd
451 #endif
452
453 #ifdef mingw32_HOST_OS
454 foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool
455
456 withThread :: IO a -> IO a
457 withThread io = do
458   m <- newEmptyMVar
459   forkIO $ try io >>= putMVar m
460   x <- takeMVar m
461   case x of
462     Right a -> return a
463     Left e  -> throwIO e
464
465 waitFd :: Fd -> CInt -> IO ()
466 waitFd fd write = do
467    throwErrnoIfMinus1 "fdReady" $
468         fdReady (fromIntegral fd) write (fromIntegral iNFINITE) 0
469    return ()
470
471 iNFINITE = 0xFFFFFFFF :: CInt -- urgh
472
473 foreign import ccall safe "fdReady"
474   fdReady :: CInt -> CInt -> CInt -> CInt -> IO CInt
475 #endif
476
477 -- ---------------------------------------------------------------------------
478 -- More docs
479
480 {- $osthreads
481
482       #osthreads# In GHC, threads created by 'forkIO' are lightweight threads, and
483       are managed entirely by the GHC runtime.  Typically Haskell
484       threads are an order of magnitude or two more efficient (in
485       terms of both time and space) than operating system threads.
486
487       The downside of having lightweight threads is that only one can
488       run at a time, so if one thread blocks in a foreign call, for
489       example, the other threads cannot continue.  The GHC runtime
490       works around this by making use of full OS threads where
491       necessary.  When the program is built with the @-threaded@
492       option (to link against the multithreaded version of the
493       runtime), a thread making a @safe@ foreign call will not block
494       the other threads in the system; another OS thread will take
495       over running Haskell threads until the original call returns.
496       The runtime maintains a pool of these /worker/ threads so that
497       multiple Haskell threads can be involved in external calls
498       simultaneously.
499
500       The "System.IO" library manages multiplexing in its own way.  On
501       Windows systems it uses @safe@ foreign calls to ensure that
502       threads doing I\/O operations don't block the whole runtime,
503       whereas on Unix systems all the currently blocked I\/O reqwests
504       are managed by a single thread (the /IO manager thread/) using
505       @select@.
506
507       The runtime will run a Haskell thread using any of the available
508       worker OS threads.  If you need control over which particular OS
509       thread is used to run a given Haskell thread, perhaps because
510       you need to call a foreign library that uses OS-thread-local
511       state, then you need bound threads (see "Control.Concurrent#boundthreads").
512
513       If you don't use the @-threaded@ option, then the runtime does
514       not make use of multiple OS threads.  Foreign calls will block
515       all other running Haskell threads until the call returns.  The
516       "System.IO" library still does multiplexing, so there can be multiple
517       threads doing I\/O, and this is handled internally by the runtime using
518       @select@.
519 -}
520
521 {- $termination
522
523       In a standalone GHC program, only the main thread is
524       required to terminate in order for the process to terminate.
525       Thus all other forked threads will simply terminate at the same
526       time as the main thread (the terminology for this kind of
527       behaviour is \"daemonic threads\").
528
529       If you want the program to wait for child threads to
530       finish before exiting, you need to program this yourself.  A
531       simple mechanism is to have each child thread write to an
532       'MVar' when it completes, and have the main
533       thread wait on all the 'MVar's before
534       exiting:
535
536 >   myForkIO :: IO () -> IO (MVar ())
537 >   myForkIO io = do
538 >     mvar <- newEmptyMVar
539 >     forkIO (io `finally` putMVar mvar ())
540 >     return mvar
541
542       Note that we use 'finally' from the
543       "Control.Exception" module to make sure that the
544       'MVar' is written to even if the thread dies or
545       is killed for some reason.
546
547       A better method is to keep a global list of all child
548       threads which we should wait for at the end of the program:
549
550 >    children :: MVar [MVar ()]
551 >    children = unsafePerformIO (newMVar [])
552 >    
553 >    waitForChildren :: IO ()
554 >    waitForChildren = do
555 >      cs <- takeMVar children
556 >      case cs of
557 >        []   -> return ()
558 >        m:ms -> do
559 >           putMVar children ms
560 >           takeMVar m
561 >           waitForChildren
562 >
563 >    forkChild :: IO () -> IO ThreadId
564 >    forkChild io = do
565 >        mvar <- newEmptyMVar
566 >        childs <- takeMVar children
567 >        putMVar children (mvar:childs)
568 >        forkIO (io `finally` putMVar mvar ())
569 >
570 >     main =
571 >       later waitForChildren $
572 >       ...
573
574       The main thread principle also applies to calls to Haskell from
575       outside, using @foreign export@.  When the @foreign export@ed
576       function is invoked, it starts a new main thread, and it returns
577       when this main thread terminates.  If the call causes new
578       threads to be forked, they may remain in the system after the
579       @foreign export@ed function has returned.
580 -}
581
582 {- $preemption
583
584       GHC implements pre-emptive multitasking: the execution of
585       threads are interleaved in a random fashion.  More specifically,
586       a thread may be pre-empted whenever it allocates some memory,
587       which unfortunately means that tight loops which do no
588       allocation tend to lock out other threads (this only seems to
589       happen with pathological benchmark-style code, however).
590
591       The rescheduling timer runs on a 20ms granularity by
592       default, but this may be altered using the
593       @-i\<n\>@ RTS option.  After a rescheduling
594       \"tick\" the running thread is pre-empted as soon as
595       possible.
596
597       One final note: the
598       @aaaa@ @bbbb@ example may not
599       work too well on GHC (see Scheduling, above), due
600       to the locking on a 'System.IO.Handle'.  Only one thread
601       may hold the lock on a 'System.IO.Handle' at any one
602       time, so if a reschedule happens while a thread is holding the
603       lock, the other thread won't be able to run.  The upshot is that
604       the switch from @aaaa@ to
605       @bbbbb@ happens infrequently.  It can be
606       improved by lowering the reschedule tick period.  We also have a
607       patch that causes a reschedule whenever a thread waiting on a
608       lock is woken up, but haven't found it to be useful for anything
609       other than this example :-)
610 -}