From 4aa74b95fb9c1d8451ea666a4c6a6fb6436c0f0f Mon Sep 17 00:00:00 2001
From: Ian Lynagh <igloo@earth.li>
Date: Sat, 22 Oct 2011 18:33:02 +0100
Subject: [PATCH] Use time (POSIXTime) rather than old-time (ClockTime)

---
 compiler/ghc.cabal.in           |    3 +++
 compiler/main/DriverPipeline.hs |   12 ++++++------
 compiler/main/Finder.lhs        |    4 ++--
 compiler/main/GHC.hs            |    4 ++--
 compiler/main/GhcMake.hs        |   20 ++++++++++----------
 compiler/main/HscTypes.lhs      |   10 +++++-----
 compiler/utils/Util.lhs         |   36 +++++++++++++++++++++++++++++-------
 7 files changed, 57 insertions(+), 32 deletions(-)

diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in
index 56d9538..1b8abd9 100755
--- a/compiler/ghc.cabal.in
+++ b/compiler/ghc.cabal.in
@@ -65,7 +65,10 @@ Library
         Build-Depends: directory  >= 1   && < 1.2,
                        process    >= 1   && < 1.2,
                        bytestring >= 0.9 && < 0.10,
+                       -- TODO: Should conditionally depend on old-time,
+                       -- depending on version of directory
                        old-time   >= 1   && < 1.1,
+                       time,
                        containers >= 0.1 && < 0.5,
                        array      >= 0.1 && < 0.4
 
diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs
index 8037cfb..202576a 100644
--- a/compiler/main/DriverPipeline.hs
+++ b/compiler/main/DriverPipeline.hs
@@ -193,7 +193,7 @@ compile' (nothingCompiler, interactiveCompiler, batchCompiler)
                                               (Just location)
                                               maybe_stub_o
                                   -- The object filename comes from the ModLocation
-                            o_time <- getModificationTime object_filename
+                            o_time <- getModificationPOSIXTime object_filename
                             return ([DotO object_filename], o_time)
                     
                     let linkable = LM unlinked_time this_mod hs_unlinked
@@ -356,13 +356,13 @@ linkingNeeded dflags linkables pkg_deps = do
         -- modification times on all of the objects and libraries, then omit
         -- linking (unless the -fforce-recomp flag was given).
   let exe_file = exeFileName dflags
-  e_exe_time <- tryIO $ getModificationTime exe_file
+  e_exe_time <- tryIO $ getModificationPOSIXTime exe_file
   case e_exe_time of
     Left _  -> return True
     Right t -> do
         -- first check object files and extra_ld_inputs
         extra_ld_inputs <- readIORef v_Ld_inputs
-        e_extra_times <- mapM (tryIO . getModificationTime) extra_ld_inputs
+        e_extra_times <- mapM (tryIO . getModificationPOSIXTime) extra_ld_inputs
         let (errs,extra_times) = splitEithers e_extra_times
         let obj_times =  map linkableTime linkables ++ extra_times
         if not (null errs) || any (t <) obj_times
@@ -378,7 +378,7 @@ linkingNeeded dflags linkables pkg_deps = do
 
         pkg_libfiles <- mapM (uncurry findHSLib) pkg_hslibs
         if any isNothing pkg_libfiles then return True else do
-        e_lib_times <- mapM (tryIO . getModificationTime)
+        e_lib_times <- mapM (tryIO . getModificationPOSIXTime)
                           (catMaybes pkg_libfiles)
         let (lib_errs,lib_times) = splitEithers e_lib_times
         if not (null lib_errs) || any (t <) lib_times
