From 40f3601e17024f07e0da8e64d3dd390177ce908b Mon Sep 17 00:00:00 2001
From: Mikhail Glushenkov <mikhail.glushenkov@gmail.com>
Date: Sun, 19 Oct 2014 20:36:03 +0200
Subject: [PATCH] Remove support for Hugs and NHC98.

Fixes #2130.
---
 Cabal/Cabal.cabal                             |   2 -
 Cabal/Distribution/Compat/TempFile.hs         |   1 +
 Cabal/Distribution/InstalledPackageInfo.hs    |   7 +-
 .../Distribution/PackageDescription/Parse.hs  |  11 +-
 Cabal/Distribution/Simple/Build.hs            |   6 -
 .../Distribution/Simple/Build/PathsModule.hs  |  24 +-
 Cabal/Distribution/Simple/BuildPaths.hs       |   5 +-
 Cabal/Distribution/Simple/Configure.hs        |   9 -
 Cabal/Distribution/Simple/GHC/IPI641.hs       |   3 +-
 Cabal/Distribution/Simple/GHC/IPI642.hs       |   3 +-
 Cabal/Distribution/Simple/Hugs.hs             | 609 ------------------
 Cabal/Distribution/Simple/Install.hs          |  14 +-
 Cabal/Distribution/Simple/InstallDirs.hs      |   7 -
 Cabal/Distribution/Simple/LocalBuildInfo.hs   |   3 -
 Cabal/Distribution/Simple/NHC.hs              | 406 ------------
 Cabal/Distribution/Simple/PreProcess.hs       |  10 +-
 Cabal/Distribution/Simple/Program.hs          |   3 -
 Cabal/Distribution/Simple/Program/Builtin.hs  |  23 -
 Cabal/Distribution/Simple/Register.hs         |  21 +-
 Cabal/Distribution/Simple/Setup.hs            |  12 +-
 Cabal/Language/Haskell/Extension.hs           |   2 +-
 Cabal/Makefile                                |  16 -
 Cabal/doc/developing-packages.markdown        |  33 +-
 Cabal/doc/installing-packages.markdown        |  27 +-
 Cabal/doc/misc.markdown                       |   2 +-
 25 files changed, 43 insertions(+), 1216 deletions(-)
 delete mode 100644 Cabal/Distribution/Simple/Hugs.hs
 delete mode 100644 Cabal/Distribution/Simple/NHC.hs

diff --git a/Cabal/Cabal.cabal b/Cabal/Cabal.cabal
index dbb6aeb1cb..a07d65ec77 100644
--- a/Cabal/Cabal.cabal
+++ b/Cabal/Cabal.cabal
@@ -183,13 +183,11 @@ library
     Distribution.Simple.Haddock
     Distribution.Simple.HaskellSuite
     Distribution.Simple.Hpc
-    Distribution.Simple.Hugs
     Distribution.Simple.Install
     Distribution.Simple.InstallDirs
     Distribution.Simple.JHC
     Distribution.Simple.LHC
     Distribution.Simple.LocalBuildInfo
-    Distribution.Simple.NHC
     Distribution.Simple.PackageIndex
     Distribution.Simple.PreProcess
     Distribution.Simple.PreProcess.Unlit
diff --git a/Cabal/Distribution/Compat/TempFile.hs b/Cabal/Distribution/Compat/TempFile.hs
index 7a2ec63dac..bb728d6d1a 100644
--- a/Cabal/Distribution/Compat/TempFile.hs
+++ b/Cabal/Distribution/Compat/TempFile.hs
@@ -38,6 +38,7 @@ import qualified System.Posix
 -- This is here for Haskell implementations that do not come with
 -- System.IO.openTempFile. This includes nhc-1.20, hugs-2006.9.
 -- TODO: Not sure about JHC
+-- TODO: This file should probably be removed.
 
 -- This is a copy/paste of the openBinaryTempFile definition, but
 -- if uses 666 rather than 600 for the permissions. The base library
diff --git a/Cabal/Distribution/InstalledPackageInfo.hs b/Cabal/Distribution/InstalledPackageInfo.hs
index 15dd058157..f7c17c5412 100644
--- a/Cabal/Distribution/InstalledPackageInfo.hs
+++ b/Cabal/Distribution/InstalledPackageInfo.hs
@@ -120,7 +120,7 @@ data InstalledPackageInfo_ m
         reexportedModules :: [ModuleReexport],
         hiddenModules     :: [m],
         trusted           :: Bool,
-        importDirs        :: [FilePath],  -- contain sources in case of Hugs
+        importDirs        :: [FilePath],
         libraryDirs       :: [FilePath],
         hsLibraries       :: [String],
         extraLibraries    :: [String],
@@ -128,7 +128,6 @@ data InstalledPackageInfo_ m
         includeDirs       :: [FilePath],
         includes          :: [String],
         depends           :: [InstalledPackageId],
-        hugsOptions       :: [String],
         ccOptions         :: [String],
         ldOptions         :: [String],
         frameworkDirs     :: [FilePath],
@@ -179,7 +178,6 @@ emptyInstalledPackageInfo
         includeDirs       = [],
         includes          = [],
         depends           = [],
-        hugsOptions       = [],
         ccOptions         = [],
         ldOptions         = [],
         frameworkDirs     = [],
@@ -328,9 +326,6 @@ installedFieldDescrs = [
  , listField   "depends"
         disp               parse
         depends            (\xs pkg -> pkg{depends=xs})
- , listField   "hugs-options"
-        showToken          parseTokenQ
-        hugsOptions        (\path  pkg -> pkg{hugsOptions=path})
  , listField   "cc-options"
         showToken          parseTokenQ
         ccOptions          (\path  pkg -> pkg{ccOptions=path})
diff --git a/Cabal/Distribution/PackageDescription/Parse.hs b/Cabal/Distribution/PackageDescription/Parse.hs
index 455025fcf0..81e84672b6 100644
--- a/Cabal/Distribution/PackageDescription/Parse.hs
+++ b/Cabal/Distribution/PackageDescription/Parse.hs
@@ -464,12 +464,15 @@ binfoFieldDescrs =
            ghcSharedOptions      (\val binfo -> binfo{ghcSharedOptions=val})
  , optsField   "ghc-options"  GHC
            options            (\path  binfo -> binfo{options=path})
- , optsField   "hugs-options" Hugs
-           options            (\path  binfo -> binfo{options=path})
- , optsField   "nhc98-options"  NHC
-           options            (\path  binfo -> binfo{options=path})
  , optsField   "jhc-options"  JHC
            options            (\path  binfo -> binfo{options=path})
+
+ -- NOTE: Hugs and NHC are not supported anymore, but these fields are kept
+ -- around for backwards compatibility.
+ , optsField   "hugs-options" Hugs
+           options            (const id)
+ , optsField   "nhc98-options" NHC
+           options            (const id)
  ]
 
 storeXFieldsBI :: UnrecFieldParser BuildInfo
diff --git a/Cabal/Distribution/Simple/Build.hs b/Cabal/Distribution/Simple/Build.hs
index a7c81a59e8..a9875ced4c 100644
--- a/Cabal/Distribution/Simple/Build.hs
+++ b/Cabal/Distribution/Simple/Build.hs
@@ -26,8 +26,6 @@ module Distribution.Simple.Build (
 import qualified Distribution.Simple.GHC  as GHC
 import qualified Distribution.Simple.JHC  as JHC
 import qualified Distribution.Simple.LHC  as LHC
-import qualified Distribution.Simple.NHC  as NHC
-import qualified Distribution.Simple.Hugs as Hugs
 import qualified Distribution.Simple.UHC  as UHC
 import qualified Distribution.Simple.HaskellSuite as HaskellSuite
 
@@ -475,8 +473,6 @@ buildLib verbosity numJobs pkg_descr lbi lib clbi =
     GHC  -> GHC.buildLib  verbosity numJobs pkg_descr lbi lib clbi
     JHC  -> JHC.buildLib  verbosity         pkg_descr lbi lib clbi
     LHC  -> LHC.buildLib  verbosity         pkg_descr lbi lib clbi
-    Hugs -> Hugs.buildLib verbosity         pkg_descr lbi lib clbi
-    NHC  -> NHC.buildLib  verbosity         pkg_descr lbi lib clbi
     UHC  -> UHC.buildLib  verbosity         pkg_descr lbi lib clbi
     HaskellSuite {} -> HaskellSuite.buildLib verbosity pkg_descr lbi lib clbi
     _    -> die "Building is not supported with this compiler."
@@ -489,8 +485,6 @@ buildExe verbosity numJobs pkg_descr lbi exe clbi =
     GHC  -> GHC.buildExe  verbosity numJobs pkg_descr lbi exe clbi
     JHC  -> JHC.buildExe  verbosity         pkg_descr lbi exe clbi
     LHC  -> LHC.buildExe  verbosity         pkg_descr lbi exe clbi
-    Hugs -> Hugs.buildExe verbosity         pkg_descr lbi exe clbi
-    NHC  -> NHC.buildExe  verbosity         pkg_descr lbi exe clbi
     UHC  -> UHC.buildExe  verbosity         pkg_descr lbi exe clbi
     _    -> die "Building is not supported with this compiler."
 
diff --git a/Cabal/Distribution/Simple/Build/PathsModule.hs b/Cabal/Distribution/Simple/Build/PathsModule.hs
index af81396db0..8fb09ded55 100644
--- a/Cabal/Distribution/Simple/Build/PathsModule.hs
+++ b/Cabal/Distribution/Simple/Build/PathsModule.hs
@@ -49,7 +49,7 @@ import Data.Maybe
 generate :: PackageDescription -> LocalBuildInfo -> String
 generate pkg_descr lbi =
    let pragmas
-        | absolute || isHugs = ""
+        | absolute = ""
         | supports_language_pragma =
           "{-# LANGUAGE ForeignFunctionInterface #-}\n"
         | otherwise =
@@ -58,7 +58,6 @@ generate pkg_descr lbi =
 
        foreign_imports
         | absolute = ""
-        | isHugs = "import System.Environment\n"
         | otherwise =
           "import Foreign\n"++
           "import Foreign.C\n"
@@ -143,8 +142,7 @@ generate pkg_descr lbi =
           libdir     = flat_libdirrel,
           datadir    = flat_datadirrel,
           libexecdir = flat_libexecdirrel,
-          sysconfdir = flat_sysconfdirrel,
-          progdir    = flat_progdirrel
+          sysconfdir = flat_sysconfdirrel
         } = prefixRelativeInstallDirs (packageId pkg_descr) lbi
 
         mkGetDir _   (Just dirrel) = "getPrefixDirRel " ++ show dirrel
@@ -158,10 +156,8 @@ generate pkg_descr lbi =
         absolute =
              hasLibs pkg_descr        -- we can only make progs relocatable
           || isNothing flat_bindirrel -- if the bin dir is an absolute path
-          || (isHugs && isNothing flat_progdirrel)
           || not (supportsRelocatableProgs (compilerFlavor (compiler lbi)))
 
-        supportsRelocatableProgs Hugs = True
         supportsRelocatableProgs GHC  = case buildOS of
                            Windows   -> True
                            _         -> False
@@ -169,12 +165,7 @@ generate pkg_descr lbi =
 
         paths_modulename = autogenModuleName pkg_descr
 
-        isHugs = compilerFlavor (compiler lbi) == Hugs
-        get_prefix_stuff
-          | isHugs    = "progdirrel :: String\n"++
-                        "progdirrel = "++show (fromJust flat_progdirrel)++"\n\n"++
-                        get_prefix_hugs
-          | otherwise = get_prefix_win32 buildArch
+        get_prefix_stuff = get_prefix_win32 buildArch
 
         path_sep = show [pathSeparator]
 
@@ -218,15 +209,6 @@ get_prefix_win32 arch =
                   X86_64 -> "ccall"
                   _ -> error "win32 supported only with I386, X86_64"
 
