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