From a96982e701e69730e6f5b1117b38f8ee4fef1276 Mon Sep 17 00:00:00 2001
From: Ben Gamari <bgamari.foss@gmail.com>
Date: Fri, 21 Sep 2012 10:41:04 -0400
Subject: [PATCH] Setup: getModificationTime returns UTCTime as of GHC 7.6

---
 Setup.hs | 7 +++++++
 1 file changed, 7 insertions(+)

diff --git a/Setup.hs b/Setup.hs
index 6d039823e..e3980624a 100644
--- a/Setup.hs
+++ b/Setup.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE CPP #-}
+
 import Distribution.Simple
 import Distribution.Simple.Setup
          (copyDest, copyVerbosity, fromFlag, installVerbosity, BuildFlags(..))
@@ -20,6 +22,7 @@ import System.Time
 import System.IO.Error ( isDoesNotExistError )
 import Data.Maybe ( catMaybes )
 import Data.List ( (\\) )
+import Data.Time.Clock (UTCTime(..))
 
 main :: IO ()
 main = do
@@ -82,7 +85,11 @@ modifiedDependencies :: FilePath -> [FilePath] -> IO [FilePath]
 modifiedDependencies file dependencies = do
   fileModTime <- catch (getModificationTime file) $
                  \e -> if isDoesNotExistError e
+#if __GLASGOW_HASKELL__ >= 706
+                          then return (UTCTime (toEnum 0) 0)   -- the minimum ClockTime
+#else
                           then return (TOD 0 0)   -- the minimum ClockTime
+#endif
                           else ioError e
   depModTimes <- mapM getModificationTime dependencies
   let modified = zipWith (\dep time -> if time > fileModTime then Just dep else Nothing) dependencies depModTimes