[commit: base] master: Remove uses of RecordWildCards in GHC.Event.TimerManager (1f81187)

Ian Lynagh igloo at earth.li
Sat Jun 8 20:14:18 CEST 2013


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

On branch  : master

https://github.com/ghc/packages-base/commit/1f81187e63dcd4f160cfd1ce62efc4b1d26603dc

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

commit 1f81187e63dcd4f160cfd1ce62efc4b1d26603dc
Author: Ian Lynagh <ian at well-typed.com>
Date:   Sat Jun 8 18:54:23 2013 +0100

    Remove uses of RecordWildCards in GHC.Event.TimerManager

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

 GHC/Event/TimerManager.hs |   21 ++++++++++-----------
 1 files changed, 10 insertions(+), 11 deletions(-)

diff --git a/GHC/Event/TimerManager.hs b/GHC/Event/TimerManager.hs
index 8a519df..b581891 100644
--- a/GHC/Event/TimerManager.hs
+++ b/GHC/Event/TimerManager.hs
@@ -3,7 +3,6 @@
            , CPP
            , ExistentialQuantification
            , NoImplicitPrelude
-           , RecordWildCards
            , TypeSynonymInstances
            , FlexibleInstances
   #-}
@@ -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
@@ -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 at 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
@@ -203,10 +202,10 @@ loop mgr at TimerManager{..} = do
             when running $ go q'
 
 step :: TimerManager -> TimeoutQueue -> IO (Bool, TimeoutQueue)
-step mgr at 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
 
@@ -215,7 +214,7 @@ step mgr at 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





More information about the ghc-commits mailing list