summaryrefslogtreecommitdiff
path: root/hadrian
diff options
context:
space:
mode:
Diffstat (limited to 'hadrian')
-rw-r--r--hadrian/src/Hadrian/Haskell/Cabal/Parse.hs69
-rw-r--r--hadrian/src/Hadrian/Haskell/Cabal/Type.hs1
-rw-r--r--hadrian/src/Oracles/ModuleFiles.hs12
-rw-r--r--hadrian/src/Packages.hs17
-rw-r--r--hadrian/src/Rules/Dependencies.hs2
-rw-r--r--hadrian/src/Rules/Documentation.hs14
-rw-r--r--hadrian/src/Rules/Generate.hs100
-rw-r--r--hadrian/src/Rules/Test.hs2
-rw-r--r--hadrian/src/Settings/Builders/Cabal.hs3
-rw-r--r--hadrian/src/Settings/Builders/Ghc.hs2
-rw-r--r--hadrian/src/Settings/Packages.hs4
11 files changed, 101 insertions, 125 deletions
diff --git a/hadrian/src/Hadrian/Haskell/Cabal/Parse.hs b/hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
index 8fe518349d..43c0c03a49 100644
--- a/hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
+++ b/hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
@@ -80,10 +80,12 @@ parsePackageData pkg = do
sorted = sort [ C.unPackageName p | C.Dependency p _ _ <- allDeps ]
deps = nubOrd sorted \\ [name]
depPkgs = catMaybes $ map findPackageByName deps
+ setupDeps = [ C.unPackageName p | C.Dependency p _ _ <- maybe [] C.setupDepends $ C.setupBuildInfo pd ]
+ setupDepPkgs = catMaybes $ map findPackageByName setupDeps
return $ PackageData name version
(C.fromShortText (C.synopsis pd))
(C.fromShortText (C.description pd))
- depPkgs gpd
+ depPkgs setupDepPkgs gpd
where
-- Collect an overapproximation of dependencies by ignoring conditionals
collectDeps :: Maybe (C.CondTree v [C.Dependency] a) -> [C.Dependency]
@@ -126,7 +128,9 @@ configurePackage :: Context -> Action ()
configurePackage context@Context {..} = do
putProgressInfo $ "| Configure package " ++ quote (pkgName package)
gpd <- pkgGenericDescription package
- depPkgs <- packageDependencies <$> readPackageData package
+ pd <- readPackageData package
+ let depPkgs = packageDependencies pd
+ let setupDepPkgs = packageSetupDependencies pd
-- Stage packages are those we have in this stage.
stagePkgs <- stagePackages stage
@@ -135,23 +139,6 @@ configurePackage context@Context {..} = do
| pkg <- depPkgs, pkg `elem` stagePkgs ]
need deps
- -- Figure out what hooks we need.
- hooks <- case C.buildType (C.flattenPackageDescription gpd) of
- C.Configure -> pure C.autoconfUserHooks
- -- The 'time' package has a 'C.Custom' Setup.hs, but it's actually
- -- 'C.Configure' plus a @./Setup test@ hook. However, Cabal is also
- -- 'C.Custom', but doesn't have a configure script.
- C.Custom -> do
- configureExists <- doesFileExist $
- replaceFileName (pkgCabalFile package) "configure"
- pure $ if configureExists then C.autoconfUserHooks else C.simpleUserHooks
- -- Not quite right, but good enough for us:
- _ | package == rts ->
- -- Don't try to do post configuration validation for 'rts'. This
- -- will simply not work, due to the @ld-options@ and @Stg.h@.
- pure $ C.simpleUserHooks { C.postConf = \_ _ _ _ -> return () }
- | otherwise -> pure C.simpleUserHooks
-
-- Compute the list of flags, and the Cabal configuration arguments
flavourArgs <- args <$> flavour
flagList <- interpret (target context (Cabal Flags stage) [] []) flavourArgs
@@ -163,14 +150,50 @@ configurePackage context@Context {..} = do
argList' = argList ++ ["--flags=" ++ unwords flagList, v]
when (verbosity >= Verbose) $
putProgressInfo $ "| Package " ++ quote (pkgName package) ++ " configuration flags: " ++ unwords argList'
- traced "cabal-configure" $
- C.defaultMainWithHooksNoReadArgs hooks gpd argList'
-
dir <- Context.buildPath context
+ createDirectory dir
+ case C.buildType (C.flattenPackageDescription gpd) of
+ C.Make -> error "Make build types are not currently supported by hadrian"
+ C.Simple
+ -- Don't try to do post configuration validation for 'rts'. This
+ -- will simply not work, due to the @ld-options@ and @Stg.h@.
+ | package == rts -> traced "cabal-configure" $ C.defaultMainWithHooksNoReadArgs C.simpleUserHooks{ C.postConf = \_ _ _ _ -> return () } gpd argList'
+ | otherwise -> traced "cabal-configure" $ C.defaultMainWithHooksNoReadArgs C.simpleUserHooks gpd argList'
+ C.Configure -> traced "cabal-configure" $ C.defaultMainWithHooksNoReadArgs C.autoconfUserHooks gpd argList'
+ C.Custom -> do
+ stage0Pkgs <- stagePackages Stage0
+ setup_deps <- sequence [ pkgConfFile (context { package = pkg, stage = Stage0 }) -- Need setup dependencies from Stage0
+ | pkg <- setupDepPkgs, pkg `elem` stage0Pkgs ]
+ need setup_deps
+ pkgFlags <- interpret (target context{stage = Stage0} (Ghc CompileHs Stage0) [] []) packageDatabaseArgs
+ ghc <- setting SystemGhc
+ need [pkgPath package -/- "Setup.hs"]
+ verbose <- getVerbosity
+ let quietlyUnlessVerbose = if verbose >= Diagnostic then withVerbosity Diagnostic else quietly
+ quietlyUnlessVerbose $ cmd_ ghc $ concat
+ [ ["-hide-all-packages", "-package-env -", "-no-user-package-db"]
+ , pkgFlags
+ , concat [["-package", pkgName p] | p <- setupDepPkgs]
+ , [pkgPath package -/- "Setup.hs", "-outputdir", dir -/- "setup-output", "-o", dir -/- "Setup" <.> exe]
+ ]
+ hadrianEnv <- if
+ | package == ghcBoot -> do
+ versionEnv <- interpretInContext context generateVersionHs
+ platformEnv <- interpretInContext context generatePlatformHostHs
+ pure $ show (versionEnv ++ platformEnv)
+ | package == compiler -> do
+ configEnv <- interpretInContext context generateConfigHs
+ pure $ show configEnv
+ | otherwise -> pure "[]"
+ cmd_ (AddEnv "HADRIAN_SETTINGS" hadrianEnv) (Traced "cabal-configure") (dir -/- "Setup" <.> exe) argList'
+
files <- liftIO $ getDirectoryFilesIO "." [ dir -/- "include" -/- "**"
, dir -/- "*.buildinfo"
, dir -/- "lib" -/- "**"
- , dir -/- "config.*" ]
+ , dir -/- "config.*"
+ , dir -/- "Setup" <.> exe
+ , dir -/- "build" -/- "global-autogen" -/- "**"
+ ]
produces files
-- | Copy the 'Package' of a given 'Context' into the package database
diff --git a/hadrian/src/Hadrian/Haskell/Cabal/Type.hs b/hadrian/src/Hadrian/Haskell/Cabal/Type.hs
index 664c7de790..ad1e98bdc4 100644
--- a/hadrian/src/Hadrian/Haskell/Cabal/Type.hs
+++ b/hadrian/src/Hadrian/Haskell/Cabal/Type.hs
@@ -30,6 +30,7 @@ data PackageData = PackageData
, synopsis :: String
, description :: String
, packageDependencies :: [Package]
+ , packageSetupDependencies :: [Package]
, genericPackageDescription :: GenericPackageDescription
} deriving (Eq, Generic, Show, Typeable)
diff --git a/hadrian/src/Oracles/ModuleFiles.hs b/hadrian/src/Oracles/ModuleFiles.hs
index b53a5901e1..9238b1df3e 100644
--- a/hadrian/src/Oracles/ModuleFiles.hs
+++ b/hadrian/src/Oracles/ModuleFiles.hs
@@ -80,11 +80,13 @@ findGenerator Context {..} file = do
return (source, builder)
-- | Find all Haskell source files for a given 'Context'.
-hsSources :: Context -> Action [FilePath]
+hsSources :: Context
+ -> Action [FilePath]
hsSources context = do
let modFile (m, Nothing)
- | "Paths_" `isPrefixOf` m = autogenFile context m
- | otherwise = generatedFile context m
+ | "Paths_" `isPrefixOf` m = autogenFile context m
+ -- | any (("//"++moduleSource m) ?==) gens = generatedFile context m
+ | otherwise = globalAutogenFile context m
modFile (m, Just file )
| takeExtension file `elem` haskellExtensions = return file
| otherwise = generatedFile context m
@@ -106,6 +108,10 @@ generatedFile context moduleName = buildPath context <&> (-/- moduleSource modul
autogenFile :: Context -> ModuleName -> Action FilePath
autogenFile context modName = autogenPath context <&> (-/- moduleSource modName)
+-- | Generated module files live in the 'Context' specific build directory.
+globalAutogenFile :: Context -> ModuleName -> Action FilePath
+globalAutogenFile context modName = globalAutogenPath context <&> (-/- moduleSource modName)
+
-- | Turn a module name (e.g. @Data.Functor@) to a path (e.g. @Data/Functor.hs@).
moduleSource :: ModuleName -> FilePath
moduleSource moduleName = replaceEq '.' '/' moduleName <.> "hs"
diff --git a/hadrian/src/Packages.hs b/hadrian/src/Packages.hs
index a44e3cd95e..c48e2cbf3c 100644
--- a/hadrian/src/Packages.hs
+++ b/hadrian/src/Packages.hs
@@ -4,15 +4,15 @@ module Packages (
array, base, binary, bytestring, cabal, cabalSyntax, checkPpr,
checkExact, countDeps,
compareSizes, compiler, containers, deepseq, deriveConstants, directory,
- exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh,
- ghcCompact, ghcHeap, ghci, ghciWrapper, ghcPkg, ghcPrim, haddock, haskeline,
+ exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot,
+ ghcBootTh, ghcCompact, ghcHeap, ghci, ghciWrapper, ghcPkg, ghcPrim, haddock, haskeline,
hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, iservProxy,
libffi, libiserv, mtl, parsec, pretty, primitive, process, remoteIserv, rts,
runGhc, stm, templateHaskell, terminfo, text, time, timeout, touchy,
transformers, unlit, unix, win32, xhtml, noteLinter, ghcPackages, isGhcPackage,
-- * Package information
- programName, nonHsMainPackage, autogenPath, programPath, timeoutPath,
+ programName, nonHsMainPackage, autogenPath, globalAutogenPath, programPath, timeoutPath,
rtsContext, rtsBuildPath, libffiBuildPath,
ensureConfigured
) where
@@ -34,9 +34,9 @@ ghcPackages :: [Package]
ghcPackages =
[ array, base, binary, bytestring, cabalSyntax, cabal, checkPpr, checkExact, countDeps
, compareSizes, compiler, containers, deepseq, deriveConstants, directory
- , exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh
- , ghcCompact, ghcHeap, ghci, ghciWrapper, ghcPkg, ghcPrim, haddock, haskeline, hsc2hs
- , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, libffi, libiserv, mtl
+ , exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot
+ , ghcBootTh , ghcCompact, ghcHeap, ghci, ghciWrapper, ghcPkg, ghcPrim, haddock, haskeline
+ , hsc2hs , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, libffi, libiserv, mtl
, parsec, pretty, process, rts, runGhc, stm, templateHaskell
, terminfo, text, time, touchy, transformers, unlit, unix, win32, xhtml
, timeout, noteLinter ]
@@ -196,6 +196,11 @@ autogenPath context@Context {..}
where
autogen dir = contextPath context <&> (-/- dir -/- "autogen")
+globalAutogenPath :: Context -> Action FilePath
+globalAutogenPath context= autogen "build"
+ where
+ autogen dir = contextPath context <&> (-/- dir -/- "global-autogen")
+
-- | Make sure a given context has already been fully configured. The
-- implementation simply calls 'need' on the context's @autogen/cabal_macros.h@
-- file, which triggers 'configurePackage' and 'buildAutogenFiles'. Why this
diff --git a/hadrian/src/Rules/Dependencies.hs b/hadrian/src/Rules/Dependencies.hs
index 9a2a23354f..f277010e05 100644
--- a/hadrian/src/Rules/Dependencies.hs
+++ b/hadrian/src/Rules/Dependencies.hs
@@ -21,8 +21,8 @@ buildPackageDependencies rs = do
root -/- "**/.dependencies.mk" %> \mk -> do
DepMkFile stage pkgpath <- getDepMkFile root mk
let context = Context stage (unsafeFindPackageByPath pkgpath) vanilla
- srcs <- hsSources context
gens <- interpretInContext context generatedDependencies
+ srcs <- hsSources context
need (srcs ++ gens)
if null srcs
then writeFileChanged mk ""
diff --git a/hadrian/src/Rules/Documentation.hs b/hadrian/src/Rules/Documentation.hs
index 6898fd12e5..d0c94de08d 100644
--- a/hadrian/src/Rules/Documentation.hs
+++ b/hadrian/src/Rules/Documentation.hs
@@ -10,10 +10,10 @@ import Hadrian.BuildPath
import Hadrian.Haskell.Cabal
import Hadrian.Haskell.Cabal.Type
-import Rules.Generate (ghcPrimDependencies)
+import Rules.Generate (generatedDependencies)
import Base
import Context
-import Expression (getContextData, interpretInContext, (?), package)
+import Expression (getContextData, interpretInContext)
import Flavour
import Oracles.ModuleFiles
import Oracles.Setting (topDirectory)
@@ -241,12 +241,8 @@ buildPackageDocumentation = do
need [ takeDirectory file -/- "haddock-prologue.txt"]
haddocks <- haddockDependencies context
- -- `ghc-prim` has a source file for 'GHC.Prim' which is generated just
- -- for Haddock. We need to 'union' (instead of '++') to avoid passing
- -- 'GHC.PrimopWrappers' (which unfortunately shows up in both
- -- `generatedSrcs` and `vanillaSrcs`) to Haddock twice.
- generatedSrcs <- interpretInContext context (Expression.package ghcPrim ? ghcPrimDependencies)
- vanillaSrcs <- hsSources context
+ generatedSrcs <- interpretInContext context generatedDependencies
+ vanillaSrcs <- hsSources generatedSrcs context
let srcs = vanillaSrcs `union` generatedSrcs
need $ srcs ++ haddocks
@@ -257,7 +253,7 @@ buildPackageDocumentation = do
let haddockWay = if dynamicPrograms then dynamic else vanilla
statsFilesDir <- haddockStatsFilesDir
createDirectory statsFilesDir
- build $ target (context {way = haddockWay}) (Haddock BuildPackage) srcs [file]
+ build $ target (context {way = haddockWay}) (Haddock BuildPackage) (filter ((".hs-incl" /=) . takeExtension) srcs) [file]
produces [
statsFilesDir </> pkgName (Context.package context) <.> "t"
]
diff --git a/hadrian/src/Rules/Generate.hs b/hadrian/src/Rules/Generate.hs
index e19d058425..95baee6e55 100644
--- a/hadrian/src/Rules/Generate.hs
+++ b/hadrian/src/Rules/Generate.hs
@@ -1,7 +1,10 @@
module Rules.Generate (
isGeneratedCmmFile, compilerDependencies, generatePackageCode,
generateRules, copyRules, generatedDependencies,
- ghcPrimDependencies
+ ghcPrimDependencies,
+ generateVersionHs,
+ generatePlatformHostHs,
+ generateConfigHs
) where
import Base
@@ -99,8 +102,7 @@ generatePackageCode :: Context -> Rules ()
generatePackageCode context@(Context stage pkg _) = do
root <- buildRootRules
let dir = buildDir context
- generated f = (root -/- dir -/- "**/*.hs") ?== f && not ("//autogen/*" ?== f)
- go gen file = generate file context gen
+ generated f = (root -/- dir -/- "**/*.hs") ?== f && not ("//autogen/*" ?== f) && not ("//global-autogen/**" ?== f)
generated ?> \file -> do
let unpack = fromMaybe . error $ "No generator for " ++ file ++ "."
(src, builder) <- unpack <$> findGenerator context file
@@ -115,14 +117,10 @@ generatePackageCode context@(Context stage pkg _) = do
priority 2.0 $ do
when (pkg == compiler) $ do
root -/- "**" -/- dir -/- "GHC/Platform/Constants.hs" %> genPlatformConstantsType context
- root -/- "**" -/- dir -/- "GHC/Settings/Config.hs" %> go generateConfigHs
root -/- "**" -/- dir -/- "*.hs-incl" %> genPrimopCode context
when (pkg == ghcPrim) $ do
root -/- "**" -/- dir -/- "GHC/Prim.hs" %> genPrimopCode context
root -/- "**" -/- dir -/- "GHC/PrimopWrappers.hs" %> genPrimopCode context
- when (pkg == ghcBoot) $ do
- root -/- "**" -/- dir -/- "GHC/Version.hs" %> go generateVersionHs
- root -/- "**" -/- dir -/- "GHC/Platform/Host.hs" %> go generatePlatformHostHs
when (pkg == compiler) $ do
root -/- primopsTxt stage %> \file -> do
@@ -355,7 +353,7 @@ generateSettings = do
-- | Generate @Config.hs@ files.
-generateConfigHs :: Expr String
+generateConfigHs :: Expr [(String,String)]
generateConfigHs = do
stage <- getStage
let chooseSetting x y = getSetting $ if stage == Stage0 then x else y
@@ -364,35 +362,12 @@ generateConfigHs = do
trackGenerateHs
cProjectName <- getSetting ProjectName
cBooterVersion <- getSetting GhcVersion
- return $ unlines
- [ "module GHC.Settings.Config"
- , " ( module GHC.Version"
- , " , cBuildPlatformString"
- , " , cHostPlatformString"
- , " , cProjectName"
- , " , cBooterVersion"
- , " , cStage"
- , " ) where"
- , ""
- , "import GHC.Prelude"
- , ""
- , "import GHC.Version"
- , ""
- , "cBuildPlatformString :: String"
- , "cBuildPlatformString = " ++ show buildPlatform
- , ""
- , "cHostPlatformString :: String"
- , "cHostPlatformString = " ++ show hostPlatform
- , ""
- , "cProjectName :: String"
- , "cProjectName = " ++ show cProjectName
- , ""
- , "cBooterVersion :: String"
- , "cBooterVersion = " ++ show cBooterVersion
- , ""
- , "cStage :: String"
- , "cStage = show (" ++ show (fromEnum stage + 1) ++ " :: Int)"
- ]
+ pure [("cBuildPlatformString", buildPlatform)
+ ,("cHostPlatformString", hostPlatform)
+ ,("cProjectName", cProjectName)
+ ,("cBooterVersion", cBooterVersion)
+ ,("cStage", show (fromEnum stage + 1))
+ ]
-- | Generate @ghcautoconf.h@ header.
generateGhcAutoconfH :: Expr String
@@ -415,7 +390,7 @@ generateGhcAutoconfH = do
| otherwise = Just s
-- | Generate @Version.hs@ files.
-generateVersionHs :: Expr String
+generateVersionHs :: Expr [(String, String)]
generateVersionHs = do
trackGenerateHs
cProjectGitCommitId <- getSetting ProjectGitCommitId
@@ -424,47 +399,20 @@ generateVersionHs = do
cProjectPatchLevel <- getSetting ProjectPatchLevel
cProjectPatchLevel1 <- getSetting ProjectPatchLevel1
cProjectPatchLevel2 <- getSetting ProjectPatchLevel2
- return $ unlines
- [ "module GHC.Version where"
- , ""
- , "import Prelude -- See Note [Why do we import Prelude here?]"
- , ""
- , "cProjectGitCommitId :: String"
- , "cProjectGitCommitId = " ++ show cProjectGitCommitId
- , ""
- , "cProjectVersion :: String"
- , "cProjectVersion = " ++ show cProjectVersion
- , ""
- , "cProjectVersionInt :: String"
- , "cProjectVersionInt = " ++ show cProjectVersionInt
- , ""
- , "cProjectPatchLevel :: String"
- , "cProjectPatchLevel = " ++ show cProjectPatchLevel
- , ""
- , "cProjectPatchLevel1 :: String"
- , "cProjectPatchLevel1 = " ++ show cProjectPatchLevel1
- , ""
- , "cProjectPatchLevel2 :: String"
- , "cProjectPatchLevel2 = " ++ show cProjectPatchLevel2
- ]
+ return $ [("cProjectGitCommitId", cProjectGitCommitId)
+ ,("cProjectVersion", cProjectVersion)
+ ,("cProjectVersionInt", cProjectVersionInt)
+ ,("cProjectPatchLevel", cProjectPatchLevel)
+ ,("cProjectPatchLevel1", cProjectPatchLevel1)
+ ,("cProjectPatchLevel2", cProjectPatchLevel2)
+ ]
-- | Generate @Platform/Host.hs@ files.
-generatePlatformHostHs :: Expr String
+generatePlatformHostHs :: Expr [(String,String)]
generatePlatformHostHs = do
trackGenerateHs
cHostPlatformArch <- getSetting HostArchHaskell
cHostPlatformOS <- getSetting HostOsHaskell
- return $ unlines
- [ "module GHC.Platform.Host where"
- , ""
- , "import GHC.Platform.ArchOS"
- , ""
- , "hostPlatformArch :: Arch"
- , "hostPlatformArch = " ++ cHostPlatformArch
- , ""
- , "hostPlatformOS :: OS"
- , "hostPlatformOS = " ++ cHostPlatformOS
- , ""
- , "hostPlatformArchOS :: ArchOS"
- , "hostPlatformArchOS = ArchOS hostPlatformArch hostPlatformOS"
- ]
+ return $ [("hostPlatformArch", cHostPlatformArch)
+ ,("hostPlatformOS", cHostPlatformOS)
+ ]
diff --git a/hadrian/src/Rules/Test.hs b/hadrian/src/Rules/Test.hs
index fe0aba04cc..cce565b068 100644
--- a/hadrian/src/Rules/Test.hs
+++ b/hadrian/src/Rules/Test.hs
@@ -17,6 +17,7 @@ import Settings.Program (programContext)
import Target
import Utilities
import Context.Type
+import Rules.CabalReinstall (findCabalPackageDb)
import qualified System.Directory as IO
ghcConfigHsPath :: FilePath
@@ -195,6 +196,7 @@ testRules = do
pythonPath <- builderPath Python
+
-- Set environment variables for test's Makefile.
-- TODO: Ideally we would define all those env vars in 'env', so that
-- Shake can keep track of them, but it is not as easy as it seems
diff --git a/hadrian/src/Settings/Builders/Cabal.hs b/hadrian/src/Settings/Builders/Cabal.hs
index 1ef20147ae..59242d1c2e 100644
--- a/hadrian/src/Settings/Builders/Cabal.hs
+++ b/hadrian/src/Settings/Builders/Cabal.hs
@@ -178,10 +178,8 @@ configureArgs cFlags' ldFlags' = do
not (null values) ?
arg ("--configure-option=" ++ key ++ "=" ++ values)
cFlags = mconcat [ remove ["-Werror"] cArgs
- , getStagedSettingList ConfCcArgs
-- See https://github.com/snowleopard/hadrian/issues/523
, arg $ "-iquote"
-
, arg $ top -/- pkgPath pkg
, cFlags'
]
@@ -198,7 +196,6 @@ configureArgs cFlags' ldFlags' = do
, conf "--with-curses-libraries" $ arg =<< getSetting CursesLibDir
, conf "--host" $ arg =<< getSetting TargetPlatformFull
, conf "--with-cc" $ arg =<< getBuilderPath . (Cc CompileC) =<< getStage
- , notStage0 ? arg "--ghc-option=-ghcversion-file=rts/include/ghcversion.h"
]
bootPackageConstraints :: Args
diff --git a/hadrian/src/Settings/Builders/Ghc.hs b/hadrian/src/Settings/Builders/Ghc.hs
index a22e0079a7..e6b2fd9e9f 100644
--- a/hadrian/src/Settings/Builders/Ghc.hs
+++ b/hadrian/src/Settings/Builders/Ghc.hs
@@ -264,12 +264,14 @@ includeGhcArgs = do
srcDirs <- getContextData srcDirs
abSrcDirs <- exprIO $ mapM makeAbsolute [ (pkgPath pkg -/- dir) | dir <- srcDirs ]
autogen <- expr (autogenPath context)
+ gbl_autogen <- exprIO . makeAbsolute =<< expr (globalAutogenPath context)
cautogen <- exprIO (makeAbsolute autogen)
let cabalMacros = autogen -/- "cabal_macros.h"
expr $ need [cabalMacros]
mconcat [ arg "-i"
, arg $ "-i" ++ path
, arg $ "-i" ++ cautogen
+ , arg $ "-i" ++ gbl_autogen
, pure [ "-i" ++ d | d <- abSrcDirs ]
, cIncludeArgs
, pure ["-optP-include", "-optP" ++ cabalMacros] ]
diff --git a/hadrian/src/Settings/Packages.hs b/hadrian/src/Settings/Packages.hs
index 6114661e14..0eb5799c29 100644
--- a/hadrian/src/Settings/Packages.hs
+++ b/hadrian/src/Settings/Packages.hs
@@ -183,10 +183,6 @@ packageArgs = do
---------------------------------- rts ---------------------------------
, package rts ? rtsPackageArgs -- RTS deserves a separate function
- -------------------------------- runGhc --------------------------------
- , package runGhc ?
- builder Ghc ? input "**/Main.hs" ?
- (\version -> ["-cpp", "-DVERSION=" ++ show version]) <$> getSetting ProjectVersion
]
ghcBignumArgs :: Args