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