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