Use explicit language extensions & remove extension fields from base.cabal
[ghc-base.git] / Data / IORef.hs
index 284c2bf..a6f29e7 100644 (file)
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, UnboxedTuples #-}
+
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Data.IORef
 
 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 ()
+        -- * 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
-
-import Prelude
+        ) where
 
 #ifdef __HUGS__
 import Hugs.IORef
 #endif
 
 #ifdef __GLASGOW_HASKELL__
-import GHC.Base                ( mkWeak# )
+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
@@ -47,13 +50,10 @@ 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'
 mkWeakIORef :: IORef a -> IO () -> IO (Weak (IORef a))
@@ -63,9 +63,33 @@ 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'.
+--
+-- This function is useful for using 'IORef' in a safe way in a multithreaded
+-- program.  If you only have one 'IORef', then using 'atomicModifyIORef' to
+-- access and modify it will prevent race conditions.
+--
+-- Extending the atomicity to multiple 'IORef's is problematic, so it
+-- is recommended that if you need to do anything more complicated
+-- then using 'Control.Concurrent.MVar.MVar' instead is a good idea.
+--
+atomicModifyIORef :: IORef a -> (a -> (a,b)) -> IO b
+#if defined(__GLASGOW_HASKELL__)
+atomicModifyIORef = GHC.IORef.atomicModifyIORef
 
-#ifndef __NHC__
-#include "Dynamic.h"
-INSTANCE_TYPEABLE1(IORef,ioRefTc,"IORef")
+#elif defined(__HUGS__)
+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
+#elif defined(__NHC__)
+atomicModifyIORef r f =
+  excludeFinalisers $ do
+    a <- readIORef r
+    let (a',b) = f a
+    writeIORef r a'
+    return b
 #endif