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