1{-# LANGUAGE Unsafe #-}
2{-# LANGUAGE NoImplicitPrelude, MagicHash #-}
3{-# LANGUAGE UnboxedTuples #-}
4{-# LANGUAGE BangPatterns #-}
5{-# OPTIONS_HADDOCK not-home #-}
6
7-----------------------------------------------------------------------------
8-- |
9-- Module      :  GHC.IORef
10-- Copyright   :  (c) The University of Glasgow 2008
11-- License     :  see libraries/base/LICENSE
12--
13-- Maintainer  :  cvs-ghc@haskell.org
14-- Stability   :  internal
15-- Portability :  non-portable (GHC Extensions)
16--
17-- The IORef type
18--
19-----------------------------------------------------------------------------
20
21module GHC.IORef (
22        IORef(..),
23        newIORef, readIORef, writeIORef, atomicModifyIORef2Lazy,
24        atomicModifyIORef2, atomicModifyIORefLazy_, atomicModifyIORef'_,
25        atomicModifyIORefP, atomicSwapIORef, atomicModifyIORef'
26    ) where
27
28import GHC.Base
29import GHC.STRef
30import GHC.IO
31
32-- ---------------------------------------------------------------------------
33-- IORefs
34
35-- |A mutable variable in the 'IO' monad
36newtype IORef a = IORef (STRef RealWorld a)
37  deriving Eq
38  -- ^ Pointer equality.
39  --
40  -- @since 4.0.0.0
41
42-- |Build a new 'IORef'
43newIORef    :: a -> IO (IORef a)
44newIORef v = stToIO (newSTRef v) >>= \ var -> return (IORef var)
45
46-- |Read the value of an 'IORef'
47readIORef   :: IORef a -> IO a
48readIORef  (IORef var) = stToIO (readSTRef var)
49
50-- |Write a new value into an 'IORef'
51writeIORef  :: IORef a -> a -> IO ()
52writeIORef (IORef var) v = stToIO (writeSTRef var v)
53
54-- Atomically apply a function to the contents of an 'IORef',
55-- installing its first component in the 'IORef' and returning
56-- the old contents and the result of applying the function.
57-- The result of the function application (the pair) is not forced.
58-- As a result, this can lead to memory leaks. It is generally better
59-- to use 'atomicModifyIORef2'.
60atomicModifyIORef2Lazy :: IORef a -> (a -> (a,b)) -> IO (a, (a, b))
61atomicModifyIORef2Lazy (IORef (STRef r#)) f =
62  IO (\s -> case atomicModifyMutVar2# r# f s of
63              (# s', old, res #) -> (# s', (old, res) #))
64
65-- Atomically apply a function to the contents of an 'IORef',
66-- installing its first component in the 'IORef' and returning
67-- the old contents and the result of applying the function.
68-- The result of the function application (the pair) is forced,
69-- but neither of its components is.
70atomicModifyIORef2 :: IORef a -> (a -> (a,b)) -> IO (a, (a, b))
71atomicModifyIORef2 ref f = do
72  r@(_old, (_new, _res)) <- atomicModifyIORef2Lazy ref f
73  return r
74
75-- | A version of 'Data.IORef.atomicModifyIORef' that forces
76-- the (pair) result of the function.
77atomicModifyIORefP :: IORef a -> (a -> (a,b)) -> IO b
78atomicModifyIORefP ref f = do
79  (_old, (_,r)) <- atomicModifyIORef2 ref f
80  pure r
81
82-- | Atomically apply a function to the contents of an
83-- 'IORef' and return the old and new values. The result
84-- of the function is not forced. As this can lead to a
85-- memory leak, it is usually better to use `atomicModifyIORef'_`.
86atomicModifyIORefLazy_ :: IORef a -> (a -> a) -> IO (a, a)
87atomicModifyIORefLazy_ (IORef (STRef ref)) f = IO $ \s ->
88  case atomicModifyMutVar_# ref f s of
89    (# s', old, new #) -> (# s', (old, new) #)
90
91-- | Atomically apply a function to the contents of an
92-- 'IORef' and return the old and new values. The result
93-- of the function is forced.
94atomicModifyIORef'_ :: IORef a -> (a -> a) -> IO (a, a)
95atomicModifyIORef'_ ref f = do
96  (old, !new) <- atomicModifyIORefLazy_ ref f
97  return (old, new)
98
99-- | Atomically replace the contents of an 'IORef', returning
100-- the old contents.
101atomicSwapIORef :: IORef a -> a -> IO a
102-- Bad implementation! This will be a primop shortly.
103atomicSwapIORef (IORef (STRef ref)) new = IO $ \s ->
104  case atomicModifyMutVar2# ref (\_old -> Box new) s of
105    (# s', old, Box _new #) -> (# s', old #)
106
107data Box a = Box a
108
109-- | Strict version of 'Data.IORef.atomicModifyIORef'. This forces both
110-- the value stored in the 'IORef' and the value returned. The new value
111-- is installed in the 'IORef' before the returned value is forced.
112-- So
113--
114-- @atomicModifyIORef' ref (\x -> (x+1, undefined))@
115--
116-- will increment the 'IORef' and then throw an exception in the calling
117-- thread.
118--
119-- @since 4.6.0.0
120atomicModifyIORef' :: IORef a -> (a -> (a,b)) -> IO b
121-- See Note [atomicModifyIORef' definition]
122atomicModifyIORef' ref f = do
123  (_old, (_new, !res)) <- atomicModifyIORef2 ref $
124    \old -> case f old of
125       r@(!_new, _res) -> r
126  pure res
127
128-- Note [atomicModifyIORef' definition]
129-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
130--
131-- atomicModifyIORef' was historically defined
132--
133--    atomicModifyIORef' ref f = do
134--        b <- atomicModifyIORef ref $ \a ->
135--                case f a of
136--                    v@(a',_) -> a' `seq` v
137--        b `seq` return b
138--
139-- The most obvious definition, now that we have atomicModifyMutVar2#,
140-- would be
141--
142--    atomicModifyIORef' ref f = do
143--      (_old, (!_new, !res)) <- atomicModifyIORef2 ref f
144--      pure res
145--
146-- Why do we force the new value on the "inside" instead of afterwards?
147-- I initially thought the latter would be okay, but then I realized
148-- that if we write
149--
150--   atomicModifyIORef' ref $ \x -> (x + 5, x - 5)
151--
152-- then we'll end up building a pair of thunks to calculate x + 5
153-- and x - 5. That's no good! With the more complicated definition,
154-- we avoid this problem; the result pair is strict in the new IORef
155-- contents. Of course, if the function passed to atomicModifyIORef'
156-- doesn't inline, we'll build a closure for it. But that was already
157-- true for the historical definition of atomicModifyIORef' (in terms
158-- of atomicModifyIORef), so we shouldn't lose anything. Note that
159-- in keeping with the historical behavior, we *don't* propagate the
160-- strict demand on the result inwards. In particular,
161--
162--   atomicModifyIORef' ref (\x -> (x + 1, undefined))
163--
164-- will increment the IORef and throw an exception; it will not
165-- install an undefined value in the IORef.
166--
167-- A clearer version, in my opinion (but one quite incompatible with
168-- the traditional one) would only force the new IORef value and not
169-- the result. This version would have been relatively inefficient
170-- to implement using atomicModifyMutVar#, but is just fine now.
171