[commit: base] master: Rename atomicReadMVar and friends to readMVar, replacing old readMVar. (abe8151)

Edward Z. Yang ezyang at ghc.haskell.org
Sun Jul 14 23:33:50 CEST 2013


Repository : http://darcs.haskell.org/ghc.git/

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/abe81515ffc7d33c89bf64ebe000e653a3ef29aa

>---------------------------------------------------------------

commit abe81515ffc7d33c89bf64ebe000e653a3ef29aa
Author: Edward Z. Yang <ezyang at mit.edu>
Date:   Fri Jul 12 18:12:44 2013 -0700

    Rename atomicReadMVar and friends to readMVar, replacing old readMVar.
    
    Signed-off-by: Edward Z. Yang <ezyang at mit.edu>

>---------------------------------------------------------------

 Control/Concurrent/MVar.hs |   21 +++------------------
 GHC/MVar.hs                |   38 +++++++++++++++++++++++++++-----------
 2 files changed, 30 insertions(+), 29 deletions(-)

diff --git a/Control/Concurrent/MVar.hs b/Control/Concurrent/MVar.hs
index 0b3a081..bfe72a8 100644
--- a/Control/Concurrent/MVar.hs
+++ b/Control/Concurrent/MVar.hs
@@ -142,8 +142,7 @@ module Control.Concurrent.MVar
         , modifyMVarMasked_
         , modifyMVarMasked
 #ifndef __HUGS__
-        , atomicReadMVar
-        , tryAtomicReadMVar
+        , tryReadMVar
         , mkWeakMVar
         , addMVarFinalizer
 #endif
@@ -157,8 +156,8 @@ import Hugs.ConcBase ( MVar, newEmptyMVar, newMVar, takeMVar, putMVar,
 
 #ifdef __GLASGOW_HASKELL__
 import GHC.MVar ( MVar(..), newEmptyMVar, newMVar, takeMVar, putMVar,
-                  tryTakeMVar, tryPutMVar, isEmptyMVar, atomicReadMVar,
-                  tryAtomicReadMVar
+                  tryTakeMVar, tryPutMVar, isEmptyMVar, readMVar,
+                  tryReadMVar
                 )
 import qualified GHC.MVar
 import GHC.Weak
@@ -173,20 +172,6 @@ import Prelude
 import Control.Exception.Base
 
 {-|
-  This is a combination of 'takeMVar' and 'putMVar'; ie. it takes the value
-  from the 'MVar', puts it back, and also returns it.  This function
-  is atomic only if there are no other producers (i.e. threads calling
-  'putMVar') for this 'MVar'.  Note: a 'tryTakeMVar' may temporarily
-  see the 'MVar' as empty while a read is occurring.
--}
-readMVar :: MVar a -> IO a
-readMVar m =
-  mask_ $ do
-    a <- takeMVar m
-    putMVar m a
-    return a
-
-{-|
   Take a value from an 'MVar', put a new value into the 'MVar' and
   return the value taken. This function is atomic only if there are
   no other producers for this 'MVar'.
diff --git a/GHC/MVar.hs b/GHC/MVar.hs
index 5e819a2..45edec8 100644
--- a/GHC/MVar.hs
+++ b/GHC/MVar.hs
@@ -23,11 +23,11 @@ module GHC.MVar (
         , newMVar
         , newEmptyMVar
         , takeMVar
-        , atomicReadMVar
+        , readMVar
         , putMVar
         , tryTakeMVar
         , tryPutMVar
-        , tryAtomicReadMVar
+        , tryReadMVar
         , isEmptyMVar
         , addMVarFinalizer
     ) where
@@ -91,13 +91,29 @@ takeMVar :: MVar a -> IO a
 takeMVar (MVar mvar#) = IO $ \ s# -> takeMVar# mvar# s#
 
 -- |Atomically read the contents of an 'MVar'.  If the 'MVar' is
--- currently empty, 'atomicReadMVar' will wait until its full.
--- 'atomicReadMVar' is guaranteed to receive the next 'putMVar'.
+-- currently empty, 'readMVar' will wait until its full.
+-- 'readMVar' is guaranteed to receive the next 'putMVar'.
 --
--- 'atomicReadMVar' is multiple-wakeup, so when multiple readers are
+-- 'readMVar' is multiple-wakeup, so when multiple readers are
 -- blocked on an 'MVar', all of them are woken up at the same time.
-atomicReadMVar :: MVar a -> IO a
-atomicReadMVar (MVar mvar#) = IO $ \ s# -> atomicReadMVar# mvar# s#
+--
+-- /Compatibility note:/ Prior to base 4.7, 'readMVar' was a combination
+-- of 'takeMVar' and 'putMVar'.  This mean that in the presence of
+-- other threads attempting to 'putMVar', 'readMVar' could block.
+-- Furthermore, 'readMVar' would not be serviced immediately if there
+-- were already pending thread blocked on 'takeMVar'.  The old behavior
+-- can be recovered by implementing 'readMVar as follows:
+--
+-- @
+--  readMVar :: MVar a -> IO a
+--  readMVar m =
+--    mask_ $ do
+--      a <- takeMVar m
+--      putMVar m a
+--      return a
+-- @
+readMVar :: MVar a -> IO a
+readMVar (MVar mvar#) = IO $ \ s# -> readMVar# mvar# s#
 
 -- |Put a value into an 'MVar'.  If the 'MVar' is currently full,
 -- 'putMVar' will wait until it becomes empty.
@@ -137,12 +153,12 @@ tryPutMVar (MVar mvar#) x = IO $ \ s# ->
         (# s, 0# #) -> (# s, False #)
         (# s, _  #) -> (# s, True #)
 
--- |A non-blocking version of 'atomicReadMVar'.  The 'tryAtomicReadMVar' function
+-- |A non-blocking version of 'readMVar'.  The 'tryReadMVar' function
 -- returns immediately, with 'Nothing' if the 'MVar' was empty, or
 -- @'Just' a@ if the 'MVar' was full with contents @a at .
-tryAtomicReadMVar :: MVar a -> IO (Maybe a)
-tryAtomicReadMVar (MVar m) = IO $ \ s ->
-    case tryAtomicReadMVar# m s of
+tryReadMVar :: MVar a -> IO (Maybe a)
+tryReadMVar (MVar m) = IO $ \ s ->
+    case tryReadMVar# m s of
         (# s', 0#, _ #) -> (# s', Nothing #)      -- MVar is empty
         (# s', _,  a #) -> (# s', Just a  #)      -- MVar is full
 






More information about the ghc-commits mailing list