@@ -901,7 +901,7 @@ runPhase (Hsc src_flavour) input_fn dflags0
   -- changed (which the compiler itself figures out).
   -- Setting source_unchanged to False tells the compiler that M.o is out of
   -- date wrt M.hs (or M.o doesn't exist) so we must recompile regardless.
-        src_timestamp <- io $ getModificationTime (basename <.> suff)
+        src_timestamp <- io $ getModificationPOSIXTime (basename <.> suff)
 
         let hsc_lang = hscTarget dflags
         source_unchanged <- io $
@@ -914,7 +914,7 @@ runPhase (Hsc src_flavour) input_fn dflags0
              else do o_file_exists <- doesFileExist o_file
                      if not o_file_exists
                         then return SourceModified       -- Need to recompile
-                        else do t2 <- getModificationTime o_file
+                        else do t2 <- getModificationPOSIXTime o_file
                                 if t2 > src_timestamp
                                   then return SourceUnmodified
                                   else return SourceModified
diff --git a/compiler/main/Finder.lhs b/compiler/main/Finder.lhs
index 3ac3a47..68f36fa 100644
--- a/compiler/main/Finder.lhs
+++ b/compiler/main/Finder.lhs
@@ -46,8 +46,8 @@ import Data.IORef       ( IORef, writeIORef, readIORef, atomicModifyIORef )
 import System.Directory
 import System.FilePath
 import Control.Monad
-import System.Time      ( ClockTime )
 import Data.List        ( partition )
+import Data.Time.Clock.POSIX
 
 
 type FileExt = String   -- Filename extension
@@ -528,7 +528,7 @@ findObjectLinkableMaybe mod locn
 
 -- Make an object linkable when we know the object file exists, and we know
 -- its modification time.
-findObjectLinkable :: Module -> FilePath -> ClockTime -> IO Linkable
+findObjectLinkable :: Module -> FilePath -> POSIXTime -> IO Linkable
 findObjectLinkable mod obj_fn obj_time = return (LM obj_time mod [DotO obj_fn])
   -- We used to look for _stub.o files here, but that was a bug (#706)
   -- Now GHC merges the stub.o into the main .o (#3687)
diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs
index 5e1eaac..f99ca2f 100644
--- a/compiler/main/GHC.hs
+++ b/compiler/main/GHC.hs
@@ -297,11 +297,11 @@ import Lexer
 import System.Directory ( doesFileExist, getCurrentDirectory )
 import Data.Maybe
 import Data.List	( find )
+import Data.Time.Clock.POSIX
 import Data.Typeable    ( Typeable )
 import Data.Word        ( Word8 )
 import Control.Monad
 import System.Exit	( exitWith, ExitCode(..) )
-import System.Time	( getClockTime )
 import Exception
 import Data.IORef
 import System.FilePath
@@ -806,7 +806,7 @@ compileToCore fn = do
 compileCoreToObj :: GhcMonad m => Bool -> CoreModule -> m ()
 compileCoreToObj simplify cm@(CoreModule{ cm_module = mName }) = do
   dflags      <- getSessionDynFlags
-  currentTime <- liftIO $ getClockTime
+  currentTime <- liftIO $ getPOSIXTime
   cwd         <- liftIO $ getCurrentDirectory
   modLocation <- liftIO $ mkHiOnlyModLocation dflags (hiSuf dflags) cwd
                    ((moduleNameSlashes . moduleName) mName)
diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs
index d27e524..63fe3e0 100644
--- a/compiler/main/GhcMake.hs
+++ b/compiler/main/GhcMake.hs
@@ -55,15 +55,15 @@ import UniqFM
 import qualified Data.Map as Map
 import qualified FiniteMap as Map( insertListWith)
 
-import System.Directory ( doesFileExist, getModificationTime )
+import System.Directory ( doesFileExist )
 import System.IO	( fixIO )
 import System.IO.Error	( isDoesNotExistError )
-import System.Time	( ClockTime )
 import System.FilePath
 import Control.Monad
 import Data.Maybe
 import Data.List
 import qualified Data.List as List
+import Data.Time.Clock.POSIX
 
 -- -----------------------------------------------------------------------------
 -- Loading the program
@@ -1193,7 +1193,7 @@ summariseFile
 	-> FilePath			-- source file name
 	-> Maybe Phase			-- start phase
         -> Bool                         -- object code allowed?
-	-> Maybe (StringBuffer,ClockTime)
+	-> Maybe (StringBuffer,POSIXTime)
 	-> IO ModSummary
 
 summariseFile hsc_env old_summaries file mb_phase obj_allowed maybe_buf
@@ -1207,10 +1207,10 @@ summariseFile hsc_env old_summaries file mb_phase obj_allowed maybe_buf
 		-- return the cached summary if the source didn't change
 	src_timestamp <- case maybe_buf of
 			   Just (_,t) -> return t
-			   Nothing    -> liftIO $ getModificationTime file
+			   Nothing    -> liftIO $ getModificationPOSIXTime file
 		-- The file exists; we checked in getRootSummary above.
 		-- If it gets removed subsequently, then this 
-		-- getModificationTime may fail, but that's the right
+		-- getModificationPOSIXTime may fail, but that's the right
 		-- behaviour.
 
 	if ms_hs_date old_summary == src_timestamp 
@@ -1244,7 +1244,7 @@ summariseFile hsc_env old_summaries file mb_phase obj_allowed maybe_buf
 
         src_timestamp <- case maybe_buf of
 			   Just (_,t) -> return t
-			   Nothing    -> liftIO $ getModificationTime file
+			   Nothing    -> liftIO $ getModificationPOSIXTime file
 			-- getMofificationTime may fail
 
         -- when the user asks to load a source file by name, we only
@@ -1278,7 +1278,7 @@ summariseModule
 	  -> IsBootInterface	-- True <=> a {-# SOURCE #-} import
 	  -> Located ModuleName	-- Imported module to be summarised
           -> Bool               -- object code allowed?
-	  -> Maybe (StringBuffer, ClockTime)
+	  -> Maybe (StringBuffer, POSIXTime)
 	  -> [ModuleName]		-- Modules to exclude
 	  -> IO (Maybe ModSummary)	-- Its new summary
 
@@ -1299,7 +1299,7 @@ summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod)
 	case maybe_buf of
 	   Just (_,t) -> check_timestamp old_summary location src_fn t
 	   Nothing    -> do
-		m <- tryIO (getModificationTime src_fn)
+		m <- tryIO (getModificationPOSIXTime src_fn)
 		case m of
 		   Right t -> check_timestamp old_summary location src_fn t
 		   Left e | isDoesNotExistError e -> find_it
@@ -1391,7 +1391,7 @@ summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod)
 			      ms_obj_date  = obj_timestamp }))
 
 
