add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[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         -- ** Memory Model
31
32         -- $memmodel
33
34         ) where
35
36 #ifdef __HUGS__
37 import Hugs.IORef
38 #endif
39
40 #ifdef __GLASGOW_HASKELL__
41 import GHC.Base
42 import GHC.STRef
43 -- import GHC.IO
44 import GHC.IORef hiding (atomicModifyIORef)
45 import qualified GHC.IORef
46 #if !defined(__PARALLEL_HASKELL__)
47 import GHC.Weak
48 #endif
49 #endif /* __GLASGOW_HASKELL__ */
50
51 #ifdef __NHC__
52 import NHC.IOExtras
53     ( IORef
54     , newIORef
55     , readIORef
56     , writeIORef
57     , excludeFinalisers
58     )
59 #endif
60
61 #if defined(__GLASGOW_HASKELL__) && !defined(__PARALLEL_HASKELL__)
62 -- |Make a 'Weak' pointer to an 'IORef', using the second argument as a finalizer
63 -- to run when 'IORef' is garbage-collected
64 mkWeakIORef :: IORef a -> IO () -> IO (Weak (IORef a))
65 mkWeakIORef r@(IORef (STRef r#)) f = IO $ \s ->
66   case mkWeak# r# r f s of (# s1, w #) -> (# s1, Weak w #)
67 #endif
68
69 -- |Mutate the contents of an 'IORef'
70 modifyIORef :: IORef a -> (a -> a) -> IO ()
71 modifyIORef ref f = readIORef ref >>= writeIORef ref . f
72
73
74 -- |Atomically modifies the contents of an 'IORef'.
75 --
76 -- This function is useful for using 'IORef' in a safe way in a multithreaded
77 -- program.  If you only have one 'IORef', then using 'atomicModifyIORef' to
78 -- access and modify it will prevent race conditions.
79 --
80 -- Extending the atomicity to multiple 'IORef's is problematic, so it
81 -- is recommended that if you need to do anything more complicated
82 -- then using 'Control.Concurrent.MVar.MVar' instead is a good idea.
83 --
84 atomicModifyIORef :: IORef a -> (a -> (a,b)) -> IO b
85 #if defined(__GLASGOW_HASKELL__)
86 atomicModifyIORef = GHC.IORef.atomicModifyIORef
87
88 #elif defined(__HUGS__)
89 atomicModifyIORef = plainModifyIORef    -- Hugs has no preemption
90   where plainModifyIORef r f = do
91                 a <- readIORef r
92                 case f a of (a',b) -> writeIORef r a' >> return b
93 #elif defined(__NHC__)
94 atomicModifyIORef r f =
95   excludeFinalisers $ do
96     a <- readIORef r
97     let (a',b) = f a
98     writeIORef r a'
99     return b
100 #endif
101
102 {- $memmodel
103
104   In a concurrent program, 'IORef' operations may appear out-of-order
105   to another thread, depending on the memory model of the underlying
106   processor architecture.  For example, on x86, loads can move ahead
107   of stores, so in the following example:
108
109 >  maybePrint :: IORef Bool -> IORef Bool -> IO ()
110 >  maybePrint myRef yourRef = do
111 >    writeIORef myRef True
112 >    yourVal <- readIORef yourRef
113 >    unless yourVal $ putStrLn "critical section"
114 >
115 >  main :: IO ()
116 >  main = do
117 >    r1 <- newIORef False
118 >    r2 <- newIORef False
119 >    forkIO $ maybePrint r1 r2
120 >    forkIO $ maybePrint r2 r1
121 >    threadDelay 1000000
122
123   it is possible that the string @"critical section"@ is printed
124   twice, even though there is no interleaving of the operations of the
125   two threads that allows that outcome.  The memory model of x86
126   allows 'readIORef' to happen before the earlier 'writeIORef'.
127
128   The implementation is required to ensure that reordering of memory
129   operations cannot cause type-correct code to go wrong.  In
130   particular, when inspecting the value read from an 'IORef', the
131   memory writes that created that value must have occurred from the
132   point of view of the current therad.
133
134   'atomicModifyIORef' acts as a barrier to reordering.  Multiple
135   'atomicModifyIORef' operations occur in strict program order.  An
136   'atomicModifyIORef' is never observed to take place ahead of any
137   earlier (in program order) 'IORef' operations, or after any later
138   'IORef' operations.
139
140 -}