summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn Ericson <John.Ericson@Obsidian.Systems>2021-10-26 02:36:22 +0000
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-11-18 22:27:55 -0500
commitaed98ddaf72cc38fb570d8415cac5de9d8888818 (patch)
treef25c5a157f27dabbef72b77c5bdc61052ea75c21
parent0acbbd2021033245c2fb70e8fc8a79fcab168394 (diff)
downloadhaskell-aed98ddaf72cc38fb570d8415cac5de9d8888818.tar.gz
Hadrian: bring up to date with latest make improvements
Headers should be associated with the RTS, and subject to less hacks. The most subtle issue was that the package-grained dependencies on generated files were being `need`ed before calculating Haskell deps, but not before calculating C/C++ deps.
-rw-r--r--hadrian/src/Base.hs8
-rw-r--r--hadrian/src/Builder.hs4
-rw-r--r--hadrian/src/Rules/Compile.hs5
-rw-r--r--hadrian/src/Rules/Docspec.hs4
-rw-r--r--hadrian/src/Rules/Generate.hs86
-rw-r--r--hadrian/src/Rules/Libffi.hs14
-rw-r--r--hadrian/src/Rules/Lint.hs16
-rw-r--r--hadrian/src/Rules/Register.hs6
-rw-r--r--hadrian/src/Rules/Rts.hs26
-rw-r--r--hadrian/src/Rules/ToolArgs.hs1
-rw-r--r--hadrian/src/Settings/Builders/Cabal.hs11
-rw-r--r--hadrian/src/Settings/Builders/Common.hs3
-rw-r--r--hadrian/src/Settings/Builders/DeriveConstants.hs10
-rw-r--r--hadrian/src/Settings/Builders/Ghc.hs30
-rw-r--r--hadrian/src/Settings/Builders/HsCpp.hs2
-rw-r--r--hadrian/src/Settings/Packages.hs4
-rw-r--r--rts/rts.cabal.in2
17 files changed, 103 insertions, 129 deletions
diff --git a/hadrian/src/Base.hs b/hadrian/src/Base.hs
index 253a436ea9..febe1ea7b2 100644
--- a/hadrian/src/Base.hs
+++ b/hadrian/src/Base.hs
@@ -26,7 +26,7 @@ module Base (
-- * Paths
hadrianPath, configPath, configFile, sourcePath, shakeFilesDir,
stageBinPath, stageLibPath, templateHscPath,
- ghcBinDeps, ghcLibDeps, includesDependencies, haddockDeps,
+ ghcBinDeps, ghcLibDeps, haddockDeps,
relativePackageDbPath, packageDbPath, packageDbStamp, mingwStamp,
) where
@@ -116,12 +116,6 @@ ghcBinDeps stage = mapM (\f -> stageLibPath stage <&> (-/- f))
, "ghci-usage.txt"
]
-includesDependencies :: Stage -> Action [FilePath]
-includesDependencies stage = do
- p <- stageLibPath stage
- pure $ (p -/-) <$>
- [ "ghcautoconf.h", "ghcplatform.h" ]
-
-- | Files the `haddock` binary depends on
haddockDeps :: Stage -> Action [FilePath]
haddockDeps stage = do
diff --git a/hadrian/src/Builder.hs b/hadrian/src/Builder.hs
index 23b709b3c2..8ef2f2b411 100644
--- a/hadrian/src/Builder.hs
+++ b/hadrian/src/Builder.hs
@@ -205,12 +205,11 @@ instance H.Builder Builder where
-- Read the boot GHC version here to make sure we rebuild when it
-- changes (#18001).
_bootGhcVersion <- setting GhcVersion
- includesDependencies Stage0
+ pure []
Ghc _ stage -> do
root <- buildRoot
touchyPath <- programPath (vanillaContext Stage0 touchy)
unlitPath <- builderPath Unlit
- ghcgens <- includesDependencies stage
-- GHC from the previous stage is used to build artifacts in the
-- current stage. Need the previous stage's GHC deps.
@@ -218,7 +217,6 @@ instance H.Builder Builder where
return $ [ unlitPath ]
++ ghcdeps
- ++ ghcgens
++ [ touchyPath | windowsHost ]
++ [ root -/- mingwStamp | windowsHost ]
-- proxy for the entire mingw toolchain that
diff --git a/hadrian/src/Rules/Compile.hs b/hadrian/src/Rules/Compile.hs
index f093d15b96..afa5abbcca 100644
--- a/hadrian/src/Rules/Compile.hs
+++ b/hadrian/src/Rules/Compile.hs
@@ -248,7 +248,10 @@ compileNonHsObject rs lang path = do
-- in the @-MM -MG@ mode and building generated dependencies if they are missing
-- until reaching a fixed point.
needDependencies :: SourceLang -> Context -> FilePath -> FilePath -> Action ()
-needDependencies lang context@Context {..} src depFile = discover
+needDependencies lang context@Context {..} src depFile = do
+ gens <- interpretInContext context generatedDependencies
+ need gens
+ discover
where
discover = do
build $ target context (Cc (FindCDependencies depType) stage) [src] [depFile]
diff --git a/hadrian/src/Rules/Docspec.hs b/hadrian/src/Rules/Docspec.hs
index e5f8eb66c4..69b49a1cc5 100644
--- a/hadrian/src/Rules/Docspec.hs
+++ b/hadrian/src/Rules/Docspec.hs
@@ -33,14 +33,12 @@ base = do
stage1Lib <- stageLibPath Stage1
let cabalFile = pkgCabalFile P.base
let topIncludes = topDir </> "includes"
- includeDeps' <- includesDependencies Stage1
buildPath' <- buildPath context
let buildIncludesPath = topDir </> buildPath' </> "include"
- let includeDeps = fmap (topDir </>) includeDeps'
mtlConfFile <- pkgConfFile $ vanillaContext Stage1 P.mtl
deepseqConfFile <- pkgConfFile $ vanillaContext Stage1 P.deepseq
bytestringConfFile <- pkgConfFile $ vanillaContext Stage1 P.bytestring
- let neededIncludes = includeDeps ++ [mtlConfFile, deepseqConfFile, bytestringConfFile]
+ let neededIncludes = [mtlConfFile, deepseqConfFile, bytestringConfFile]
need neededIncludes
command_ [] "cabal-docspec" [ "-w", stage1GHC
diff --git a/hadrian/src/Rules/Generate.hs b/hadrian/src/Rules/Generate.hs
index eb7a780d97..d760dd55db 100644
--- a/hadrian/src/Rules/Generate.hs
+++ b/hadrian/src/Rules/Generate.hs
@@ -4,8 +4,6 @@ module Rules.Generate (
ghcPrimDependencies
) where
-import Data.Foldable (for_)
-
import Base
import qualified Context
import Expression
@@ -16,7 +14,6 @@ import Oracles.Setting
import Packages
import Rules.Libffi
import Settings
-import Settings.Builders.DeriveConstants (deriveConstantsPairs)
import Target
import Utilities
@@ -39,20 +36,29 @@ ghcPrimDependencies = do
path <- expr $ buildPath (vanillaContext stage ghcPrim)
return [path -/- "GHC/Prim.hs", path -/- "GHC/PrimopWrappers.hs"]
-derivedConstantsFiles :: [FilePath]
-derivedConstantsFiles =
- [ "DerivedConstants.h"
- ]
+rtsDependencies :: Expr [FilePath]
+rtsDependencies = do
+ stage <- getStage
+ rtsPath <- expr (rtsBuildPath stage)
+ let headers =
+ [ "ghcautoconf.h", "ghcplatform.h"
+ , "DerivedConstants.h"
+ ]
+ ++ libffiHeaderFiles
+ pure $ ((rtsPath -/- "include") -/-) <$> headers
+
+genapplyDependencies :: Expr [FilePath]
+genapplyDependencies = do
+ stage <- getStage
+ rtsPath <- expr (rtsBuildPath $ succ stage)
+ ((stage /= Stage3) ?) $ pure $ ((rtsPath -/- "include") -/-) <$>
+ [ "ghcautoconf.h", "ghcplatform.h" ]
compilerDependencies :: Expr [FilePath]
compilerDependencies = do
stage <- getStage
ghcPath <- expr $ buildPath (vanillaContext stage compiler)
- rtsPath <- expr (rtsBuildPath stage)
- libDir <- expr $ stageLibPath stage
- mconcat [ return $ (libDir -/-) <$> derivedConstantsFiles
- , notStage0 ? return ((rtsPath -/-) <$> libffiHeaderFiles)
- , return $ fmap (ghcPath -/-)
+ pure $ (ghcPath -/-) <$>
[ "primop-can-fail.hs-incl"
, "primop-code-size.hs-incl"
, "primop-commutable.hs-incl"
@@ -70,20 +76,15 @@ compilerDependencies = do
, "primop-vector-uniques.hs-incl"
, "primop-docs.hs-incl"
, "GHC/Platform/Constants.hs"
- ] ]
+ ]
generatedDependencies :: Expr [FilePath]
generatedDependencies = do
- stage <- getStage
- rtsPath <- expr (rtsBuildPath stage)
- includes <- expr $ includesDependencies stage
- libDir <- expr $ stageLibPath stage
mconcat [ package compiler ? compilerDependencies
, package ghcPrim ? ghcPrimDependencies
- , package rts ? return (fmap (rtsPath -/-) libffiHeaderFiles
- ++ includes
- ++ ((libDir -/-) <$> derivedConstantsFiles))
- , stage0 ? return includes ]
+ , package rts ? rtsDependencies
+ , package genapply ? genapplyDependencies
+ ]
generate :: FilePath -> Context -> Expr String -> Action ()
generate file context expr = do
@@ -122,21 +123,16 @@ generatePackageCode context@(Context stage pkg _) = do
when (pkg == compiler) $ do
root -/- primopsTxt stage %> \file -> do
- includes <- includesDependencies stage
- need $ [primopsSource] ++ includes
+ need $ [primopsSource]
build $ target context HsCpp [primopsSource] [file]
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") <~ stageLibPath stage
- (root -/- "**" -/- dir -/- "ghcautoconf.h") <~ stageLibPath stage
- (root -/- "**" -/- dir -/- "ghcplatform.h") <~ stageLibPath stage
- where
- pattern <~ mdir = pattern %> \file -> do
- dir <- mdir
- copyFile (dir -/- takeFileName file) file
+ let go gen file = generate file (semiEmptyTarget stage) gen
+ root -/- "**" -/- dir -/- "include/ghcautoconf.h" %> go generateGhcAutoconfH
+ root -/- "**" -/- dir -/- "include/ghcplatform.h" %> go generateGhcPlatformH
+ root -/- "**" -/- dir -/- "include/DerivedConstants.h" %> genPlatformConstantsHeader context
genPrimopCode :: Context -> FilePath -> Action ()
genPrimopCode context@(Context stage _pkg _) file = do
@@ -147,7 +143,19 @@ genPrimopCode context@(Context stage _pkg _) file = do
genPlatformConstantsType :: Context -> FilePath -> Action ()
genPlatformConstantsType context file = do
withTempDir $ \tmpdir ->
- build $ target context DeriveConstants [] [file,"--gen-haskell-type",tmpdir]
+ build $ target context DeriveConstants [] [file,tmpdir]
+
+genPlatformConstantsHeader :: Context -> FilePath -> Action ()
+genPlatformConstantsHeader context file = do
+ -- N.B. deriveConstants needs to compile programs which #include
+ -- PosixSource.h, which #include's ghcplatform.h. Fixes #18290.
+ let prefix = takeDirectory file
+ need
+ [ prefix -/- "ghcplatform.h"
+ , prefix -/- "ghcautoconf.h"
+ ]
+ withTempDir $ \tmpdir -> build $
+ target context DeriveConstants [] [file, tmpdir]
copyRules :: Rules ()
copyRules = do
@@ -180,20 +188,8 @@ generateRules = do
forM_ [Stage0 ..] $ \stage -> do
let prefix = root -/- stageString stage -/- "lib"
go gen file = generate file (semiEmptyTarget stage) gen
- (prefix -/- "ghcplatform.h") %> go generateGhcPlatformH
(prefix -/- "settings") %> go generateSettings
- (prefix -/- "ghcautoconf.h") %> go generateGhcAutoconfH
- -- TODO: simplify, get rid of fake rts context
- for_ (fst <$> deriveConstantsPairs) $ \constantsFile ->
- prefix -/- constantsFile %> \file -> do
- -- N.B. deriveConstants needs to compile programs which #include
- -- PosixSource.h, which #include's ghcplatform.h. Fixes #18290.
- need
- [ prefix -/- "ghcplatform.h"
- , prefix -/- "ghcautoconf.h"
- ]
- withTempDir $ \dir -> build $
- target (rtsContext stage) DeriveConstants [] [file, dir]
+
where
file <~+ gen = file %> \out -> generate out emptyTarget gen >> makeExecutable out
diff --git a/hadrian/src/Rules/Libffi.hs b/hadrian/src/Rules/Libffi.hs
index 27a4a3e9f2..df7529ffc5 100644
--- a/hadrian/src/Rules/Libffi.hs
+++ b/hadrian/src/Rules/Libffi.hs
@@ -3,7 +3,7 @@
module Rules.Libffi (
LibffiDynLibs(..),
needLibffi, askLibffilDynLibs, libffiRules, libffiLibrary, libffiHeaderFiles,
- libffiHeaders, libffiSystemHeaders, libffiName
+ libffiHeaderDir, libffiSystemHeaderDir, libffiName
) where
import Hadrian.Utilities
@@ -106,15 +106,13 @@ libffiLibrary = "inst/lib/libffi.a"
libffiHeaderFiles :: [FilePath]
libffiHeaderFiles = ["ffi.h", "ffitarget.h"]
-libffiHeaders :: Stage -> Action [FilePath]
-libffiHeaders stage = do
+libffiHeaderDir :: Stage -> Action FilePath
+libffiHeaderDir stage = do
path <- libffiBuildPath stage
- return $ fmap ((path -/- "inst/include") -/-) libffiHeaderFiles
+ return $ path -/- "inst/include"
-libffiSystemHeaders :: Action [FilePath]
-libffiSystemHeaders = do
- ffiIncludeDir <- setting FfiIncludeDir
- return $ fmap (ffiIncludeDir -/-) libffiHeaderFiles
+libffiSystemHeaderDir :: Action FilePath
+libffiSystemHeaderDir = setting FfiIncludeDir
fixLibffiMakefile :: FilePath -> String -> String
fixLibffiMakefile top =
diff --git a/hadrian/src/Rules/Lint.hs b/hadrian/src/Rules/Lint.hs
index 828744ba0b..bb7df1687a 100644
--- a/hadrian/src/Rules/Lint.hs
+++ b/hadrian/src/Rules/Lint.hs
@@ -47,10 +47,10 @@ runHLint includeDirs defines dir = do
base :: Action ()
base = do
buildDir <- buildRoot
- let stage1Lib = buildDir </> "stage1/lib"
+ let stage1RtsInc = buildDir </> "stage1/rts/build/include"
let machDeps = "rts/include/MachDeps.h"
- let ghcautoconf = stage1Lib </> "ghcautoconf.h"
- let ghcplatform = stage1Lib </> "ghcplatform.h"
+ let ghcautoconf = stage1RtsInc </> "ghcautoconf.h"
+ let ghcplatform = stage1RtsInc </> "ghcplatform.h"
-- ./configure is called here manually because we need to generate
-- HsBaseConfig.h, which is created from HsBaseConfig.h.in. ./configure
-- is usually run by Cabal which generates this file but if we do that
@@ -62,22 +62,22 @@ base = do
let includeDirs =
[ "rts/include"
, "libraries/base/include"
- , stage1Lib
+ , stage1RtsInc
]
runHLint includeDirs [] "libraries/base"
compiler :: Action ()
compiler = do
buildDir <- buildRoot
- let stage1Lib = buildDir </> "stage1/lib"
+ let stage1RtsInc = buildDir </> "stage1/rts/build/include"
let stage1Compiler = buildDir </> "stage1/compiler/build"
let machDeps = "rts/include/MachDeps.h"
let compilerDir = "compiler"
- let ghcautoconf = stage1Lib </> "ghcautoconf.h"
- let ghcplatform = stage1Lib </> "ghcplatform.h"
+ let ghcautoconf = stage1RtsInc </> "ghcautoconf.h"
+ let ghcplatform = stage1RtsInc </> "ghcplatform.h"
need $ mconcat [[ghcautoconf, ghcplatform], hsIncls stage1Compiler, [machDeps]]
let includeDirs =
- [ stage1Lib
+ [ stage1RtsInc
, compilerDir
, ghcplatform
, stage1Compiler
diff --git a/hadrian/src/Rules/Register.hs b/hadrian/src/Rules/Register.hs
index 6b603c6858..89c0cadd84 100644
--- a/hadrian/src/Rules/Register.hs
+++ b/hadrian/src/Rules/Register.hs
@@ -125,9 +125,9 @@ buildConf _ context@Context {..} _conf = do
when (package == rts) $
-- If Cabal knew about "generated-headers", we could read them from the
-- 'configuredCabal' information, and just "need" them here.
- need [ path -/- "DerivedConstants.h"
- , path -/- "ghcautoconf.h"
- , path -/- "ghcplatform.h"
+ need [ path -/- "include/DerivedConstants.h"
+ , path -/- "include/ghcautoconf.h"
+ , path -/- "include/ghcplatform.h"
]
-- we need to generate this file for GMP
diff --git a/hadrian/src/Rules/Rts.hs b/hadrian/src/Rules/Rts.hs
index a6abcdeb3e..4e6b4f7532 100644
--- a/hadrian/src/Rules/Rts.hs
+++ b/hadrian/src/Rules/Rts.hs
@@ -26,7 +26,8 @@ rtsRules = priority 3 $ do
let buildPath = root -/- buildDir (rtsContext stage)
-- Header files
- (fmap (buildPath -/-) libffiHeaderFiles) &%> const (copyLibffiHeaders stage)
+ forM_ libffiHeaderFiles $ \header ->
+ buildPath -/- "include" -/- header %> copyLibffiHeader stage
-- Static libraries.
buildPath -/- "libCffi*.a" %> copyLibffiStatic stage
@@ -41,18 +42,18 @@ withLibffi stage action = needLibffi stage
>> (join $ action <$> libffiBuildPath stage
<*> rtsBuildPath stage)
--- | Copy all header files wither from the system libffi or from the libffi
+-- | Copy a header files wither from the system libffi or from the libffi
-- build dir to the rts build dir.
-copyLibffiHeaders :: Stage -> Action ()
-copyLibffiHeaders stage = do
- rtsPath <- rtsBuildPath stage
+copyLibffiHeader :: Stage -> FilePath -> Action ()
+copyLibffiHeader stage header = do
useSystemFfi <- flag UseSystemFfi
- (fromStr, headers) <- if useSystemFfi
- then ("system",) <$> libffiSystemHeaders
+ (fromStr, headerDir) <- if useSystemFfi
+ then ("system",) <$> libffiSystemHeaderDir
else needLibffi stage
- >> ("custom",) <$> libffiHeaders stage
- forM_ headers $ \ header -> copyFile header
- (rtsPath -/- takeFileName header)
+ >> ("custom",) <$> libffiHeaderDir stage
+ copyFile
+ (headerDir -/- takeFileName header)
+ header
putSuccess $ "| Successfully copied " ++ fromStr ++ " FFI library header "
++ "files to RTS build directory."
@@ -117,7 +118,7 @@ needRtsLibffiTargets stage = do
useSystemFfi <- flag UseSystemFfi
-- Header files (in the rts build dir).
- let headers = fmap (rtsPath -/-) libffiHeaderFiles
+ let headers = fmap ((rtsPath -/- "include") -/-) libffiHeaderFiles
if useSystemFfi
then return headers
@@ -127,9 +128,6 @@ needRtsLibffiTargets stage = do
needLibffi stage
dynLibffSource <- askLibffilDynLibs stage
- -- Header files (in the rts build dir).
- let headers = fmap (rtsPath -/-) libffiHeaderFiles
-
-- Dynamic library files (in the rts build dir).
let dynLibffis = fmap (\ lib -> rtsPath -/- takeFileName lib)
dynLibffSource
diff --git a/hadrian/src/Rules/ToolArgs.hs b/hadrian/src/Rules/ToolArgs.hs
index 8277d580fa..1ed15d8f05 100644
--- a/hadrian/src/Rules/ToolArgs.hs
+++ b/hadrian/src/Rules/ToolArgs.hs
@@ -63,7 +63,6 @@ allDeps = do
(Ghc ToolArgs Stage0) [] ["ignored"]
-- need the autogenerated files so that they are precompiled
- includesDependencies Stage0 >>= need
interpret fake_target Rules.Generate.compilerDependencies >>= need
root <- buildRoot
diff --git a/hadrian/src/Settings/Builders/Cabal.hs b/hadrian/src/Settings/Builders/Cabal.hs
index e38eba1cf0..19bc8c315e 100644
--- a/hadrian/src/Settings/Builders/Cabal.hs
+++ b/hadrian/src/Settings/Builders/Cabal.hs
@@ -102,25 +102,20 @@ configureArgs :: Args
configureArgs = do
top <- expr topDirectory
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" ++ libPath
-- See https://github.com/snowleopard/hadrian/issues/523
, arg $ "-iquote"
, arg $ top -/- pkgPath pkg ]
ldFlags = ldArgs <> (getStagedSettingList ConfGccLinkerArgs)
- cppFlags = cppArgs <> (getStagedSettingList ConfCppArgs)
cldFlags <- unwords <$> (cFlags <> ldFlags)
mconcat
[ conf "CFLAGS" cFlags
, conf "LDFLAGS" ldFlags
- , conf "CPPFLAGS" cppFlags
, not (null cldFlags) ? arg ("--gcc-options=" ++ cldFlags)
, conf "--with-iconv-includes" $ arg =<< getSetting IconvIncludeDir
, conf "--with-iconv-libraries" $ arg =<< getSetting IconvLibDir
@@ -141,12 +136,6 @@ bootPackageConstraints = stage0 ? do
return $ ((pkgName pkg ++ " == ") ++) version
pure $ concat [ ["--constraint", c] | c <- constraints ]
-cppArgs :: Args
-cppArgs = do
- stage <- getStage
- libPath <- expr $ stageLibPath stage
- arg $ "-I" ++ libPath
-
withBuilderKey :: Builder -> String
withBuilderKey b = case b of
Ar _ _ -> "--with-ar="
diff --git a/hadrian/src/Settings/Builders/Common.hs b/hadrian/src/Settings/Builders/Common.hs
index 4ffca988a0..ad6f5c048a 100644
--- a/hadrian/src/Settings/Builders/Common.hs
+++ b/hadrian/src/Settings/Builders/Common.hs
@@ -24,7 +24,6 @@ cIncludeArgs = do
path <- getBuildPath
incDirs <- getContextData includeDirs
depDirs <- getContextData depIncludeDirs
- stage <- getStage
-- TODO: Why is any of this necessary? We should have already told Cabal about these paths.
iconvIncludeDir <- getSetting IconvIncludeDir
gmpIncludeDir <- getSetting GmpIncludeDir
@@ -32,9 +31,7 @@ cIncludeArgs = do
libdwIncludeDir <- getSetting LibdwIncludeDir
numaIncludeDir <- getSetting LibnumaIncludeDir
cursesIncludeDir <- getSetting CursesIncludeDir
- libPath <- expr $ stageLibPath stage
mconcat [ notStage0 ? arg "-Irts/include"
- , arg $ "-I" ++ libPath
, arg $ "-I" ++ path
, pure . map ("-I"++) . filter (/= "") $ [iconvIncludeDir, gmpIncludeDir, numaIncludeDir, cursesIncludeDir]
, flag UseSystemFfi ? if not (null ffiIncludeDir) then arg ("-I" ++ ffiIncludeDir) else mempty
diff --git a/hadrian/src/Settings/Builders/DeriveConstants.hs b/hadrian/src/Settings/Builders/DeriveConstants.hs
index 6801dc05fb..b2ecb0488f 100644
--- a/hadrian/src/Settings/Builders/DeriveConstants.hs
+++ b/hadrian/src/Settings/Builders/DeriveConstants.hs
@@ -1,13 +1,15 @@
module Settings.Builders.DeriveConstants (
- deriveConstantsBuilderArgs, deriveConstantsPairs
+ deriveConstantsBuilderArgs
) where
import Builder
+import Packages
import Settings.Builders.Common
deriveConstantsPairs :: [(String, String)]
deriveConstantsPairs =
- [ ("DerivedConstants.h", "--gen-header")
+ [ ("Constants.hs", "--gen-haskell-type")
+ , ("DerivedConstants.h", "--gen-header")
]
deriveConstantsBuilderArgs :: Args
@@ -36,13 +38,13 @@ deriveConstantsBuilderArgs = builder DeriveConstants ? do
includeCcArgs :: Args
includeCcArgs = do
stage <- getStage
- libPath <- expr $ stageLibPath stage
+ rtsPath <- expr $ rtsBuildPath stage
mconcat [ cArgs
, cWarnings
, getSettingList $ ConfCcArgs Stage1
, flag GhcUnregisterised ? arg "-DUSE_MINIINTERPRETER"
, arg "-Irts"
, arg "-Irts/include"
- , arg $ "-I" ++ libPath
+ , arg $ "-I" ++ rtsPath </> "include"
, notM targetSupportsSMP ? arg "-DNOSMP"
, arg "-fcommon" ]
diff --git a/hadrian/src/Settings/Builders/Ghc.hs b/hadrian/src/Settings/Builders/Ghc.hs
index 1d315e50ea..a22e0079a7 100644
--- a/hadrian/src/Settings/Builders/Ghc.hs
+++ b/hadrian/src/Settings/Builders/Ghc.hs
@@ -14,8 +14,20 @@ import Rules.Libffi (libffiName)
import System.Directory
ghcBuilderArgs :: Args
-ghcBuilderArgs = mconcat [ compileAndLinkHs, compileC, compileCxx, findHsDependencies
- , toolArgs]
+ghcBuilderArgs = mconcat
+ [ package genapply ? do
+ -- TODO: this is here because this -I needs to come before the others.
+ -- Otherwise this would go in Settings.Packages.
+ --
+ -- genapply bakes in the next stage's headers to bake in the target
+ -- config at build time.
+ -- See Note [Genapply target as host for RTS macros].
+ stage <- getStage
+ nextStageRtsBuildDir <- expr $ rtsBuildPath $ succ stage
+ let nextStageRtsBuildIncludeDir = nextStageRtsBuildDir </> "include"
+ builder Ghc ? arg ("-I" ++ nextStageRtsBuildIncludeDir)
+ , compileAndLinkHs, compileC, compileCxx, findHsDependencies
+ , toolArgs]
toolArgs :: Args
toolArgs = do
@@ -170,16 +182,8 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
findHsDependencies :: Args
findHsDependencies = builder (Ghc FindHsDependencies) ? do
ways <- getLibraryWays
- stage <- getStage
- ghcVersion :: [Int] <- fmap read . splitOn "." <$> expr (ghcVersionStage stage)
mconcat [ arg "-M"
-
- -- "-include-cpp-deps" is a new ish feature so is version gated.
- -- Without this feature some dependencies will be missing in stage0.
- -- TODO Remove version gate when minimum supported Stage0 compiler
- -- is >= 8.9.0.
- , ghcVersion > [8,9,0] ? arg "-include-cpp-deps"
-
+ , arg "-include-cpp-deps"
, commonGhcArgs
, defaultGhcWarningsArgs
, arg "-include-pkg-deps"
@@ -261,8 +265,6 @@ includeGhcArgs = do
abSrcDirs <- exprIO $ mapM makeAbsolute [ (pkgPath pkg -/- dir) | dir <- srcDirs ]
autogen <- expr (autogenPath context)
cautogen <- exprIO (makeAbsolute autogen)
- stage <- getStage
- libPath <- expr (stageLibPath stage)
let cabalMacros = autogen -/- "cabal_macros.h"
expr $ need [cabalMacros]
mconcat [ arg "-i"
@@ -270,6 +272,4 @@ includeGhcArgs = do
, arg $ "-i" ++ cautogen
, pure [ "-i" ++ d | d <- abSrcDirs ]
, cIncludeArgs
- , 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 9f821d66b8..e77833e758 100644
--- a/hadrian/src/Settings/Builders/HsCpp.hs
+++ b/hadrian/src/Settings/Builders/HsCpp.hs
@@ -7,11 +7,9 @@ hsCppBuilderArgs :: Args
hsCppBuilderArgs = builder HsCpp ? do
stage <- getStage
ghcPath <- expr $ buildPath (vanillaContext stage compiler)
- libPath <- expr $ stageLibPath stage
mconcat [ getSettingList HsCppArgs
, arg "-P"
, arg "-Irts/include"
- , arg $ "-I" ++ libPath
, arg $ "-I" ++ ghcPath
, arg "-x", arg "c"
, arg =<< getInput ]
diff --git a/hadrian/src/Settings/Packages.hs b/hadrian/src/Settings/Packages.hs
index 3be0b92050..ed5a03a2d9 100644
--- a/hadrian/src/Settings/Packages.hs
+++ b/hadrian/src/Settings/Packages.hs
@@ -170,6 +170,10 @@ packageArgs = do
, package hsc2hs ?
builder (Cabal Flags) ? arg "in-ghc-tree"
+ -------------------------------- genapply --------------------------------
+ -- TODO: The logic here needs to come first, so it's hacked into
+ -- Settings.Builder.Ghc instead.
+
------------------------------ ghc-bignum ------------------------------
, ghcBignumArgs
diff --git a/rts/rts.cabal.in b/rts/rts.cabal.in
index a2f78f15b6..b8500d6ef4 100644
--- a/rts/rts.cabal.in
+++ b/rts/rts.cabal.in
@@ -144,7 +144,7 @@ library
if !flag(smp)
cpp-options: -DNOSMP
- include-dirs: build include
+ include-dirs: include
@FFIIncludeDir@
@LibdwIncludeDir@
includes: Stg.h