[commit: base] master: Use atomicModifyIORef' rather than atomicModifyIORef (86c5358)

Ian Lynagh igloo at earth.li
Sun Jun 9 14:15:50 CEST 2013


Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

https://github.com/ghc/packages-base/commit/86c53585835066f9d67c478744c59f3297a3e32c

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

commit 86c53585835066f9d67c478744c59f3297a3e32c
Author: Ian Lynagh <ian at well-typed.com>
Date:   Sat Jun 8 21:35:53 2013 +0100

    Use atomicModifyIORef' rather than atomicModifyIORef
    
    I don't know of any particular problems that this fixes, but as far as I
    know it's not wrong, and it should be safer.

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

 GHC/Event/Array.hs   |    7 +++----
 GHC/Event/Manager.hs |   10 +++++-----
 2 files changed, 8 insertions(+), 9 deletions(-)

diff --git a/GHC/Event/Array.hs b/GHC/Event/Array.hs
index fbc2a97..47f1bc8 100644
--- a/GHC/Event/Array.hs
+++ b/GHC/Event/Array.hs
@@ -26,7 +26,7 @@ module GHC.Event.Array
 
 import Control.Monad hiding (forM_)
 import Data.Bits ((.|.), shiftR)
-import Data.IORef (IORef, atomicModifyIORef, newIORef, readIORef, writeIORef)
+import Data.IORef (IORef, atomicModifyIORef', newIORef, readIORef, writeIORef)
 import Data.Maybe
 import Foreign.C.Types (CSize(..))
 import Foreign.ForeignPtr (ForeignPtr, withForeignPtr)
@@ -173,9 +173,8 @@ snoc (Array ref) e = do
 
 clear :: Storable a => Array a -> IO ()
 clear (Array ref) = do
-  !_ <- atomicModifyIORef ref $ \(AC es _ cap) ->
-        let e = AC es 0 cap in (e, e)
-  return ()
+  atomicModifyIORef' ref $ \(AC es _ cap) ->
+        (AC es 0 cap, ())
 
 forM_ :: Storable a => Array a -> (a -> IO ()) -> IO ()
 forM_ ary g = forHack ary g undefined
diff --git a/GHC/Event/Manager.hs b/GHC/Event/Manager.hs
index 16ca53a..a514915 100644
--- a/GHC/Event/Manager.hs
+++ b/GHC/Event/Manager.hs
@@ -53,7 +53,7 @@ import Control.Concurrent.MVar (MVar, modifyMVar, newMVar, readMVar, putMVar,
 import Control.Exception (onException)
 import Control.Monad ((=<<), forM_, liftM, when, replicateM, void)
 import Data.Bits ((.&.))
-import Data.IORef (IORef, atomicModifyIORef, mkWeakIORef, newIORef, readIORef,
+import Data.IORef (IORef, atomicModifyIORef', mkWeakIORef, newIORef, readIORef,
                    writeIORef)
 import Data.Maybe (Maybe(..))
 import Data.Monoid (mappend, mconcat, mempty)
@@ -176,7 +176,7 @@ newWith oneShot be = do
   state <- newIORef Created
   us <- newSource
   _ <- mkWeakIORef state $ do
-               st <- atomicModifyIORef state $ \s -> (Finished, s)
+               st <- atomicModifyIORef' state $ \s -> (Finished, s)
                when (st /= Finished) $ do
                  I.delete be
                  closeControl ctrl
@@ -209,14 +209,14 @@ registerControlFd mgr fd evs =
 -- | Asynchronously shuts down the event manager, if running.
 shutdown :: EventManager -> IO ()
 shutdown mgr = do
-  state <- atomicModifyIORef (emState mgr) $ \s -> (Dying, s)
+  state <- atomicModifyIORef' (emState mgr) $ \s -> (Dying, s)
   when (state == Running) $ sendDie (emControl mgr)
 
 -- | Asynchronously tell the thread executing the event
 -- manager loop to exit.
 release :: EventManager -> IO ()
 release EventManager{..} = do
-  state <- atomicModifyIORef emState $ \s -> (Releasing, s)
+  state <- atomicModifyIORef' emState $ \s -> (Releasing, s)
   when (state == Running) $ sendWakeup emControl
 
 finished :: EventManager -> IO Bool
@@ -240,7 +240,7 @@ cleanup EventManager{..} = do
 loop :: EventManager -> IO ()
 loop mgr at EventManager{..} = do
   void $ takeMVar emLock
-  state <- atomicModifyIORef emState $ \s -> case s of
+  state <- atomicModifyIORef' emState $ \s -> case s of
     Created -> (Running, s)
     Releasing -> (Running, s)
     _       -> (s, s)





More information about the ghc-commits mailing list