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