[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: Update and expand atomic modification Haddocks

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Sun Mar 26 17:02:58 UTC 2023



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


Commits:
17371c5b by David Feuer at 2023-03-26T13:02:50-04:00
Update and expand atomic modification Haddocks

* The documentation for `atomicModifyIORef` and `atomicModifyIORef'`
  were incomplete, and the documentation for `atomicModifyIORef` was
  out of date. Update and expand.

* Remove a useless lazy pattern match in the definition of
  `atomicModifyIORef`. The pair it claims to match lazily
  was already forced by `atomicModifyIORef2`.

- - - - -
7281d5aa by David Feuer at 2023-03-26T13:02:54-04:00
Document the constructor name for lists

Derived `Data` instances use raw infix constructor names when applicable.
The `Data.Data [a]` instance, if derived, would have a constructor name
of `":"`. However, it actually uses constructor name `"(:)"`. Document this
peculiarity.

See https://github.com/haskell/core-libraries-committee/issues/147

- - - - -


3 changed files:

- libraries/base/Data/Data.hs
- libraries/base/Data/IORef.hs
- libraries/base/GHC/IORef.hs


Changes:

=====================================
libraries/base/Data/Data.hs
=====================================
@@ -1136,7 +1136,10 @@ consConstr   = mkConstr listDataType "(:)" [] Infix
 listDataType :: DataType
 listDataType = mkDataType "Prelude.[]" [nilConstr,consConstr]
 
--- | @since 4.0.0.0
+-- | For historical reasons, the constructor name used for @(:)@ is
+-- @"(:)"@. In a derived instance, it would be @":"@.
+--
+-- @since 4.0.0.0
 instance Data a => Data [a] where
   gfoldl _ z []     = z []
   gfoldl f z (x:xs) = z (:) `f` x `f` xs


=====================================
libraries/base/Data/IORef.hs
=====================================
@@ -85,21 +85,45 @@ modifyIORef' ref f = do
 -- is recommended that if you need to do anything more complicated
 -- then using 'Control.Concurrent.MVar.MVar' instead is a good idea.
 --
--- 'atomicModifyIORef' does not apply the function strictly.  This is important
--- to know even if all you are doing is replacing the value.  For example, this
--- will leak memory:
+-- Conceptually,
 --
--- >ref <- newIORef '1'
--- >forever $ atomicModifyIORef ref (\_ -> ('2', ()))
+-- @
+-- atomicModifyIORef ref f = do
+--   -- Begin atomic block
+--   old <- 'readIORef' ref
+--   let r = f old
+--       new = fst r
+--   'writeIORef' ref new
+--   -- End atomic block
+--   case r of
+--     (_new, res) -> pure res
+-- @
 --
--- Use 'atomicModifyIORef'' or 'atomicWriteIORef' to avoid this problem.
+-- The actions in the section labeled \"atomic block\" are not subject to
+-- interference from other threads. In particular, it is impossible for the
+-- value in the 'IORef' to change between the 'readIORef' and 'writeIORef'
+-- invocations.
 --
--- This function imposes a memory barrier, preventing reordering;
--- see "Data.IORef#memmodel" for details.
+-- The user-supplied function is applied to the value stored in the 'IORef',
+-- yielding a new value to store in the 'IORef' and a value to return. After
+-- the new value is (lazily) stored in the 'IORef', @atomicModifyIORef@ forces
+-- the result pair, but does not force either component of the result. To force
+-- /both/ components, use 'atomicModifyIORef''.
+--
+-- Note that
+--
+-- @atomicModifyIORef ref (\_ -> undefined)@
+--
+-- will raise an exception in the calling thread, but will /also/
+-- install the bottoming value in the 'IORef', where it may be read by
+-- other threads.
+--
+-- This function imposes a memory barrier, preventing reordering around the
+-- \"atomic block\"; see "Data.IORef#memmodel" for details.
 --
 atomicModifyIORef :: IORef a -> (a -> (a,b)) -> IO b
 atomicModifyIORef ref f = do
-  (_old, ~(_new, res)) <- atomicModifyIORef2 ref f
+  (_old, (_new, res)) <- atomicModifyIORef2 ref f
   pure res
 
 -- | Variant of 'writeIORef'. The prefix "atomic" relates to a fact that


=====================================
libraries/base/GHC/IORef.hs
=====================================
@@ -134,9 +134,28 @@ atomicSwapIORef (IORef (STRef ref)) new = IO $ \s ->
 
 data Box a = Box a
 
--- | Strict version of 'Data.IORef.atomicModifyIORef'. This forces both
--- the value stored in the 'IORef' and the value returned. The new value
--- is installed in the 'IORef' before the returned value is forced.
+-- | A strict version of 'Data.IORef.atomicModifyIORef'.  This forces both the
+-- value stored in the 'IORef' and the value returned.
+--
+-- Conceptually,
+--
+-- @
+-- atomicModifyIORef' ref f = do
+--   -- Begin atomic block
+--   old <- 'readIORef' ref
+--   let r = f old
+--       new = fst r
+--   'writeIORef' ref new
+--   -- End atomic block
+--   case r of
+--     (!_new, !res) -> pure res
+-- @
+--
+-- The actions in the \"atomic block\" are not subject to interference
+-- by other threads. In particular, the value in the 'IORef' cannot
+-- change between the 'readIORef' and 'writeIORef' invocations.
+--
+-- The new value is installed in the 'IORef' before either value is forced.
 -- So
 --
 -- @atomicModifyIORef' ref (\x -> (x+1, undefined))@
@@ -144,8 +163,18 @@ 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.
+-- @atomicModifyIORef' ref (\x -> (undefined, x))@
+--
+-- and
+--
+-- @atomicModifyIORef' ref (\_ -> undefined)@
+--
+-- will each raise an exception in the calling thread, but will /also/
+-- install the bottoming value in the 'IORef', where it may be read by
+-- other threads.
+--
+-- This function imposes a memory barrier, preventing reordering around
+-- the \"atomic block\"; see "Data.IORef#memmodel" for details.
 --
 -- @since 4.6.0.0
 atomicModifyIORef' :: IORef a -> (a -> (a,b)) -> IO b



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/31e40fdf2ed3f56f710afe96da7db1ed7b4e21cb...7281d5aa8e7acdae876fab25a27f839efebb80f2

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/31e40fdf2ed3f56f710afe96da7db1ed7b4e21cb...7281d5aa8e7acdae876fab25a27f839efebb80f2
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/20230326/d57e5289/attachment-0001.html>


More information about the ghc-commits mailing list