-get_prefix_hugs :: String
-get_prefix_hugs =
-  "getPrefixDirRel :: FilePath -> IO FilePath\n"++
-  "getPrefixDirRel dirRel = do\n"++
-  "  mainPath <- getProgName\n"++
-  "  let (progPath,_) = splitFileName mainPath\n"++
-  "  let (progdir,_) = splitFileName progPath\n"++
-  "  return ((progdir `minusFileName` progdirrel) `joinFileName` dirRel)\n"
-
 filename_stuff :: String
 filename_stuff =
   "minusFileName :: FilePath -> String -> FilePath\n"++
diff --git a/Cabal/Distribution/Simple/BuildPaths.hs b/Cabal/Distribution/Simple/BuildPaths.hs
index 6d3b8f4646..7b95ff7288 100644
--- a/Cabal/Distribution/Simple/BuildPaths.hs
+++ b/Cabal/Distribution/Simple/BuildPaths.hs
@@ -107,9 +107,8 @@ exeExtension = case buildOS of
                    Windows -> "exe"
                    _       -> ""
 
--- ToDo: This should be determined via autoconf (AC_OBJEXT)
--- | Extension for object files. For GHC and NHC the extension is @\"o\"@.
--- Hugs uses either @\"o\"@ or @\"obj\"@ depending on the used C compiler.
+-- TODO: This should be determined via autoconf (AC_OBJEXT)
+-- | Extension for object files. For GHC the extension is @\"o\"@.
 objExtension :: String
 objExtension = "o"
 
diff --git a/Cabal/Distribution/Simple/Configure.hs b/Cabal/Distribution/Simple/Configure.hs
index 6dc72d131f..d97ddf2040 100644
--- a/Cabal/Distribution/Simple/Configure.hs
+++ b/Cabal/Distribution/Simple/Configure.hs
@@ -113,8 +113,6 @@ import Distribution.Verbosity
 import qualified Distribution.Simple.GHC  as GHC
 import qualified Distribution.Simple.JHC  as JHC
 import qualified Distribution.Simple.LHC  as LHC
-import qualified Distribution.Simple.NHC  as NHC
-import qualified Distribution.Simple.Hugs as Hugs
 import qualified Distribution.Simple.UHC  as UHC
 import qualified Distribution.Simple.HaskellSuite as HaskellSuite
 
@@ -604,9 +602,6 @@ configure (pkg_descr0, pbi) cfg
                     compiler            = comp,
                     hostPlatform        = compPlatform,
                     buildDir            = buildDir',
-                    scratchDir          = fromFlagOrDefault
-                                            (distPref </> "scratch")
-                                            (configScratchDir cfg),
                     componentsConfigs   = buildComponents,
                     installedPkgs       = packageDependsIndex,
                     pkgDescrFile        = Nothing,
@@ -782,10 +777,8 @@ getInstalledPackages verbosity comp packageDBs progconf = do
   info verbosity "Reading installed packages..."
   case compilerFlavor comp of
     GHC -> GHC.getInstalledPackages verbosity packageDBs progconf
-    Hugs->Hugs.getInstalledPackages verbosity packageDBs progconf
     JHC -> JHC.getInstalledPackages verbosity packageDBs progconf
     LHC -> LHC.getInstalledPackages verbosity packageDBs progconf
-    NHC -> NHC.getInstalledPackages verbosity packageDBs progconf
     UHC -> UHC.getInstalledPackages verbosity comp packageDBs progconf
     HaskellSuite {} ->
       HaskellSuite.getInstalledPackages verbosity packageDBs progconf
@@ -1056,8 +1049,6 @@ configCompilerEx (Just hcFlavor) hcPath hcPkg conf verbosity = do
     JHC  -> JHC.configure  verbosity hcPath hcPkg conf
     LHC  -> do (_, _, ghcConf) <- GHC.configure  verbosity Nothing hcPkg conf
                LHC.configure  verbosity hcPath Nothing ghcConf
-    Hugs -> Hugs.configure verbosity hcPath hcPkg conf
-    NHC  -> NHC.configure  verbosity hcPath hcPkg conf
     UHC  -> UHC.configure  verbosity hcPath hcPkg conf
     HaskellSuite {} -> HaskellSuite.configure verbosity hcPath hcPkg conf
     _    -> die "Unknown compiler"
diff --git a/Cabal/Distribution/Simple/GHC/IPI641.hs b/Cabal/Distribution/Simple/GHC/IPI641.hs
index 775507bcf4..0240230f79 100644
--- a/Cabal/Distribution/Simple/GHC/IPI641.hs
+++ b/Cabal/Distribution/Simple/GHC/IPI641.hs
@@ -9,7 +9,7 @@
 --
 
 module Distribution.Simple.GHC.IPI641 (
-    InstalledPackageInfo,
+    InstalledPackageInfo(..),
     toCurrent,
   ) where
 
@@ -94,7 +94,6 @@ toCurrent ipi@InstalledPackageInfo{} =
     Current.includeDirs        = includeDirs ipi,
     Current.includes           = includes ipi,
     Current.depends            = map (mkInstalledPackageId.convertPackageId) (depends ipi),
-    Current.hugsOptions        = hugsOptions ipi,
     Current.ccOptions          = ccOptions ipi,
     Current.ldOptions          = ldOptions ipi,
     Current.frameworkDirs      = frameworkDirs ipi,
