Skip to content

Commit

Permalink
Remove uses of RecordWildCards in GHC.Event.TimerManager
Browse files Browse the repository at this point in the history
  • Loading branch information
Ian Lynagh committed Jun 8, 2013
1 parent ddbe37f commit 1f81187
Showing 1 changed file with 10 additions and 11 deletions.
21 changes: 10 additions & 11 deletions GHC/Event/TimerManager.hs
Expand Up @@ -3,7 +3,6 @@
, CPP
, ExistentialQuantification
, NoImplicitPrelude
, RecordWildCards
, TypeSynonymInstances
, FlexibleInstances
#-}
Expand Down Expand Up @@ -174,10 +173,10 @@ finished :: TimerManager -> IO Bool
finished mgr = (== Finished) `liftM` readIORef (emState mgr)

cleanup :: TimerManager -> IO ()
cleanup TimerManager{..} = do
writeIORef emState Finished
I.delete emBackend
closeControl emControl
cleanup mgr = do
writeIORef (emState mgr) Finished
I.delete (emBackend mgr)
closeControl (emControl mgr)

------------------------------------------------------------------------
-- Event loop
Expand All @@ -188,8 +187,8 @@ cleanup TimerManager{..} = do
-- /Note/: This loop can only be run once per 'TimerManager', as it
-- closes all of its control resources when it finishes.
loop :: TimerManager -> IO ()
loop mgr@TimerManager{..} = do
state <- atomicModifyIORef emState $ \s -> case s of
loop mgr = do
state <- atomicModifyIORef (emState mgr) $ \s -> case s of
Created -> (Running, s)
_ -> (s, s)
case state of
Expand All @@ -203,10 +202,10 @@ loop mgr@TimerManager{..} = do
when running $ go q'

step :: TimerManager -> TimeoutQueue -> IO (Bool, TimeoutQueue)
step mgr@TimerManager{..} tq = do
step mgr tq = do
(timeout, q') <- mkTimeout tq
_ <- I.poll emBackend (Just timeout) (handleControlEvent mgr)
state <- readIORef emState
_ <- I.poll (emBackend mgr) (Just timeout) (handleControlEvent mgr)
state <- readIORef (emState mgr)
state `seq` return (state == Running, q')
where

Expand All @@ -215,7 +214,7 @@ step mgr@TimerManager{..} tq = do
mkTimeout :: TimeoutQueue -> IO (Timeout, TimeoutQueue)
mkTimeout q = do
now <- getMonotonicTime
applyEdits <- atomicModifyIORef emTimeouts $ \f -> (id, f)
applyEdits <- atomicModifyIORef (emTimeouts mgr) $ \f -> (id, f)
let (expired, q'') = let q' = applyEdits q in q' `seq` Q.atMost now q'
sequence_ $ map Q.value expired
let timeout = case Q.minView q'' of
Expand Down

0 comments on commit 1f81187

Please sign in to comment.