1 {-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, UnboxedTuples #-}
3 -----------------------------------------------------------------------------
6 -- Copyright : (c) The University of Glasgow 2001
7 -- License : BSD-style (see the file libraries/base/LICENSE)
9 -- Maintainer : libraries@haskell.org
10 -- Stability : experimental
11 -- Portability : portable
13 -- Mutable references in the IO monad.
15 -----------------------------------------------------------------------------
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
27 #if !defined(__PARALLEL_HASKELL__) && defined(__GLASGOW_HASKELL__)
28 mkWeakIORef, -- :: IORef a -> IO () -> IO (Weak (IORef a))
36 #ifdef __GLASGOW_HASKELL__
40 import GHC.IORef hiding (atomicModifyIORef)
41 import qualified GHC.IORef
42 #if !defined(__PARALLEL_HASKELL__)
45 #endif /* __GLASGOW_HASKELL__ */
57 #if defined(__GLASGOW_HASKELL__) && !defined(__PARALLEL_HASKELL__)
58 -- |Make a 'Weak' pointer to an 'IORef', using the second argument as a finalizer
59 -- to run when 'IORef' is garbage-collected
60 mkWeakIORef :: IORef a -> IO () -> IO (Weak (IORef a))
61 mkWeakIORef r@(IORef (STRef r#)) f = IO $ \s ->
62 case mkWeak# r# r f s of (# s1, w #) -> (# s1, Weak w #)
65 -- |Mutate the contents of an 'IORef'
66 modifyIORef :: IORef a -> (a -> a) -> IO ()
67 modifyIORef ref f = readIORef ref >>= writeIORef ref . f
70 -- |Atomically modifies the contents of an 'IORef'.
72 -- This function is useful for using 'IORef' in a safe way in a multithreaded
73 -- program. If you only have one 'IORef', then using 'atomicModifyIORef' to
74 -- access and modify it will prevent race conditions.
76 -- Extending the atomicity to multiple 'IORef's is problematic, so it
77 -- is recommended that if you need to do anything more complicated
78 -- then using 'Control.Concurrent.MVar.MVar' instead is a good idea.
80 atomicModifyIORef :: IORef a -> (a -> (a,b)) -> IO b
81 #if defined(__GLASGOW_HASKELL__)
82 atomicModifyIORef = GHC.IORef.atomicModifyIORef
84 #elif defined(__HUGS__)
85 atomicModifyIORef = plainModifyIORef -- Hugs has no preemption
86 where plainModifyIORef r f = do
88 case f a of (a',b) -> writeIORef r a' >> return b
89 #elif defined(__NHC__)
90 atomicModifyIORef r f =
91 excludeFinalisers $ do