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