add a way to ask the IO manager thread to exit
[ghc-base.git] / GHC / Conc.lhs
1 \begin{code}
2 {-# OPTIONS_GHC -fno-implicit-prelude #-}
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.Conc
6 -- Copyright   :  (c) The University of Glasgow, 1994-2002
7 -- License     :  see libraries/base/LICENSE
8 -- 
9 -- Maintainer  :  cvs-ghc@haskell.org
10 -- Stability   :  internal
11 -- Portability :  non-portable (GHC extensions)
12 --
13 -- Basic concurrency stuff.
14 -- 
15 -----------------------------------------------------------------------------
16
17 -- No: #hide, because bits of this module are exposed by the stm package.
18 -- However, we don't want this module to be the home location for the
19 -- bits it exports, we'd rather have Control.Concurrent and the other
20 -- higher level modules be the home.  Hence:
21
22 -- #not-home
23 module GHC.Conc
24         ( ThreadId(..)
25
26         -- Forking and suchlike
27         , forkIO        -- :: IO a -> IO ThreadId
28         , forkOnIO      -- :: Int -> IO a -> IO ThreadId
29         , childHandler  -- :: Exception -> IO ()
30         , myThreadId    -- :: IO ThreadId
31         , killThread    -- :: ThreadId -> IO ()
32         , throwTo       -- :: ThreadId -> Exception -> IO ()
33         , par           -- :: a -> b -> b
34         , pseq          -- :: a -> b -> b
35         , yield         -- :: IO ()
36         , labelThread   -- :: ThreadId -> String -> IO ()
37
38         -- Waiting
39         , threadDelay           -- :: Int -> IO ()
40         , registerDelay         -- :: Int -> IO (TVar Bool)
41         , threadWaitRead        -- :: Int -> IO ()
42         , threadWaitWrite       -- :: Int -> IO ()
43
44         -- MVars
45         , MVar          -- abstract
46         , newMVar       -- :: a -> IO (MVar a)
47         , newEmptyMVar  -- :: IO (MVar a)
48         , takeMVar      -- :: MVar a -> IO a
49         , putMVar       -- :: MVar a -> a -> IO ()
50         , tryTakeMVar   -- :: MVar a -> IO (Maybe a)
51         , tryPutMVar    -- :: MVar a -> a -> IO Bool
52         , isEmptyMVar   -- :: MVar a -> IO Bool
53         , addMVarFinalizer -- :: MVar a -> IO () -> IO ()
54
55         -- TVars
56         , STM           -- abstract
57         , atomically    -- :: STM a -> IO a
58         , retry         -- :: STM a
59         , orElse        -- :: STM a -> STM a -> STM a
60         , catchSTM      -- :: STM a -> (Exception -> STM a) -> STM a
61         , TVar          -- abstract
62         , newTVar       -- :: a -> STM (TVar a)
63         , newTVarIO     -- :: a -> STM (TVar a)
64         , readTVar      -- :: TVar a -> STM a
65         , writeTVar     -- :: a -> TVar a -> STM ()
66         , unsafeIOToSTM -- :: IO a -> STM a
67
68 #ifdef mingw32_HOST_OS
69         , asyncRead     -- :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
70         , asyncWrite    -- :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
71         , asyncDoProc   -- :: FunPtr (Ptr a -> IO Int) -> Ptr a -> IO Int
72
73         , asyncReadBA   -- :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int, Int)
74         , asyncWriteBA  -- :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int, Int)
75 #endif
76
77 #ifndef mingw32_HOST_OS
78         , ensureIOManagerIsRunning
79 #endif
80         ) where
81
82 import System.Posix.Types
83 import System.Posix.Internals
84 import Foreign
85 import Foreign.C
86
87 #ifndef __HADDOCK__
88 import {-# SOURCE #-} GHC.TopHandler ( reportError, reportStackOverflow )
89 #endif
90
91 import Data.Maybe
92
93 import GHC.Base
94 import GHC.IOBase
95 import GHC.Num          ( Num(..) )
96 import GHC.Real         ( fromIntegral, quot )
97 import GHC.Base         ( Int(..) )
98 import GHC.Exception    ( catchException, Exception(..), AsyncException(..) )
99 import GHC.Pack         ( packCString# )
100 import GHC.Ptr          ( Ptr(..), plusPtr, FunPtr(..) )
101 import GHC.STRef
102 import GHC.Show         ( Show(..), showString )
103 import Data.Typeable
104
105 infixr 0 `par`, `pseq`
106 \end{code}
107
108 %************************************************************************
109 %*                                                                      *
110 \subsection{@ThreadId@, @par@, and @fork@}
111 %*                                                                      *
112 %************************************************************************
113
114 \begin{code}
115 data ThreadId = ThreadId ThreadId# deriving( Typeable )
116 -- ToDo: data ThreadId = ThreadId (Weak ThreadId#)
117 -- But since ThreadId# is unlifted, the Weak type must use open
118 -- type variables.
119 {- ^
120 A 'ThreadId' is an abstract type representing a handle to a thread.
121 'ThreadId' is an instance of 'Eq', 'Ord' and 'Show', where
122 the 'Ord' instance implements an arbitrary total ordering over
123 'ThreadId's. The 'Show' instance lets you convert an arbitrary-valued
124 'ThreadId' to string form; showing a 'ThreadId' value is occasionally
125 useful when debugging or diagnosing the behaviour of a concurrent
126 program.
127
128 /Note/: in GHC, if you have a 'ThreadId', you essentially have
129 a pointer to the thread itself.  This means the thread itself can\'t be
130 garbage collected until you drop the 'ThreadId'.
131 This misfeature will hopefully be corrected at a later date.
132
133 /Note/: Hugs does not provide any operations on other threads;
134 it defines 'ThreadId' as a synonym for ().
135 -}
136
137 instance Show ThreadId where
138    showsPrec d t = 
139         showString "ThreadId " . 
140         showsPrec d (getThreadId (id2TSO t))
141
142 foreign import ccall unsafe "rts_getThreadId" getThreadId :: ThreadId# -> Int
143
144 id2TSO :: ThreadId -> ThreadId#
145 id2TSO (ThreadId t) = t
146
147 foreign import ccall unsafe "cmp_thread" cmp_thread :: ThreadId# -> ThreadId# -> CInt
148 -- Returns -1, 0, 1
149
150 cmpThread :: ThreadId -> ThreadId -> Ordering
151 cmpThread t1 t2 = 
152    case cmp_thread (id2TSO t1) (id2TSO t2) of
153       -1 -> LT
154       0  -> EQ
155       _  -> GT -- must be 1
156
157 instance Eq ThreadId where
158    t1 == t2 = 
159       case t1 `cmpThread` t2 of
160          EQ -> True
161          _  -> False
162
163 instance Ord ThreadId where
164    compare = cmpThread
165
166 {- |
167 This sparks off a new thread to run the 'IO' computation passed as the
168 first argument, and returns the 'ThreadId' of the newly created
169 thread.
170
171 The new thread will be a lightweight thread; if you want to use a foreign
172 library that uses thread-local storage, use 'forkOS' instead.
173 -}
174 forkIO :: IO () -> IO ThreadId
175 forkIO action = IO $ \ s -> 
176    case (fork# action_plus s) of (# s1, id #) -> (# s1, ThreadId id #)
177  where
178   action_plus = catchException action childHandler
179
180 forkOnIO :: Int -> IO () -> IO ThreadId
181 forkOnIO (I# cpu) action = IO $ \ s -> 
182    case (forkOn# cpu action_plus s) of (# s1, id #) -> (# s1, ThreadId id #)
183  where
184   action_plus = catchException action childHandler
185
186 childHandler :: Exception -> IO ()
187 childHandler err = catchException (real_handler err) childHandler
188
189 real_handler :: Exception -> IO ()
190 real_handler ex =
191   case ex of
192         -- ignore thread GC and killThread exceptions:
193         BlockedOnDeadMVar            -> return ()
194         BlockedIndefinitely          -> return ()
195         AsyncException ThreadKilled  -> return ()
196
197         -- report all others:
198         AsyncException StackOverflow -> reportStackOverflow
199         other       -> reportError other
200
201 {- | 'killThread' terminates the given thread (GHC only).
202 Any work already done by the thread isn\'t
203 lost: the computation is suspended until required by another thread.
204 The memory used by the thread will be garbage collected if it isn\'t
205 referenced from anywhere.  The 'killThread' function is defined in
206 terms of 'throwTo':
207
208 > killThread tid = throwTo tid (AsyncException ThreadKilled)
209
210 -}
211 killThread :: ThreadId -> IO ()
212 killThread tid = throwTo tid (AsyncException ThreadKilled)
213
214 {- | 'throwTo' raises an arbitrary exception in the target thread (GHC only).
215
216 'throwTo' does not return until the exception has been raised in the
217 target thread.  The calling thread can thus be certain that the target
218 thread has received the exception.  This is a useful property to know
219 when dealing with race conditions: eg. if there are two threads that
220 can kill each other, it is guaranteed that only one of the threads
221 will get to kill the other.
222
223 If the target thread is currently making a foreign call, then the
224 exception will not be raised (and hence 'throwTo' will not return)
225 until the call has completed.  This is the case regardless of whether
226 the call is inside a 'block' or not.
227  -}
228 throwTo :: ThreadId -> Exception -> IO ()
229 throwTo (ThreadId id) ex = IO $ \ s ->
230    case (killThread# id ex s) of s1 -> (# s1, () #)
231
232 -- | Returns the 'ThreadId' of the calling thread (GHC only).
233 myThreadId :: IO ThreadId
234 myThreadId = IO $ \s ->
235    case (myThreadId# s) of (# s1, id #) -> (# s1, ThreadId id #)
236
237
238 -- |The 'yield' action allows (forces, in a co-operative multitasking
239 -- implementation) a context-switch to any other currently runnable
240 -- threads (if any), and is occasionally useful when implementing
241 -- concurrency abstractions.
242 yield :: IO ()
243 yield = IO $ \s -> 
244    case (yield# s) of s1 -> (# s1, () #)
245
246 {- | 'labelThread' stores a string as identifier for this thread if
247 you built a RTS with debugging support. This identifier will be used in
248 the debugging output to make distinction of different threads easier
249 (otherwise you only have the thread state object\'s address in the heap).
250
251 Other applications like the graphical Concurrent Haskell Debugger
252 (<http://www.informatik.uni-kiel.de/~fhu/chd/>) may choose to overload
253 'labelThread' for their purposes as well.
254 -}
255
256 labelThread :: ThreadId -> String -> IO ()
257 labelThread (ThreadId t) str = IO $ \ s ->
258    let ps  = packCString# str
259        adr = byteArrayContents# ps in
260      case (labelThread# t adr s) of s1 -> (# s1, () #)
261
262 --      Nota Bene: 'pseq' used to be 'seq'
263 --                 but 'seq' is now defined in PrelGHC
264 --
265 -- "pseq" is defined a bit weirdly (see below)
266 --
267 -- The reason for the strange "lazy" call is that
268 -- it fools the compiler into thinking that pseq  and par are non-strict in
269 -- their second argument (even if it inlines pseq at the call site).
270 -- If it thinks pseq is strict in "y", then it often evaluates
271 -- "y" before "x", which is totally wrong.  
272
273 {-# INLINE pseq  #-}
274 pseq :: a -> b -> b
275 pseq  x y = x `seq` lazy y
276
277 {-# INLINE par  #-}
278 par :: a -> b -> b
279 par  x y = case (par# x) of { _ -> lazy y }
280 \end{code}
281
282
283 %************************************************************************
284 %*                                                                      *
285 \subsection[stm]{Transactional heap operations}
286 %*                                                                      *
287 %************************************************************************
288
289 TVars are shared memory locations which support atomic memory
290 transactions.
291
292 \begin{code}
293 newtype STM a = STM (State# RealWorld -> (# State# RealWorld, a #)) deriving( Typeable )
294
295 unSTM :: STM a -> (State# RealWorld -> (# State# RealWorld, a #))
296 unSTM (STM a) = a
297
298 instance  Functor STM where
299    fmap f x = x >>= (return . f)
300
301 instance  Monad STM  where
302     {-# INLINE return #-}
303     {-# INLINE (>>)   #-}
304     {-# INLINE (>>=)  #-}
305     m >> k      = thenSTM m k
306     return x    = returnSTM x
307     m >>= k     = bindSTM m k
308
309 bindSTM :: STM a -> (a -> STM b) -> STM b
310 bindSTM (STM m) k = STM ( \s ->
311   case m s of 
312     (# new_s, a #) -> unSTM (k a) new_s
313   )
314
315 thenSTM :: STM a -> STM b -> STM b
316 thenSTM (STM m) k = STM ( \s ->
317   case m s of 
318     (# new_s, a #) -> unSTM k new_s
319   )
320
321 returnSTM :: a -> STM a
322 returnSTM x = STM (\s -> (# s, x #))
323
324 -- | Unsafely performs IO in the STM monad.
325 unsafeIOToSTM :: IO a -> STM a
326 unsafeIOToSTM (IO m) = STM m
327
328 -- |Perform a series of STM actions atomically.
329 atomically :: STM a -> IO a
330 atomically (STM m) = IO (\s -> (atomically# m) s )
331
332 -- |Retry execution of the current memory transaction because it has seen
333 -- values in TVars which mean that it should not continue (e.g. the TVars
334 -- represent a shared buffer that is now empty).  The implementation may
335 -- block the thread until one of the TVars that it has read from has been
336 -- udpated.
337 retry :: STM a
338 retry = STM $ \s# -> retry# s#
339
340 -- |Compose two alternative STM actions.  If the first action completes without
341 -- retrying then it forms the result of the orElse.  Otherwise, if the first
342 -- action retries, then the second action is tried in its place.  If both actions
343 -- retry then the orElse as a whole retries.
344 orElse :: STM a -> STM a -> STM a
345 orElse (STM m) e = STM $ \s -> catchRetry# m (unSTM e) s
346
347 -- |Exception handling within STM actions.
348 catchSTM :: STM a -> (Exception -> STM a) -> STM a
349 catchSTM (STM m) k = STM $ \s -> catchSTM# m (\ex -> unSTM (k ex)) s
350
351 data TVar a = TVar (TVar# RealWorld a) deriving( Typeable )
352
353 instance Eq (TVar a) where
354         (TVar tvar1#) == (TVar tvar2#) = sameTVar# tvar1# tvar2#
355
356 -- |Create a new TVar holding a value supplied
357 newTVar :: a -> STM (TVar a)
358 newTVar val = STM $ \s1# ->
359     case newTVar# val s1# of
360          (# s2#, tvar# #) -> (# s2#, TVar tvar# #)
361
362 -- |@IO@ version of 'newTVar'.  This is useful for creating top-level
363 -- 'TVar's using 'System.IO.Unsafe.unsafePerformIO', because using
364 -- 'atomically' inside 'System.IO.Unsafe.unsafePerformIO' isn't
365 -- possible.
366 newTVarIO :: a -> IO (TVar a)
367 newTVarIO val = IO $ \s1# ->
368     case newTVar# val s1# of
369          (# s2#, tvar# #) -> (# s2#, TVar tvar# #)
370
371 -- |Return the current value stored in a TVar
372 readTVar :: TVar a -> STM a
373 readTVar (TVar tvar#) = STM $ \s# -> readTVar# tvar# s#
374
375 -- |Write the supplied value into a TVar
376 writeTVar :: TVar a -> a -> STM ()
377 writeTVar (TVar tvar#) val = STM $ \s1# ->
378     case writeTVar# tvar# val s1# of
379          s2# -> (# s2#, () #)
380   
381 \end{code}
382
383 %************************************************************************
384 %*                                                                      *
385 \subsection[mvars]{M-Structures}
386 %*                                                                      *
387 %************************************************************************
388
389 M-Vars are rendezvous points for concurrent threads.  They begin
390 empty, and any attempt to read an empty M-Var blocks.  When an M-Var
391 is written, a single blocked thread may be freed.  Reading an M-Var
392 toggles its state from full back to empty.  Therefore, any value
393 written to an M-Var may only be read once.  Multiple reads and writes
394 are allowed, but there must be at least one read between any two
395 writes.
396
397 \begin{code}
398 --Defined in IOBase to avoid cycle: data MVar a = MVar (SynchVar# RealWorld a)
399
400 -- |Create an 'MVar' which is initially empty.
401 newEmptyMVar  :: IO (MVar a)
402 newEmptyMVar = IO $ \ s# ->
403     case newMVar# s# of
404          (# s2#, svar# #) -> (# s2#, MVar svar# #)
405
406 -- |Create an 'MVar' which contains the supplied value.
407 newMVar :: a -> IO (MVar a)
408 newMVar value =
409     newEmptyMVar        >>= \ mvar ->
410     putMVar mvar value  >>
411     return mvar
412
413 -- |Return the contents of the 'MVar'.  If the 'MVar' is currently
414 -- empty, 'takeMVar' will wait until it is full.  After a 'takeMVar', 
415 -- the 'MVar' is left empty.
416 -- 
417 -- There are two further important properties of 'takeMVar':
418 --
419 --   * 'takeMVar' is single-wakeup.  That is, if there are multiple
420 --     threads blocked in 'takeMVar', and the 'MVar' becomes full,
421 --     only one thread will be woken up.  The runtime guarantees that
422 --     the woken thread completes its 'takeMVar' operation.
423 --
424 --   * When multiple threads are blocked on an 'MVar', they are
425 --     woken up in FIFO order.  This is useful for providing
426 --     fairness properties of abstractions built using 'MVar's.
427 --
428 takeMVar :: MVar a -> IO a
429 takeMVar (MVar mvar#) = IO $ \ s# -> takeMVar# mvar# s#
430
431 -- |Put a value into an 'MVar'.  If the 'MVar' is currently full,
432 -- 'putMVar' will wait until it becomes empty.
433 --
434 -- There are two further important properties of 'putMVar':
435 --
436 --   * 'putMVar' is single-wakeup.  That is, if there are multiple
437 --     threads blocked in 'putMVar', and the 'MVar' becomes empty,
438 --     only one thread will be woken up.  The runtime guarantees that
439 --     the woken thread completes its 'putMVar' operation.
440 --
441 --   * When multiple threads are blocked on an 'MVar', they are
442 --     woken up in FIFO order.  This is useful for providing
443 --     fairness properties of abstractions built using 'MVar's.
444 --
445 putMVar  :: MVar a -> a -> IO ()
446 putMVar (MVar mvar#) x = IO $ \ s# ->
447     case putMVar# mvar# x s# of
448         s2# -> (# s2#, () #)
449
450 -- |A non-blocking version of 'takeMVar'.  The 'tryTakeMVar' function
451 -- returns immediately, with 'Nothing' if the 'MVar' was empty, or
452 -- @'Just' a@ if the 'MVar' was full with contents @a@.  After 'tryTakeMVar',
453 -- the 'MVar' is left empty.
454 tryTakeMVar :: MVar a -> IO (Maybe a)
455 tryTakeMVar (MVar m) = IO $ \ s ->
456     case tryTakeMVar# m s of
457         (# s, 0#, _ #) -> (# s, Nothing #)      -- MVar is empty
458         (# s, _,  a #) -> (# s, Just a  #)      -- MVar is full
459
460 -- |A non-blocking version of 'putMVar'.  The 'tryPutMVar' function
461 -- attempts to put the value @a@ into the 'MVar', returning 'True' if
462 -- it was successful, or 'False' otherwise.
463 tryPutMVar  :: MVar a -> a -> IO Bool
464 tryPutMVar (MVar mvar#) x = IO $ \ s# ->
465     case tryPutMVar# mvar# x s# of
466         (# s, 0# #) -> (# s, False #)
467         (# s, _  #) -> (# s, True #)
468
469 -- |Check whether a given 'MVar' is empty.
470 --
471 -- Notice that the boolean value returned  is just a snapshot of
472 -- the state of the MVar. By the time you get to react on its result,
473 -- the MVar may have been filled (or emptied) - so be extremely
474 -- careful when using this operation.   Use 'tryTakeMVar' instead if possible.
475 isEmptyMVar :: MVar a -> IO Bool
476 isEmptyMVar (MVar mv#) = IO $ \ s# -> 
477     case isEmptyMVar# mv# s# of
478         (# s2#, flg #) -> (# s2#, not (flg ==# 0#) #)
479
480 -- |Add a finalizer to an 'MVar' (GHC only).  See "Foreign.ForeignPtr" and
481 -- "System.Mem.Weak" for more about finalizers.
482 addMVarFinalizer :: MVar a -> IO () -> IO ()
483 addMVarFinalizer (MVar m) finalizer = 
484   IO $ \s -> case mkWeak# m () finalizer s of { (# s1, w #) -> (# s1, () #) }
485 \end{code}
486
487
488 %************************************************************************
489 %*                                                                      *
490 \subsection{Thread waiting}
491 %*                                                                      *
492 %************************************************************************
493
494 \begin{code}
495 #ifdef mingw32_HOST_OS
496
497 -- Note: threadDelay, threadWaitRead and threadWaitWrite aren't really functional
498 -- on Win32, but left in there because lib code (still) uses them (the manner
499 -- in which they're used doesn't cause problems on a Win32 platform though.)
500
501 asyncRead :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
502 asyncRead  (I# fd) (I# isSock) (I# len) (Ptr buf) =
503   IO $ \s -> case asyncRead# fd isSock len buf s of 
504                (# s, len#, err# #) -> (# s, (I# len#, I# err#) #)
505
506 asyncWrite :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
507 asyncWrite  (I# fd) (I# isSock) (I# len) (Ptr buf) =
508   IO $ \s -> case asyncWrite# fd isSock len buf s of 
509                (# s, len#, err# #) -> (# s, (I# len#, I# err#) #)
510
511 asyncDoProc :: FunPtr (Ptr a -> IO Int) -> Ptr a -> IO Int
512 asyncDoProc (FunPtr proc) (Ptr param) = 
513     -- the 'length' value is ignored; simplifies implementation of
514     -- the async*# primops to have them all return the same result.
515   IO $ \s -> case asyncDoProc# proc param s  of 
516                (# s, len#, err# #) -> (# s, I# err# #)
517
518 -- to aid the use of these primops by the IO Handle implementation,
519 -- provide the following convenience funs:
520
521 -- this better be a pinned byte array!
522 asyncReadBA :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int,Int)
523 asyncReadBA fd isSock len off bufB = 
524   asyncRead fd isSock len ((Ptr (byteArrayContents# (unsafeCoerce# bufB))) `plusPtr` off)
525   
526 asyncWriteBA :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int,Int)
527 asyncWriteBA fd isSock len off bufB = 
528   asyncWrite fd isSock len ((Ptr (byteArrayContents# (unsafeCoerce# bufB))) `plusPtr` off)
529
530 #endif
531
532 -- -----------------------------------------------------------------------------
533 -- Thread IO API
534
535 -- | Block the current thread until data is available to read on the
536 -- given file descriptor (GHC only).
537 threadWaitRead :: Fd -> IO ()
538 threadWaitRead fd
539 #ifndef mingw32_HOST_OS
540   | threaded  = waitForReadEvent fd
541 #endif
542   | otherwise = IO $ \s -> 
543         case fromIntegral fd of { I# fd# ->
544         case waitRead# fd# s of { s -> (# s, () #)
545         }}
546
547 -- | Block the current thread until data can be written to the
548 -- given file descriptor (GHC only).
549 threadWaitWrite :: Fd -> IO ()
550 threadWaitWrite fd
551 #ifndef mingw32_HOST_OS
552   | threaded  = waitForWriteEvent fd
553 #endif
554   | otherwise = IO $ \s -> 
555         case fromIntegral fd of { I# fd# ->
556         case waitWrite# fd# s of { s -> (# s, () #)
557         }}
558
559 -- | Suspends the current thread for a given number of microseconds
560 -- (GHC only).
561 --
562 -- Note that the resolution used by the Haskell runtime system's
563 -- internal timer is 1\/50 second, and 'threadDelay' will round its
564 -- argument up to the nearest multiple of this resolution.
565 --
566 -- There is no guarantee that the thread will be rescheduled promptly
567 -- when the delay has expired, but the thread will never continue to
568 -- run /earlier/ than specified.
569 --
570 threadDelay :: Int -> IO ()
571 threadDelay time
572 #ifndef mingw32_HOST_OS
573   | threaded  = waitForDelayEvent time
574 #else
575   | threaded  = c_Sleep (fromIntegral (time `quot` 1000))
576 #endif
577   | otherwise = IO $ \s -> 
578         case fromIntegral time of { I# time# ->
579         case delay# time# s of { s -> (# s, () #)
580         }}
581
582 registerDelay usecs 
583 #ifndef mingw32_HOST_OS
584   | threaded = waitForDelayEventSTM usecs
585   | otherwise = error "registerDelay: requires -threaded"
586 #else
587   = error "registerDelay: not currently supported on Windows"
588 #endif
589
590 -- On Windows, we just make a safe call to 'Sleep' to implement threadDelay.
591 #ifdef mingw32_HOST_OS
592 foreign import stdcall safe "Sleep" c_Sleep :: CInt -> IO ()
593 #endif
594
595 foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool
596
597 -- ----------------------------------------------------------------------------
598 -- Threaded RTS implementation of threadWaitRead, threadWaitWrite, threadDelay
599
600 -- In the threaded RTS, we employ a single IO Manager thread to wait
601 -- for all outstanding IO requests (threadWaitRead,threadWaitWrite)
602 -- and delays (threadDelay).  
603 --
604 -- We can do this because in the threaded RTS the IO Manager can make
605 -- a non-blocking call to select(), so we don't have to do select() in
606 -- the scheduler as we have to in the non-threaded RTS.  We get performance
607 -- benefits from doing it this way, because we only have to restart the select()
608 -- when a new request arrives, rather than doing one select() each time
609 -- around the scheduler loop.  Furthermore, the scheduler can be simplified
610 -- by not having to check for completed IO requests.
611
612 -- Issues, possible problems:
613 --
614 --      - we might want bound threads to just do the blocking
615 --        operation rather than communicating with the IO manager
616 --        thread.  This would prevent simgle-threaded programs which do
617 --        IO from requiring multiple OS threads.  However, it would also
618 --        prevent bound threads waiting on IO from being killed or sent
619 --        exceptions.
620 --
621 --      - Apprently exec() doesn't work on Linux in a multithreaded program.
622 --        I couldn't repeat this.
623 --
624 --      - How do we handle signal delivery in the multithreaded RTS?
625 --
626 --      - forkProcess will kill the IO manager thread.  Let's just
627 --        hope we don't need to do any blocking IO between fork & exec.
628
629 #ifndef mingw32_HOST_OS
630
631 data IOReq
632   = Read   {-# UNPACK #-} !Fd {-# UNPACK #-} !(MVar ())
633   | Write  {-# UNPACK #-} !Fd {-# UNPACK #-} !(MVar ())
634
635 data DelayReq
636   = Delay    {-# UNPACK #-} !Int {-# UNPACK #-} !(MVar ())
637   | DelaySTM {-# UNPACK #-} !Int {-# UNPACK #-} !(TVar Bool)
638
639 pendingEvents :: IORef [IOReq]
640 pendingDelays :: IORef [DelayReq]
641         -- could use a strict list or array here
642 {-# NOINLINE pendingEvents #-}
643 {-# NOINLINE pendingDelays #-}
644 (pendingEvents,pendingDelays) = unsafePerformIO $ do
645   startIOManagerThread
646   reqs <- newIORef []
647   dels <- newIORef []
648   return (reqs, dels)
649         -- the first time we schedule an IO request, the service thread
650         -- will be created (cool, huh?)
651
652 ensureIOManagerIsRunning :: IO ()
653 ensureIOManagerIsRunning 
654   | threaded  = seq pendingEvents $ return ()
655   | otherwise = return ()
656
657 startIOManagerThread :: IO ()
658 startIOManagerThread = do
659         allocaArray 2 $ \fds -> do
660         throwErrnoIfMinus1 "startIOManagerThread" (c_pipe fds)
661         rd_end <- peekElemOff fds 0
662         wr_end <- peekElemOff fds 1
663         writeIORef stick (fromIntegral wr_end)
664         c_setIOManagerPipe wr_end
665         forkIO $ do
666             allocaBytes sizeofFdSet   $ \readfds -> do
667             allocaBytes sizeofFdSet   $ \writefds -> do 
668             allocaBytes sizeofTimeVal $ \timeval -> do
669             service_loop (fromIntegral rd_end) readfds writefds timeval [] []
670         return ()
671
672 service_loop
673    :: Fd                -- listen to this for wakeup calls
674    -> Ptr CFdSet
675    -> Ptr CFdSet
676    -> Ptr CTimeVal
677    -> [IOReq]
678    -> [DelayReq]
679    -> IO ()
680 service_loop wakeup readfds writefds ptimeval old_reqs old_delays = do
681
682   -- pick up new IO requests
683   new_reqs <- atomicModifyIORef pendingEvents (\a -> ([],a))
684   let reqs = new_reqs ++ old_reqs
685
686   -- pick up new delay requests
687   new_delays <- atomicModifyIORef pendingDelays (\a -> ([],a))
688   let  delays = foldr insertDelay old_delays new_delays
689
690   -- build the FDSets for select()
691   fdZero readfds
692   fdZero writefds
693   fdSet wakeup readfds
694   maxfd <- buildFdSets 0 readfds writefds reqs
695
696   -- perform the select()
697   let do_select delays = do
698           -- check the current time and wake up any thread in
699           -- threadDelay whose timeout has expired.  Also find the
700           -- timeout value for the select() call.
701           now <- getTicksOfDay
702           (delays', timeout) <- getDelay now ptimeval delays
703
704           res <- c_select ((max wakeup maxfd)+1) readfds writefds 
705                         nullPtr timeout
706           if (res == -1)
707              then do
708                 err <- getErrno
709                 case err of
710                   _ | err == eINTR ->  do_select delays'
711                         -- EINTR: just redo the select()
712                   _ | err == eBADF ->  return (True, delays)
713                         -- EBADF: one of the file descriptors is closed or bad,
714                         -- we don't know which one, so wake everyone up.
715                   _ | otherwise    ->  throwErrno "select"
716                         -- otherwise (ENOMEM or EINVAL) something has gone
717                         -- wrong; report the error.
718              else
719                 return (False,delays')
720
721   (wakeup_all,delays') <- do_select delays
722
723   exit <-
724     if wakeup_all then return False
725       else do
726         b <- fdIsSet wakeup readfds
727         if b == 0 
728           then return False
729           else alloca $ \p -> do 
730                  c_read (fromIntegral wakeup) p 1; return ()
731                  s <- peek p            
732                  case s of
733                   _ | s == io_MANAGER_WAKEUP -> return False
734                   _ | s == io_MANAGER_DIE    -> return True
735                   _ -> do handler_tbl <- peek handlers
736                           sp <- peekElemOff handler_tbl (fromIntegral s)
737                           forkIO (do io <- deRefStablePtr sp; io)
738                           return False
739
740   if exit then return () else do
741
742   takeMVar prodding
743   putMVar prodding False
744
745   reqs' <- if wakeup_all then do wakeupAll reqs; return []
746                          else completeRequests reqs readfds writefds []
747
748   service_loop wakeup readfds writefds ptimeval reqs' delays'
749
750 stick :: IORef Fd
751 {-# NOINLINE stick #-}
752 stick = unsafePerformIO (newIORef 0)
753
754 io_MANAGER_WAKEUP = 0xff :: CChar
755 io_MANAGER_DIE    = 0xfe :: CChar
756
757 prodding :: MVar Bool
758 {-# NOINLINE prodding #-}
759 prodding = unsafePerformIO (newMVar False)
760
761 prodServiceThread :: IO ()
762 prodServiceThread = do
763   b <- takeMVar prodding
764   if (not b) 
765     then do fd <- readIORef stick
766             with io_MANAGER_WAKEUP $ \pbuf -> do 
767                 c_write (fromIntegral fd) pbuf 1; return ()
768     else return ()
769   putMVar prodding True
770
771 foreign import ccall "&signal_handlers" handlers :: Ptr (Ptr (StablePtr (IO ())))
772
773 foreign import ccall "setIOManagerPipe"
774   c_setIOManagerPipe :: CInt -> IO ()
775
776 -- -----------------------------------------------------------------------------
777 -- IO requests
778
779 buildFdSets maxfd readfds writefds [] = return maxfd
780 buildFdSets maxfd readfds writefds (Read fd m : reqs)
781   | fd >= fD_SETSIZE =  error "buildFdSets: file descriptor out of range"
782   | otherwise        =  do
783         fdSet fd readfds
784         buildFdSets (max maxfd fd) readfds writefds reqs
785 buildFdSets maxfd readfds writefds (Write fd m : reqs)
786   | fd >= fD_SETSIZE =  error "buildFdSets: file descriptor out of range"
787   | otherwise        =  do
788         fdSet fd writefds
789         buildFdSets (max maxfd fd) readfds writefds reqs
790
791 completeRequests [] _ _ reqs' = return reqs'
792 completeRequests (Read fd m : reqs) readfds writefds reqs' = do
793   b <- fdIsSet fd readfds
794   if b /= 0
795     then do putMVar m (); completeRequests reqs readfds writefds reqs'
796     else completeRequests reqs readfds writefds (Read fd m : reqs')
797 completeRequests (Write fd m : reqs) readfds writefds reqs' = do
798   b <- fdIsSet fd writefds
799   if b /= 0
800     then do putMVar m (); completeRequests reqs readfds writefds reqs'
801     else completeRequests reqs readfds writefds (Write fd m : reqs')
802
803 wakeupAll [] = return ()
804 wakeupAll (Read  fd m : reqs) = do putMVar m (); wakeupAll reqs
805 wakeupAll (Write fd m : reqs) = do putMVar m (); wakeupAll reqs
806
807 waitForReadEvent :: Fd -> IO ()
808 waitForReadEvent fd = do
809   m <- newEmptyMVar
810   atomicModifyIORef pendingEvents (\xs -> (Read fd m : xs, ()))
811   prodServiceThread
812   takeMVar m
813
814 waitForWriteEvent :: Fd -> IO ()
815 waitForWriteEvent fd = do
816   m <- newEmptyMVar
817   atomicModifyIORef pendingEvents (\xs -> (Write fd m : xs, ()))
818   prodServiceThread
819   takeMVar m
820
821 -- XXX: move into GHC.IOBase from Data.IORef?
822 atomicModifyIORef :: IORef a -> (a -> (a,b)) -> IO b
823 atomicModifyIORef (IORef (STRef r#)) f = IO $ \s -> atomicModifyMutVar# r# f s
824
825 -- -----------------------------------------------------------------------------
826 -- Delays
827
828 waitForDelayEvent :: Int -> IO ()
829 waitForDelayEvent usecs = do
830   m <- newEmptyMVar
831   now <- getTicksOfDay
832   let target = now + usecs `quot` tick_usecs
833   atomicModifyIORef pendingDelays (\xs -> (Delay target m : xs, ()))
834   prodServiceThread
835   takeMVar m
836
837 -- Delays for use in STM
838 waitForDelayEventSTM :: Int -> IO (TVar Bool)
839 waitForDelayEventSTM usecs = do
840    t <- atomically $ newTVar False
841    now <- getTicksOfDay
842    let target = now + usecs `quot` tick_usecs
843    atomicModifyIORef pendingDelays (\xs -> (DelaySTM target t : xs, ()))
844    prodServiceThread
845    return t  
846     
847 -- Walk the queue of pending delays, waking up any that have passed
848 -- and return the smallest delay to wait for.  The queue of pending
849 -- delays is kept ordered.
850 getDelay :: Ticks -> Ptr CTimeVal -> [DelayReq] -> IO ([DelayReq], Ptr CTimeVal)
851 getDelay now ptimeval [] = return ([],nullPtr)
852 getDelay now ptimeval all@(d : rest) 
853   = case d of
854      Delay time m | now >= time -> do
855         putMVar m ()
856         getDelay now ptimeval rest
857      DelaySTM time t | now >= time -> do
858         atomically $ writeTVar t True
859         getDelay now ptimeval rest
860      _otherwise -> do
861         setTimevalTicks ptimeval (delayTime d - now)
862         return (all,ptimeval)
863
864 insertDelay :: DelayReq -> [DelayReq] -> [DelayReq]
865 insertDelay d [] = [d]
866 insertDelay d1 ds@(d2 : rest)
867   | delayTime d1 <= delayTime d2 = d1 : ds
868   | otherwise                    = d2 : insertDelay d1 rest
869
870 delayTime (Delay t _) = t
871 delayTime (DelaySTM t _) = t
872
873 type Ticks = Int
874 tick_freq  = 50 :: Ticks  -- accuracy of threadDelay (ticks per sec)
875 tick_usecs = 1000000 `quot` tick_freq :: Int
876
877 newtype CTimeVal = CTimeVal ()
878
879 foreign import ccall unsafe "sizeofTimeVal"
880   sizeofTimeVal :: Int
881
882 foreign import ccall unsafe "getTicksOfDay" 
883   getTicksOfDay :: IO Ticks
884
885 foreign import ccall unsafe "setTimevalTicks" 
886   setTimevalTicks :: Ptr CTimeVal -> Ticks -> IO ()
887
888 -- ----------------------------------------------------------------------------
889 -- select() interface
890
891 -- ToDo: move to System.Posix.Internals?
892
893 newtype CFdSet = CFdSet ()
894
895 foreign import ccall safe "select"
896   c_select :: Fd -> Ptr CFdSet -> Ptr CFdSet -> Ptr CFdSet -> Ptr CTimeVal
897            -> IO CInt
898
899 foreign import ccall unsafe "hsFD_SETSIZE"
900   fD_SETSIZE :: Fd
901
902 foreign import ccall unsafe "hsFD_CLR"
903   fdClr :: Fd -> Ptr CFdSet -> IO ()
904
905 foreign import ccall unsafe "hsFD_ISSET"
906   fdIsSet :: Fd -> Ptr CFdSet -> IO CInt
907
908 foreign import ccall unsafe "hsFD_SET"
909   fdSet :: Fd -> Ptr CFdSet -> IO ()
910
911 foreign import ccall unsafe "hsFD_ZERO"
912   fdZero :: Ptr CFdSet -> IO ()
913
914 foreign import ccall unsafe "sizeof_fd_set"
915   sizeofFdSet :: Int
916
917 #endif
918 \end{code}