Use explicit language extensions & remove extension fields from base.cabal
[ghc-base.git] / Data / IORef.hs
1 {-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, UnboxedTuples #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  Data.IORef
6 -- Copyright   :  (c) The University of Glasgow 2001
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 -- 
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  experimental
11 -- Portability :  portable
12 --
13 -- Mutable references in the IO monad.
14 --
15 -----------------------------------------------------------------------------
16
17 module Data.IORef
18   ( 
19         -- * IORefs
20         IORef,                -- abstract, instance of: Eq, Typeable
21         newIORef,             -- :: a -> IO (IORef a)
22         readIORef,            -- :: IORef a -> IO a
23         writeIORef,           -- :: IORef a -> a -> IO ()
24         modifyIORef,          -- :: IORef a -> (a -> a) -> IO ()
25         atomicModifyIORef,    -- :: IORef a -> (a -> (a,b)) -> IO b
26
27 #if !defined(__PARALLEL_HASKELL__) && defined(__GLASGOW_HASKELL__)
28         mkWeakIORef,          -- :: IORef a -> IO () -> IO (Weak (IORef a))
29 #endif
30         ) where
31
32 #ifdef __HUGS__
33 import Hugs.IORef
34 #endif
35
36 #ifdef __GLASGOW_HASKELL__
37 import GHC.Base
38 import GHC.STRef
39 -- import GHC.IO
40 import GHC.IORef hiding (atomicModifyIORef)
41 import qualified GHC.IORef
42 #if !defined(__PARALLEL_HASKELL__)
43 import GHC.Weak
44 #endif
45 #endif /* __GLASGOW_HASKELL__ */
46
47 #ifdef __NHC__
48 import NHC.IOExtras
49     ( IORef
50     , newIORef
51     , readIORef
52     , writeIORef
53     , excludeFinalisers
54     )
55 #endif
56
57 #if defined(__GLASGOW_HASKELL__) && !defined(__PARALLEL_HASKELL__)
58 -- |Make a 'Weak' pointer to an 'IORef'
59 mkWeakIORef :: IORef a -> IO () -> IO (Weak (IORef a))
60 mkWeakIORef r@(IORef (STRef r#)) f = IO $ \s ->
61   case mkWeak# r# r f s of (# s1, w #) -> (# s1, Weak w #)
62 #endif
63
64 -- |Mutate the contents of an 'IORef'
65 modifyIORef :: IORef a -> (a -> a) -> IO ()
66 modifyIORef ref f = readIORef ref >>= writeIORef ref . f
67
68
69 -- |Atomically modifies the contents of an 'IORef'.
70 --
71 -- This function is useful for using 'IORef' in a safe way in a multithreaded
72 -- program.  If you only have one 'IORef', then using 'atomicModifyIORef' to
73 -- access and modify it will prevent race conditions.
74 --
75 -- Extending the atomicity to multiple 'IORef's is problematic, so it
76 -- is recommended that if you need to do anything more complicated
77 -- then using 'Control.Concurrent.MVar.MVar' instead is a good idea.
78 --
79 atomicModifyIORef :: IORef a -> (a -> (a,b)) -> IO b
80 #if defined(__GLASGOW_HASKELL__)
81 atomicModifyIORef = GHC.IORef.atomicModifyIORef
82
83 #elif defined(__HUGS__)
84 atomicModifyIORef = plainModifyIORef    -- Hugs has no preemption
85   where plainModifyIORef r f = do
86                 a <- readIORef r
87                 case f a of (a',b) -> writeIORef r a' >> return b
88 #elif defined(__NHC__)
89 atomicModifyIORef r f =
90   excludeFinalisers $ do
91     a <- readIORef r
92     let (a',b) = f a
93     writeIORef r a'
94     return b
95 #endif