summaryrefslogtreecommitdiff
path: root/libraries/base/Data/IORef.hs
diff options
context:
space:
mode:
Diffstat (limited to 'libraries/base/Data/IORef.hs')
-rw-r--r--libraries/base/Data/IORef.hs53
1 files changed, 24 insertions, 29 deletions
diff --git a/libraries/base/Data/IORef.hs b/libraries/base/Data/IORef.hs
index c6275f5433..44769268cf 100644
--- a/libraries/base/Data/IORef.hs
+++ b/libraries/base/Data/IORef.hs
@@ -1,5 +1,6 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples #-}
+{-# LANGUAGE BangPatterns #-}
-----------------------------------------------------------------------------
-- |
@@ -36,8 +37,7 @@ module Data.IORef
import GHC.Base
import GHC.STRef
-import GHC.IORef hiding (atomicModifyIORef)
-import qualified GHC.IORef
+import GHC.IORef
import GHC.Weak
-- |Make a 'Weak' pointer to an 'IORef', using the second argument as a finalizer
@@ -91,18 +91,9 @@ modifyIORef' ref f = do
-- Use 'atomicModifyIORef'' or 'atomicWriteIORef' to avoid this problem.
--
atomicModifyIORef :: IORef a -> (a -> (a,b)) -> IO b
-atomicModifyIORef = GHC.IORef.atomicModifyIORef
-
--- | Strict version of 'atomicModifyIORef'. This forces both the value stored
--- in the 'IORef' as well as the value returned.
---
--- @since 4.6.0.0
-atomicModifyIORef' :: IORef a -> (a -> (a,b)) -> IO b
-atomicModifyIORef' ref f = do
- b <- atomicModifyIORef ref $ \a ->
- case f a of
- v@(a',_) -> a' `seq` v
- b `seq` return b
+atomicModifyIORef ref f = do
+ (_old, ~(_new, res)) <- atomicModifyIORef2 ref f
+ pure res
-- | Variant of 'writeIORef' with the \"barrier to reordering\" property that
-- 'atomicModifyIORef' has.
@@ -110,8 +101,8 @@ atomicModifyIORef' ref f = do
-- @since 4.6.0.0
atomicWriteIORef :: IORef a -> a -> IO ()
atomicWriteIORef ref a = do
- x <- atomicModifyIORef ref (\_ -> (a, ()))
- x `seq` return ()
+ _ <- atomicSwapIORef ref a
+ pure ()
{- $memmodel
@@ -120,19 +111,23 @@ atomicWriteIORef ref a = do
processor architecture. For example, on x86, loads can move ahead
of stores, so in the following example:
-> maybePrint :: IORef Bool -> IORef Bool -> IO ()
-> maybePrint myRef yourRef = do
-> writeIORef myRef True
-> yourVal <- readIORef yourRef
-> unless yourVal $ putStrLn "critical section"
->
-> main :: IO ()
-> main = do
-> r1 <- newIORef False
-> r2 <- newIORef False
-> forkIO $ maybePrint r1 r2
-> forkIO $ maybePrint r2 r1
-> threadDelay 1000000
+ > import Data.IORef
+ > import Control.Monad (unless)
+ > import Control.Concurrent (forkIO, threadDelay)
+ >
+ > maybePrint :: IORef Bool -> IORef Bool -> IO ()
+ > maybePrint myRef yourRef = do
+ > writeIORef myRef True
+ > yourVal <- readIORef yourRef
+ > unless yourVal $ putStrLn "critical section"
+ >
+ > main :: IO ()
+ > main = do
+ > r1 <- newIORef False
+ > r2 <- newIORef False
+ > forkIO $ maybePrint r1 r2
+ > forkIO $ maybePrint r2 r1
+ > threadDelay 1000000
it is possible that the string @"critical section"@ is printed
twice, even though there is no interleaving of the operations of the