diff --git a/Cabal/Distribution/Simple/GHC/IPI642.hs b/Cabal/Distribution/Simple/GHC/IPI642.hs
index 851cd63c1e..60a5d9e13d 100644
--- a/Cabal/Distribution/Simple/GHC/IPI642.hs
+++ b/Cabal/Distribution/Simple/GHC/IPI642.hs
@@ -9,7 +9,7 @@
 --
 
 module Distribution.Simple.GHC.IPI642 (
-    InstalledPackageInfo,
+    InstalledPackageInfo(..),
     toCurrent,
 
     -- Don't use these, they're only for conversion purposes
@@ -129,7 +129,6 @@ toCurrent ipi@InstalledPackageInfo{} =
     Current.includeDirs        = includeDirs ipi,
     Current.includes           = includes ipi,
     Current.depends            = map (mkInstalledPackageId.convertPackageId) (depends ipi),
-    Current.hugsOptions        = hugsOptions ipi,
     Current.ccOptions          = ccOptions ipi,
     Current.ldOptions          = ldOptions ipi,
     Current.frameworkDirs      = frameworkDirs ipi,
diff --git a/Cabal/Distribution/Simple/Hugs.hs b/Cabal/Distribution/Simple/Hugs.hs
deleted file mode 100644
index 850b0841f1..0000000000
--- a/Cabal/Distribution/Simple/Hugs.hs
+++ /dev/null
@@ -1,609 +0,0 @@
------------------------------------------------------------------------------
--- |
--- Module      :  Distribution.Simple.Hugs
--- Copyright   :  Isaac Jones 2003-2006
---                Duncan Coutts 2009
--- License     :  BSD3
---
--- Maintainer  :  cabal-devel@haskell.org
--- Portability :  portable
---
--- This module contains most of the NHC-specific code for configuring, building
--- and installing packages.
-
-module Distribution.Simple.Hugs (
-    configure,
-    getInstalledPackages,
-    buildLib,
-    buildExe,
-    install,
-    registerPackage,
-  ) where
-
-import Distribution.Package
-         ( PackageName, PackageIdentifier(..), InstalledPackageId(..)
-         , packageName )
-import Distribution.InstalledPackageInfo
-         ( InstalledPackageInfo, emptyInstalledPackageInfo
-         , InstalledPackageInfo_( InstalledPackageInfo, installedPackageId
-                                , sourcePackageId )
-         , parseInstalledPackageInfo, showInstalledPackageInfo )
-import Distribution.PackageDescription
-         ( PackageDescription(..), BuildInfo(..), hcOptions, allExtensions
-         , Executable(..), withExe, Library(..), withLib, libModules )
-import Distribution.ModuleName (ModuleName)
-import qualified Distribution.ModuleName as ModuleName
-import Distribution.Simple.Compiler
-         ( CompilerFlavor(..), CompilerId(..)
-         , Compiler(..), Flag, languageToFlags, extensionsToFlags
-         , PackageDB(..), PackageDBStack )
-import qualified Distribution.Simple.PackageIndex as PackageIndex
-import Distribution.Simple.PackageIndex (InstalledPackageIndex)
-import Distribution.Simple.Program
-         ( Program(programFindVersion)
-         , ProgramConfiguration, userMaybeSpecifyPath
-         , requireProgram, requireProgramVersion
-         , rawSystemProgramConf, programPath
-         , ffihugsProgram, hugsProgram )
-import Distribution.Version
-         ( Version(..), orLaterVersion )
-import Distribution.Simple.PreProcess   ( ppCpp, runSimplePreProcessor )
-import Distribution.Simple.PreProcess.Unlit
-                                ( unlit )
-import Distribution.Simple.LocalBuildInfo
-         ( LocalBuildInfo(..), ComponentLocalBuildInfo(..)
-         , InstallDirs(..), absoluteInstallDirs )
-import Distribution.Simple.BuildPaths
-                                ( autogenModuleName, autogenModulesDir,
-                                  dllExtension )
-import Distribution.Simple.Setup
-         ( CopyDest(..) )
-import Distribution.Simple.Utils
-         ( createDirectoryIfMissingVerbose
-         , installOrdinaryFiles, setFileExecutable
-         , withUTF8FileContents, writeFileAtomic, writeUTF8File
-         , copyFileVerbose, findFile, findFileWithExtension, findModuleFiles
-         , rawSystemStdInOut
-         , die, info, notice )
-import Language.Haskell.Extension
-         ( Language(Haskell98), Extension(..), KnownExtension(..) )
-import System.FilePath          ( (</>), takeExtension, (<.>),
-                                  searchPathSeparator, normalise, takeDirectory )
-import Distribution.System
-         ( OS(..), buildOS )
-import Distribution.Text
-         ( display, simpleParse )
-import Distribution.ParseUtils
-         ( ParseResult(..) )
-import Distribution.Verbosity
-
-import Data.Char                ( isSpace )
-import qualified Data.Map as M  ( empty )
-import Data.Maybe               ( mapMaybe, catMaybes )
-import Data.Monoid              ( Monoid(..) )
-import Control.Monad            ( unless, when, filterM )
-import Data.List                ( nub, sort, isSuffixOf )
-import System.Directory
-         ( doesFileExist, doesDirectoryExist, getDirectoryContents
-         , removeDirectoryRecursive, getHomeDirectory )
-import System.Exit
-         ( ExitCode(ExitSuccess) )
-import Distribution.Compat.Exception
-import Distribution.System ( Platform )
-
-import qualified Data.ByteString.Lazy.Char8 as BS.Char8
-
--- -----------------------------------------------------------------------------
--- Configuring
-
-configure :: Verbosity -> Maybe FilePath -> Maybe FilePath
-          -> ProgramConfiguration -> IO (Compiler, Maybe Platform, ProgramConfiguration)
-configure verbosity hcPath _hcPkgPath conf = do
-
-  (_ffihugsProg, conf') <- requireProgram verbosity ffihugsProgram
-                            (userMaybeSpecifyPath "ffihugs" hcPath conf)
-  (_hugsProg, version, conf'')
-                        <- requireProgramVersion verbosity hugsProgram'
-                            (orLaterVersion (Version [2006] [])) conf'
-
-  let comp = Compiler {
-        compilerId             = CompilerId Hugs version,
-        compilerLanguages      = hugsLanguages,
-        compilerExtensions     = hugsLanguageExtensions,
-        compilerProperties     = M.empty
-      }
-      compPlatform = Nothing
-  return (comp, compPlatform, conf'')
-
-  where
-    hugsProgram' = hugsProgram { programFindVersion = getVersion }
-
-getVersion :: Verbosity -> FilePath -> IO (Maybe Version)
-getVersion verbosity hugsPath = do
-  (output, _err, exit) <- rawSystemStdInOut verbosity hugsPath []
-                              Nothing Nothing
-                              (Just (":quit", False)) False
-  if exit == ExitSuccess
-    then return $! findVersion output
-    else return Nothing
-
-  where
-    findVersion output = do
-      (monthStr, yearStr) <- selectWords output
-      year  <- convertYear yearStr
-      month <- convertMonth monthStr
-      return (Version [year, month] [])
-
-    selectWords output =
-      case [ (month, year)
-           | [_,_,"Version:", month, year,_] <- map words (lines output) ] of
-        [(month, year)] -> Just (month, year)
-        _               -> Nothing
-    convertYear year = case reads year of
-      [(y, [])] | y >= 1999 && y < 2020 -> Just y
-      _                                 -> Nothing
-    convertMonth month = lookup month (zip months [1..])
-    months = [ "January", "February", "March", "April", "May", "June", "July"
-             , "August", "September", "October", "November", "December" ]
-
-hugsLanguages :: [(Language, Flag)]
-hugsLanguages = [(Haskell98, "")] --default is 98 mode
-
--- | The flags for the supported extensions
-hugsLanguageExtensions :: [(Extension, Flag)]
-hugsLanguageExtensions =
-    let doFlag (f, (enable, disable)) = [(EnableExtension  f, enable),
-                                         (DisableExtension f, disable)]
-        alwaysOn = ("", ""{- wrong -})
-        ext98 = ("-98", ""{- wrong -})
-    in concatMap doFlag
-    [(OverlappingInstances       , ("+o",  "-o"))
-    ,(IncoherentInstances        , ("+oO", "-O"))
-    ,(HereDocuments              , ("+H",  "-H"))
-    ,(TypeSynonymInstances       , ext98)
-    ,(RecursiveDo                , ext98)
-    ,(ParallelListComp           , ext98)
-    ,(MultiParamTypeClasses      , ext98)
-    ,(FunctionalDependencies     , ext98)
-    ,(Rank2Types                 , ext98)
-    ,(PolymorphicComponents      , ext98)
-    ,(ExistentialQuantification  , ext98)
-    ,(ScopedTypeVariables        , ext98)
-    ,(ImplicitParams             , ext98)
-    ,(ExtensibleRecords          , ext98)
-    ,(RestrictedTypeSynonyms     , ext98)
-    ,(FlexibleContexts           , ext98)
-    ,(FlexibleInstances          , ext98)
-    ,(ForeignFunctionInterface   , alwaysOn)
-    ,(EmptyDataDecls             , alwaysOn)
-    ,(CPP                        , alwaysOn)
-    ]
-
-getInstalledPackages :: Verbosity -> PackageDBStack -> ProgramConfiguration
-                     -> IO InstalledPackageIndex
-getInstalledPackages verbosity packagedbs conf = do
-  homedir       <- getHomeDirectory
-  (hugsProg, _) <- requireProgram verbosity hugsProgram conf
-  let hugsbindir = takeDirectory (programPath hugsProg)
-      hugslibdir = takeDirectory hugsbindir </> "lib" </> "hugs"
-      dbdirs = nub (concatMap (packageDbPaths homedir hugslibdir) packagedbs)
-  indexes  <- mapM getIndividualDBPackages dbdirs
-  return $! mconcat indexes
-
-  where
-    getIndividualDBPackages :: FilePath -> IO InstalledPackageIndex
-    getIndividualDBPackages dbdir = do
-      pkgdirs <- getPackageDbDirs dbdir
-      pkgs    <- sequence [ getInstalledPackage pkgname pkgdir
-                          | (pkgname, pkgdir) <- pkgdirs ]
-      let pkgs' = map setInstalledPackageId (catMaybes pkgs)
-      return (PackageIndex.fromList pkgs')
-
-packageDbPaths :: FilePath -> FilePath -> PackageDB -> [FilePath]
-packageDbPaths home hugslibdir db = case db of
-  GlobalPackageDB        -> [ hugslibdir </> "packages"
-                            , "/usr/local/lib/hugs/packages" ]
-  UserPackageDB          -> [ home </> "lib/hugs/packages" ]
-  SpecificPackageDB path -> [ path ]
-
-getPackageDbDirs :: FilePath -> IO [(PackageName, FilePath)]
-getPackageDbDirs dbdir = do
-  dbexists <- doesDirectoryExist dbdir
-  if not dbexists
-    then return []
-    else do
-      entries  <- getDirectoryContents dbdir
-      pkgdirs  <- sequence
-        [ do pkgdirExists <- doesDirectoryExist pkgdir
-             return (pkgname, pkgdir, pkgdirExists)
-        | (entry, Just pkgname) <- [ (entry, simpleParse entry)
-                                   | entry <- entries ]
-        , let pkgdir = dbdir </> entry ]
-      return [ (pkgname, pkgdir) | (pkgname, pkgdir, True) <- pkgdirs ]
-
-getInstalledPackage :: PackageName -> FilePath -> IO (Maybe InstalledPackageInfo)
-getInstalledPackage pkgname pkgdir = do
-  let pkgconfFile = pkgdir </> "package.conf"
-  pkgconfExists <- doesFileExist pkgconfFile
-
-  let pathsModule = pkgdir </> ("Paths_" ++ display pkgname)  <.> "hs"
-  pathsModuleExists <- doesFileExist pathsModule
-
-  case () of
-    _ | pkgconfExists     -> getFullInstalledPackageInfo pkgname pkgconfFile
-      | pathsModuleExists -> getPhonyInstalledPackageInfo pkgname pathsModule
-      | otherwise         -> return Nothing
-
-getFullInstalledPackageInfo :: PackageName -> FilePath
-                            -> IO (Maybe InstalledPackageInfo)
-getFullInstalledPackageInfo pkgname pkgconfFile =
-  withUTF8FileContents pkgconfFile $ \contents ->
-    case parseInstalledPackageInfo contents of
-      ParseOk _ pkginfo | packageName pkginfo == pkgname
-                        -> return (Just pkginfo)
-      _                 -> return Nothing
-
--- | This is a backup option for existing versions of Hugs which do not supply
--- proper installed package info files for the bundled libs. Instead we look
--- for the Paths_pkgname.hs file and extract the package version from that.
--- We don't know any other details for such packages, in particular we pretend
--- that they have no dependencies.
---
-getPhonyInstalledPackageInfo :: PackageName -> FilePath
-                             -> IO (Maybe InstalledPackageInfo)
-getPhonyInstalledPackageInfo pkgname pathsModule = do
-  content <- readFile pathsModule
-  case extractVersion content of
-    Nothing      -> return Nothing
-    Just version -> return (Just pkginfo)
-      where
-        pkgid   = PackageIdentifier pkgname version
-        pkginfo = emptyInstalledPackageInfo { sourcePackageId = pkgid }
-  where
-    -- search through the Paths_pkgname.hs file, looking for a line like:
-    --
-    -- > version = Version {versionBranch = [2,0], versionTags = []}
-    --
-    -- and parse it using 'Read'. Yes we are that evil.
-    --
-    extractVersion content =
-      case [ version
-           | ("version":"=":rest) <- map words (lines content)
-           , (version, []) <- reads (concat rest) ] of
-        [version] -> Just version
-        _         -> Nothing
-
--- Older installed package info files did not have the installedPackageId
--- field, so if it is missing then we fill it as the source package ID.
-setInstalledPackageId :: InstalledPackageInfo -> InstalledPackageInfo
-setInstalledPackageId pkginfo@InstalledPackageInfo {
-                        installedPackageId = InstalledPackageId "",
-                        sourcePackageId    = pkgid
-                      }
-                    = pkginfo {
-                        --TODO use a proper named function for the conversion
-                        -- from source package id to installed package id
-                        installedPackageId = InstalledPackageId (display pkgid)
-                      }
-setInstalledPackageId pkginfo = pkginfo
-
--- -----------------------------------------------------------------------------
--- Building
-
--- |Building a package for Hugs.
-buildLib :: Verbosity -> PackageDescription -> LocalBuildInfo
-                      -> Library            -> ComponentLocalBuildInfo -> IO ()
-buildLib verbosity pkg_descr lbi lib _clbi = do
-    let pref = scratchDir lbi
-    createDirectoryIfMissingVerbose verbosity True pref
-    copyFileVerbose verbosity (autogenModulesDir lbi </> paths_modulename)
-                              (pref </> paths_modulename)
-    compileBuildInfo verbosity pref [] (libModules lib) (libBuildInfo lib) lbi
-  where
-    paths_modulename = ModuleName.toFilePath (autogenModuleName pkg_descr)
-                         <.> ".hs"
-    --TODO: switch to using autogenModulesDir as a search dir, rather than
-    --      always copying the file over.
-
--- |Building an executable for Hugs.
-buildExe :: Verbosity -> PackageDescription -> LocalBuildInfo
-                      -> Executable         -> ComponentLocalBuildInfo -> IO ()
-buildExe verbosity pkg_descr lbi
-  exe@Executable {modulePath=mainPath, buildInfo=bi} _clbi = do
-    let pref = scratchDir lbi
-    createDirectoryIfMissingVerbose verbosity True pref
-    
-    let destDir = pref </> "programs"
-    let exeMods = otherModules bi
-    srcMainFile <- findFile (hsSourceDirs bi) mainPath
-    let exeDir = destDir </> exeName exe
-    let destMainFile = exeDir </> hugsMainFilename exe
-    copyModule verbosity (EnableExtension CPP `elem` allExtensions bi) bi lbi srcMainFile destMainFile
-    let destPathsFile = exeDir </> paths_modulename
-    copyFileVerbose verbosity (autogenModulesDir lbi </> paths_modulename)
-                              destPathsFile
-    compileBuildInfo verbosity exeDir 
-      (maybe [] (hsSourceDirs . libBuildInfo) (library pkg_descr)) exeMods bi lbi
-    compileFiles verbosity bi lbi exeDir [destMainFile, destPathsFile]
-
-  where
-    paths_modulename = ModuleName.toFilePath (autogenModuleName pkg_descr)
-                         <.> ".hs"
-
-compileBuildInfo :: Verbosity
-                 -> FilePath -- ^output directory
-                 -> [FilePath] -- ^library source dirs, if building exes
-                 -> [ModuleName] -- ^Modules
-                 -> BuildInfo
-                 -> LocalBuildInfo
-                 -> IO ()
---TODO: should not be using mLibSrcDirs at all
-compileBuildInfo verbosity destDir mLibSrcDirs mods bi lbi = do
-    -- Pass 1: copy or cpp files from build directory to scratch directory
-    let useCpp = EnableExtension CPP `elem` allExtensions bi
-    let srcDir = buildDir lbi
-        srcDirs = nub $ srcDir : hsSourceDirs bi ++ mLibSrcDirs
-    info verbosity $ "Source directories: " ++ show srcDirs
-    flip mapM_ mods $ \ m -> do
-        fs <- findFileWithExtension suffixes srcDirs (ModuleName.toFilePath m)
-        case fs of
-          Nothing ->
-            die ("can't find source for module " ++ display m)
-          Just srcFile -> do
-            let ext = takeExtension srcFile
-            copyModule verbosity useCpp bi lbi srcFile
-                (destDir </> ModuleName.toFilePath m <.> ext)
-    -- Pass 2: compile foreign stubs in scratch directory
-    stubsFileLists <- fmap catMaybes $ sequence
-      [ findFileWithExtension suffixes [destDir] (ModuleName.toFilePath modu)
-      | modu <- mods]
-    compileFiles verbosity bi lbi destDir stubsFileLists
-
-suffixes :: [String]
-suffixes = ["hs", "lhs"]
-
--- Copy or cpp a file from the source directory to the build directory.
-copyModule :: Verbosity -> Bool -> BuildInfo -> LocalBuildInfo -> FilePath -> FilePath -> IO ()
-copyModule verbosity cppAll bi lbi srcFile destFile = do
-    createDirectoryIfMissingVerbose verbosity True (takeDirectory destFile)
-    (exts, opts, _) <- getOptionsFromSource srcFile
-    let ghcOpts = [ op | (GHC, ops) <- opts, op <- ops ]
-    if cppAll || EnableExtension CPP `elem` exts || "-cpp" `elem` ghcOpts then do
-        runSimplePreProcessor (ppCpp bi lbi) srcFile destFile verbosity
-        return ()
-      else
-        copyFileVerbose verbosity srcFile destFile
-
-compileFiles :: Verbosity -> BuildInfo -> LocalBuildInfo -> FilePath -> [FilePath] -> IO ()
-compileFiles verbosity bi lbi modDir fileList = do
-    ffiFileList <- filterM testFFI fileList
-    unless (null ffiFileList) $ do
-        notice verbosity "Compiling FFI stubs"
-        mapM_ (compileFFI verbosity bi lbi modDir) ffiFileList
-
--- Only compile FFI stubs for a file if it contains some FFI stuff
-testFFI :: FilePath -> IO Bool
-testFFI file =
-  withHaskellFile file $ \inp ->
-    return $! "foreign" `elem` symbols (stripComments False inp)
-
-compileFFI :: Verbosity -> BuildInfo -> LocalBuildInfo -> FilePath -> FilePath -> IO ()
-compileFFI verbosity bi lbi modDir file = do
-    (_, opts, file_incs) <- getOptionsFromSource file
-    let ghcOpts = [ op | (GHC, ops) <- opts, op <- ops ]
-    let pkg_incs = ["\"" ++ inc ++ "\"" | inc <- includes bi]
-    let incs = nub (sort (file_incs ++ includeOpts ghcOpts ++ pkg_incs))
-    let pathFlag = "-P" ++ modDir ++ [searchPathSeparator]
-    let hugsArgs = "-98" : pathFlag : map ("-i" ++) incs
-    cfiles <- getCFiles file
-    let cArgs =
-            ["-I" ++ dir | dir <- includeDirs bi] ++
-            ccOptions bi ++
-            cfiles ++
-            ["-L" ++ dir | dir <- extraLibDirs bi] ++
-            ldOptions bi ++
-            ["-l" ++ lib | lib <- extraLibs bi] ++
-            concat [["-framework", f] | f <- frameworks bi]
-    rawSystemProgramConf verbosity ffihugsProgram (withPrograms lbi)
-      (hugsArgs ++ file : cArgs)
-
-includeOpts :: [String] -> [String]
-includeOpts [] = []
-includeOpts ("-#include" : arg : opts) = arg : includeOpts opts
-includeOpts (_ : opts) = includeOpts opts
-
--- get C file names from CFILES pragmas throughout the source file
-getCFiles :: FilePath -> IO [String]
-getCFiles file =
-  withHaskellFile file $ \inp ->
-    let cfiles =
-          [ normalise cfile
-          | "{-#" : "CFILES" : rest <- map words
-                                     $ lines
-                                     $ stripComments True inp
-          , last rest == "#-}"
-          , cfile <- init rest]
-     in seq (length cfiles) (return cfiles)
-
--- List of terminal symbols in a source file.
-symbols :: String -> [String]
-symbols cs = case lex cs of
-    (sym, cs'):_ | not (null sym) -> sym : symbols cs'
-    _ -> []
-
--- Get the non-literate source of a Haskell module.
-withHaskellFile :: FilePath -> (String -> IO a) -> IO a
-withHaskellFile file action =
-    withUTF8FileContents file $ \text ->
-        if ".lhs" `isSuffixOf` file
-          then either action die (unlit file text)
-          else action text
-
--- ------------------------------------------------------------
--- * options in source files
--- ------------------------------------------------------------
-
--- |Read the initial part of a source file, before any Haskell code,
--- and return the contents of any LANGUAGE, OPTIONS and INCLUDE pragmas.
-getOptionsFromSource
-    :: FilePath
-    -> IO ([Extension],                 -- LANGUAGE pragma, if any
-           [(CompilerFlavor,[String])], -- OPTIONS_FOO pragmas
-           [String]                     -- INCLUDE pragmas
-          )
-getOptionsFromSource file =
-    withHaskellFile file $
-        (return $!)
-      . foldr appendOptions ([],[],[]) . map getOptions
-      . takeWhileJust . map getPragma
-      . filter textLine . map (dropWhile isSpace) . lines
-      . stripComments True
-
-  where textLine [] = False
-        textLine ('#':_) = False
-        textLine _ = True
-
-        getPragma :: String -> Maybe [String]
-        getPragma line = case words line of
-            ("{-#" : rest) | last rest == "#-}" -> Just (init rest)
-            _ -> Nothing
-
-        getOptions ("OPTIONS":opts) = ([], [(GHC, opts)], [])
-        getOptions ("OPTIONS_GHC":opts) = ([], [(GHC, opts)], [])
-        getOptions ("OPTIONS_NHC98":opts) = ([], [(NHC, opts)], [])
-        getOptions ("OPTIONS_HUGS":opts) = ([], [(Hugs, opts)], [])
-        getOptions ("LANGUAGE":ws) = (mapMaybe readExtension ws, [], [])
-          where readExtension :: String -> Maybe Extension
-                readExtension w = case reads w of
-                    [(ext, "")] -> Just ext
-                    [(ext, ",")] -> Just ext
-                    _ -> Nothing
-        getOptions ("INCLUDE":ws) = ([], [], ws)
-        getOptions _ = ([], [], [])
-
-        appendOptions (exts, opts, incs) (exts', opts', incs')
-          = (exts++exts', opts++opts', incs++incs')
-
--- takeWhileJust f = map fromJust . takeWhile isJust
-takeWhileJust :: [Maybe a] -> [a]
-takeWhileJust (Just x:xs) = x : takeWhileJust xs
-takeWhileJust _ = []
-
--- |Strip comments from Haskell source.
-stripComments
-    :: Bool     -- ^ preserve pragmas?
-    -> String   -- ^ input source text
-    -> String
-stripComments keepPragmas = stripCommentsLevel 0
-  where stripCommentsLevel :: Int -> String -> String
-        stripCommentsLevel 0 ('"':cs) = '"':copyString cs
-        stripCommentsLevel 0 ('-':'-':cs) =     -- FIX: symbols like -->
-            stripCommentsLevel 0 (dropWhile (/= '\n') cs)
-        stripCommentsLevel 0 ('{':'-':'#':cs)
-          | keepPragmas = '{' : '-' : '#' : copyPragma cs
-        stripCommentsLevel n ('{':'-':cs) = stripCommentsLevel (n+1) cs
-        stripCommentsLevel 0 (c:cs) = c : stripCommentsLevel 0 cs
-        stripCommentsLevel n ('-':'}':cs) = stripCommentsLevel (n-1) cs
-        stripCommentsLevel n (_:cs) = stripCommentsLevel n cs
-        stripCommentsLevel _ [] = []
-
-        copyString ('\\':c:cs) = '\\' : c : copyString cs
-        copyString ('"':cs) = '"' : stripCommentsLevel 0 cs
-        copyString (c:cs) = c : copyString cs
-        copyString [] = []
-
-        copyPragma ('#':'-':'}':cs) = '#' : '-' : '}' : stripCommentsLevel 0 cs
-        copyPragma (c:cs) = c : copyPragma cs
-        copyPragma [] = []
-
--- -----------------------------------------------------------------------------
--- |Install for Hugs.
--- For install, copy-prefix = prefix, but for copy they're different.
--- The library goes in \<copy-prefix>\/lib\/hugs\/packages\/\<pkgname>
--- (i.e. \<prefix>\/lib\/hugs\/packages\/\<pkgname> on the target system).
--- Each executable goes in \<copy-prefix>\/lib\/hugs\/programs\/\<exename>
--- (i.e. \<prefix>\/lib\/hugs\/programs\/\<exename> on the target system)
--- with a script \<copy-prefix>\/bin\/\<exename> pointing at
--- \<prefix>\/lib\/hugs\/programs\/\<exename>.
-install
-    :: Verbosity -- ^verbosity
-    -> LocalBuildInfo
-    -> FilePath  -- ^Library install location
-    -> FilePath  -- ^Program install location
-    -> FilePath  -- ^Executable install location
-    -> FilePath  -- ^Program location on target system
-    -> FilePath  -- ^Build location
-    -> (FilePath,FilePath)  -- ^Executable (prefix,suffix)
-    -> PackageDescription
-    -> IO ()
---FIXME: this script should be generated at build time, just installed at this stage
-install verbosity lbi libDir installProgDir binDir targetProgDir buildPref (progprefix,progsuffix) pkg_descr = do
-    removeDirectoryRecursive libDir `catchIO` \_ -> return ()
-    withLib pkg_descr $ \ lib ->
-      findModuleFiles [buildPref] hugsInstallSuffixes (libModules lib)
-        >>= installOrdinaryFiles verbosity libDir
-    let buildProgDir = buildPref </> "programs"
-    when (any (buildable . buildInfo) (executables pkg_descr)) $
-        createDirectoryIfMissingVerbose verbosity True binDir
-    withExe pkg_descr $ \ exe -> do
-        let bi = buildInfo exe
-        let theBuildDir = buildProgDir </> exeName exe
-        let installDir = installProgDir </> exeName exe
-        let targetDir = targetProgDir </> exeName exe
-        removeDirectoryRecursive installDir `catchIO` \_ -> return ()
-        findModuleFiles [theBuildDir] hugsInstallSuffixes
-                        (ModuleName.main : autogenModuleName pkg_descr
-                                         : otherModules (buildInfo exe))
-          >>= installOrdinaryFiles verbosity installDir
-        let targetName = "\"" ++ (targetDir </> hugsMainFilename exe) ++ "\""
-        let hugsOptions = hcOptions Hugs (buildInfo exe)
-                       ++ languageToFlags (compiler lbi) (defaultLanguage bi)
-                       ++ extensionsToFlags (compiler lbi) (allExtensions bi)
-            --TODO: also need to consider options, extensions etc of deps
-            --      see ticket #43
-        let baseExeFile = progprefix ++ (exeName exe) ++ progsuffix
-        let exeFile = case buildOS of
-                          Windows -> binDir </> baseExeFile <.> ".bat"
-                          _       -> binDir </> baseExeFile
-        let script = case buildOS of
-                         Windows ->
-                             let args = hugsOptions ++ [targetName, "%*"]
-                             in unlines ["@echo off",
-                                         unwords ("runhugs" : args)]
-                         _ ->
-                             let args = hugsOptions ++ [targetName, "\"$@\""]
-                             in unlines ["#! /bin/sh",
-                                         unwords ("runhugs" : args)]
-        writeFileAtomic exeFile (BS.Char8.pack script)
-        setFileExecutable exeFile
-
-hugsInstallSuffixes :: [String]
-hugsInstallSuffixes = [".hs", ".lhs", dllExtension]
-
--- |Filename used by Hugs for the main module of an executable.
--- This is a simple filename, so that Hugs will look for any auxiliary
--- modules it uses relative to the directory it's in.
-hugsMainFilename :: Executable -> FilePath
-hugsMainFilename exe = "Main" <.> ext
-  where ext = takeExtension (modulePath exe)
-
--- -----------------------------------------------------------------------------
--- Registering
-
-registerPackage
-  :: Verbosity
-  -> InstalledPackageInfo
-  -> PackageDescription
-  -> LocalBuildInfo
-  -> Bool
-  -> PackageDBStack
-  -> IO ()
-registerPackage verbosity installedPkgInfo pkg lbi inplace _packageDbs = do
-  --TODO: prefer to have it based on the packageDbs, but how do we know
-  -- the package subdir based on the name? the user can set crazy libsubdir
-  let installDirs = absoluteInstallDirs pkg lbi NoCopyDest
-      pkgdir  | inplace   = buildDir lbi
-              | otherwise = libdir installDirs
-  createDirectoryIfMissingVerbose verbosity True pkgdir
-  writeUTF8File (pkgdir </> "package.conf")
-                (showInstalledPackageInfo installedPkgInfo)
diff --git a/Cabal/Distribution/Simple/Install.hs b/Cabal/Distribution/Simple/Install.hs
index 3efcceee0f..f36feb69da 100644
--- a/Cabal/Distribution/Simple/Install.hs
+++ b/Cabal/Distribution/Simple/Install.hs
@@ -30,13 +30,11 @@ import Distribution.Simple.Utils
          , die, info, notice, warn, matchDirFileGlob )
 import Distribution.Simple.Compiler
          ( CompilerFlavor(..), compilerFlavor )
-import Distribution.Simple.Setup (CopyFlags(..), CopyDest(..), fromFlag)
+import Distribution.Simple.Setup (CopyFlags(..), fromFlag)
 
 import qualified Distribution.Simple.GHC  as GHC
-import qualified Distribution.Simple.NHC  as NHC
 import qualified Distribution.Simple.JHC  as JHC
 import qualified Distribution.Simple.LHC  as LHC
-import qualified Distribution.Simple.Hugs as Hugs
 import qualified Distribution.Simple.UHC  as UHC
 import qualified Distribution.Simple.HaskellSuite as HaskellSuite
 
@@ -51,8 +49,7 @@ import Distribution.Text
          ( display )
 
 -- |Perform the \"@.\/setup install@\" and \"@.\/setup copy@\"
--- actions.  Move files into place based on the prefix argument.  FIX:
--- nhc isn't implemented yet.
+-- actions.  Move files into place based on the prefix argument.
 
 install :: PackageDescription -- ^information from the .cabal file
         -> LocalBuildInfo -- ^information from the configure step
@@ -67,7 +64,6 @@ install pkg_descr lbi flags = do
          libdir     = libPref,
 --         dynlibdir  = dynlibPref, --see TODO below
          datadir    = dataPref,
-         progdir    = progPref,
          docdir     = docPref,
          htmldir    = htmlPref,
          haddockdir = interfacePref,
@@ -142,12 +138,6 @@ install pkg_descr lbi flags = do
                   JHC.installLib verbosity libPref buildPref pkg_descr
                 withExe pkg_descr $
                   JHC.installExe verbosity binPref buildPref (progPrefixPref, progSuffixPref) pkg_descr
-     Hugs -> do
-       let targetProgPref = progdir (absoluteInstallDirs pkg_descr lbi NoCopyDest)
-       let scratchPref = scratchDir lbi
-       Hugs.install verbosity lbi libPref progPref binPref targetProgPref scratchPref (progPrefixPref, progSuffixPref) pkg_descr
-     NHC  -> do withLibLBI pkg_descr lbi $ NHC.installLib verbosity libPref buildPref (packageId pkg_descr)
-                withExe pkg_descr $ NHC.installExe verbosity binPref buildPref (progPrefixPref, progSuffixPref)
      UHC  -> do withLib pkg_descr $ UHC.installLib verbosity lbi libPref dynlibPref buildPref pkg_descr
      HaskellSuite {} ->
        withLib pkg_descr $
diff --git a/Cabal/Distribution/Simple/InstallDirs.hs b/Cabal/Distribution/Simple/InstallDirs.hs
index 33c09fb676..fb8f35928c 100644
--- a/Cabal/Distribution/Simple/InstallDirs.hs
+++ b/Cabal/Distribution/Simple/InstallDirs.hs
@@ -84,7 +84,6 @@ data InstallDirs dir = InstallDirs {
         libsubdir    :: dir,
         dynlibdir    :: dir,
         libexecdir   :: dir,
-        progdir      :: dir,
         includedir   :: dir,
         datadir      :: dir,
         datasubdir   :: dir,
@@ -105,7 +104,6 @@ instance Functor InstallDirs where
     libsubdir    = f (libsubdir dirs),
     dynlibdir    = f (dynlibdir dirs),
     libexecdir   = f (libexecdir dirs),
-    progdir      = f (progdir dirs),
     includedir   = f (includedir dirs),
     datadir      = f (datadir dirs),
     datasubdir   = f (datasubdir dirs),
@@ -124,7 +122,6 @@ instance Monoid dir => Monoid (InstallDirs dir) where
       libsubdir    = mempty,
       dynlibdir    = mempty,
       libexecdir   = mempty,
-      progdir      = mempty,
       includedir   = mempty,
       datadir      = mempty,
       datasubdir   = mempty,
@@ -147,7 +144,6 @@ combineInstallDirs combine a b = InstallDirs {
     libsubdir    = libsubdir a  `combine` libsubdir b,
     dynlibdir    = dynlibdir a  `combine` dynlibdir b,
     libexecdir   = libexecdir a `combine` libexecdir b,
-    progdir      = progdir a    `combine` progdir b,
     includedir   = includedir a `combine` includedir b,
     datadir      = datadir a    `combine` datadir b,
     datasubdir   = datasubdir a `combine` datasubdir b,
@@ -213,7 +209,6 @@ defaultInstallDirs comp userInstall _hasLibs = do
       bindir       = "$prefix" </> "bin",
       libdir       = installLibDir,
       libsubdir    = case comp of
-           Hugs   -> "hugs" </> "packages" </> "$pkg"
            JHC    -> "$compiler"
            LHC    -> "$compiler"
            UHC    -> "$pkgid"
@@ -222,7 +217,6 @@ defaultInstallDirs comp userInstall _hasLibs = do
       libexecdir   = case buildOS of
         Windows   -> "$prefix" </> "$pkgkey"
         _other    -> "$prefix" </> "libexec",
-      progdir      = "$libdir" </> "hugs" </> "programs",
       includedir   = "$libdir" </> "$libsubdir" </> "include",
       datadir      = case buildOS of
         Windows   -> "$prefix"
@@ -262,7 +256,6 @@ substituteInstallDirTemplates env dirs = dirs'
       libsubdir  = subst libsubdir  [],
       dynlibdir  = subst dynlibdir  [prefixVar, bindirVar, libdirVar],
       libexecdir = subst libexecdir prefixBinLibVars,
-      progdir    = subst progdir    prefixBinLibVars,
       includedir = subst includedir prefixBinLibVars,
       datadir    = subst datadir    prefixBinLibVars,
       datasubdir = subst datasubdir [],
diff --git a/Cabal/Distribution/Simple/LocalBuildInfo.hs b/Cabal/Distribution/Simple/LocalBuildInfo.hs
index d90a64755a..7b89b89d7c 100644
--- a/Cabal/Distribution/Simple/LocalBuildInfo.hs
+++ b/Cabal/Distribution/Simple/LocalBuildInfo.hs
@@ -110,9 +110,6 @@ data LocalBuildInfo = LocalBuildInfo {
                 -- ^ The platform we're building for
         buildDir      :: FilePath,
                 -- ^ Where to build the package.
-        --TODO: eliminate hugs's scratchDir, use builddir
-        scratchDir    :: FilePath,
-                -- ^ Where to put the result of the Hugs build.
         componentsConfigs   :: [(ComponentName, ComponentLocalBuildInfo, [ComponentName])],
                 -- ^ All the components to build, ordered by topological sort, and with their dependencies
                 -- over the intrapackage dependency graph
diff --git a/Cabal/Distribution/Simple/NHC.hs b/Cabal/Distribution/Simple/NHC.hs
deleted file mode 100644
index eb06bd5433..0000000000
--- a/Cabal/Distribution/Simple/NHC.hs
+++ /dev/null
@@ -1,406 +0,0 @@
------------------------------------------------------------------------------
--- |
--- Module      :  Distribution.Simple.NHC
--- Copyright   :  Isaac Jones 2003-2006
---                Duncan Coutts 2009
--- License     :  BSD3
---
--- Maintainer  :  cabal-devel@haskell.org
--- Portability :  portable
---
--- This module contains most of the NHC-specific code for configuring, building
--- and installing packages.
-
-module Distribution.Simple.NHC (
-    configure,
-    getInstalledPackages,
-    buildLib,
-    buildExe,
-    installLib,
-    installExe,
-  ) where
-
-import Distribution.Package
-         ( PackageName, PackageIdentifier(..), InstalledPackageId(..)
-         , packageName )
-import Distribution.InstalledPackageInfo
-         ( InstalledPackageInfo
-         , InstalledPackageInfo_( InstalledPackageInfo, installedPackageId
-                                , sourcePackageId )
-         , emptyInstalledPackageInfo, parseInstalledPackageInfo )
-import Distribution.PackageDescription
-        ( PackageDescription(..), BuildInfo(..), Library(..), Executable(..)
-        , hcOptions, usedExtensions )
-import Distribution.ModuleName (ModuleName)
-import qualified Distribution.ModuleName as ModuleName
-import Distribution.Simple.LocalBuildInfo
-        ( LocalBuildInfo(..), ComponentLocalBuildInfo(..) )
-import Distribution.Simple.BuildPaths
-        ( mkLibName, objExtension, exeExtension )
-import Distribution.Simple.Compiler
-         ( CompilerFlavor(..), CompilerId(..), Compiler(..)
-         , Flag, languageToFlags, extensionsToFlags
-         , PackageDB(..), PackageDBStack )
-import qualified Distribution.Simple.PackageIndex as PackageIndex
-import Distribution.Simple.PackageIndex (InstalledPackageIndex)
-import Language.Haskell.Extension
-         ( Language(Haskell98), Extension(..), KnownExtension(..) )
-import Distribution.Simple.Program
-         ( ProgramConfiguration, userMaybeSpecifyPath, programPath
-         , requireProgram, requireProgramVersion, lookupProgram
-         , nhcProgram, hmakeProgram, ldProgram, arProgram
-         , rawSystemProgramConf )
-import Distribution.Simple.Utils
-        ( die, info, findFileWithExtension, findModuleFiles
-        , installOrdinaryFile, installExecutableFile, installOrdinaryFiles
-        , createDirectoryIfMissingVerbose, withUTF8FileContents )
-import Distribution.Version
-        ( Version(..), orLaterVersion )
-import Distribution.Verbosity
-import Distribution.Text
-         ( display, simpleParse )
-import Distribution.ParseUtils
-         ( ParseResult(..) )
-
-import System.FilePath
-        ( (</>), (<.>), normalise, takeDirectory, dropExtension )
-import System.Directory
-         ( doesFileExist, doesDirectoryExist, getDirectoryContents
-         , removeFile, getHomeDirectory )
-
-import Data.Char               ( toLower )
-import Data.List               ( nub )
-import Data.Maybe              ( catMaybes )
-import qualified Data.Map as M ( empty )
-import Data.Monoid             ( Monoid(..) )
-import Control.Monad           ( when, unless )
-import Distribution.Compat.Exception
-import Distribution.System ( Platform )
-
--- -----------------------------------------------------------------------------
--- Configuring
-
-configure :: Verbosity -> Maybe FilePath -> Maybe FilePath
-          -> ProgramConfiguration -> IO (Compiler, Maybe Platform, ProgramConfiguration)
-configure verbosity hcPath _hcPkgPath conf = do
-
-  (_nhcProg, nhcVersion, conf') <-
-    requireProgramVersion verbosity nhcProgram
-      (orLaterVersion (Version [1,20] []))
-      (userMaybeSpecifyPath "nhc98" hcPath conf)
-
-  (_hmakeProg, _hmakeVersion, conf'') <-
-    requireProgramVersion verbosity hmakeProgram
-     (orLaterVersion (Version [3,13] [])) conf'
-  (_ldProg, conf''')   <- requireProgram verbosity ldProgram conf''
-  (_arProg, conf'''')  <- requireProgram verbosity arProgram conf'''
-
-  --TODO: put this stuff in a monad so we can say just:
-  -- requireProgram hmakeProgram (orLaterVersion (Version [3,13] []))
-  -- requireProgram ldProgram anyVersion
-  -- requireProgram ldPrograrProgramam anyVersion
-  -- unless (null (cSources bi)) $ requireProgram ccProgram anyVersion
-
-  let comp = Compiler {
-        compilerId         = CompilerId NHC nhcVersion,
-        compilerLanguages  = nhcLanguages,
-        compilerExtensions = nhcLanguageExtensions,
-        compilerProperties = M.empty
-      }
-      compPlatform = Nothing
-  return (comp, compPlatform,  conf'''')
-
-nhcLanguages :: [(Language, Flag)]
-nhcLanguages = [(Haskell98, "-98")]
-
--- | The flags for the supported extensions
-nhcLanguageExtensions :: [(Extension, Flag)]
-nhcLanguageExtensions =
-    -- TODO: pattern guards in 1.20
-     -- NHC doesn't enforce the monomorphism restriction at all.
-     -- Technically it therefore doesn't support MonomorphismRestriction,
-     -- but that would mean it doesn't support Haskell98, so we pretend
-     -- that it does.
-    [(EnableExtension  MonomorphismRestriction,   "")
-    ,(DisableExtension MonomorphismRestriction,   "")
-     -- Similarly, I assume the FFI is always on
-    ,(EnableExtension  ForeignFunctionInterface,  "")
-    ,(DisableExtension ForeignFunctionInterface,  "")
-     -- Similarly, I assume existential quantification is always on
-    ,(EnableExtension  ExistentialQuantification, "")
-    ,(DisableExtension ExistentialQuantification, "")
-     -- Similarly, I assume empty data decls is always on
-    ,(EnableExtension  EmptyDataDecls,            "")
-    ,(DisableExtension EmptyDataDecls,            "")
-    ,(EnableExtension  NamedFieldPuns,            "-puns")
-    ,(DisableExtension NamedFieldPuns,            "-nopuns")
-     -- CPP can't actually be turned off, but we pretend that it can
-    ,(EnableExtension  CPP,                       "-cpp")
-    ,(DisableExtension CPP,                       "")
-    ]
-
-getInstalledPackages :: Verbosity -> PackageDBStack -> ProgramConfiguration
-                     -> IO InstalledPackageIndex
-getInstalledPackages verbosity packagedbs conf = do
-  homedir      <- getHomeDirectory
-  (nhcProg, _) <- requireProgram verbosity nhcProgram conf
-  let bindir = takeDirectory (programPath nhcProg)
-      incdir = takeDirectory bindir </> "include" </> "nhc98"
-      dbdirs = nub (concatMap (packageDbPaths homedir incdir) packagedbs)
-  indexes  <- mapM getIndividualDBPackages dbdirs
-  return $! mconcat indexes
-
-  where
-    getIndividualDBPackages :: FilePath -> IO InstalledPackageIndex
-    getIndividualDBPackages dbdir = do
-      pkgdirs <- getPackageDbDirs dbdir
-      pkgs    <- sequence [ getInstalledPackage pkgname pkgdir
-                          | (pkgname, pkgdir) <- pkgdirs ]
-      let pkgs' = map setInstalledPackageId (catMaybes pkgs)
-      return (PackageIndex.fromList pkgs')
-
-packageDbPaths :: FilePath -> FilePath -> PackageDB -> [FilePath]
-packageDbPaths _home incdir db = case db of
-  GlobalPackageDB        -> [ incdir </> "packages" ]
-  UserPackageDB          -> [] --TODO any standard per-user db?
-  SpecificPackageDB path -> [ path ]
-
-getPackageDbDirs :: FilePath -> IO [(PackageName, FilePath)]
-getPackageDbDirs dbdir = do
-  dbexists <- doesDirectoryExist dbdir
-  if not dbexists
-    then return []
-    else do
-      entries  <- getDirectoryContents dbdir
-      pkgdirs  <- sequence
-        [ do pkgdirExists <- doesDirectoryExist pkgdir
-             return (pkgname, pkgdir, pkgdirExists)
-        | (entry, Just pkgname) <- [ (entry, simpleParse entry)
-                                   | entry <- entries ]
-        , let pkgdir = dbdir </> entry ]
-      return [ (pkgname, pkgdir) | (pkgname, pkgdir, True) <- pkgdirs ]
-
-getInstalledPackage :: PackageName -> FilePath -> IO (Maybe InstalledPackageInfo)
-getInstalledPackage pkgname pkgdir = do
-  let pkgconfFile = pkgdir </> "package.conf"
-  pkgconfExists <- doesFileExist pkgconfFile
-
-  let cabalFile = pkgdir <.> "cabal"
-  cabalExists <- doesFileExist cabalFile
-
-  case () of
-    _ | pkgconfExists -> getFullInstalledPackageInfo pkgname pkgconfFile
-      | cabalExists   -> getPhonyInstalledPackageInfo pkgname cabalFile
-      | otherwise     -> return Nothing
-
-getFullInstalledPackageInfo :: PackageName -> FilePath
-                            -> IO (Maybe InstalledPackageInfo)
-getFullInstalledPackageInfo pkgname pkgconfFile =
-  withUTF8FileContents pkgconfFile $ \contents ->
-    case parseInstalledPackageInfo contents of
-      ParseOk _ pkginfo | packageName pkginfo == pkgname
-                        -> return (Just pkginfo)
-      _                 -> return Nothing
-
--- | This is a backup option for existing versions of nhc98 which do not supply
--- proper installed package info files for the bundled libs. Instead we look
--- for the .cabal file and extract the package version from that.
--- We don't know any other details for such packages, in particular we pretend
--- that they have no dependencies.
---
-getPhonyInstalledPackageInfo :: PackageName -> FilePath
-                             -> IO (Maybe InstalledPackageInfo)
-getPhonyInstalledPackageInfo pkgname pathsModule = do
-  content <- readFile pathsModule
-  case extractVersion content of
-    Nothing      -> return Nothing
-    Just version -> return (Just pkginfo)
-      where
-        pkgid   = PackageIdentifier pkgname version
-        pkginfo = emptyInstalledPackageInfo { sourcePackageId = pkgid }
-  where
-    -- search through the .cabal file, looking for a line like:
-    --
-    -- > version: 2.0
-    --
-    extractVersion :: String -> Maybe Version
-    extractVersion content =
-      case catMaybes (map extractVersionLine (lines content)) of
-        [version] -> Just version
-        _         -> Nothing
-    extractVersionLine :: String -> Maybe Version
-    extractVersionLine line =
-      case words line of
-        [versionTag, ":", versionStr]
-          | map toLower versionTag == "version"  -> simpleParse versionStr
-        [versionTag,      versionStr]
-          | map toLower versionTag == "version:" -> simpleParse versionStr
-        _                                        -> Nothing
-
--- Older installed package info files did not have the installedPackageId
--- field, so if it is missing then we fill it as the source package ID.
-setInstalledPackageId :: InstalledPackageInfo -> InstalledPackageInfo
-setInstalledPackageId pkginfo@InstalledPackageInfo {
-                        installedPackageId = InstalledPackageId "",
-                        sourcePackageId    = pkgid
-                      }
-                    = pkginfo {
-                        --TODO use a proper named function for the conversion
-                        -- from source package id to installed package id
-                        installedPackageId = InstalledPackageId (display pkgid)
-                      }
-setInstalledPackageId pkginfo = pkginfo
-
--- -----------------------------------------------------------------------------
--- Building
-
--- |FIX: For now, the target must contain a main module.  Not used
--- ATM. Re-add later.
-buildLib :: Verbosity -> PackageDescription -> LocalBuildInfo
-                      -> Library            -> ComponentLocalBuildInfo -> IO ()
-buildLib verbosity pkg_descr lbi lib clbi = do
-  libName <- case componentLibraries clbi of
-             [libName] -> return libName
-             [] -> die "No library name found when building library"
-             _  -> die "Multiple library names found when building library"
-  let conf = withPrograms lbi
-      Just nhcProg = lookupProgram nhcProgram conf
-  let bi = libBuildInfo lib
-      modules = exposedModules lib ++ otherModules bi
-      -- Unsupported extensions have already been checked by configure
-      languageFlags = languageToFlags (compiler lbi) (defaultLanguage bi)
-                   ++ extensionsToFlags (compiler lbi) (usedExtensions bi)
-  inFiles <- getModulePaths lbi bi modules
-  let targetDir = buildDir lbi
-      srcDirs  = nub (map takeDirectory inFiles)
-      destDirs = map (targetDir </>) srcDirs
-  mapM_ (createDirectoryIfMissingVerbose verbosity True) destDirs
-  rawSystemProgramConf verbosity hmakeProgram conf $
-       ["-hc=" ++ programPath nhcProg]
-    ++ nhcVerbosityOptions verbosity
-    ++ ["-d", targetDir, "-hidir", targetDir]
-    ++ maybe [] (hcOptions NHC . libBuildInfo)
-                           (library pkg_descr)
-    ++ languageFlags
-    ++ concat [ ["-package", display (packageName pkgid) ]
-              | (_, pkgid) <- componentPackageDeps clbi ]
-    ++ inFiles
-{-
-  -- build any C sources
-  unless (null (cSources bi)) $ do
-     info verbosity "Building C Sources..."
-     let commonCcArgs = (if verbosity >= deafening then ["-v"] else [])
-                     ++ ["-I" ++ dir | dir <- includeDirs bi]
-                     ++ [opt | opt <- ccOptions bi]
-                     ++ (if withOptimization lbi then ["-O2"] else [])
-     flip mapM_ (cSources bi) $ \cfile -> do
-       let ofile = targetDir </> cfile `replaceExtension` objExtension
-       createDirectoryIfMissingVerbose verbosity True (takeDirectory ofile)
-       rawSystemProgramConf verbosity hmakeProgram conf
-         (commonCcArgs ++ ["-c", cfile, "-o", ofile])
--}
-  -- link:
-  info verbosity "Linking..."
-  let --cObjs = [ targetDir </> cFile `replaceExtension` objExtension
-      --        | cFile <- cSources bi ]
-      libFilePath = targetDir </> mkLibName libName
-      hObjs = [ targetDir </> ModuleName.toFilePath m <.> objExtension
-              | m <- modules ]
-
-  unless (null hObjs {-&& null cObjs-}) $ do
-    -- first remove library if it exists
-    removeFile libFilePath `catchIO` \_ -> return ()
-
-    let arVerbosity | verbosity >= deafening = "v"
-                    | verbosity >= normal = ""
-                    | otherwise = "c"
-
-    rawSystemProgramConf verbosity arProgram (withPrograms lbi) $
-         ["q"++ arVerbosity, libFilePath]
-      ++ hObjs
---    ++ cObjs
-
--- | Building an executable for NHC.
-buildExe :: Verbosity -> PackageDescription -> LocalBuildInfo
-                      -> Executable         -> ComponentLocalBuildInfo -> IO ()
-buildExe verbosity pkg_descr lbi exe clbi = do
-  let conf = withPrograms lbi
-      Just nhcProg = lookupProgram nhcProgram conf
-  when (dropExtension (modulePath exe) /= exeName exe) $
-    die $ "hmake does not support exe names that do not match the name of "
-       ++ "the 'main-is' file. You will have to rename your executable to "
-       ++ show (dropExtension (modulePath exe))
-  let bi = buildInfo exe
-      modules = otherModules bi
-      -- Unsupported extensions have already been checked by configure
-      languageFlags = languageToFlags (compiler lbi) (defaultLanguage bi)
-                   ++ extensionsToFlags (compiler lbi) (usedExtensions bi)
-  inFiles <- getModulePaths lbi bi modules
-  let targetDir = buildDir lbi </> exeName exe
-      exeDir    = targetDir </> (exeName exe ++ "-tmp")
-      srcDirs   = nub (map takeDirectory (modulePath exe : inFiles))
-      destDirs  = map (exeDir </>) srcDirs
-  mapM_ (createDirectoryIfMissingVerbose verbosity True) destDirs
-  rawSystemProgramConf verbosity hmakeProgram conf $
-       ["-hc=" ++ programPath nhcProg]
-    ++ nhcVerbosityOptions verbosity
-    ++ ["-d", targetDir, "-hidir", targetDir]
-    ++ maybe [] (hcOptions NHC . libBuildInfo)
-                           (library pkg_descr)
-    ++ languageFlags
-    ++ concat [ ["-package", display (packageName pkgid) ]
-              | (_, pkgid) <- componentPackageDeps clbi ]
-    ++ inFiles
-    ++ [exeName exe]
-
-nhcVerbosityOptions :: Verbosity -> [String]
-nhcVerbosityOptions verbosity
-     | verbosity >= deafening = ["-v"]
-     | verbosity >= normal    = []
-     | otherwise              = ["-q"]
-
---TODO: where to put this? it's duplicated in .Simple too
-getModulePaths :: LocalBuildInfo -> BuildInfo -> [ModuleName] -> IO [FilePath]
-getModulePaths lbi bi modules = sequence
-   [ findFileWithExtension ["hs", "lhs"] (buildDir lbi : hsSourceDirs bi)
-       (ModuleName.toFilePath module_) >>= maybe (notFound module_) (return . normalise)
-   | module_ <- modules ]
-   where notFound module_ = die $ "can't find source for module " ++ display module_
-
--- -----------------------------------------------------------------------------
--- Installing
-
--- |Install executables for NHC.
-installExe :: Verbosity -- ^verbosity
-           -> FilePath  -- ^install location
-           -> FilePath  -- ^Build location
-           -> (FilePath, FilePath)  -- ^Executable (prefix,suffix)
-           -> Executable
-           -> IO ()
-installExe verbosity pref buildPref (progprefix,progsuffix) exe
-    = do createDirectoryIfMissingVerbose verbosity True pref
-         let exeBaseName = exeName exe
-             exeFileName = exeBaseName <.> exeExtension
-             fixedExeFileName = (progprefix ++ exeBaseName ++ progsuffix) <.> exeExtension
-         installExecutableFile verbosity
-           (buildPref </> exeBaseName </> exeFileName)
-           (pref </> fixedExeFileName)
-
--- |Install for nhc98: .hi and .a files
-installLib    :: Verbosity -- ^verbosity
-              -> FilePath  -- ^install location
-              -> FilePath  -- ^Build location
-              -> PackageIdentifier
-              -> Library
-              -> ComponentLocalBuildInfo
-              -> IO ()
-installLib verbosity pref buildPref _pkgid lib clbi
-    = do let bi = libBuildInfo lib
-             modules = exposedModules lib ++ otherModules bi
-         findModuleFiles [buildPref] ["hi"] modules
-           >>= installOrdinaryFiles verbosity pref
-         let libNames = map mkLibName (componentLibraries clbi)
-             installLib' libName = installOrdinaryFile verbosity
-                                                       (buildPref </> libName)
-                                                       (pref </> libName)
-         mapM_ installLib' libNames
diff --git a/Cabal/Distribution/Simple/PreProcess.hs b/Cabal/Distribution/Simple/PreProcess.hs
index e4db4d8db0..381256d4c6 100644
--- a/Cabal/Distribution/Simple/PreProcess.hs
+++ b/Cabal/Distribution/Simple/PreProcess.hs
@@ -192,11 +192,9 @@ preprocessComponent pd comp lbi isSrcDist verbosity handlers = case comp of
       BenchmarkUnsupported tt -> die $ "No support for preprocessing benchmark "
                                  ++ "type " ++ display tt
   where
-    builtinHaskellSuffixes
-      | NHC == compilerFlavor (compiler lbi) = ["hs", "lhs", "gc"]
-      | otherwise                            = ["hs", "lhs"]
-    builtinCSuffixes = cSourceExtensions
-    builtinSuffixes = builtinHaskellSuffixes ++ builtinCSuffixes
+    builtinHaskellSuffixes = ["hs", "lhs"]
+    builtinCSuffixes       = cSourceExtensions
+    builtinSuffixes        = builtinHaskellSuffixes ++ builtinCSuffixes
     localHandlers bi = [(ext, h bi lbi) | (ext, h) <- handlers]
     pre dirs dir lhndlrs fp =
       preprocessFile dirs dir isSrcDist fp verbosity builtinSuffixes lhndlrs
@@ -507,8 +505,6 @@ platformDefines lbi =
       map (\os'   -> "-D" ++ os'   ++ "_HOST_OS=1")   osStr ++
       map (\arch' -> "-D" ++ arch' ++ "_HOST_ARCH=1") archStr
     JHC  -> ["-D__JHC__=" ++ versionInt version]
-    NHC  -> ["-D__NHC__=" ++ versionInt version]
-    Hugs -> ["-D__HUGS__"]
     HaskellSuite {} ->
       ["-D__HASKELL_SUITE__"] ++
         map (\os'   -> "-D" ++ os'   ++ "_HOST_OS=1")   osStr ++
diff --git a/Cabal/Distribution/Simple/Program.hs b/Cabal/Distribution/Simple/Program.hs
index dd35b427c5..312299b488 100644
--- a/Cabal/Distribution/Simple/Program.hs
+++ b/Cabal/Distribution/Simple/Program.hs
@@ -93,11 +93,8 @@ module Distribution.Simple.Program (
     , ghcPkgProgram
     , lhcProgram
     , lhcPkgProgram
-    , nhcProgram
     , hmakeProgram
     , jhcProgram
-    , hugsProgram
-    , ffihugsProgram
     , uhcProgram
     , gccProgram
     , arProgram
diff --git a/Cabal/Distribution/Simple/Program/Builtin.hs b/Cabal/Distribution/Simple/Program/Builtin.hs
index 3ca02817e7..4245961c60 100644
--- a/Cabal/Distribution/Simple/Program/Builtin.hs
+++ b/Cabal/Distribution/Simple/Program/Builtin.hs
@@ -20,11 +20,8 @@ module Distribution.Simple.Program.Builtin (
     ghcPkgProgram,
     lhcProgram,
     lhcPkgProgram,
-    nhcProgram,
     hmakeProgram,
     jhcProgram,
-    hugsProgram,
-    ffihugsProgram,
     haskellSuiteProgram,
     haskellSuitePkgProgram,
     uhcProgram,
@@ -77,11 +74,8 @@ builtinPrograms =
     -- compilers and related progs
       ghcProgram
     , ghcPkgProgram
-    , hugsProgram
-    , ffihugsProgram
     , haskellSuiteProgram
     , haskellSuitePkgProgram
-    , nhcProgram
     , hmakeProgram
     , jhcProgram
     , lhcProgram
@@ -150,16 +144,6 @@ lhcPkgProgram = (simpleProgram "lhc-pkg") {
         _               -> ""
   }
 
-nhcProgram :: Program
-nhcProgram = (simpleProgram "nhc98") {
-    programFindVersion = findProgramVersion "--version" $ \str ->
-      -- Invoking "nhc98 --version" gives a string like
-      -- "/usr/local/bin/nhc98: v1.20 (2007-11-22)"
-      case words str of
-        (_:('v':ver):_) -> ver
-        _               -> ""
-  }
-
 hmakeProgram :: Program
 hmakeProgram = (simpleProgram "hmake") {
     programFindVersion = findProgramVersion "--version" $ \str ->
@@ -195,13 +179,6 @@ hpcProgram = (simpleProgram "hpc")
                 _ -> ""
     }
 
--- AArgh! Finding the version of hugs or ffihugs is almost impossible.
-hugsProgram :: Program
-hugsProgram = simpleProgram "hugs"
-
-ffihugsProgram :: Program
-ffihugsProgram = simpleProgram "ffihugs"
-
 -- This represents a haskell-suite compiler. Of course, the compiler
 -- itself probably is not called "haskell-suite", so this is not a real
 -- program. (But we don't know statically the name of the actual compiler,
diff --git a/Cabal/Distribution/Simple/Register.hs b/Cabal/Distribution/Simple/Register.hs
index de74ad4871..00c98a2af3 100644
--- a/Cabal/Distribution/Simple/Register.hs
+++ b/Cabal/Distribution/Simple/Register.hs
@@ -44,7 +44,6 @@ import Distribution.Simple.LocalBuildInfo
 import Distribution.Simple.BuildPaths (haddockName)
 import qualified Distribution.Simple.GHC  as GHC
 import qualified Distribution.Simple.LHC  as LHC
-import qualified Distribution.Simple.Hugs as Hugs
 import qualified Distribution.Simple.UHC  as UHC
 import qualified Distribution.Simple.HaskellSuite as HaskellSuite
 import Distribution.Simple.Compiler
@@ -61,7 +60,7 @@ import Distribution.Simple.Setup
          ( RegisterFlags(..), CopyDest(..)
          , fromFlag, fromFlagOrDefault, flagToMaybe )
 import Distribution.PackageDescription
-         ( PackageDescription(..), Library(..), BuildInfo(..), hcOptions )
+         ( PackageDescription(..), Library(..), BuildInfo(..) )
 import Distribution.Package
          ( Package(..), packageName, InstalledPackageId(..) )
 import Distribution.InstalledPackageInfo
@@ -78,12 +77,10 @@ import Distribution.Text
 import Distribution.Version ( Version(..) )
 import Distribution.Verbosity as Verbosity
          ( Verbosity, normal )
-import Distribution.Compat.Exception
-         ( tryIO )
 
 import System.FilePath ((</>), (<.>), isAbsolute)
 import System.Directory
-         ( getCurrentDirectory, removeDirectoryRecursive )
+         ( getCurrentDirectory )
 
 import Control.Monad (when)
 import Data.Maybe
@@ -140,9 +137,7 @@ register pkg@PackageDescription { library       = Just lib  } lbi regFlags
                    writeHcPkgRegisterScript verbosity installedPkgInfo ghcPkg packageDbs
         LHC  -> do (lhcPkg, _) <- requireProgram verbosity lhcPkgProgram (withPrograms lbi)
                    writeHcPkgRegisterScript verbosity installedPkgInfo lhcPkg packageDbs
-        Hugs -> notice verbosity "Registration scripts not needed for hugs"
         JHC  -> notice verbosity "Registration scripts not needed for jhc"
-        NHC  -> notice verbosity "Registration scripts not needed for nhc98"
         UHC  -> notice verbosity "Registration scripts not needed for uhc"
         _    -> die "Registration scripts are not implemented for this compiler"
 
@@ -218,10 +213,8 @@ registerPackage verbosity installedPkgInfo pkg lbi inplace packageDbs = do
   case compilerFlavor (compiler lbi) of
     GHC  -> GHC.registerPackage  verbosity installedPkgInfo pkg lbi inplace packageDbs
     LHC  -> LHC.registerPackage  verbosity installedPkgInfo pkg lbi inplace packageDbs
-    Hugs -> Hugs.registerPackage verbosity installedPkgInfo pkg lbi inplace packageDbs
     UHC  -> UHC.registerPackage  verbosity installedPkgInfo pkg lbi inplace packageDbs
     JHC  -> notice verbosity "Registering for jhc (nothing to do)"
-    NHC  -> notice verbosity "Registering for nhc98 (nothing to do)"
     HaskellSuite {} ->
       HaskellSuite.registerPackage verbosity installedPkgInfo pkg lbi inplace packageDbs
     _    -> die "Registering is not implemented for this compiler"
@@ -295,7 +288,6 @@ generalInstalledPackageInfo adjustRelIncDirs pkg ipid lib lbi clbi installDirs =
     IPI.includeDirs        = absinc ++ adjustRelIncDirs relinc,
     IPI.includes           = includes bi,
     IPI.depends            = map fst (componentPackageDeps clbi),
-    IPI.hugsOptions        = hcOptions Hugs bi,
     IPI.ccOptions          = [], -- Note. NOT ccOptions bi!
                                  -- We don't want cc-options to be propagated
                                  -- to C compilations in other packages.
@@ -388,7 +380,6 @@ unregister pkg lbi regFlags = do
       verbosity = fromFlag (regVerbosity regFlags)
       packageDb = fromFlagOrDefault (registrationPackageDB (withPackageDB lbi))
                                     (regPackageDB regFlags)
-      installDirs = absoluteInstallDirs pkg lbi NoCopyDest
   setupMessage verbosity "Unregistering" pkgid
   case compilerFlavor (compiler lbi) of
     GHC ->
@@ -399,14 +390,8 @@ unregister pkg lbi regFlags = do
            then writeFileAtomic unregScriptFileName
                   (BS.Char8.pack $ invocationAsSystemScript buildOS invocation)
             else runProgramInvocation verbosity invocation
-    Hugs -> do
-        _ <- tryIO $ removeDirectoryRecursive (libdir installDirs)
-        return ()
-    NHC -> do
-        _ <- tryIO $ removeDirectoryRecursive (libdir installDirs)
-        return ()
     _ ->
-        die ("only unregistering with GHC and Hugs is implemented")
+        die ("unregistering is only implemented for GHC")
 
 unregScriptFileName :: FilePath
 unregScriptFileName = case buildOS of
diff --git a/Cabal/Distribution/Simple/Setup.hs b/Cabal/Distribution/Simple/Setup.hs
index c83bc48256..7e0c02de49 100644
--- a/Cabal/Distribution/Simple/Setup.hs
+++ b/Cabal/Distribution/Simple/Setup.hs
@@ -262,7 +262,7 @@ data ConfigFlags = ConfigFlags {
     configProgramPathExtra :: NubList FilePath,  -- ^Extend the $PATH
     configHcFlavor      :: Flag CompilerFlavor, -- ^The \"flavor\" of the
                                                 -- compiler, such as GHC or
-                                                -- Hugs.
+                                                -- JHC.
     configHcPath        :: Flag FilePath, -- ^given compiler location
     configHcPkg         :: Flag FilePath, -- ^given hc-pkg location
     configVanillaLib    :: Flag Bool,     -- ^Enable vanilla library
@@ -375,10 +375,8 @@ configureOptions showOrParseArgs =
       ,option [] ["compiler"] "compiler"
          configHcFlavor (\v flags -> flags { configHcFlavor = v })
          (choiceOpt [ (Flag GHC, ("g", ["ghc"]), "compile with GHC")
-                    , (Flag NHC, ([] , ["nhc98"]), "compile with NHC")
                     , (Flag JHC, ([] , ["jhc"]), "compile with JHC")
                     , (Flag LHC, ([] , ["lhc"]), "compile with LHC")
-                    , (Flag Hugs,([] , ["hugs"]), "compile with Hugs")
                     , (Flag UHC, ([] , ["uhc"]), "compile with UHC")
 
                     -- "haskell-suite" compiler id string will be replaced
@@ -397,13 +395,7 @@ configureOptions showOrParseArgs =
          (reqArgFlag "PATH")
       ]
    ++ map liftInstallDirs installDirsOptions
-   ++ [option "b" ["scratchdir"]
-         "directory to receive the built package (hugs-only)"
-         configScratchDir (\v flags -> flags { configScratchDir = v })
-         (reqArgFlag "DIR")
-      --TODO: eliminate scratchdir flag
-
-      ,option "" ["program-prefix"]
+   ++ [option "" ["program-prefix"]
           "prefix to be applied to installed executables"
           configProgPrefix
           (\v flags -> flags { configProgPrefix = v })
diff --git a/Cabal/Language/Haskell/Extension.hs b/Cabal/Language/Haskell/Extension.hs
index b368fcc1af..67f5307c1d 100644
--- a/Cabal/Language/Haskell/Extension.hs
+++ b/Cabal/Language/Haskell/Extension.hs
@@ -83,7 +83,7 @@ classifyLanguage = \str -> case lookup str langTable of
 -- Note: if you add a new 'KnownExtension':
 --
 -- * also add it to the Distribution.Simple.X.languageExtensions lists
---   (where X is each compiler: GHC, JHC, Hugs, NHC)
+--   (where X is each compiler: GHC, JHC, LHC, UHC, HaskellSuite)
 --
 -- | This represents language extensions beyond a base 'Language' definition
 -- (such as 'Haskell98') that are supported by some implementations, usually
diff --git a/Cabal/Makefile b/Cabal/Makefile
index c9a969e470..f8a2b4720f 100644
--- a/Cabal/Makefile
+++ b/Cabal/Makefile
@@ -29,9 +29,6 @@ setup: $(SOURCES) Setup.hs
 	-mkdir -p dist/setup
 	$(HC) $(GHCFLAGS) --make -i. -odir dist/setup -hidir dist/setup Setup.hs -o setup
 
-Setup-nhc:
-	hmake -nhc98 -package base -prelude Setup
-
 $(CONFIG_STAMP): setup Cabal.cabal
 	./setup configure --with-compiler=$(HC) --prefix=$(PREFIX)
 
@@ -42,19 +39,6 @@ $(BUILD_STAMP): $(CONFIG_STAMP) $(SOURCES)
 install: $(BUILD_STAMP)
 	./setup install
 
-hugsbootstrap:
-	rm -rf dist/tmp dist/hugs
-	mkdir -p dist/tmp
-	mkdir dist/hugs
-	cp -r Distribution dist/tmp
-	hugs-package dist/tmp dist/hugs
-	cp Setup.lhs Cabal.cabal dist/hugs
-
-hugsinstall: hugsbootstrap
-	cd dist/hugs && ./Setup.lhs configure --hugs
-	cd dist/hugs && ./Setup.lhs build
-	cd dist/hugs && ./Setup.lhs install
-
 # documentation...
 
 haddock: $(HADDOCK_STAMP)
diff --git a/Cabal/doc/developing-packages.markdown b/Cabal/doc/developing-packages.markdown
index 009822c212..bdbe1a4081 100644
--- a/Cabal/doc/developing-packages.markdown
+++ b/Cabal/doc/developing-packages.markdown
@@ -525,7 +525,6 @@ library
   exposed-modules: Foo
   extensions:      ForeignFunctionInterface
   ghc-options:     -Wall
-  nhc98-options:   -K4m
   if os(windows)
     build-depends: Win32
 ~~~~~~~~~~~~~~~~
@@ -619,7 +618,7 @@ infrastructure_ provided by the Cabal library (see
 [Distribution.Simple][dist-simple]). The simplicity lies in its
 interface rather that its implementation. It automatically handles
 preprocessing with standard preprocessors, and builds packages for all
-the Haskell implementations (except nhc98, for now).
+the Haskell implementations.
 
 The simple build infrastructure can also handle packages where building
 is governed by system-dependent parameters, if you specify a little more
@@ -689,9 +688,8 @@ _identifier_
 :   A letter followed by zero or more alphanumerics or underscores.
 
 _compiler_
-:   A compiler flavor (one of: `GHC`, `NHC`, `YHC`, `Hugs`, `HBC`,
-    `Helium`, `JHC`, or `LHC`) followed by a version range.  For
-    example, `GHC ==6.10.3`, or `LHC >=0.6 && <0.8`.
+:   A compiler flavor (one of: `GHC`, `JHC`, `UHC` or `LHC`) followed by a
+    version range.  For example, `GHC ==6.10.3`, or `LHC >=0.6 && <0.8`.
 
 ### Modules and preprocessors ###
 
@@ -1372,20 +1370,6 @@ values for these fields.
 `ghc-shared-options:` _token list_
 :   Additional options for GHC when the package is built as shared library.
 
-`hugs-options:` _token list_
-:   Additional options for Hugs. You can often achieve the same effect
-    using the `extensions` field, which is preferred.
-
-    Options required only by one module may be specified by placing an
-    `OPTIONS_HUGS` pragma in the source file affected.
-
-`nhc98-options:` _token list_
-:   Additional options for nhc98. You can often achieve the same effect
-    using the `extensions` field, which is preferred.
-
-    Options required only by one module may be specified by placing an
-    `OPTIONS_NHC98` pragma in the source file affected.
-
 `includes:` _filename list_
 :   A list of header files to be included in any compilations via C.
     This field applies to both header files that are already installed
@@ -1408,17 +1392,12 @@ values for these fields.
 
 `include-dirs:` _directory list_
 :   A list of directories to search for header files, when preprocessing
-    with `c2hs`, `hsc2hs`, `ffihugs`, `cpphs` or the C preprocessor, and
+    with `c2hs`, `hsc2hs`, `cpphs` or the C preprocessor, and
     also when compiling via C.
 
 `c-sources:` _filename list_
 :   A list of C source files to be compiled and linked with the Haskell files.
 
-    If you use this field, you should also name the C files in `CFILES`
-    pragmas in the Haskell source files that use them, e.g.: `{-# CFILES
-    dir/file1.c dir/file2.c #-}` These are ignored by the compilers, but
-    needed by Hugs.
-
 `extra-libraries:` _token list_
 :   A list of extra libraries to link with.
 
@@ -1705,11 +1684,11 @@ and outside then they are combined using the following rules.
 
     ~~~~~~~~~~~~~~~~
     Extensions: CPP
-    if impl(ghc) || impl(hugs)
+    if impl(ghc)
       Extensions: MultiParamTypeClasses
     ~~~~~~~~~~~~~~~~
 
-    when compiled using Hugs or GHC will be combined to
+    when compiled using GHC will be combined to
 
     ~~~~~~~~~~~~~~~~
     Extensions: CPP, MultiParamTypeClasses
diff --git a/Cabal/doc/installing-packages.markdown b/Cabal/doc/installing-packages.markdown
index fb23856544..ca881e51e2 100644
--- a/Cabal/doc/installing-packages.markdown
+++ b/Cabal/doc/installing-packages.markdown
@@ -280,7 +280,7 @@ and all options specified with `--configure-option=` are passed on.
 The following options govern the programs used to process the source
 files of a package:
 
-`--ghc` or `-g`, `--nhc`, `--jhc`, `--hugs`
+`--ghc` or `-g`, `--jhc`, `--lhc`, `--uhc`
 :   Specify which Haskell implementation to use to build the package.
     At most one of these flags may be given. If none is given, the
     implementation under which the setup script was compiled or
@@ -497,7 +497,6 @@ Option                     Windows Default
 `--prefix` (per-user)      `C:\Documents And Settings\user\Application Data\cabal`   `$HOME/.cabal`
 `--bindir`                 `$prefix\bin`                                             `$prefix/bin`
 `--libdir`                 `$prefix`                                                 `$prefix/lib`
-`--libsubdir` (Hugs)       `hugs\packages\$pkg`                                      `hugs/packages/$pkg`
 `--libsubdir` (others)     `$pkgid\$compiler`                                        `$pkgid/$compiler`
 `--libexecdir`             `$prefix\$pkgid`                                          `$prefix/libexec`
 `--datadir` (executable)   `$prefix`                                                 `$prefix/share`
@@ -512,15 +511,14 @@ Option                     Windows Default
 
 #### Prefix-independence ####
 
-On Windows, and when using Hugs on any system, it is possible to obtain
-the pathname of the running program. This means that we can construct an
-installable executable package that is independent of its absolute
-install location. The executable can find its auxiliary files by finding
-its own path and knowing the location of the other files relative to
-`$bindir`.  Prefix-independence is particularly
-useful: it means the user can choose the install location (i.e. the
-value of `$prefix`) at install-time, rather than
-having to bake the path into the binary when it is built.
+On Windows it is possible to obtain the pathname of the running program. This
+means that we can construct an installable executable package that is
+independent of its absolute install location. The executable can find its
+auxiliary files by finding its own path and knowing the location of the other
+files relative to `$bindir`.  Prefix-independence is particularly useful: it
+means the user can choose the install location (i.e. the value of `$prefix`) at
+install-time, rather than having to bake the path into the binary when it is
+built.
 
 In order to achieve this, we require that for an executable on Windows,
 all of `$bindir`, `$libdir`, `$datadir` and `$libexecdir` begin with
@@ -757,13 +755,6 @@ be controlled with the following command line options.
     It's also possible to enable `--allow-newer` permanently by setting
     `allow-newer: True` in the `~/.cabal/config` file.
 
-
-In the simple build infrastructure, an additional option is recognized:
-
-`--scratchdir=`_dir_
-:   Specify the directory into which the Hugs output will be placed
-    (default: `dist/scratch`).
-
 ## setup build ##
 
 Perform any preprocessing or compilation needed to make this package ready for installation.
diff --git a/Cabal/doc/misc.markdown b/Cabal/doc/misc.markdown
index 8d732edcea..8ad9612079 100644
--- a/Cabal/doc/misc.markdown
+++ b/Cabal/doc/misc.markdown
@@ -34,7 +34,7 @@ deprecated without breaking older packages.
 * `./setup configure`
   * `--prefix`
   * `--user`
-  * `--ghc`, `--hugs`
+  * `--ghc`, `--uhc`
   * `--verbose`
   * `--prefix`
 
-- 
GitLab