X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=Data%2FIORef.hs;h=934f1de7945ec6a7ed557a1e9be7fe50f2fc5580;hb=HEAD;hp=af8ebda4ca8bbe2be2055619829e058fd3124b22;hpb=bfdd52de414c485c3173b4c899d4a58b67dc725c;p=ghc-base.git diff --git a/Data/IORef.hs b/Data/IORef.hs index af8ebda..934f1de 100644 --- a/Data/IORef.hs +++ b/Data/IORef.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, UnboxedTuples #-} + ----------------------------------------------------------------------------- -- | -- Module : Data.IORef @@ -14,29 +16,33 @@ module Data.IORef ( - -- * IORefs - IORef, -- abstract, instance of: Eq, Typeable - newIORef, -- :: a -> IO (IORef a) - readIORef, -- :: IORef a -> IO a - writeIORef, -- :: IORef a -> a -> IO () - modifyIORef, -- :: IORef a -> (a -> a) -> IO () - atomicModifyIORef, -- :: IORef a -> (a -> (a,b)) -> IO b + -- * IORefs + IORef, -- abstract, instance of: Eq, Typeable + newIORef, -- :: a -> IO (IORef a) + readIORef, -- :: IORef a -> IO a + writeIORef, -- :: IORef a -> a -> IO () + modifyIORef, -- :: IORef a -> (a -> a) -> IO () + atomicModifyIORef, -- :: IORef a -> (a -> (a,b)) -> IO b #if !defined(__PARALLEL_HASKELL__) && defined(__GLASGOW_HASKELL__) - mkWeakIORef, -- :: IORef a -> IO () -> IO (Weak (IORef a)) + mkWeakIORef, -- :: IORef a -> IO () -> IO (Weak (IORef a)) #endif - ) where + -- ** Memory Model + + -- $memmodel -import Prelude + ) where #ifdef __HUGS__ import Hugs.IORef #endif #ifdef __GLASGOW_HASKELL__ -import GHC.Base ( mkWeak#, atomicModifyMutVar# ) +import GHC.Base import GHC.STRef -import GHC.IOBase +-- import GHC.IO +import GHC.IORef hiding (atomicModifyIORef) +import qualified GHC.IORef #if !defined(__PARALLEL_HASKELL__) import GHC.Weak #endif @@ -48,15 +54,13 @@ import NHC.IOExtras , newIORef , readIORef , writeIORef + , excludeFinalisers ) #endif -#ifndef __NHC__ -import Data.Dynamic -#endif - #if defined(__GLASGOW_HASKELL__) && !defined(__PARALLEL_HASKELL__) --- |Make a 'Weak' pointer to an 'IORef' +-- |Make a 'Weak' pointer to an 'IORef', using the second argument as a finalizer +-- to run when 'IORef' is garbage-collected mkWeakIORef :: IORef a -> IO () -> IO (Weak (IORef a)) mkWeakIORef r@(IORef (STRef r#)) f = IO $ \s -> case mkWeak# r# r f s of (# s1, w #) -> (# s1, Weak w #) @@ -64,7 +68,7 @@ mkWeakIORef r@(IORef (STRef r#)) f = IO $ \s -> -- |Mutate the contents of an 'IORef' modifyIORef :: IORef a -> (a -> a) -> IO () -modifyIORef ref f = writeIORef ref . f =<< readIORef ref +modifyIORef ref f = readIORef ref >>= writeIORef ref . f -- |Atomically modifies the contents of an 'IORef'. @@ -75,15 +79,62 @@ modifyIORef ref f = writeIORef ref . f =<< readIORef ref -- -- Extending the atomicity to multiple 'IORef's is problematic, so it -- is recommended that if you need to do anything more complicated --- then using 'MVar' instead is a good idea. +-- then using 'Control.Concurrent.MVar.MVar' instead is a good idea. -- atomicModifyIORef :: IORef a -> (a -> (a,b)) -> IO b #if defined(__GLASGOW_HASKELL__) -atomicModifyIORef (IORef (STRef r#)) f = IO $ \s -> atomicModifyMutVar# r# f s +atomicModifyIORef = GHC.IORef.atomicModifyIORef #elif defined(__HUGS__) -atomicModifyIORef = plainModifyIORef -- Hugs has no preemption +atomicModifyIORef = plainModifyIORef -- Hugs has no preemption where plainModifyIORef r f = do - a <- readIORef r - case f a of (a',b) -> writeIORef r a' >> return b + a <- readIORef r + case f a of (a',b) -> writeIORef r a' >> return b +#elif defined(__NHC__) +atomicModifyIORef r f = + excludeFinalisers $ do + a <- readIORef r + let (a',b) = f a + writeIORef r a' + return b #endif + +{- $memmodel + + In a concurrent program, 'IORef' operations may appear out-of-order + to another thread, depending on the memory model of the underlying + processor architecture. For example, on x86, loads can move ahead + of stores, so in the following example: + +> maybePrint :: IORef Bool -> IORef Bool -> IO () +> maybePrint myRef yourRef = do +> writeIORef myRef True +> yourVal <- readIORef yourRef +> unless yourVal $ putStrLn "critical section" +> +> main :: IO () +> main = do +> r1 <- newIORef False +> r2 <- newIORef False +> forkIO $ maybePrint r1 r2 +> forkIO $ maybePrint r2 r1 +> threadDelay 1000000 + + it is possible that the string @"critical section"@ is printed + twice, even though there is no interleaving of the operations of the + two threads that allows that outcome. The memory model of x86 + allows 'readIORef' to happen before the earlier 'writeIORef'. + + The implementation is required to ensure that reordering of memory + operations cannot cause type-correct code to go wrong. In + particular, when inspecting the value read from an 'IORef', the + memory writes that created that value must have occurred from the + point of view of the current therad. + + 'atomicModifyIORef' acts as a barrier to reordering. Multiple + 'atomicModifyIORef' operations occur in strict program order. An + 'atomicModifyIORef' is never observed to take place ahead of any + earlier (in program order) 'IORef' operations, or after any later + 'IORef' operations. + +-}