[commit: ghc] master: build: require GHC 7.6 for bootstrapping (527bcc4)

git at git.haskell.org git at git.haskell.org
Tue Aug 19 11:36:39 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/527bcc41630918977c73584d99125ff164400695/ghc

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

commit 527bcc41630918977c73584d99125ff164400695
Author: Austin Seipp <austin at well-typed.com>
Date:   Tue Aug 19 06:36:02 2014 -0500

    build: require GHC 7.6 for bootstrapping
    
    Summary:
    Per the usual standards, a build of GHC is only compileable
    by the last two releases (e.g. 7.8 only by 7.4 and 7.6). To make sure
    we don't get suckered into supporting older compilers, let's remove
    this support now.
    
    Signed-off-by: Austin Seipp <austin at well-typed.com>
    
    Test Plan:
    Try to bootstrap with GHC 7.4, watch it fail. Bootstrap
    with 7.6 or better, and everything works.
    
    Reviewers: hvr
    
    Reviewed By: hvr
    
    Subscribers: simonmar, ezyang, carter
    
    Differential Revision: https://phabricator.haskell.org/D167


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

527bcc41630918977c73584d99125ff164400695
 compiler/cmm/SMRep.lhs   |  6 +-----
 compiler/ghci/Linker.lhs |  4 ----
 compiler/utils/Panic.lhs | 20 --------------------
 compiler/utils/Util.lhs  | 10 ----------
 configure.ac             |  8 +++-----
 5 files changed, 4 insertions(+), 44 deletions(-)

diff --git a/compiler/cmm/SMRep.lhs b/compiler/cmm/SMRep.lhs
index 0713620..53c9d0a 100644
--- a/compiler/cmm/SMRep.lhs
+++ b/compiler/cmm/SMRep.lhs
@@ -105,11 +105,7 @@ StgWord is a type representing an StgWord on the target platform.
 \begin{code}
 -- A Word64 is large enough to hold a Word for either a 32bit or 64bit platform
 newtype StgWord = StgWord Word64
-    deriving (Eq,
-#if __GLASGOW_HASKELL__ < 706
-              Num,
-#endif
-              Bits)
+    deriving (Eq, Bits)
 
 fromStgWord :: StgWord -> Integer
 fromStgWord (StgWord i) = toInteger i
diff --git a/compiler/ghci/Linker.lhs b/compiler/ghci/Linker.lhs
index 40b83bb..86d7b26 100644
--- a/compiler/ghci/Linker.lhs
+++ b/compiler/ghci/Linker.lhs
@@ -63,11 +63,7 @@ import Control.Concurrent.MVar
 
 import System.FilePath
 import System.IO
-#if __GLASGOW_HASKELL__ > 704
 import System.Directory hiding (findFile)
-#else
-import System.Directory
-#endif
 
 import Distribution.Package hiding (depends, mkPackageKey, PackageKey)
 
diff --git a/compiler/utils/Panic.lhs b/compiler/utils/Panic.lhs
index 583174b..23bf01c 100644
--- a/compiler/utils/Panic.lhs
+++ b/compiler/utils/Panic.lhs
@@ -35,9 +35,6 @@ import Exception
 
 import Control.Concurrent
 import Data.Dynamic
-#if __GLASGOW_HASKELL__ < 705
-import Data.Maybe
-#endif
 import Debug.Trace        ( trace )
 import System.IO.Unsafe
 import System.Exit
@@ -52,10 +49,7 @@ import GHC.ConsoleHandler
 #endif
 
 import GHC.Stack
-
-#if __GLASGOW_HASKELL__ >= 705
 import System.Mem.Weak  ( Weak, deRefWeak )
-#endif
 
 -- | GHC's own exception type
 --   error messages all take the form:
@@ -286,7 +280,6 @@ installSignalHandlers = do
   return ()
 #endif
 
-#if __GLASGOW_HASKELL__ >= 705
 {-# NOINLINE interruptTargetThread #-}
 interruptTargetThread :: MVar [Weak ThreadId]
 interruptTargetThread = unsafePerformIO (newMVar [])
@@ -306,19 +299,6 @@ peekInterruptTargetThread =
      case r of
        Nothing -> loop ts
        Just t  -> return (Just t)
-#else
-{-# NOINLINE interruptTargetThread #-}
-interruptTargetThread :: MVar [ThreadId]
-interruptTargetThread = unsafePerformIO (newMVar [])
-
-pushInterruptTargetThread :: ThreadId -> IO ()
-pushInterruptTargetThread tid = do
- modifyMVar_ interruptTargetThread $ return . (tid :)
-
-peekInterruptTargetThread :: IO (Maybe ThreadId)
-peekInterruptTargetThread =
-  withMVar interruptTargetThread $ return . listToMaybe
-#endif
 
 popInterruptTargetThread :: IO ()
 popInterruptTargetThread =
diff --git a/compiler/utils/Util.lhs b/compiler/utils/Util.lhs
index 2dcc73f..dfac0ae 100644
--- a/compiler/utils/Util.lhs
+++ b/compiler/utils/Util.lhs
@@ -129,10 +129,6 @@ import qualified Data.IntMap as IM
 import qualified Data.Set as Set
 
 import Data.Time
-#if __GLASGOW_HASKELL__ < 705
-import Data.Time.Clock.POSIX
-import System.Time
-#endif
 
 infixr 9 `thenCmp`
 \end{code}
@@ -954,13 +950,7 @@ doesDirNameExist fpath = case takeDirectory fpath of
 -- Backwards compatibility definition of getModificationTime
 
 getModificationUTCTime :: FilePath -> IO UTCTime
-#if __GLASGOW_HASKELL__ < 705
-getModificationUTCTime f = do
-    TOD secs _ <- getModificationTime f
-    return $ posixSecondsToUTCTime (realToFrac secs)
-#else
 getModificationUTCTime = getModificationTime
-#endif
 
 -- --------------------------------------------------------------
 -- check existence & modification time at the same time
diff --git a/configure.ac b/configure.ac
index 1c72cfa..9e31c52 100644
--- a/configure.ac
+++ b/configure.ac
@@ -136,8 +136,8 @@ if test "$WithGhc" = ""
 then
     AC_MSG_ERROR([GHC is required.])
 fi
-FP_COMPARE_VERSIONS([$GhcVersion],[-lt],[7.4],
-    [AC_MSG_ERROR([GHC version 7.4 or later is required to compile GHC.])])dnl
+FP_COMPARE_VERSIONS([$GhcVersion],[-lt],[7.6],
+    [AC_MSG_ERROR([GHC version 7.6 or later is required to compile GHC.])])
 
 if test `expr $GhcMinVersion % 2` = "1"
 then
@@ -151,9 +151,7 @@ then
     fi
 fi
 
-FP_COMPARE_VERSIONS([$GhcVersion],[-lt],[7.5],
-                    GHC_PACKAGE_DB_FLAG=package-conf,
-                    GHC_PACKAGE_DB_FLAG=package-db)
+GHC_PACKAGE_DB_FLAG=package-db
 AC_SUBST(GHC_PACKAGE_DB_FLAG)
 
 # GHC 7.7+ needs -fcmm-sink when compiling Parser.hs. See #8182



More information about the ghc-commits mailing list