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