[project @ 1997-09-24 00:58:27 by sof]
[ghc-hetmet.git] / ghc / lib / ghc / ConcBase.lhs
index 3a53271..20d0346 100644 (file)
@@ -7,6 +7,7 @@
 Basic concurrency stuff
 
 \begin{code}
+{-# OPTIONS -fno-implicit-prelude #-}
 module ConcBase(
                -- Forking and suchlike
        ST,     forkST,
@@ -19,14 +20,14 @@ module ConcBase(
        MVar, newMVar, newEmptyMVar, takeMVar, putMVar, readMVar, swapMVar
     ) where
 
-import Prelude
+import PrelBase
 import STBase  ( PrimIO(..), ST(..), State(..), StateAndPtr#(..) )
-import IOBase  ( IO(..) )
+import IOBase  ( IO(..), MVar(..) )
 import GHCerr  ( parError )
 import PrelBase        ( Int(..) )
 import GHC     ( fork#, delay#, waitRead#, waitWrite#,
                  SynchVar#, newSynchVar#, takeMVar#, putMVar#,
-                 State#, RealWorld
+                 State#, RealWorld, par#
                )
 
 infixr 0 `par`, `fork`
@@ -66,13 +67,18 @@ par, fork :: Eval a => a -> b -> b
 {-# INLINE par  #-}
 {-# INLINE fork #-}
 
-#ifdef __CONCURRENT_HASKELL__
+#if defined(__PARALLEL_HASKELL__) || defined (__GRANSIM__)
 par  x y = case (par#  x) of { 0# -> parError; _ -> y }
-fork x y = case (fork# x) of { 0# -> parError; _ -> y }
 #else
 par  x y = y
+#endif
+
+#if defined(__CONCURRENT_HASKELL__) || defined (__GRANSIM__)
+fork x y = case (fork# x) of { 0# -> parError; _ -> y }
+#else
 fork x y = y
 #endif
+
 \end{code}
 
 %************************************************************************
@@ -90,7 +96,7 @@ are allowed, but there must be at least one read between any two
 writes.
 
 \begin{code}
-data MVar a = MVar (SynchVar# RealWorld a)
+--Defined in IOBase to avoid cycle: data MVar a = MVar (SynchVar# RealWorld a)
 
 newEmptyMVar  :: IO (MVar a)
 
@@ -147,8 +153,9 @@ virtual time, so we start ticking in real time.  (The granularity is
 the effective resolution of the context switch timer, so it is
 affected by the RTS -C option.)
 
-@threadWait@ delays rescheduling of a thread until input on the
+@threadWaitRead@ delays rescheduling of a thread until input on the
 specified file descriptor is available for reading (just like select).
+@threadWaitWrite@ is similar, but for writing on a file descriptor.
 
 \begin{code}
 threadDelay, threadWaitRead, threadWaitWrite :: Int -> IO ()