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