-getObjTimestamp :: ModLocation -> Bool -> IO (Maybe ClockTime)
+getObjTimestamp :: ModLocation -> Bool -> IO (Maybe POSIXTime)
 getObjTimestamp location is_boot
   = if is_boot then return Nothing
 	       else modificationTimeIfExists (ml_obj_file location)
@@ -1400,7 +1400,7 @@ getObjTimestamp location is_boot
 preprocessFile :: HscEnv
                -> FilePath
                -> Maybe Phase -- ^ Starting phase
-               -> Maybe (StringBuffer,ClockTime)
+               -> Maybe (StringBuffer,POSIXTime)
                -> IO (DynFlags, FilePath, StringBuffer)
 preprocessFile hsc_env src_fn mb_phase Nothing
   = do
diff --git a/compiler/main/HscTypes.lhs b/compiler/main/HscTypes.lhs
index c14544c..9294dcd 100644
--- a/compiler/main/HscTypes.lhs
+++ b/compiler/main/HscTypes.lhs
@@ -157,10 +157,10 @@ import ErrUtils
 import Util
 
 import System.FilePath
-import System.Time	( ClockTime )
 import Data.IORef
 import Data.Array       ( Array, array )
 import Data.Map         ( Map )
+import Data.Time.Clock.POSIX
 import Data.Word
 import Control.Monad    ( mplus, guard, liftM, when )
 import Exception
@@ -333,7 +333,7 @@ hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
 data Target = Target
       { targetId           :: TargetId  -- ^ module or filename
       , targetAllowObjCode :: Bool      -- ^ object code allowed?
-      , targetContents     :: Maybe (StringBuffer,ClockTime)
+      , targetContents     :: Maybe (StringBuffer,POSIXTime)
                                         -- ^ in-memory text buffer?
       }
 
@@ -1751,8 +1751,8 @@ data ModSummary
         ms_mod          :: Module,		-- ^ Identity of the module
 	ms_hsc_src      :: HscSource,		-- ^ The module source either plain Haskell, hs-boot or external core
         ms_location     :: ModLocation,		-- ^ Location of the various files belonging to the module
