Skip to content

Commit

Permalink
Replace all atomicModifyIORef calls in GHC.Event.TimerManager
Browse files Browse the repository at this point in the history
with atomicModifyIORef' calls. I'm not sure if it was causing any
problems, but I don't think there's any reason they couldn't be
strict, and it's safer this way.
  • Loading branch information
Ian Lynagh committed Jun 8, 2013
1 parent 13ac46d commit 9450515
Showing 1 changed file with 5 additions and 5 deletions.
10 changes: 5 additions & 5 deletions GHC/Event/TimerManager.hs
Expand Up @@ -39,7 +39,7 @@ module GHC.Event.TimerManager

import Control.Exception (finally)
import Control.Monad ((=<<), liftM, sequence_, when)
import Data.IORef (IORef, atomicModifyIORef, atomicModifyIORef', mkWeakIORef, newIORef, readIORef,
import Data.IORef (IORef, atomicModifyIORef', mkWeakIORef, newIORef, readIORef,
writeIORef)
import Data.Maybe (Maybe(..))
import Data.Monoid (mempty)
Expand Down Expand Up @@ -149,7 +149,7 @@ newWith 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
Expand All @@ -166,7 +166,7 @@ newWith be = do
-- | Asynchronously shuts down the event manager, if running.
shutdown :: TimerManager -> IO ()
shutdown mgr = do
state <- atomicModifyIORef (emState mgr) $ \s -> (Dying, s)
state <- atomicModifyIORef' (emState mgr) $ \s -> (Dying, s)
when (state == Running) $ sendDie (emControl mgr)

finished :: TimerManager -> IO Bool
Expand All @@ -188,7 +188,7 @@ cleanup mgr = do
-- closes all of its control resources when it finishes.
loop :: TimerManager -> IO ()
loop mgr = do
state <- atomicModifyIORef (emState mgr) $ \s -> case s of
state <- atomicModifyIORef' (emState mgr) $ \s -> case s of
Created -> (Running, s)
_ -> (s, s)
case state of
Expand All @@ -214,7 +214,7 @@ step mgr = do
mkTimeout :: IO Timeout
mkTimeout = do
now <- getMonotonicTime
(expired, timeout) <- atomicModifyIORef (emTimeouts mgr) $ \tq ->
(expired, timeout) <- atomicModifyIORef' (emTimeouts mgr) $ \tq ->
let (expired, tq') = Q.atMost now tq
timeout = case Q.minView tq' of
Nothing -> Forever
Expand Down

0 comments on commit 9450515

Please sign in to comment.