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