disambiguate uses of foldr for nhc98 to compile without errors
[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 -- #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 atomically :: STM a -> IO a
332 atomically (STM m) = IO (\s -> (atomically# m) s )
333
334 -- |Retry execution of the current memory transaction because it has seen
335 -- values in TVars which mean that it should not continue (e.g. the TVars
336 -- represent a shared buffer that is now empty).  The implementation may
337 -- block the thread until one of the TVars that it has read from has been
338 -- udpated. (GHC only)
339 retry :: STM a
340 retry = STM $ \s# -> retry# s#
341
342 -- |Compose two alternative STM actions (GHC only).  If the first action
343 -- completes without retrying then it forms the result of the orElse.
344 -- Otherwise, if the first action retries, then the second action is
345 -- tried in its place.  If both actions retry then the orElse as a
346 -- whole retries.
347 orElse :: STM a -> STM a -> STM a
348 orElse (STM m) e = STM $ \s -> catchRetry# m (unSTM e) s
349
350 -- |Exception handling within STM actions.
351 catchSTM :: STM a -> (Exception -> STM a) -> STM a
352 catchSTM (STM m) k = STM $ \s -> catchSTM# m (\ex -> unSTM (k ex)) s
353
354 -- |Shared memory locations that support atomic memory transactions.
355 data TVar a = TVar (TVar# RealWorld a) deriving( Typeable )
356
357 instance Eq (TVar a) where
358         (TVar tvar1#) == (TVar tvar2#) = sameTVar# tvar1# tvar2#
359
360 -- |Create a new TVar holding a value supplied
361 newTVar :: a -> STM (TVar a)
362 newTVar val = STM $ \s1# ->
363     case newTVar# val s1# of
364          (# s2#, tvar# #) -> (# s2#, TVar tvar# #)
365
366 -- |@IO@ version of 'newTVar'.  This is useful for creating top-level
367 -- 'TVar's using 'System.IO.Unsafe.unsafePerformIO', because using
368 -- 'atomically' inside 'System.IO.Unsafe.unsafePerformIO' isn't
369 -- possible.
370 newTVarIO :: a -> IO (TVar a)
371 newTVarIO val = IO $ \s1# ->
372     case newTVar# val s1# of
373          (# s2#, tvar# #) -> (# s2#, TVar tvar# #)
374
375 -- |Return the current value stored in a TVar
376 readTVar :: TVar a -> STM a
377 readTVar (TVar tvar#) = STM $ \s# -> readTVar# tvar# s#
378
379 -- |Write the supplied value into a TVar
380 writeTVar :: TVar a -> a -> STM ()
381 writeTVar (TVar tvar#) val = STM $ \s1# ->
382     case writeTVar# tvar# val s1# of
383          s2# -> (# s2#, () #)
384   
385 \end{code}
386
387 %************************************************************************
388 %*                                                                      *
389 \subsection[mvars]{M-Structures}
390 %*                                                                      *
391 %************************************************************************
392
393 M-Vars are rendezvous points for concurrent threads.  They begin
394 empty, and any attempt to read an empty M-Var blocks.  When an M-Var
395 is written, a single blocked thread may be freed.  Reading an M-Var
396 toggles its state from full back to empty.  Therefore, any value
397 written to an M-Var may only be read once.  Multiple reads and writes
398 are allowed, but there must be at least one read between any two
399 writes.
400
401 \begin{code}
402 --Defined in IOBase to avoid cycle: data MVar a = MVar (SynchVar# RealWorld a)
403
404 -- |Create an 'MVar' which is initially empty.
405 newEmptyMVar  :: IO (MVar a)
406 newEmptyMVar = IO $ \ s# ->
407     case newMVar# s# of
408          (# s2#, svar# #) -> (# s2#, MVar svar# #)
409
410 -- |Create an 'MVar' which contains the supplied value.
411 newMVar :: a -> IO (MVar a)
412 newMVar value =
413     newEmptyMVar        >>= \ mvar ->
414     putMVar mvar value  >>
415     return mvar
416
417 -- |Return the contents of the 'MVar'.  If the 'MVar' is currently
418 -- empty, 'takeMVar' will wait until it is full.  After a 'takeMVar', 
419 -- the 'MVar' is left empty.
420 -- 
421 -- There are two further important properties of 'takeMVar':
422 --
423 --   * 'takeMVar' is single-wakeup.  That is, if there are multiple
424 --     threads blocked in 'takeMVar', and the 'MVar' becomes full,
425 --     only one thread will be woken up.  The runtime guarantees that
426 --     the woken thread completes its 'takeMVar' operation.
427 --
428 --   * When multiple threads are blocked on an 'MVar', they are
429 --     woken up in FIFO order.  This is useful for providing
430 --     fairness properties of abstractions built using 'MVar's.
431 --
432 takeMVar :: MVar a -> IO a
433 takeMVar (MVar mvar#) = IO $ \ s# -> takeMVar# mvar# s#
434
435 -- |Put a value into an 'MVar'.  If the 'MVar' is currently full,
436 -- 'putMVar' will wait until it becomes empty.
437 --
438 -- There are two further important properties of 'putMVar':
439 --
440 --   * 'putMVar' is single-wakeup.  That is, if there are multiple
441 --     threads blocked in 'putMVar', and the 'MVar' becomes empty,
442 --     only one thread will be woken up.  The runtime guarantees that
443 --     the woken thread completes its 'putMVar' operation.
444 --
445 --   * When multiple threads are blocked on an 'MVar', they are
446 --     woken up in FIFO order.  This is useful for providing
447 --     fairness properties of abstractions built using 'MVar's.
448 --
449 putMVar  :: MVar a -> a -> IO ()
450 putMVar (MVar mvar#) x = IO $ \ s# ->
451     case putMVar# mvar# x s# of
452         s2# -> (# s2#, () #)
453
454 -- |A non-blocking version of 'takeMVar'.  The 'tryTakeMVar' function
455 -- returns immediately, with 'Nothing' if the 'MVar' was empty, or
456 -- @'Just' a@ if the 'MVar' was full with contents @a@.  After 'tryTakeMVar',
457 -- the 'MVar' is left empty.
458 tryTakeMVar :: MVar a -> IO (Maybe a)
459 tryTakeMVar (MVar m) = IO $ \ s ->
460     case tryTakeMVar# m s of
461         (# s, 0#, _ #) -> (# s, Nothing #)      -- MVar is empty
462         (# s, _,  a #) -> (# s, Just a  #)      -- MVar is full
463
464 -- |A non-blocking version of 'putMVar'.  The 'tryPutMVar' function
465 -- attempts to put the value @a@ into the 'MVar', returning 'True' if
466 -- it was successful, or 'False' otherwise.
467 tryPutMVar  :: MVar a -> a -> IO Bool
468 tryPutMVar (MVar mvar#) x = IO $ \ s# ->
469     case tryPutMVar# mvar# x s# of
470         (# s, 0# #) -> (# s, False #)
471         (# s, _  #) -> (# s, True #)
472
473 -- |Check whether a given 'MVar' is empty.
474 --
475 -- Notice that the boolean value returned  is just a snapshot of
476 -- the state of the MVar. By the time you get to react on its result,
477 -- the MVar may have been filled (or emptied) - so be extremely
478 -- careful when using this operation.   Use 'tryTakeMVar' instead if possible.
479 isEmptyMVar :: MVar a -> IO Bool
480 isEmptyMVar (MVar mv#) = IO $ \ s# -> 
481     case isEmptyMVar# mv# s# of
482         (# s2#, flg #) -> (# s2#, not (flg ==# 0#) #)
483
484 -- |Add a finalizer to an 'MVar' (GHC only).  See "Foreign.ForeignPtr" and
485 -- "System.Mem.Weak" for more about finalizers.
486 addMVarFinalizer :: MVar a -> IO () -> IO ()
487 addMVarFinalizer (MVar m) finalizer = 
488   IO $ \s -> case mkWeak# m () finalizer s of { (# s1, w #) -> (# s1, () #) }
489 \end{code}
490
491
492 %************************************************************************
493 %*                                                                      *
494 \subsection{Thread waiting}
495 %*                                                                      *
496 %************************************************************************
497
498 \begin{code}
499 #ifdef mingw32_HOST_OS
500
501 -- Note: threadDelay, threadWaitRead and threadWaitWrite aren't really functional
502 -- on Win32, but left in there because lib code (still) uses them (the manner
503 -- in which they're used doesn't cause problems on a Win32 platform though.)
504
505 asyncRead :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
506 asyncRead  (I# fd) (I# isSock) (I# len) (Ptr buf) =
507   IO $ \s -> case asyncRead# fd isSock len buf s of 
508                (# s, len#, err# #) -> (# s, (I# len#, I# err#) #)
509
510 asyncWrite :: Int -> Int -> Int -> Ptr a -> IO (Int, Int)
511 asyncWrite  (I# fd) (I# isSock) (I# len) (Ptr buf) =
512   IO $ \s -> case asyncWrite# fd isSock len buf s of 
513                (# s, len#, err# #) -> (# s, (I# len#, I# err#) #)
514
515 asyncDoProc :: FunPtr (Ptr a -> IO Int) -> Ptr a -> IO Int
516 asyncDoProc (FunPtr proc) (Ptr param) = 
517     -- the 'length' value is ignored; simplifies implementation of
518     -- the async*# primops to have them all return the same result.
519   IO $ \s -> case asyncDoProc# proc param s  of 
520                (# s, len#, err# #) -> (# s, I# err# #)
521
522 -- to aid the use of these primops by the IO Handle implementation,
523 -- provide the following convenience funs:
524
525 -- this better be a pinned byte array!
526 asyncReadBA :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int,Int)
527 asyncReadBA fd isSock len off bufB = 
528   asyncRead fd isSock len ((Ptr (byteArrayContents# (unsafeCoerce# bufB))) `plusPtr` off)
529   
530 asyncWriteBA :: Int -> Int -> Int -> Int -> MutableByteArray# RealWorld -> IO (Int,Int)
531 asyncWriteBA fd isSock len off bufB = 
532   asyncWrite fd isSock len ((Ptr (byteArrayContents# (unsafeCoerce# bufB))) `plusPtr` off)
533
534 #endif
535
536 -- -----------------------------------------------------------------------------
537 -- Thread IO API
538
539 -- | Block the current thread until data is available to read on the
540 -- given file descriptor (GHC only).
541 threadWaitRead :: Fd -> IO ()
542 threadWaitRead fd
543 #ifndef mingw32_HOST_OS
544   | threaded  = waitForReadEvent fd
545 #endif
546   | otherwise = IO $ \s -> 
547         case fromIntegral fd of { I# fd# ->
548         case waitRead# fd# s of { s -> (# s, () #)
549         }}
550
551 -- | Block the current thread until data can be written to the
552 -- given file descriptor (GHC only).
553 threadWaitWrite :: Fd -> IO ()
554 threadWaitWrite fd
555 #ifndef mingw32_HOST_OS
556   | threaded  = waitForWriteEvent fd
557 #endif
558   | otherwise = IO $ \s -> 
559         case fromIntegral fd of { I# fd# ->
560         case waitWrite# fd# s of { s -> (# s, () #)
561         }}
562
563 -- | Suspends the current thread for a given number of microseconds
564 -- (GHC only).
565 --
566 -- Note that the resolution used by the Haskell runtime system's
567 -- internal timer is 1\/50 second, and 'threadDelay' will round its
568 -- argument up to the nearest multiple of this resolution.
569 --
570 -- There is no guarantee that the thread will be rescheduled promptly
571 -- when the delay has expired, but the thread will never continue to
572 -- run /earlier/ than specified.
573 --
574 threadDelay :: Int -> IO ()
575 threadDelay time
576 #ifndef mingw32_HOST_OS
577   | threaded  = waitForDelayEvent time
578 #else
579   | threaded  = c_Sleep (fromIntegral (time `quot` 1000))
580 #endif
581   | otherwise = IO $ \s -> 
582         case fromIntegral time of { I# time# ->
583         case delay# time# s of { s -> (# s, () #)
584         }}
585
586 registerDelay :: Int -> IO (TVar Bool)
587 registerDelay usecs 
588 #ifndef mingw32_HOST_OS
589   | threaded = waitForDelayEventSTM usecs
590   | otherwise = error "registerDelay: requires -threaded"
591 #else
592   = error "registerDelay: not currently supported on Windows"
593 #endif
594
595 -- On Windows, we just make a safe call to 'Sleep' to implement threadDelay.
596 #ifdef mingw32_HOST_OS
597 foreign import stdcall safe "Sleep" c_Sleep :: CInt -> IO ()
598 #endif
599
600 foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool
601
602 -- ----------------------------------------------------------------------------
603 -- Threaded RTS implementation of threadWaitRead, threadWaitWrite, threadDelay
604
605 -- In the threaded RTS, we employ a single IO Manager thread to wait
606 -- for all outstanding IO requests (threadWaitRead,threadWaitWrite)
607 -- and delays (threadDelay).  
608 --
609 -- We can do this because in the threaded RTS the IO Manager can make
610 -- a non-blocking call to select(), so we don't have to do select() in
611 -- the scheduler as we have to in the non-threaded RTS.  We get performance
612 -- benefits from doing it this way, because we only have to restart the select()
613 -- when a new request arrives, rather than doing one select() each time
614 -- around the scheduler loop.  Furthermore, the scheduler can be simplified
615 -- by not having to check for completed IO requests.
616
617 -- Issues, possible problems:
618 --
619 --      - we might want bound threads to just do the blocking
620 --        operation rather than communicating with the IO manager
621 --        thread.  This would prevent simgle-threaded programs which do
622 --        IO from requiring multiple OS threads.  However, it would also
623 --        prevent bound threads waiting on IO from being killed or sent
624 --        exceptions.
625 --
626 --      - Apprently exec() doesn't work on Linux in a multithreaded program.
627 --        I couldn't repeat this.
628 --
629 --      - How do we handle signal delivery in the multithreaded RTS?
630 --
631 --      - forkProcess will kill the IO manager thread.  Let's just
632 --        hope we don't need to do any blocking IO between fork & exec.
633
634 #ifndef mingw32_HOST_OS
635
636 data IOReq
637   = Read   {-# UNPACK #-} !Fd {-# UNPACK #-} !(MVar ())
638   | Write  {-# UNPACK #-} !Fd {-# UNPACK #-} !(MVar ())
639
640 data DelayReq
641   = Delay    {-# UNPACK #-} !Int {-# UNPACK #-} !(MVar ())
642   | DelaySTM {-# UNPACK #-} !Int {-# UNPACK #-} !(TVar Bool)
643
644 pendingEvents :: IORef [IOReq]
645 pendingDelays :: IORef [DelayReq]
646         -- could use a strict list or array here
647 {-# NOINLINE pendingEvents #-}
648 {-# NOINLINE pendingDelays #-}
649 (pendingEvents,pendingDelays) = unsafePerformIO $ do
650   startIOManagerThread
651   reqs <- newIORef []
652   dels <- newIORef []
653   return (reqs, dels)
654         -- the first time we schedule an IO request, the service thread
655         -- will be created (cool, huh?)
656
657 ensureIOManagerIsRunning :: IO ()
658 ensureIOManagerIsRunning 
659   | threaded  = seq pendingEvents $ return ()
660   | otherwise = return ()
661
662 startIOManagerThread :: IO ()
663 startIOManagerThread = do
664         allocaArray 2 $ \fds -> do
665         throwErrnoIfMinus1 "startIOManagerThread" (c_pipe fds)
666         rd_end <- peekElemOff fds 0
667         wr_end <- peekElemOff fds 1
668         writeIORef stick (fromIntegral wr_end)
669         c_setIOManagerPipe wr_end
670         forkIO $ do
671             allocaBytes sizeofFdSet   $ \readfds -> do
672             allocaBytes sizeofFdSet   $ \writefds -> do 
673             allocaBytes sizeofTimeVal $ \timeval -> do
674             service_loop (fromIntegral rd_end) readfds writefds timeval [] []
675         return ()
676
677 service_loop
678    :: Fd                -- listen to this for wakeup calls
679    -> Ptr CFdSet
680    -> Ptr CFdSet
681    -> Ptr CTimeVal
682    -> [IOReq]
683    -> [DelayReq]
684    -> IO ()
685 service_loop wakeup readfds writefds ptimeval old_reqs old_delays = do
686
687   -- pick up new IO requests
688   new_reqs <- atomicModifyIORef pendingEvents (\a -> ([],a))
689   let reqs = new_reqs ++ old_reqs
690
691   -- pick up new delay requests
692   new_delays <- atomicModifyIORef pendingDelays (\a -> ([],a))
693   let  delays = foldr insertDelay old_delays new_delays
694
695   -- build the FDSets for select()
696   fdZero readfds
697   fdZero writefds
698   fdSet wakeup readfds
699   maxfd <- buildFdSets 0 readfds writefds reqs
700
701   -- perform the select()
702   let do_select delays = do
703           -- check the current time and wake up any thread in
704           -- threadDelay whose timeout has expired.  Also find the
705           -- timeout value for the select() call.
706           now <- getTicksOfDay
707           (delays', timeout) <- getDelay now ptimeval delays
708
709           res <- c_select ((max wakeup maxfd)+1) readfds writefds 
710                         nullPtr timeout
711           if (res == -1)
712              then do
713                 err <- getErrno
714                 case err of
715                   _ | err == eINTR ->  do_select delays'
716                         -- EINTR: just redo the select()
717                   _ | err == eBADF ->  return (True, delays)
718                         -- EBADF: one of the file descriptors is closed or bad,
719                         -- we don't know which one, so wake everyone up.
720                   _ | otherwise    ->  throwErrno "select"
721                         -- otherwise (ENOMEM or EINVAL) something has gone
722                         -- wrong; report the error.
723              else
724                 return (False,delays')
725
726   (wakeup_all,delays') <- do_select delays
727
728   exit <-
729     if wakeup_all then return False
730       else do
731         b <- fdIsSet wakeup readfds
732         if b == 0 
733           then return False
734           else alloca $ \p -> do 
735                  c_read (fromIntegral wakeup) p 1; return ()
736                  s <- peek p            
737                  case s of
738                   _ | s == io_MANAGER_WAKEUP -> return False
739                   _ | s == io_MANAGER_DIE    -> return True
740                   _ -> do handler_tbl <- peek handlers
741                           sp <- peekElemOff handler_tbl (fromIntegral s)
742                           forkIO (do io <- deRefStablePtr sp; io)
743                           return False
744
745   if exit then return () else do
746
747   takeMVar prodding
748   putMVar prodding False
749
750   reqs' <- if wakeup_all then do wakeupAll reqs; return []
751                          else completeRequests reqs readfds writefds []
752
753   service_loop wakeup readfds writefds ptimeval reqs' delays'
754
755 stick :: IORef Fd
756 {-# NOINLINE stick #-}
757 stick = unsafePerformIO (newIORef 0)
758
759 io_MANAGER_WAKEUP = 0xff :: CChar
760 io_MANAGER_DIE    = 0xfe :: CChar
761
762 prodding :: MVar Bool
763 {-# NOINLINE prodding #-}
764 prodding = unsafePerformIO (newMVar False)
765
766 prodServiceThread :: IO ()
767 prodServiceThread = do
768   b <- takeMVar prodding
769   if (not b) 
770     then do fd <- readIORef stick
771             with io_MANAGER_WAKEUP $ \pbuf -> do 
772                 c_write (fromIntegral fd) pbuf 1; return ()
773     else return ()
774   putMVar prodding True
775
776 foreign import ccall "&signal_handlers" handlers :: Ptr (Ptr (StablePtr (IO ())))
777
778 foreign import ccall "setIOManagerPipe"
779   c_setIOManagerPipe :: CInt -> IO ()
780
781 -- -----------------------------------------------------------------------------
782 -- IO requests
783
784 buildFdSets maxfd readfds writefds [] = return maxfd
785 buildFdSets maxfd readfds writefds (Read fd m : reqs)
786   | fd >= fD_SETSIZE =  error "buildFdSets: file descriptor out of range"
787   | otherwise        =  do
788         fdSet fd readfds
789         buildFdSets (max maxfd fd) readfds writefds reqs
790 buildFdSets maxfd readfds writefds (Write fd m : reqs)
791   | fd >= fD_SETSIZE =  error "buildFdSets: file descriptor out of range"
792   | otherwise        =  do
793         fdSet fd writefds
794         buildFdSets (max maxfd fd) readfds writefds reqs
795
796 completeRequests [] _ _ reqs' = return reqs'
797 completeRequests (Read fd m : reqs) readfds writefds reqs' = do
798   b <- fdIsSet fd readfds
799   if b /= 0
800     then do putMVar m (); completeRequests reqs readfds writefds reqs'
801     else completeRequests reqs readfds writefds (Read fd m : reqs')
802 completeRequests (Write fd m : reqs) readfds writefds reqs' = do
803   b <- fdIsSet fd writefds
804   if b /= 0
805     then do putMVar m (); completeRequests reqs readfds writefds reqs'
806     else completeRequests reqs readfds writefds (Write fd m : reqs')
807
808 wakeupAll [] = return ()
809 wakeupAll (Read  fd m : reqs) = do putMVar m (); wakeupAll reqs
810 wakeupAll (Write fd m : reqs) = do putMVar m (); wakeupAll reqs
811
812 waitForReadEvent :: Fd -> IO ()
813 waitForReadEvent fd = do
814   m <- newEmptyMVar
815   atomicModifyIORef pendingEvents (\xs -> (Read fd m : xs, ()))
816   prodServiceThread
817   takeMVar m
818
819 waitForWriteEvent :: Fd -> IO ()
820 waitForWriteEvent fd = do
821   m <- newEmptyMVar
822   atomicModifyIORef pendingEvents (\xs -> (Write fd m : xs, ()))
823   prodServiceThread
824   takeMVar m
825
826 -- XXX: move into GHC.IOBase from Data.IORef?
827 atomicModifyIORef :: IORef a -> (a -> (a,b)) -> IO b
828 atomicModifyIORef (IORef (STRef r#)) f = IO $ \s -> atomicModifyMutVar# r# f s
829
830 -- -----------------------------------------------------------------------------
831 -- Delays
832
833 waitForDelayEvent :: Int -> IO ()
834 waitForDelayEvent usecs = do
835   m <- newEmptyMVar
836   now <- getTicksOfDay
837   let target = now + usecs `quot` tick_usecs
838   atomicModifyIORef pendingDelays (\xs -> (Delay target m : xs, ()))
839   prodServiceThread
840   takeMVar m
841
842 -- Delays for use in STM
843 waitForDelayEventSTM :: Int -> IO (TVar Bool)
844 waitForDelayEventSTM usecs = do
845    t <- atomically $ newTVar False
846    now <- getTicksOfDay
847    let target = now + usecs `quot` tick_usecs
848    atomicModifyIORef pendingDelays (\xs -> (DelaySTM target t : xs, ()))
849    prodServiceThread
850    return t  
851     
852 -- Walk the queue of pending delays, waking up any that have passed
853 -- and return the smallest delay to wait for.  The queue of pending
854 -- delays is kept ordered.
855 getDelay :: Ticks -> Ptr CTimeVal -> [DelayReq] -> IO ([DelayReq], Ptr CTimeVal)
856 getDelay now ptimeval [] = return ([],nullPtr)
857 getDelay now ptimeval all@(d : rest) 
858   = case d of
859      Delay time m | now >= time -> do
860         putMVar m ()
861         getDelay now ptimeval rest
862      DelaySTM time t | now >= time -> do
863         atomically $ writeTVar t True
864         getDelay now ptimeval rest
865      _otherwise -> do
866         setTimevalTicks ptimeval (delayTime d - now)
867         return (all,ptimeval)
868
869 insertDelay :: DelayReq -> [DelayReq] -> [DelayReq]
870 insertDelay d [] = [d]
871 insertDelay d1 ds@(d2 : rest)
872   | delayTime d1 <= delayTime d2 = d1 : ds
873   | otherwise                    = d2 : insertDelay d1 rest
874
875 delayTime (Delay t _) = t
876 delayTime (DelaySTM t _) = t
877
878 type Ticks = Int
879 tick_freq  = 50 :: Ticks  -- accuracy of threadDelay (ticks per sec)
880 tick_usecs = 1000000 `quot` tick_freq :: Int
881
882 newtype CTimeVal = CTimeVal ()
883
884 foreign import ccall unsafe "sizeofTimeVal"
885   sizeofTimeVal :: Int
886
887 foreign import ccall unsafe "getTicksOfDay" 
888   getTicksOfDay :: IO Ticks
889
890 foreign import ccall unsafe "setTimevalTicks" 
891   setTimevalTicks :: Ptr CTimeVal -> Ticks -> IO ()
892
893 -- ----------------------------------------------------------------------------
894 -- select() interface
895
896 -- ToDo: move to System.Posix.Internals?
897
898 newtype CFdSet = CFdSet ()
899
900 foreign import ccall safe "select"
901   c_select :: Fd -> Ptr CFdSet -> Ptr CFdSet -> Ptr CFdSet -> Ptr CTimeVal
902            -> IO CInt
903
904 foreign import ccall unsafe "hsFD_SETSIZE"
905   fD_SETSIZE :: Fd
906
907 foreign import ccall unsafe "hsFD_CLR"
908   fdClr :: Fd -> Ptr CFdSet -> IO ()
909
910 foreign import ccall unsafe "hsFD_ISSET"
911   fdIsSet :: Fd -> Ptr CFdSet -> IO CInt
912
913 foreign import ccall unsafe "hsFD_SET"
914   fdSet :: Fd -> Ptr CFdSet -> IO ()
915
916 foreign import ccall unsafe "hsFD_ZERO"
917   fdZero :: Ptr CFdSet -> IO ()
918
919 foreign import ccall unsafe "sizeof_fd_set"
920   sizeofFdSet :: Int
921
922 #endif
923 \end{code}