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