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