-        ms_hs_date      :: ClockTime,		-- ^ Timestamp of source file
-	ms_obj_date     :: Maybe ClockTime,	-- ^ Timestamp of object, if we have one
+        ms_hs_date      :: POSIXTime,		-- ^ Timestamp of source file
+	ms_obj_date     :: Maybe POSIXTime,	-- ^ Timestamp of object, if we have one
         ms_srcimps      :: [Located (ImportDecl RdrName)],	-- ^ Source imports of the module
         ms_textual_imps :: [Located (ImportDecl RdrName)],	-- ^ Non-source imports of the module from the module *text*
         ms_hspp_file    :: FilePath,		-- ^ Filename of preprocessed source file
@@ -2028,7 +2028,7 @@ stuff is the *dynamic* linker, and isn't present in a stage-1 compiler
 \begin{code}
 -- | Information we can use to dynamically link modules into the compiler
 data Linkable = LM {
-  linkableTime     :: ClockTime,	-- ^ Time at which this linkable was built
+  linkableTime     :: POSIXTime,	-- ^ Time at which this linkable was built
 					-- (i.e. when the bytecodes were produced,
 					--	 or the mod date on the files)
   linkableModule   :: Module,           -- ^ The linkable module itself
diff --git a/compiler/utils/Util.lhs b/compiler/utils/Util.lhs
index dccb52d..4372c50 100644
--- a/compiler/utils/Util.lhs
+++ b/compiler/utils/Util.lhs
@@ -74,6 +74,7 @@ module Util (
         -- * IO-ish utilities
         createDirectoryHierarchy,
         doesDirNameExist,
+        getModificationPOSIXTime,
         modificationTimeIfExists,
 
         global, consIORef, globalM,
@@ -107,11 +108,14 @@ import FastTypes
 #endif
 
 import Control.Monad    ( unless, liftM )
+import Data.Time.Clock.POSIX
 import System.IO.Error as IO ( isDoesNotExistError )
 import System.Directory ( doesDirectoryExist, createDirectory,
                           getModificationTime )
 import System.FilePath
-import System.Time      ( ClockTime )
+#if __GLASGOW_HASKELL__ < 703
+import System.Time      ( ClockTime(..) )
+#endif
 
 import Data.Char        ( isUpper, isAlphaNum, isSpace, chr, ord, isDigit )
 import Data.Ratio       ( (%) )
@@ -1020,15 +1024,33 @@ doesDirNameExist fpath = case takeDirectory fpath of
                          "" -> return True -- XXX Hack
                          _  -> doesDirectoryExist (takeDirectory fpath)
 
+-----------------------------------------------------------------------------
+-- backwards compatibility version of getModificationTime
+
+getModificationPOSIXTime :: FilePath -> IO POSIXTime
+#if __GLASGOW_HASKELL__ < 703
+getModificationPOSIXTime fp = do TOD secs _ <- getModificationTime fp
+                                 return $ realToFrac secs
+#else
+getModificationPOSIXTime = getModificationTime
+#endif
+
 -- --------------------------------------------------------------
 -- check existence & modification time at the same time
 
-modificationTimeIfExists :: FilePath -> IO (Maybe ClockTime)
-modificationTimeIfExists f = do
-  (do t <- getModificationTime f; return (Just t))
-        `catchIO` \e -> if isDoesNotExistError e
-                        then return Nothing
-                        else ioError e
+modificationTimeIfExists :: FilePath -> IO (Maybe POSIXTime)
+modificationTimeIfExists f =
+    (do t <- getModificationTime f
+#if __GLASGOW_HASKELL__ < 703
+        let t' = case t of
+                 TOD secs _ -> realToFrac secs
+#else
+        let t' = t
+#endif
+        return (Just t'))
+    `catchIO` \e -> if isDoesNotExistError e
+                    then return Nothing
+                    else ioError e
 
 -- split a string at the last character where 'pred' is True,
 -- returning a pair of strings. The first component holds the string
-- 
1.7.2.5

