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