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