[commit: ghc] master: Expose monotonic time from GHC.Event.Clock (1ba2851)

git at git.haskell.org git at git.haskell.org
Fri Oct 20 02:42:59 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/1ba28510e0731d91fcab560269c4ed5950d5e458/ghc

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

commit 1ba28510e0731d91fcab560269c4ed5950d5e458
Author: Tom Sydney Kerckhove <syd.kerckhove at gmail.com>
Date:   Wed Oct 18 16:24:46 2017 -0400

    Expose monotonic time from GHC.Event.Clock
    
    This diff exposes the monotonic time api from GHC.Event.Clock.
    
    This is necessary for future work on regression tests (#D4074) for
    the timeout problems (8684, for example) in #D4041, #D4011, #D4012
    
    Test Plan: Still builds ...
    
    Reviewers: nh2, bgamari, austin, hvr
    
    Reviewed By: bgamari
    
    Subscribers: rwbarton, thomie
    
    Differential Revision: https://phabricator.haskell.org/D4079


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

1ba28510e0731d91fcab560269c4ed5950d5e458
 libraries/base/GHC/{Event => }/Clock.hsc | 6 +++++-
 libraries/base/GHC/Event/TimerManager.hs | 2 +-
 libraries/base/base.cabal                | 2 +-
 3 files changed, 7 insertions(+), 3 deletions(-)

diff --git a/libraries/base/GHC/Event/Clock.hsc b/libraries/base/GHC/Clock.hsc
similarity index 90%
rename from libraries/base/GHC/Event/Clock.hsc
rename to libraries/base/GHC/Clock.hsc
index 7f98a03..6339dc0 100644
--- a/libraries/base/GHC/Event/Clock.hsc
+++ b/libraries/base/GHC/Clock.hsc
@@ -1,7 +1,7 @@
 {-# LANGUAGE Trustworthy #-}
 {-# LANGUAGE NoImplicitPrelude #-}
 
-module GHC.Event.Clock
+module GHC.Clock
     ( getMonotonicTime
     , getMonotonicTimeNSec
     ) where
@@ -11,11 +11,15 @@ import GHC.Real
 import Data.Word
 
 -- | Return monotonic time in seconds, since some unspecified starting point
+--
+-- @since 4.11.0.0
 getMonotonicTime :: IO Double
 getMonotonicTime = do w <- getMonotonicTimeNSec
                       return (fromIntegral w / 1000000000)
 
 -- | Return monotonic time in nanoseconds, since some unspecified starting point
+--
+-- @since 4.11.0.0
 foreign import ccall unsafe "getMonotonicNSec"
     getMonotonicTimeNSec :: IO Word64
 
diff --git a/libraries/base/GHC/Event/TimerManager.hs b/libraries/base/GHC/Event/TimerManager.hs
index f3dbb21..b7e7615 100644
--- a/libraries/base/GHC/Event/TimerManager.hs
+++ b/libraries/base/GHC/Event/TimerManager.hs
@@ -43,11 +43,11 @@ import Data.Foldable (sequence_)
 import Data.IORef (IORef, atomicModifyIORef', mkWeakIORef, newIORef, readIORef,
                    writeIORef)
 import GHC.Base
+import GHC.Clock (getMonotonicTimeNSec)
 import GHC.Conc.Signal (runHandlers)
 import GHC.Num (Num(..))
 import GHC.Real (fromIntegral)
 import GHC.Show (Show(..))
-import GHC.Event.Clock (getMonotonicTimeNSec)
 import GHC.Event.Control
 import GHC.Event.Internal (Backend, Event, evtRead, Timeout(..))
 import GHC.Event.Unique (Unique, UniqueSource, newSource, newUnique)
diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal
index 2b9d557..43c7882 100644
--- a/libraries/base/base.cabal
+++ b/libraries/base/base.cabal
@@ -204,6 +204,7 @@ Library
         GHC.Base
         GHC.ByteOrder
         GHC.Char
+        GHC.Clock
         GHC.Conc
         GHC.Conc.IO
         GHC.Conc.Signal
@@ -369,7 +370,6 @@ Library
         other-modules:
             GHC.Event.Arr
             GHC.Event.Array
-            GHC.Event.Clock
             GHC.Event.Control
             GHC.Event.EPoll
             GHC.Event.IntTable



More information about the ghc-commits mailing list