[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: Extend documentation for Data.IORef

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Sun Nov 20 12:18:57 UTC 2022



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
a73f9044 by Bodigrim at 2022-11-20T07:18:50-05:00
Extend documentation for Data.IORef

- - - - -
2d4b06eb by Simon Peyton Jones at 2022-11-20T07:18:51-05:00
Buglet in GHC.Tc.Module.checkBootTyCon

This lurking bug used the wrong function to compare two
types in GHC.Tc.Module.checkBootTyCon

It's hard to trigger the bug, which only came up during
!9343, so there's no regression test in this MR.

- - - - -


3 changed files:

- compiler/GHC/Tc/Module.hs
- libraries/base/Data/IORef.hs
- libraries/base/GHC/IORef.hs


Changes:

=====================================
compiler/GHC/Tc/Module.hs
=====================================
@@ -1096,6 +1096,7 @@ checkBootTyCon is_boot tc1 tc2
        -- Order of pattern matching matters.
        subDM _ Nothing _ = True
        subDM _ _ Nothing = False
+
        -- If the hsig wrote:
        --
        --   f :: a -> a
@@ -1103,11 +1104,14 @@ checkBootTyCon is_boot tc1 tc2
        --
        -- this should be validly implementable using an old-fashioned
        -- vanilla default method.
-       subDM t1 (Just (_, GenericDM t2)) (Just (_, VanillaDM))
-        = eqTypeX env t1 t2
+       subDM t1 (Just (_, GenericDM gdm_t1)) (Just (_, VanillaDM))
+        = eqType t1 gdm_t1   -- Take care (#22476).  Both t1 and gdm_t1 come
+                             -- from tc1, so use eqType, and /not/ eqTypeX
+
        -- This case can occur when merging signatures
        subDM t1 (Just (_, VanillaDM)) (Just (_, GenericDM t2))
         = eqTypeX env t1 t2
+
        subDM _ (Just (_, VanillaDM)) (Just (_, VanillaDM)) = True
        subDM _ (Just (_, GenericDM t1)) (Just (_, GenericDM t2))
         = eqTypeX env t1 t2


=====================================
libraries/base/Data/IORef.hs
=====================================
@@ -46,7 +46,9 @@ mkWeakIORef :: IORef a -> IO () -> IO (Weak (IORef a))
 mkWeakIORef r@(IORef (STRef r#)) (IO finalizer) = IO $ \s ->
     case mkWeak# r# r finalizer s of (# s1, w #) -> (# s1, Weak w #)
 
--- |Mutate the contents of an 'IORef'.
+-- |Mutate the contents of an 'IORef', combining 'readIORef' and 'writeIORef'.
+-- This is not an atomic update, consider using 'atomicModifyIORef' when
+-- operating in a multithreaded environment.
 --
 -- Be warned that 'modifyIORef' does not apply the function strictly.  This
 -- means if the program calls 'modifyIORef' many times, but seldom uses the
@@ -62,7 +64,9 @@ mkWeakIORef r@(IORef (STRef r#)) (IO finalizer) = IO $ \s ->
 modifyIORef :: IORef a -> (a -> a) -> IO ()
 modifyIORef ref f = readIORef ref >>= writeIORef ref . f
 
--- |Strict version of 'modifyIORef'
+-- |Strict version of 'modifyIORef'.
+-- This is not an atomic update, consider using 'atomicModifyIORef'' when
+-- operating in a multithreaded environment.
 --
 -- @since 4.6.0.0
 modifyIORef' :: IORef a -> (a -> a) -> IO ()
@@ -90,13 +94,18 @@ modifyIORef' ref f = do
 --
 -- Use 'atomicModifyIORef'' or 'atomicWriteIORef' to avoid this problem.
 --
+-- This function imposes a memory barrier, preventing reordering;
+-- see "Data.IORef#memmodel" for details.
+--
 atomicModifyIORef :: IORef a -> (a -> (a,b)) -> IO 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.
+-- | Variant of 'writeIORef'. The prefix "atomic" relates to a fact that
+-- it imposes a reordering barrier, similar to 'atomicModifyIORef'.
+-- Such a write will not be reordered with other reads
+-- or writes even on CPUs with weak memory model.
 --
 -- @since 4.6.0.0
 atomicWriteIORef :: IORef a -> a -> IO ()
@@ -105,11 +114,15 @@ atomicWriteIORef ref a = do
   pure ()
 
 {- $memmodel
+  #memmodel#
+
+  Most modern CPU achitectures (e.g. x86/64, ARM) have a memory model which allows
+  threads to reorder reads with earlier writes to different locations,
+  e.g. see <https://www.intel.com/content/www/us/en/developer/articles/technical/intel-sdm.html the x86/64 architecture manual>,
+  8.2.3.4 Loads May Be Reordered with Earlier Stores to Different Locations.
 
-  In a concurrent program, 'IORef' operations may appear out-of-order
-  to another thread, depending on the memory model of the underlying
-  processor architecture.  For example, on x86, loads can move ahead
-  of stores, so in the following example:
+  Because of that, in a concurrent program, 'IORef' operations may appear out-of-order
+  to another thread. In the following example:
 
   > import Data.IORef
   > import Control.Monad (unless)
@@ -131,20 +144,23 @@ atomicWriteIORef ref a = do
 
   it is possible that the string @"critical section"@ is printed
   twice, even though there is no interleaving of the operations of the
-  two threads that allows that outcome.  The memory model of x86
+  two threads that allows that outcome.  The memory model of x86/64
   allows 'readIORef' to happen before the earlier 'writeIORef'.
 
+  The ARM memory order model is typically even weaker than x86/64, allowing
+  any reordering of reads and writes as long as they are independent
+  from the point of view of the current thread.
+
   The implementation is required to ensure that reordering of memory
   operations cannot cause type-correct code to go wrong.  In
   particular, when inspecting the value read from an 'IORef', the
   memory writes that created that value must have occurred from the
   point of view of the current thread.
 
-  'atomicModifyIORef' acts as a barrier to reordering.  Multiple
-  'atomicModifyIORef' operations occur in strict program order.  An
-  'atomicModifyIORef' is never observed to take place ahead of any
+  'atomicWriteIORef', 'atomicModifyIORef' and 'atomicModifyIORef'' act
+  as a barrier to reordering. Multiple calls to these functions
+  occur in strict program order, never taking place ahead of any
   earlier (in program order) 'IORef' operations, or after any later
   'IORef' operations.
 
 -}
-


=====================================
libraries/base/GHC/IORef.hs
=====================================
@@ -32,7 +32,27 @@ import GHC.IO
 -- ---------------------------------------------------------------------------
 -- IORefs
 
--- |A mutable variable in the 'IO' monad
+-- |A mutable variable in the 'IO' monad.
+--
+-- >>> import Data.IORef
+-- >>> r <- newIORef 0
+-- >>> readIORef r
+-- 0
+-- >>> writeIORef r 1
+-- >>> readIORef r
+-- 1
+-- >>> atomicWriteIORef r 2
+-- >>> readIORef r
+-- 2
+-- >>> modifyIORef' r (+ 1)
+-- >>> readIORef r
+-- 3
+-- >>> atomicModifyIORef' r (\a -> (a + 1, ()))
+-- >>> readIORef r
+-- 4
+--
+-- See also 'Data.STRef.STRef' and 'Control.Concurrent.MVar.MVar'.
+--
 newtype IORef a = IORef (STRef RealWorld a)
   deriving Eq
   -- ^ Pointer equality.
@@ -43,11 +63,19 @@ newtype IORef a = IORef (STRef RealWorld a)
 newIORef    :: a -> IO (IORef a)
 newIORef v = stToIO (newSTRef v) >>= \ var -> return (IORef var)
 
--- |Read the value of an 'IORef'
+-- |Read the value of an 'IORef'.
+--
+-- Beware that the CPU executing a thread can reorder reads or writes
+-- to independent locations. See "Data.IORef#memmodel" for more details.
 readIORef   :: IORef a -> IO a
 readIORef  (IORef var) = stToIO (readSTRef var)
 
--- |Write a new value into an 'IORef'
+-- |Write a new value into an 'IORef'.
+--
+-- This function does not create a memory barrier and can be reordered
+-- with other independent reads and writes within a thread, which may cause issues
+-- for multithreaded execution. In these cases, consider using 'Data.IORef.atomicWriteIORef'
+-- instead. See "Data.IORef#memmodel" for more details.
 writeIORef  :: IORef a -> a -> IO ()
 writeIORef (IORef var) v = stToIO (writeSTRef var v)
 
@@ -116,6 +144,9 @@ data Box a = Box a
 -- will increment the 'IORef' and then throw an exception in the calling
 -- thread.
 --
+-- This function imposes a memory barrier, preventing reordering;
+-- see "Data.IORef#memmodel" for details.
+--
 -- @since 4.6.0.0
 atomicModifyIORef' :: IORef a -> (a -> (a,b)) -> IO b
 -- See Note [atomicModifyIORef' definition]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5b2b89bae4f5ab9dc2971814169870190e2eeffd...2d4b06ebd34427f711dda87a3b60ba69e5637243

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5b2b89bae4f5ab9dc2971814169870190e2eeffd...2d4b06ebd34427f711dda87a3b60ba69e5637243
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20221120/fa482abc/attachment-0001.html>


More information about the ghc-commits mailing list