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