diff --git a/Cabal/Cabal.cabal b/Cabal/Cabal.cabal
index 791af9234b7b7fe90afdea9c214b5a3bfa358d8c..d79fb62a23c3ba36153f90502713b842751cecb9 100644
--- a/Cabal/Cabal.cabal
+++ b/Cabal/Cabal.cabal
@@ -426,8 +426,6 @@ library
     Distribution.Utils.String
     Distribution.Simple.GHC.EnvironmentParser
     Distribution.Simple.GHC.Internal
-    Distribution.Simple.GHC.IPI642
-    Distribution.Simple.GHC.IPIConvert
     Distribution.Simple.GHC.ImplInfo
     Paths_Cabal
 
diff --git a/Cabal/Distribution/Simple/Build/PathsModule.hs b/Cabal/Distribution/Simple/Build/PathsModule.hs
index 678ccbca3222820cca33a3134617ae4cb667572d..44823e863546f8f4e515ec60a220c2639d67b97d 100644
--- a/Cabal/Distribution/Simple/Build/PathsModule.hs
+++ b/Cabal/Distribution/Simple/Build/PathsModule.hs
@@ -46,23 +46,19 @@ generate pkg_descr lbi clbi =
          ++ warning_pragmas
 
        cpp_pragma
-         | supports_cpp = "{-# LANGUAGE CPP #-}\n"
-         | otherwise    = ""
+         = "{-# LANGUAGE CPP #-}\n"
 
        -- -XRebindableSyntax is problematic because when paired with
        -- -XOverloadedLists, 'fromListN' is not in scope,
        -- or -XOverloadedStrings 'fromString' is not in scope,
        -- so we disable 'RebindableSyntax'.
        no_rebindable_syntax_pragma
-         | supports_rebindable_syntax = "{-# LANGUAGE NoRebindableSyntax #-}\n"
-         | otherwise                  = ""
+         = "{-# LANGUAGE NoRebindableSyntax #-}\n"
 
        ffi_pragmas
         | absolute = ""
-        | supports_language_pragma =
-          "{-# LANGUAGE ForeignFunctionInterface #-}\n"
         | otherwise =
-          "{-# OPTIONS_GHC -fffi #-}\n"
+          "{-# LANGUAGE ForeignFunctionInterface #-}\n"
 
        warning_pragmas =
         "{-# OPTIONS_GHC -fno-warn-missing-import-lists #-}\n"
@@ -93,21 +89,7 @@ generate pkg_descr lbi clbi =
         reloc_imports ++
         "import Prelude\n"++
         "\n"++
-        (if supports_cpp
-         then
-           ("#if defined(VERSION_base)\n"++
-            "\n"++
-            "#if MIN_VERSION_base(4,0,0)\n"++
-            "catchIO :: IO a -> (Exception.IOException -> IO a) -> IO a\n"++
-            "#else\n"++
-            "catchIO :: IO a -> (Exception.Exception -> IO a) -> IO a\n"++
-            "#endif\n"++
-            "\n"++
-            "#else\n"++
-            "catchIO :: IO a -> (Exception.IOException -> IO a) -> IO a\n"++
-            "#endif\n")
-         else
-           "catchIO :: IO a -> (Exception.IOException -> IO a) -> IO a\n")++
+        "catchIO :: IO a -> (Exception.IOException -> IO a) -> IO a\n"++
         "catchIO = Exception.catch\n" ++
         "\n"++
         "version :: Version"++
@@ -242,19 +224,10 @@ generate pkg_descr lbi clbi =
 
         paths_modulename = autogenPathsModuleName pkg_descr
 
-        get_prefix_stuff = get_prefix_win32 supports_cpp buildArch
+        get_prefix_stuff = get_prefix_win32
 
         path_sep = show [pathSeparator]
 
-        supports_cpp = supports_language_pragma
-        supports_rebindable_syntax= ghc_newer_than (mkVersion [7,0,1])
-        supports_language_pragma = ghc_newer_than (mkVersion [6,6,1])
-
-        ghc_newer_than minVersion =
-          case compilerCompatVersion GHC (compiler lbi) of
-            Nothing -> False
-            Just version -> version `withinRange` orLaterVersion minVersion
-
 -- | Generates the name of the environment variable controlling the path
 -- component of interest.
 --
