summaryrefslogtreecommitdiff
path: root/hadrian/src
diff options
context:
space:
mode:
authorJohn Ericson <git@JohnEricson.me>2019-05-08 02:52:35 -0400
committerMarge Bot <ben+marge-bot@smart-cactus.org>2019-10-04 21:44:29 -0400
commit05419e55cab272ed39790695f448b311f22669f7 (patch)
treeb3f652d4eb27c0ad6108edd6bca5fc73e165981a /hadrian/src
parentec93d2a90a2d4f189feafd21575b9e9ba5ba9a5d (diff)
downloadhaskell-05419e55cab272ed39790695f448b311f22669f7.tar.gz
Per stage headers, ghc_boot_platform.h -> stage 0 ghcplatform.h
The generated headers are now generated per stage, which means we can skip hacks like `ghc_boot_platform.h` and just have that be the stage 0 header as proper. In general, stages are to be embraced: freely generate everything in each stage but then just build what you depend on, and everything is symmetrical and efficient. Trying to avoid stages because bootstrapping is a mind bender just creates tons of bespoke mini-mind-benders that add up to something far crazier. Hadrian was pretty close to this "stage-major" approach already, and so was fairly easy to fix. Make needed more work, however: it did know about stages so at least there was a scaffold, but few packages except for the compiler cared, and the compiler used its own counting system. That said, make and Hadrian now work more similarly, which is good for the transition to Hadrian. The merits of embracing stage aside, the change may be worthy for easing that transition alone.
Diffstat (limited to 'hadrian/src')
-rw-r--r--hadrian/src/Base.hs23
-rw-r--r--hadrian/src/Builder.hs4
-rw-r--r--hadrian/src/Packages.hs11
-rw-r--r--hadrian/src/Rules.hs2
-rw-r--r--hadrian/src/Rules/Generate.hs148
-rw-r--r--hadrian/src/Settings/Builders/Cabal.hs12
-rw-r--r--hadrian/src/Settings/Builders/Common.hs5
-rw-r--r--hadrian/src/Settings/Builders/DeriveConstants.hs25
-rw-r--r--hadrian/src/Settings/Builders/Ghc.hs10
-rw-r--r--hadrian/src/Settings/Builders/HsCpp.hs4
10 files changed, 102 insertions, 142 deletions
diff --git a/hadrian/src/Base.hs b/hadrian/src/Base.hs
index bc4eab354e..f7f1029d4e 100644
--- a/hadrian/src/Base.hs
+++ b/hadrian/src/Base.hs
@@ -23,7 +23,7 @@ module Base (
-- * Paths
hadrianPath, configPath, configFile, sourcePath, shakeFilesDir,
- generatedDir, generatedPath, stageBinPath, stageLibPath, templateHscPath,
+ stageBinPath, stageLibPath, templateHscPath,
ghcBinDeps, ghcLibDeps, includesDependencies, haddockDeps,
relativePackageDbPath, packageDbPath, packageDbStamp, mingwStamp,
) where
@@ -68,22 +68,14 @@ sourcePath = hadrianPath -/- "src"
configH :: FilePath
configH = "mk/config.h"
-ghcVersionH :: Action FilePath
-ghcVersionH = generatedPath <&> (-/- "ghcversion.h")
+ghcVersionH :: Stage -> Action FilePath
+ghcVersionH stage = stageLibPath stage <&> (-/- "ghcversion.h")
-- | The directory in 'buildRoot' containing the Shake database and other
-- auxiliary files generated by Hadrian.
shakeFilesDir :: FilePath
shakeFilesDir = "hadrian"
--- | The directory in 'buildRoot' containing generated source files that are not
--- package-specific, e.g. @ghcplatform.h@.
-generatedDir :: FilePath
-generatedDir = "generated"
-
-generatedPath :: Action FilePath
-generatedPath = buildRoot <&> (-/- generatedDir)
-
-- | Path to the package database for a given build stage, relative to the build
-- root.
relativePackageDbPath :: Stage -> FilePath
@@ -122,10 +114,11 @@ ghcBinDeps stage = mapM (\f -> stageLibPath stage <&> (-/- f))
, "ghci-usage.txt"
]
-includesDependencies :: Action [FilePath]
-includesDependencies = do
- path <- generatedPath
- return $ (path -/-) <$> [ "ghcautoconf.h", "ghcplatform.h", "ghcversion.h" ]
+includesDependencies :: Stage -> Action [FilePath]
+includesDependencies stage = do
+ p <- stageLibPath stage
+ pure $ (p -/-) <$>
+ [ "ghcautoconf.h", "ghcplatform.h", "ghcversion.h" ]
-- | Files the `haddock` binary depends on
haddockDeps :: Stage -> Action [FilePath]
diff --git a/hadrian/src/Builder.hs b/hadrian/src/Builder.hs
index 587c62fa16..34027d7bbb 100644
--- a/hadrian/src/Builder.hs
+++ b/hadrian/src/Builder.hs
@@ -176,12 +176,12 @@ instance H.Builder Builder where
Autoreconf dir -> return [dir -/- "configure.ac"]
Configure dir -> return [dir -/- "configure"]
- Ghc _ Stage0 -> generatedGhcDependencies Stage0
+ Ghc _ Stage0 -> includesDependencies Stage0
Ghc _ stage -> do
root <- buildRoot
touchyPath <- programPath (vanillaContext Stage0 touchy)
unlitPath <- builderPath Unlit
- ghcgens <- generatedGhcDependencies stage
+ ghcgens <- includesDependencies stage
-- GHC from the previous stage is used to build artifacts in the
-- current stage. Need the previous stage's GHC deps.
diff --git a/hadrian/src/Packages.hs b/hadrian/src/Packages.hs
index 53ecb6897e..c4ae780fb3 100644
--- a/hadrian/src/Packages.hs
+++ b/hadrian/src/Packages.hs
@@ -13,7 +13,7 @@ module Packages (
-- * Package information
programName, nonHsMainPackage, autogenPath, programPath, timeoutPath,
rtsContext, rtsBuildPath, libffiBuildPath, libffiLibraryName,
- generatedGhcDependencies, ensureConfigured
+ ensureConfigured
) where
import Hadrian.Package
@@ -216,12 +216,3 @@ libffiLibraryName = do
(True , False) -> "ffi"
(False, False) -> "Cffi"
(_ , True ) -> "Cffi-6"
-
--- | Generated header files required by GHC in runtime.
-generatedGhcDependencies :: Stage -> Action [FilePath]
-generatedGhcDependencies stage = do
- let context = vanillaContext stage compiler
- bh <- buildPath context <&> (-/- "ghc_boot_platform.h")
- ch <- contextPath context <&> (-/- "ghc_boot_platform.h")
- is <- includesDependencies
- return $ is ++ [bh, ch]
diff --git a/hadrian/src/Rules.hs b/hadrian/src/Rules.hs
index e72623d4ce..3f6397fdcc 100644
--- a/hadrian/src/Rules.hs
+++ b/hadrian/src/Rules.hs
@@ -46,7 +46,7 @@ toolArgsTarget = do
(Ghc ToolArgs Stage0) [] ["ignored"]
-- need the autogenerated files so that they are precompiled
- generatedGhcDependencies Stage0 >>= need
+ includesDependencies Stage0 >>= need
interpret fake_target Rules.Generate.compilerDependencies >>= need
root <- buildRoot
diff --git a/hadrian/src/Rules/Generate.hs b/hadrian/src/Rules/Generate.hs
index ef3d8aa3b4..c2c3c14372 100644
--- a/hadrian/src/Rules/Generate.hs
+++ b/hadrian/src/Rules/Generate.hs
@@ -1,9 +1,11 @@
module Rules.Generate (
isGeneratedCmmFile, compilerDependencies, generatePackageCode,
- generateRules, copyRules, generatedDependencies, generatedGhcDependencies,
+ generateRules, copyRules, generatedDependencies,
ghcPrimDependencies
) where
+import Data.Foldable (for_)
+
import Base
import qualified Context
import Expression
@@ -16,6 +18,7 @@ import Packages
import Rules.Gmp
import Rules.Libffi
import Settings
+import Settings.Builders.DeriveConstants (deriveConstantsPairs)
import Target
import Utilities
@@ -38,8 +41,8 @@ ghcPrimDependencies = do
path <- expr $ buildPath (vanillaContext stage ghcPrim)
return [path -/- "GHC/Prim.hs", path -/- "GHC/PrimopWrappers.hs"]
-derivedConstantsDependencies :: [FilePath]
-derivedConstantsDependencies = fmap (generatedDir -/-)
+derivedConstantsFiles :: [FilePath]
+derivedConstantsFiles =
[ "DerivedConstants.h"
, "GHCConstantsHaskellExports.hs"
, "GHCConstantsHaskellType.hs"
@@ -47,13 +50,13 @@ derivedConstantsDependencies = fmap (generatedDir -/-)
compilerDependencies :: Expr [FilePath]
compilerDependencies = do
- root <- getBuildRoot
stage <- getStage
isGmp <- (== integerGmp) <$> getIntegerPackage
ghcPath <- expr $ buildPath (vanillaContext stage compiler)
gmpPath <- expr gmpBuildPath
rtsPath <- expr (rtsBuildPath stage)
- mconcat [ return ((root -/-) <$> derivedConstantsDependencies)
+ libDir <- expr $ stageLibPath stage
+ mconcat [ return $ (libDir -/-) <$> derivedConstantsFiles
, notStage0 ? isGmp ? return [gmpPath -/- gmpLibraryH]
, notStage0 ? return ((rtsPath -/-) <$> libffiHeaderFiles)
, return $ fmap (ghcPath -/-)
@@ -75,15 +78,15 @@ compilerDependencies = do
generatedDependencies :: Expr [FilePath]
generatedDependencies = do
- root <- getBuildRoot
stage <- getStage
rtsPath <- expr (rtsBuildPath stage)
- includes <- expr includesDependencies
+ includes <- expr $ includesDependencies stage
+ libDir <- expr $ stageLibPath stage
mconcat [ package compiler ? compilerDependencies
, package ghcPrim ? ghcPrimDependencies
, package rts ? return (fmap (rtsPath -/-) libffiHeaderFiles
++ includes
- ++ fmap (root -/-) derivedConstantsDependencies)
+ ++ ((libDir -/-) <$> derivedConstantsFiles))
, stage0 ? return includes ]
generate :: FilePath -> Context -> Expr String -> Action ()
@@ -121,21 +124,18 @@ generatePackageCode context@(Context stage pkg _) = do
when (pkg == compiler) $ do
root -/- primopsTxt stage %> \file -> do
- includes <- includesDependencies
+ includes <- includesDependencies stage
need $ [primopsSource] ++ includes
build $ target context HsCpp [primopsSource] [file]
- root -/- stageString stage -/- "**" -/- "ghc_boot_platform.h" %>
- go generateGhcBootPlatformH
-
when (pkg == rts) $ do
root -/- "**" -/- dir -/- "cmm/AutoApply.cmm" %> \file ->
build $ target context GenApply [] [file]
-- TODO: This should be fixed properly, e.g. generated here on demand.
- (root -/- "**" -/- dir -/- "DerivedConstants.h") <~ (buildRoot <&> (-/- generatedDir))
- (root -/- "**" -/- dir -/- "ghcautoconf.h") <~ (buildRoot <&> (-/- generatedDir))
- (root -/- "**" -/- dir -/- "ghcplatform.h") <~ (buildRoot <&> (-/- generatedDir))
- (root -/- "**" -/- dir -/- "ghcversion.h") <~ (buildRoot <&> (-/- generatedDir))
+ (root -/- "**" -/- dir -/- "DerivedConstants.h") <~ stageLibPath stage
+ (root -/- "**" -/- dir -/- "ghcautoconf.h") <~ stageLibPath stage
+ (root -/- "**" -/- dir -/- "ghcplatform.h") <~ stageLibPath stage
+ (root -/- "**" -/- dir -/- "ghcversion.h") <~ stageLibPath stage
where
pattern <~ mdir = pattern %> \file -> do
dir <- mdir
@@ -162,7 +162,6 @@ copyRules = do
prefix -/- "ghci-usage.txt" <~ return "driver"
prefix -/- "llvm-targets" <~ return "."
prefix -/- "llvm-passes" <~ return "."
- prefix -/- "platformConstants" <~ (buildRoot <&> (-/- generatedDir))
prefix -/- "template-hsc.h" <~ return (pkgPath hsc2hs)
prefix -/- "html/**" <~ return "utils/haddock/haddock-api/resources"
@@ -175,20 +174,19 @@ generateRules = do
(root -/- "ghc-stage1") <~+ ghcWrapper Stage1
(root -/- "ghc-stage2") <~+ ghcWrapper Stage2
- priority 2.0 $ (root -/- generatedDir -/- "ghcautoconf.h") <~ generateGhcAutoconfH
- priority 2.0 $ (root -/- generatedDir -/- "ghcplatform.h") <~ generateGhcPlatformH
- priority 2.0 $ (root -/- generatedDir -/- "ghcversion.h") <~ generateGhcVersionH
forM_ [Stage0 ..] $ \stage -> do
let prefix = root -/- stageString stage -/- "lib"
go gen file = generate file (semiEmptyTarget stage) gen
- priority 2.0 $ (prefix -/- "settings") %> go generateSettings
-
- -- TODO: simplify, get rid of fake rts context
- root -/- generatedDir -/- "**" %> \file -> do
- withTempDir $ \dir -> build $
- target (rtsContext Stage1) DeriveConstants [] [file, dir]
+ (prefix -/- "ghcplatform.h") %> go generateGhcPlatformH
+ (prefix -/- "settings") %> go generateSettings
+ (prefix -/- "ghcautoconf.h") %> go generateGhcAutoconfH
+ (prefix -/- "ghcversion.h") %> go generateGhcVersionH
+ -- TODO: simplify, get rid of fake rts context
+ for_ (fst <$> deriveConstantsPairs) $ \constantsFile ->
+ prefix -/- constantsFile %> \file -> do
+ withTempDir $ \dir -> build $
+ target (rtsContext stage) DeriveConstants [] [file, dir]
where
- file <~ gen = file %> \out -> generate out emptyTarget gen
file <~+ gen = file %> \out -> generate out emptyTarget gen >> makeExecutable out
-- TODO: Use the Types, Luke! (drop partial function)
@@ -225,39 +223,44 @@ cppify = replaceEq '-' '_' . replaceEq '.' '_'
generateGhcPlatformH :: Expr String
generateGhcPlatformH = do
trackGenerateHs
- hostPlatform <- getSetting HostPlatform
- hostArch <- getSetting HostArch
- hostOs <- getSetting HostOs
- hostVendor <- getSetting HostVendor
- targetPlatform <- getSetting TargetPlatform
- targetArch <- getSetting TargetArch
- targetOs <- getSetting TargetOs
- targetVendor <- getSetting TargetVendor
+ stage <- getStage
+ let chooseSetting x y = getSetting $ if stage == Stage0 then x else y
+ buildPlatform <- chooseSetting BuildPlatform HostPlatform
+ buildArch <- chooseSetting BuildArch HostArch
+ buildOs <- chooseSetting BuildOs HostOs
+ buildVendor <- chooseSetting BuildVendor HostVendor
+ hostPlatform <- chooseSetting HostPlatform TargetPlatform
+ hostArch <- chooseSetting HostArch TargetArch
+ hostOs <- chooseSetting HostOs TargetOs
+ hostVendor <- chooseSetting HostVendor TargetVendor
ghcUnreg <- getFlag GhcUnregisterised
return . unlines $
[ "#if !defined(__GHCPLATFORM_H__)"
, "#define __GHCPLATFORM_H__"
, ""
- , "#define BuildPlatform_TYPE " ++ cppify hostPlatform
- , "#define HostPlatform_TYPE " ++ cppify targetPlatform
+ , "#define BuildPlatform_NAME " ++ show buildPlatform
+ , "#define HostPlatform_NAME " ++ show hostPlatform
, ""
- , "#define " ++ cppify hostPlatform ++ "_BUILD 1"
- , "#define " ++ cppify targetPlatform ++ "_HOST 1"
+ , "#define BuildPlatform_TYPE " ++ cppify buildPlatform
+ , "#define HostPlatform_TYPE " ++ cppify hostPlatform
, ""
- , "#define " ++ hostArch ++ "_BUILD_ARCH 1"
- , "#define " ++ targetArch ++ "_HOST_ARCH 1"
- , "#define BUILD_ARCH " ++ show hostArch
- , "#define HOST_ARCH " ++ show targetArch
+ , "#define " ++ cppify buildPlatform ++ "_BUILD 1"
+ , "#define " ++ cppify hostPlatform ++ "_HOST 1"
, ""
- , "#define " ++ hostOs ++ "_BUILD_OS 1"
- , "#define " ++ targetOs ++ "_HOST_OS 1"
- , "#define BUILD_OS " ++ show hostOs
- , "#define HOST_OS " ++ show targetOs
+ , "#define " ++ buildArch ++ "_BUILD_ARCH 1"
+ , "#define " ++ hostArch ++ "_HOST_ARCH 1"
+ , "#define BUILD_ARCH " ++ show buildArch
+ , "#define HOST_ARCH " ++ show hostArch
, ""
- , "#define " ++ hostVendor ++ "_BUILD_VENDOR 1"
- , "#define " ++ targetVendor ++ "_HOST_VENDOR 1"
- , "#define BUILD_VENDOR " ++ show hostVendor
- , "#define HOST_VENDOR " ++ show targetVendor
+ , "#define " ++ buildOs ++ "_BUILD_OS 1"
+ , "#define " ++ hostOs ++ "_HOST_OS 1"
+ , "#define BUILD_OS " ++ show buildOs
+ , "#define HOST_OS " ++ show hostOs
+ , ""
+ , "#define " ++ buildVendor ++ "_BUILD_VENDOR 1"
+ , "#define " ++ hostVendor ++ "_HOST_VENDOR 1"
+ , "#define BUILD_VENDOR " ++ show buildVendor
+ , "#define HOST_VENDOR " ++ show hostVendor
, ""
]
++
@@ -351,7 +354,7 @@ generateConfigHs = do
, ""
, "import GHC.Version"
, ""
- , "#include \"ghc_boot_platform.h\""
+ , "#include \"ghcplatform.h\""
, ""
, "cBuildPlatformString :: String"
, "cBuildPlatformString = BuildPlatform_NAME"
@@ -395,47 +398,6 @@ generateGhcAutoconfH = do
= "/* #undef " ++ takeWhile (/=' ') (drop 8 s) ++ " */"
| otherwise = s
--- | Generate @ghc_boot_platform.h@ headers.
-generateGhcBootPlatformH :: Expr String
-generateGhcBootPlatformH = do
- trackGenerateHs
- stage <- getStage
- let chooseSetting x y = getSetting $ if stage == Stage0 then x else y
- buildPlatform <- chooseSetting BuildPlatform HostPlatform
- buildArch <- chooseSetting BuildArch HostArch
- buildOs <- chooseSetting BuildOs HostOs
- buildVendor <- chooseSetting BuildVendor HostVendor
- hostPlatform <- chooseSetting HostPlatform TargetPlatform
- hostArch <- chooseSetting HostArch TargetArch
- hostOs <- chooseSetting HostOs TargetOs
- hostVendor <- chooseSetting HostVendor TargetVendor
- return $ unlines
- [ "#if !defined(__PLATFORM_H__)"
- , "#define __PLATFORM_H__"
- , ""
- , "#define BuildPlatform_NAME " ++ show buildPlatform
- , "#define HostPlatform_NAME " ++ show hostPlatform
- , ""
- , "#define " ++ cppify buildPlatform ++ "_BUILD 1"
- , "#define " ++ cppify hostPlatform ++ "_HOST 1"
- , ""
- , "#define " ++ buildArch ++ "_BUILD_ARCH 1"
- , "#define " ++ hostArch ++ "_HOST_ARCH 1"
- , "#define BUILD_ARCH " ++ show buildArch
- , "#define HOST_ARCH " ++ show hostArch
- , ""
- , "#define " ++ buildOs ++ "_BUILD_OS 1"
- , "#define " ++ hostOs ++ "_HOST_OS 1"
- , "#define BUILD_OS " ++ show buildOs
- , "#define HOST_OS " ++ show hostOs
- , ""
- , "#define " ++ buildVendor ++ "_BUILD_VENDOR 1"
- , "#define " ++ hostVendor ++ "_HOST_VENDOR 1"
- , "#define BUILD_VENDOR " ++ show buildVendor
- , "#define HOST_VENDOR " ++ show hostVendor
- , ""
- , "#endif /* __PLATFORM_H__ */" ]
-
-- | Generate @ghcversion.h@ header.
generateGhcVersionH :: Expr String
generateGhcVersionH = do
diff --git a/hadrian/src/Settings/Builders/Cabal.hs b/hadrian/src/Settings/Builders/Cabal.hs
index 96f67b4abf..763f51636b 100644
--- a/hadrian/src/Settings/Builders/Cabal.hs
+++ b/hadrian/src/Settings/Builders/Cabal.hs
@@ -99,15 +99,16 @@ libraryArgs = do
configureArgs :: Args
configureArgs = do
top <- expr topDirectory
- root <- getBuildRoot
pkg <- getPackage
+ stage <- getStage
+ libPath <- expr $ stageLibPath stage
let conf key expr = do
values <- unwords <$> expr
not (null values) ?
arg ("--configure-option=" ++ key ++ "=" ++ values)
cFlags = mconcat [ remove ["-Werror"] cArgs
, getStagedSettingList ConfCcArgs
- , arg $ "-I" ++ top -/- root -/- generatedDir
+ , arg $ "-I" ++ libPath
-- See https://github.com/snowleopard/hadrian/issues/523
, arg $ "-iquote"
, arg $ top -/- pkgPath pkg
@@ -127,7 +128,7 @@ configureArgs = do
, conf "--with-curses-libraries" $ arg =<< getSetting CursesLibDir
, flag CrossCompiling ? (conf "--host" $ arg =<< getSetting TargetPlatformFull)
, conf "--with-cc" $ arg =<< getBuilderPath . (Cc CompileC) =<< getStage
- , notStage0 ? (arg =<< ("--ghc-option=-ghcversion-file=" ++) <$> expr ((-/-) <$> topDirectory <*> ghcVersionH))]
+ , notStage0 ? (arg =<< ("--ghc-option=-ghcversion-file=" ++) <$> expr ((-/-) <$> topDirectory <*> ghcVersionH stage))]
bootPackageConstraints :: Args
bootPackageConstraints = stage0 ? do
@@ -140,8 +141,9 @@ bootPackageConstraints = stage0 ? do
cppArgs :: Args
cppArgs = do
- root <- getBuildRoot
- arg $ "-I" ++ root -/- generatedDir
+ stage <- getStage
+ libPath <- expr $ stageLibPath stage
+ arg $ "-I" ++ libPath
withBuilderKey :: Builder -> String
withBuilderKey b = case b of
diff --git a/hadrian/src/Settings/Builders/Common.hs b/hadrian/src/Settings/Builders/Common.hs
index 5856935fb9..7d9e0fe716 100644
--- a/hadrian/src/Settings/Builders/Common.hs
+++ b/hadrian/src/Settings/Builders/Common.hs
@@ -22,15 +22,16 @@ import UserSettings
cIncludeArgs :: Args
cIncludeArgs = do
pkg <- getPackage
- root <- getBuildRoot
path <- getBuildPath
incDirs <- getContextData includeDirs
depDirs <- getContextData depIncludeDirs
+ stage <- getStage
iconvIncludeDir <- getSetting IconvIncludeDir
gmpIncludeDir <- getSetting GmpIncludeDir
ffiIncludeDir <- getSetting FfiIncludeDir
+ libPath <- expr $ stageLibPath stage
mconcat [ notStage0 ||^ package compiler ? arg "-Iincludes"
- , arg $ "-I" ++ root -/- generatedDir
+ , arg $ "-I" ++ libPath
, arg $ "-I" ++ path
, pure . map ("-I"++) . filter (/= "") $ [iconvIncludeDir, gmpIncludeDir]
, flag UseSystemFfi ? arg ("-I" ++ ffiIncludeDir)
diff --git a/hadrian/src/Settings/Builders/DeriveConstants.hs b/hadrian/src/Settings/Builders/DeriveConstants.hs
index 90068b3c4a..0747162f43 100644
--- a/hadrian/src/Settings/Builders/DeriveConstants.hs
+++ b/hadrian/src/Settings/Builders/DeriveConstants.hs
@@ -1,8 +1,19 @@
-module Settings.Builders.DeriveConstants (deriveConstantsBuilderArgs) where
+module Settings.Builders.DeriveConstants (
+ deriveConstantsBuilderArgs, deriveConstantsPairs
+ ) where
import Builder
import Settings.Builders.Common
+deriveConstantsPairs :: [(String, String)]
+deriveConstantsPairs =
+ [ ("DerivedConstants.h", "--gen-header")
+ , ("GHCConstantsHaskellType.hs", "--gen-haskell-type")
+ , ("platformConstants", "--gen-haskell-value")
+ , ("GHCConstantsHaskellWrappers.hs", "--gen-haskell-wrappers")
+ , ("GHCConstantsHaskellExports.hs", "--gen-haskell-exports")
+ ]
+
-- TODO: do we need to support `includes_CC_OPTS += -DDYNAMIC_BY_DEFAULT`?
deriveConstantsBuilderArgs :: Args
deriveConstantsBuilderArgs = builder DeriveConstants ? do
@@ -12,11 +23,8 @@ deriveConstantsBuilderArgs = builder DeriveConstants ? do
[a, b] -> (a, b)
_ -> error $ "DeriveConstants: expected two outputs, got " ++ show outs
mconcat
- [ output "**/DerivedConstants.h" ? arg "--gen-header"
- , output "**/GHCConstantsHaskellType.hs" ? arg "--gen-haskell-type"
- , output "**/platformConstants" ? arg "--gen-haskell-value"
- , output "**/GHCConstantsHaskellWrappers.hs" ? arg "--gen-haskell-wrappers"
- , output "**/GHCConstantsHaskellExports.hs" ? arg "--gen-haskell-exports"
+ [ mconcat $ flip fmap deriveConstantsPairs $ \(fileName, flag) ->
+ output ("**/" ++ fileName) ? arg flag
, arg "-o", arg outputFile
, arg "--tmpdir", arg tempDir
, arg "--gcc-program", arg =<< getBuilderPath (Cc CompileC Stage1)
@@ -28,13 +36,14 @@ deriveConstantsBuilderArgs = builder DeriveConstants ? do
includeCcArgs :: Args
includeCcArgs = do
- root <- getBuildRoot
+ stage <- getStage
+ libPath <- expr $ stageLibPath stage
mconcat [ cArgs
, cWarnings
, getSettingList $ ConfCcArgs Stage1
, flag GhcUnregisterised ? arg "-DUSE_MINIINTERPRETER"
, arg "-Irts"
, arg "-Iincludes"
- , arg $ "-I" ++ root -/- generatedDir
+ , arg $ "-I" ++ libPath
, notM ghcWithSMP ? arg "-DNOSMP"
, arg "-fcommon" ]
diff --git a/hadrian/src/Settings/Builders/Ghc.hs b/hadrian/src/Settings/Builders/Ghc.hs
index 2db62aa4e1..54315484c1 100644
--- a/hadrian/src/Settings/Builders/Ghc.hs
+++ b/hadrian/src/Settings/Builders/Ghc.hs
@@ -161,7 +161,8 @@ commonGhcArgs :: Args
commonGhcArgs = do
way <- getWay
path <- getBuildPath
- ghcVersion <- expr ghcVersionH
+ stage <- getStage
+ ghcVersion <- expr $ ghcVersionH stage
mconcat [ arg "-hisuf", arg $ hisuf way
, arg "-osuf" , arg $ osuf way
, arg "-hcsuf", arg $ hcsuf way
@@ -208,10 +209,11 @@ includeGhcArgs :: Args
includeGhcArgs = do
pkg <- getPackage
path <- getBuildPath
- root <- getBuildRoot
context <- getContext
srcDirs <- getContextData srcDirs
autogen <- expr $ autogenPath context
+ stage <- getStage
+ libPath <- expr $ stageLibPath stage
let cabalMacros = autogen -/- "cabal_macros.h"
expr $ need [cabalMacros]
mconcat [ arg "-i"
@@ -219,6 +221,6 @@ includeGhcArgs = do
, arg $ "-i" ++ autogen
, pure [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ]
, cIncludeArgs
- , arg $ "-I" ++ root -/- generatedDir
- , arg $ "-optc-I" ++ root -/- generatedDir
+ , arg $ "-I" ++ libPath
+ , arg $ "-optc-I" ++ libPath
, pure ["-optP-include", "-optP" ++ cabalMacros] ]
diff --git a/hadrian/src/Settings/Builders/HsCpp.hs b/hadrian/src/Settings/Builders/HsCpp.hs
index e33061c9d0..4595e2098e 100644
--- a/hadrian/src/Settings/Builders/HsCpp.hs
+++ b/hadrian/src/Settings/Builders/HsCpp.hs
@@ -6,12 +6,12 @@ import Settings.Builders.Common
hsCppBuilderArgs :: Args
hsCppBuilderArgs = builder HsCpp ? do
stage <- getStage
- root <- getBuildRoot
ghcPath <- expr $ buildPath (vanillaContext stage compiler)
+ libPath <- expr $ stageLibPath stage
mconcat [ getSettingList HsCppArgs
, arg "-P"
, arg "-Iincludes"
- , arg $ "-I" ++ root -/- generatedDir
+ , arg $ "-I" ++ libPath
, arg $ "-I" ++ ghcPath
, arg "-x", arg "c"
, arg =<< getInput ]