X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=GHC%2FConc.lhs;h=93ffba76c774eb931e27f12fbf40461a0e1dda27;hb=de2b563a240bafc20b656729d1ecde0c890d22da;hp=eb4c88a7167a0f52084805fc2bde56617f882d12;hpb=e816bd912de53222ae9baf9343236e9bd1462d23;p=ghc-base.git diff --git a/GHC/Conc.lhs b/GHC/Conc.lhs index eb4c88a..93ffba7 100644 --- a/GHC/Conc.lhs +++ b/GHC/Conc.lhs @@ -1,5 +1,5 @@ \begin{code} -{-# OPTIONS -fno-implicit-prelude #-} +{-# OPTIONS_GHC -fno-implicit-prelude #-} ----------------------------------------------------------------------------- -- | -- Module : GHC.Conc @@ -14,7 +14,6 @@ -- ----------------------------------------------------------------------------- -#include "ghcconfig.h" module GHC.Conc ( ThreadId(..) @@ -53,8 +52,9 @@ module GHC.Conc , newTVar -- :: a -> STM (TVar a) , readTVar -- :: TVar a -> STM a , writeTVar -- :: a -> TVar a -> STM () + , unsafeIOToSTM -- :: IO a -> STM a -#ifdef mingw32_TARGET_OS +#ifdef mingw32_HOST_OS , asyncRead -- :: Int -> Int -> Int -> Ptr a -> IO (Int, Int) , asyncWrite -- :: Int -> Int -> Int -> Ptr a -> IO (Int, Int) , asyncDoProc -- :: FunPtr (Ptr a -> IO Int) -> Ptr a -> IO Int @@ -80,6 +80,8 @@ import GHC.Exception ( Exception(..), AsyncException(..) ) import GHC.Pack ( packCString# ) import GHC.Ptr ( Ptr(..), plusPtr, FunPtr(..) ) import GHC.STRef +import Data.Typeable +#include "Typeable.h" infixr 0 `par`, `pseq` \end{code} @@ -113,6 +115,9 @@ This misfeature will hopefully be corrected at a later date. it defines 'ThreadId' as a synonym for (). -} +INSTANCE_TYPEABLE0(ThreadId,threadIdTc,"ThreadId") + + --forkIO has now been hoisted out into the Concurrent library. {- | 'killThread' terminates the given thread (GHC only). @@ -203,6 +208,8 @@ transactions. \begin{code} newtype STM a = STM (State# RealWorld -> (# State# RealWorld, a #)) +INSTANCE_TYPEABLE1(STM,stmTc,"STM" ) + unSTM :: STM a -> (State# RealWorld -> (# State# RealWorld, a #)) unSTM (STM a) = a @@ -213,7 +220,7 @@ instance Monad STM where {-# INLINE return #-} {-# INLINE (>>) #-} {-# INLINE (>>=) #-} - m >> k = m >>= \_ -> k + m >> k = thenSTM m k return x = returnSTM x m >>= k = bindSTM m k @@ -232,6 +239,10 @@ thenSTM (STM m) k = STM ( \s -> returnSTM :: a -> STM a returnSTM x = STM (\s -> (# s, x #)) +-- | Unsafely performs IO in the STM monad. +unsafeIOToSTM :: IO a -> STM a +unsafeIOToSTM (IO m) = STM m + -- |Perform a series of STM actions atomically. atomically :: STM a -> IO a atomically (STM m) = IO (\s -> (atomically# m) s ) @@ -257,6 +268,8 @@ catchSTM (STM m) k = STM $ \s -> catchSTM# m (\ex -> unSTM (k ex)) s data TVar a = TVar (TVar# RealWorld a) +INSTANCE_TYPEABLE1(TVar,tvarTc,"TVar" ) + instance Eq (TVar a) where (TVar tvar1#) == (TVar tvar2#) = sameTVar# tvar1# tvar2# @@ -295,6 +308,8 @@ writes. \begin{code} --Defined in IOBase to avoid cycle: data MVar a = MVar (SynchVar# RealWorld a) +INSTANCE_TYPEABLE1(MVar,mvarTc,"MVar" ) + -- |Create an 'MVar' which is initially empty. newEmptyMVar :: IO (MVar a) newEmptyMVar = IO $ \ s# -> @@ -372,25 +387,20 @@ addMVarFinalizer (MVar m) finalizer = %************************************************************************ \begin{code} -#ifdef mingw32_TARGET_OS +#ifdef mingw32_HOST_OS -- Note: threadDelay, threadWaitRead and threadWaitWrite aren't really functional -- on Win32, but left in there because lib code (still) uses them (the manner -- in which they're used doesn't cause problems on a Win32 platform though.) asyncRead :: Int -> Int -> Int -> Ptr a -> IO (Int, Int) -asyncRead (I# fd) (I# isSock) (I# len) (Ptr buf) = do - (l, rc) <- IO (\s -> case asyncRead# fd isSock len buf s of - (# s, len#, err# #) -> (# s, (I# len#, I# err#) #)) - -- special handling for Ctrl+C-aborted 'standard input' reads; - -- see rts/win32/ConsoleHandler.c for details. - if (l == 0 && rc == -2) - then asyncRead (I# fd) (I# isSock) (I# len) (Ptr buf) - else return (l,rc) +asyncRead (I# fd) (I# isSock) (I# len) (Ptr buf) = + IO $ \s -> case asyncRead# fd isSock len buf s of + (# s, len#, err# #) -> (# s, (I# len#, I# err#) #) asyncWrite :: Int -> Int -> Int -> Ptr a -> IO (Int, Int) -asyncWrite (I# fd) (I# isSock) (I# len) (Ptr buf) = - IO $ \s -> case asyncWrite# fd isSock len buf s of +asyncWrite (I# fd) (I# isSock) (I# len) (Ptr buf) = + IO $ \s -> case asyncWrite# fd isSock len buf s of (# s, len#, err# #) -> (# s, (I# len#, I# err#) #) asyncDoProc :: FunPtr (Ptr a -> IO Int) -> Ptr a -> IO Int @@ -421,7 +431,7 @@ asyncWriteBA fd isSock len off bufB = -- given file descriptor (GHC only). threadWaitRead :: Fd -> IO () threadWaitRead fd -#ifndef mingw32_TARGET_OS +#ifndef mingw32_HOST_OS | threaded = waitForReadEvent fd #endif | otherwise = IO $ \s -> @@ -433,7 +443,7 @@ threadWaitRead fd -- given file descriptor (GHC only). threadWaitWrite :: Fd -> IO () threadWaitWrite fd -#ifndef mingw32_TARGET_OS +#ifndef mingw32_HOST_OS | threaded = waitForWriteEvent fd #endif | otherwise = IO $ \s -> @@ -454,7 +464,7 @@ threadWaitWrite fd -- threadDelay :: Int -> IO () threadDelay time -#ifndef mingw32_TARGET_OS +#ifndef mingw32_HOST_OS | threaded = waitForDelayEvent time #else | threaded = c_Sleep (fromIntegral (time `quot` 1000)) @@ -465,7 +475,7 @@ threadDelay time }} -- On Windows, we just make a safe call to 'Sleep' to implement threadDelay. -#ifdef mingw32_TARGET_OS +#ifdef mingw32_HOST_OS foreign import ccall safe "Sleep" c_Sleep :: CInt -> IO () #endif @@ -503,7 +513,7 @@ foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool -- - forkProcess will kill the IO manager thread. Let's just -- hope we don't need to do any blocking IO between fork & exec. -#ifndef mingw32_TARGET_OS +#ifndef mingw32_HOST_OS data IOReq = Read {-# UNPACK #-} !Fd {-# UNPACK #-} !(MVar ()) @@ -587,10 +597,10 @@ service_loop wakeup readfds writefds ptimeval old_reqs old_delays = do res <- do_select -- ToDo: check result - old <- atomicModifyIORef prodding (\old -> (False,old)) - if old - then alloca $ \p -> do c_read (fromIntegral wakeup) p 1; return () - else return () + b <- takeMVar prodding + if b then alloca $ \p -> do c_read (fromIntegral wakeup) p 1; return () + else return () + putMVar prodding False reqs' <- completeRequests reqs readfds writefds [] service_loop wakeup readfds writefds ptimeval reqs' delays' @@ -599,19 +609,18 @@ stick :: IORef Fd {-# NOINLINE stick #-} stick = unsafePerformIO (newIORef 0) -prodding :: IORef Bool +prodding :: MVar Bool {-# NOINLINE prodding #-} -prodding = unsafePerformIO (newIORef False) +prodding = unsafePerformIO (newMVar False) prodServiceThread :: IO () prodServiceThread = do - b <- atomicModifyIORef prodding (\old -> (True,old)) -- compare & swap! - if (not b) - then do - fd <- readIORef stick - with 42 $ \pbuf -> do c_write (fromIntegral fd) pbuf 1; return () - else - return () + b <- takeMVar prodding + if (not b) + then do fd <- readIORef stick + with 42 $ \pbuf -> do c_write (fromIntegral fd) pbuf 1; return () + else return () + putMVar prodding True -- ----------------------------------------------------------------------------- -- IO requests