@@ -279,8 +252,8 @@ get_prefix_reloc_stuff =
   "  let (bindir,_) = splitFileName exePath\n"++
   "  return ((bindir `minusFileName` bindirrel) `joinFileName` dirRel)\n"
 
-get_prefix_win32 :: Bool -> Arch -> String
-get_prefix_win32 supports_cpp arch =
+get_prefix_win32 :: String
+get_prefix_win32 =
   "getPrefixDirRel :: FilePath -> IO FilePath\n"++
   "getPrefixDirRel dirRel = try_size 2048 -- plenty, PATH_MAX is 512 under Win32.\n"++
   "  where\n"++
@@ -294,23 +267,15 @@ get_prefix_win32 supports_cpp arch =
   "              return ((bindir `minusFileName` bindirrel) `joinFileName` dirRel)\n"++
   "            | otherwise  -> try_size (size * 2)\n"++
   "\n"++
-  (case supports_cpp of
-    False -> ""
-    True  -> "#if defined(i386_HOST_ARCH)\n"++
-             "# define WINDOWS_CCONV stdcall\n"++
-             "#elif defined(x86_64_HOST_ARCH)\n"++
-             "# define WINDOWS_CCONV ccall\n"++
-             "#else\n"++
-             "# error Unknown mingw32 arch\n"++
-             "#endif\n")++
-  "foreign import " ++ cconv ++ " unsafe \"windows.h GetModuleFileNameW\"\n"++
+  "#if defined(i386_HOST_ARCH)\n"++
+  "# define WINDOWS_CCONV stdcall\n"++
+  "#elif defined(x86_64_HOST_ARCH)\n"++
+  "# define WINDOWS_CCONV ccall\n"++
+  "#else\n"++
+  "# error Unknown mingw32 arch\n"++
+  "#endif\n"++
+  "foreign import WINDOWS_CCONV unsafe \"windows.h GetModuleFileNameW\"\n"++
   "  c_GetModuleFileName :: Ptr () -> CWString -> Int32 -> IO Int32\n"
-    where cconv = if supports_cpp
-                     then "WINDOWS_CCONV"
-                     else case arch of
-                            I386 -> "stdcall"
-                            X86_64 -> "ccall"
-                            _ -> error "win32 supported only with I386, X86_64"
 
 filename_stuff :: String
 filename_stuff =
diff --git a/Cabal/Distribution/Simple/Configure.hs b/Cabal/Distribution/Simple/Configure.hs
index f927b8b9bde1a67172222aa96f0a307d812dad86..6c53a7cedae241d3bb201b905e83fdd23225a3e9 100644
--- a/Cabal/Distribution/Simple/Configure.hs
+++ b/Cabal/Distribution/Simple/Configure.hs
@@ -627,7 +627,7 @@ configure (pkg_descr0, pbi) cfg = do
                                       "--enable-split-objs are mutually" ++
                                       "exclusive; ignoring the latter")
                                 return False
-                        GHC | compilerVersion comp >= mkVersion [6,5]
+                        GHC
                           -> return True
                         GHCJS
                           -> return True
diff --git a/Cabal/Distribution/Simple/GHC.hs b/Cabal/Distribution/Simple/GHC.hs
index 5361906fb3bc67fb9518bc7fe6416e7b842844ea..37a9bd6de9127cb301b59ad8149f6eb08e304b1a 100644
--- a/Cabal/Distribution/Simple/GHC.hs
+++ b/Cabal/Distribution/Simple/GHC.hs
@@ -70,7 +70,6 @@ module Distribution.Simple.GHC (
 import Prelude ()
 import Distribution.Compat.Prelude
 
-import qualified Distribution.Simple.GHC.IPI642 as IPI642
 import qualified Distribution.Simple.GHC.Internal as Internal
 import Distribution.Simple.GHC.ImplInfo
 import Distribution.Simple.GHC.EnvironmentParser
@@ -133,11 +132,11 @@ configure verbosity hcPath hcPkgPath conf0 = do
 
   (ghcProg, ghcVersion, progdb1) <-
     requireProgramVersion verbosity ghcProgram
-      (orLaterVersion (mkVersion [6,11]))
+      (orLaterVersion (mkVersion [7,0,1]))
       (userMaybeSpecifyPath "ghc" hcPath conf0)
   let implInfo = ghcVersionImplInfo ghcVersion
 
-  -- Cabal currently supports ghc >= 6.11 && < 8.8
+  -- Cabal currently supports ghc >= 7.0.1 && < 8.8
   unless (ghcVersion < mkVersion [8,8]) $
     warn verbosity $
          "Unknown/unsupported 'ghc' version detected "
@@ -393,9 +392,7 @@ getUserPackageDB _verbosity ghcProg platform = do
   where
     platformAndVersion = Internal.ghcPlatformAndVersionString
                            platform ghcVersion
-    packageConfFileName
-      | ghcVersion >= mkVersion [6,12]   = "package.conf.d"
-      | otherwise                        = "package.conf"
+    packageConfFileName = "package.conf.d"
     Just ghcVersion = programVersion ghcProg
 
 checkPackageDbEnvVar :: Verbosity -> IO ()
@@ -443,47 +440,12 @@ removeMingwIncludeDir pkg =
 --
 getInstalledPackages' :: Verbosity -> [PackageDB] -> ProgramDb
                      -> IO [(PackageDB, [InstalledPackageInfo])]
-getInstalledPackages' verbosity packagedbs progdb
-  | ghcVersion >= mkVersion [6,9] =
+getInstalledPackages' verbosity packagedbs progdb =
   sequenceA
     [ do pkgs <- HcPkg.dump (hcPkgInfo progdb) verbosity packagedb
          return (packagedb, pkgs)
     | packagedb <- packagedbs ]
 
-  where
-    Just ghcProg    = lookupProgram ghcProgram progdb
-    Just ghcVersion = programVersion ghcProg
-
-getInstalledPackages' verbosity packagedbs progdb = do
-    str <- getDbProgramOutput verbosity ghcPkgProgram progdb ["list"]
-    let pkgFiles = [ init line | line <- lines str, last line == ':' ]
-        dbFile packagedb = case (packagedb, pkgFiles) of
-          (GlobalPackageDB, global:_)      -> return $ Just global
-          (UserPackageDB,  _global:user:_) -> return $ Just user
-          (UserPackageDB,  _global:_)      -> return $ Nothing
-          (SpecificPackageDB specific, _)  -> return $ Just specific
-          _ -> die' verbosity "cannot read ghc-pkg package listing"
-    pkgFiles' <- traverse dbFile packagedbs
-    sequenceA [ withFileContents file $ \content -> do
-                  pkgs <- readPackages file content
-                  return (db, pkgs)
-              | (db , Just file) <- zip packagedbs pkgFiles' ]
-  where
-    -- Depending on the version of ghc we use a different type's Read
-    -- instance to parse the package file and then convert.
-    -- It's a bit yuck. But that's what we get for using Read/Show.
-    readPackages
-      | ghcVersion >= mkVersion [6,4,2]
-      = \file content -> case reads content of
-          [(pkgs, _)] -> return (map IPI642.toCurrent pkgs)
-          _           -> failToRead file
-      -- We dropped support for 6.4.2 and earlier.
-      | otherwise
-      = \file _ -> failToRead file
-    Just ghcProg = lookupProgram ghcProgram progdb
-    Just ghcVersion = programVersion ghcProg
-    failToRead file = die' verbosity $ "cannot read ghc package database " ++ file
-
 getInstalledPackagesMonitorFiles :: Verbosity -> Platform
                                  -> ProgramDb
                                  -> [PackageDB]
@@ -553,8 +515,7 @@ buildOrReplLib mReplFlags verbosity numJobs pkg_descr lbi lib clbi = do
   (ghcProg, _) <- requireProgram verbosity ghcProgram (withPrograms lbi)
   let runGhcProg = runGHC verbosity ghcProg comp platform
 
-  libBi <- hackThreadedFlag verbosity
-             comp (withProfLib lbi) (libBuildInfo lib)
+  let libBi = libBuildInfo lib
 
   let isGhcDynamic        = isDynamic comp
       dynamicTooSupported = supportsDynamicToo comp
@@ -1218,8 +1179,7 @@ gbuild verbosity numJobs pkg_descr lbi bm clbi = do
       implInfo   = getImplInfo comp
       runGhcProg = runGHC verbosity ghcProg comp platform
 
-  bnfo <- hackThreadedFlag verbosity
-            comp (withProfExe lbi) (gbuildInfo bm)
+  let bnfo = gbuildInfo bm
 
   -- the name that GHC really uses (e.g., with .exe on Windows for executables)
   let targetName = gbuildTargetName lbi bm
@@ -1644,22 +1604,6 @@ getRPaths lbi clbi | supportRPaths hostOS = do
 
 getRPaths _ _ = return mempty
 
--- | Filter the "-threaded" flag when profiling as it does not
---   work with ghc-6.8 and older.
-hackThreadedFlag :: Verbosity -> Compiler -> Bool -> BuildInfo -> IO BuildInfo
-hackThreadedFlag verbosity comp prof bi
-  | not mustFilterThreaded = return bi
-  | otherwise              = do
-    warn verbosity $ "The ghc flag '-threaded' is not compatible with "
-                  ++ "profiling in ghc-6.8 and older. It will be disabled."
-    return bi { options = filterHcOptions (/= "-threaded") (options bi) }
-  where
-    mustFilterThreaded = prof && compilerVersion comp < mkVersion [6, 10]
-                      && "-threaded" `elem` hcOptions GHC bi
-    filterHcOptions p hcoptss =
-      [ (hc, if hc == GHC then filter p opts else opts)
-      | (hc, opts) <- hcoptss ]
-
 
 -- | Extracts a String representing a hash of the ABI of a built
 -- library.  It can fail if the library has not yet been built.
@@ -1667,9 +1611,8 @@ hackThreadedFlag verbosity comp prof bi
 libAbiHash :: Verbosity -> PackageDescription -> LocalBuildInfo
            -> Library -> ComponentLocalBuildInfo -> IO String
 libAbiHash verbosity _pkg_descr lbi lib clbi = do
-  libBi <- hackThreadedFlag verbosity
-             (compiler lbi) (withProfLib lbi) (libBuildInfo lib)
   let
+      libBi = libBuildInfo lib
       comp        = compiler lbi
       platform    = hostPlatform lbi
       vanillaArgs0 =
diff --git a/Cabal/Distribution/Simple/GHC/IPI642.hs b/Cabal/Distribution/Simple/GHC/IPI642.hs
deleted file mode 100644
index 46def94e9929b0c18c44ceccdcaa3dbb444bcff4..0000000000000000000000000000000000000000
--- a/Cabal/Distribution/Simple/GHC/IPI642.hs
+++ /dev/null
@@ -1,116 +0,0 @@
------------------------------------------------------------------------------
--- |
--- Module      :  Distribution.Simple.GHC.IPI642
--- Copyright   :  (c) The University of Glasgow 2004
--- License     :  BSD3
---
--- Maintainer  :  cabal-devel@haskell.org
--- Portability :  portable
---
-
-module Distribution.Simple.GHC.IPI642 (
-    InstalledPackageInfo(..),
-    toCurrent,
-  ) where
-
-import Prelude ()
-import Distribution.Compat.Prelude
-
-import qualified Distribution.InstalledPackageInfo as Current
-import qualified Distribution.Types.AbiHash        as Current
-import qualified Distribution.Types.ComponentId    as Current
-import qualified Distribution.Types.UnitId         as Current
-import Distribution.Simple.GHC.IPIConvert
-import Distribution.Text
-
--- | This is the InstalledPackageInfo type used by ghc-6.4.2 and later.
---
--- It's here purely for the 'Read' instance so that we can read the package
--- database used by those ghc versions. It is a little hacky to read the
--- package db directly, but we do need the info and until ghc-6.9 there was
--- no better method.
---
--- In ghc-6.4.1 and before the format was slightly different.
--- See "Distribution.Simple.GHC.IPI642"
---
-data InstalledPackageInfo = InstalledPackageInfo {
-    package           :: PackageIdentifier,
-    license           :: License,
-    copyright         :: String,
-    maintainer        :: String,
-    author            :: String,
-    stability         :: String,
-    homepage          :: String,
-    pkgUrl            :: String,
-    description       :: String,
-    category          :: String,
-    exposed           :: Bool,
-    exposedModules    :: [String],
-    hiddenModules     :: [String],
-    importDirs        :: [FilePath],
-    libraryDirs       :: [FilePath],
-    hsLibraries       :: [String],
-    extraLibraries    :: [String],
-    extraGHCiLibraries:: [String],
-    includeDirs       :: [FilePath],
-    includes          :: [String],
-    depends           :: [PackageIdentifier],
-    hugsOptions       :: [String],
-    ccOptions         :: [String],
-    cxxOptions        :: [String],
-    ldOptions         :: [String],
-    frameworkDirs     :: [FilePath],
-    frameworks        :: [String],
-    haddockInterfaces :: [FilePath],
-    haddockHTMLs      :: [FilePath]
-  }
-  deriving Read
-
-toCurrent :: InstalledPackageInfo -> Current.InstalledPackageInfo
-toCurrent ipi@InstalledPackageInfo{} =
-  let mkExposedModule m = Current.ExposedModule m Nothing
-      pid = convertPackageId (package ipi)
-  in Current.InstalledPackageInfo {
-    Current.sourcePackageId    = pid,
-    Current.installedUnitId    = Current.mkLegacyUnitId pid,
-    Current.installedComponentId_ = Current.mkComponentId (display pid),
-    Current.instantiatedWith   = [],
-    -- Internal libraries not supported!
-    Current.sourceLibName      = Nothing,
-    Current.compatPackageKey   = "",
-    Current.abiHash            = Current.mkAbiHash "", -- bogus but old GHCs don't care.
-    Current.license            = convertLicense (license ipi),
-    Current.copyright          = copyright ipi,
-    Current.maintainer         = maintainer ipi,
-    Current.author             = author ipi,
-    Current.stability          = stability ipi,
-    Current.homepage           = homepage ipi,
-    Current.pkgUrl             = pkgUrl ipi,
-    Current.synopsis           = "",
-    Current.description        = description ipi,
-    Current.category           = category ipi,
-    Current.indefinite         = False,
-    Current.exposed            = exposed ipi,
-    Current.exposedModules     = map (mkExposedModule . convertModuleName) (exposedModules ipi),
-    Current.hiddenModules      = map convertModuleName (hiddenModules ipi),
-    Current.trusted            = Current.trusted Current.emptyInstalledPackageInfo,
-    Current.importDirs         = importDirs ipi,
-    Current.libraryDirs        = libraryDirs ipi,
-    Current.libraryDynDirs     = [],
-    Current.dataDir            = "",
-    Current.hsLibraries        = hsLibraries ipi,
-    Current.extraLibraries     = extraLibraries ipi,
-    Current.extraGHCiLibraries = extraGHCiLibraries ipi,
-    Current.includeDirs        = includeDirs ipi,
-    Current.includes           = includes ipi,
-    Current.depends            = map (Current.mkLegacyUnitId . convertPackageId) (depends ipi),
-    Current.abiDepends         = [],
-    Current.ccOptions          = ccOptions ipi,
-    Current.cxxOptions         = cxxOptions ipi,
-    Current.ldOptions          = ldOptions ipi,
-    Current.frameworkDirs      = frameworkDirs ipi,
-    Current.frameworks         = frameworks ipi,
-    Current.haddockInterfaces  = haddockInterfaces ipi,
-    Current.haddockHTMLs       = haddockHTMLs ipi,
-    Current.pkgRoot            = Nothing
-  }
diff --git a/Cabal/Distribution/Simple/GHC/IPIConvert.hs b/Cabal/Distribution/Simple/GHC/IPIConvert.hs
deleted file mode 100644
index 6fd8cc2e959b34ff3ea5a146c29b3938d48aa60e..0000000000000000000000000000000000000000
--- a/Cabal/Distribution/Simple/GHC/IPIConvert.hs
+++ /dev/null
@@ -1,55 +0,0 @@
------------------------------------------------------------------------------
--- |
--- Module      :  Distribution.Simple.GHC.IPI642
--- Copyright   :  (c) The University of Glasgow 2004
--- License     :  BSD3
---
--- Maintainer  :  cabal-devel@haskell.org
--- Portability :  portable
---
--- Helper functions for 'Distribution.Simple.GHC.IPI642'.
-module Distribution.Simple.GHC.IPIConvert (
-    PackageIdentifier, convertPackageId,
-    License, convertLicense,
-    convertModuleName
-  ) where
-
-import Prelude ()
-import Distribution.Compat.Prelude
-
-import qualified Distribution.Types.PackageId as Current
-import qualified Distribution.Types.PackageName as Current
-import qualified Distribution.License as Current
-import qualified Distribution.SPDX as SPDX
-
-import Distribution.Version
-import Distribution.ModuleName
-import Distribution.Text
-
--- | This is a indeed a munged package id, but the constructor name cannot be
--- changed or the Read instance (the entire point of this type) will break.
-data PackageIdentifier = PackageIdentifier {
-    pkgName    :: String,
-    pkgVersion :: Version
-  }
-  deriving Read
-
-convertPackageId :: PackageIdentifier -> Current.PackageId
-convertPackageId PackageIdentifier { pkgName = n, pkgVersion = v } =
-  Current.PackageIdentifier (Current.mkPackageName n) v
-
-data License = GPL | LGPL | BSD3 | BSD4
-             | PublicDomain | AllRightsReserved | OtherLicense
-  deriving Read
-
-convertModuleName :: String -> ModuleName
-convertModuleName s = fromMaybe (error "convertModuleName") $ simpleParse s
-
-convertLicense :: License -> Either SPDX.License Current.License
-convertLicense GPL               = Right $ Current.GPL  Nothing
-convertLicense LGPL              = Right $ Current.LGPL Nothing
-convertLicense BSD3              = Right $ Current.BSD3
-convertLicense BSD4              = Right $ Current.BSD4
-convertLicense PublicDomain      = Right $ Current.PublicDomain
-convertLicense AllRightsReserved = Right $ Current.AllRightsReserved
-convertLicense OtherLicense      = Right $ Current.OtherLicense
diff --git a/Cabal/Distribution/Simple/PreProcess.hs b/Cabal/Distribution/Simple/PreProcess.hs
index b9984c7fa797c4c7870499327b6c4d25af30db73..47013ff943e11fdf9650e55160464df92be9496a 100644
--- a/Cabal/Distribution/Simple/PreProcess.hs
+++ b/Cabal/Distribution/Simple/PreProcess.hs
@@ -343,8 +343,8 @@ ppCpp = ppCpp' []
 ppCpp' :: [String] -> BuildInfo -> LocalBuildInfo -> ComponentLocalBuildInfo -> PreProcessor
 ppCpp' extraArgs bi lbi clbi =
   case compilerFlavor (compiler lbi) of
-    GHC   -> ppGhcCpp ghcProgram   (>= mkVersion [6,6])  args bi lbi clbi
-    GHCJS -> ppGhcCpp ghcjsProgram (const True)          args bi lbi clbi
+    GHC   -> ppGhcCpp ghcProgram   (const True) args bi lbi clbi
+    GHCJS -> ppGhcCpp ghcjsProgram (const True) args bi lbi clbi
     _     -> ppCpphs  args bi lbi clbi
   where cppArgs = getCppOptions bi lbi
         args    = cppArgs ++ extraArgs
diff --git a/Cabal/Distribution/Simple/Register.hs b/Cabal/Distribution/Simple/Register.hs
index 1756833aa96351cee1a4248cb335f84a0a935754..3545199595f153dde18df34a3ff08788ef9fbb80 100644
--- a/Cabal/Distribution/Simple/Register.hs
+++ b/Cabal/Distribution/Simple/Register.hs
@@ -255,7 +255,7 @@ abiHash :: Verbosity
         -> IO AbiHash
 abiHash verbosity pkg distPref lbi lib clbi =
     case compilerFlavor comp of
-     GHC | compilerVersion comp >= mkVersion [6,11] -> do
+     GHC -> do
             fmap mkAbiHash $ GHC.libAbiHash verbosity pkg lbi' lib clbi
      GHCJS -> do
             fmap mkAbiHash $ GHCJS.libAbiHash verbosity pkg lbi' lib clbi