summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorRodrigo Mesquita <rodrigo.m.mesquita@gmail.com>2023-05-15 18:28:49 +0100
committerRodrigo Mesquita <rodrigo.m.mesquita@gmail.com>2023-05-15 18:28:50 +0100
commitf83f08a950d6f3a8bcf04289402e51d89c04bc4f (patch)
tree06dac5e00ca6837fa7432bcf8426f0a822c098fd
parent3ffeaa32e5e5980e1224ebdd4379cb3cc1667e15 (diff)
downloadhaskell-f83f08a950d6f3a8bcf04289402e51d89c04bc4f.tar.gz
Delete CMD_OPTS_STAGEX
Instead of having configure configure different options for different programs depend on the stage, we delete this completely and have hadrian select the correct target toolchain configuration file depending on the stage, from which it can read those options.
-rw-r--r--hadrian/cfg/system.config.in29
-rw-r--r--hadrian/src/Context.hs13
-rw-r--r--hadrian/src/Hadrian/Haskell/Hash.hs1
-rw-r--r--hadrian/src/Hadrian/Oracles/TextFile.hs1
-rw-r--r--hadrian/src/Oracles/Setting.hs50
-rw-r--r--hadrian/src/Rules/BinaryDist.hs8
-rw-r--r--hadrian/src/Rules/Gmp.hs4
-rw-r--r--hadrian/src/Rules/Libffi.hs4
-rw-r--r--hadrian/src/Settings/Builders/Cabal.hs10
-rw-r--r--hadrian/src/Settings/Builders/Cc.hs4
-rw-r--r--hadrian/src/Settings/Builders/DeriveConstants.hs4
-rw-r--r--hadrian/src/Settings/Builders/Ghc.hs21
-rw-r--r--hadrian/src/Settings/Builders/HsCpp.hs4
-rw-r--r--hadrian/src/Settings/Builders/Hsc2Hs.hs8
-rw-r--r--hadrian/src/Settings/Builders/Ld.hs4
-rw-r--r--hadrian/src/Settings/Builders/MergeObjects.hs4
16 files changed, 70 insertions, 99 deletions
diff --git a/hadrian/cfg/system.config.in b/hadrian/cfg/system.config.in
index 339768961f..e578c4ff12 100644
--- a/hadrian/cfg/system.config.in
+++ b/hadrian/cfg/system.config.in
@@ -96,35 +96,6 @@ project-patch-level1 = @ProjectPatchLevel1@
project-patch-level2 = @ProjectPatchLevel2@
project-git-commit-id = @ProjectGitCommitId@
-# Compilation and linking flags:
-#===============================
-
-conf-cc-args-stage0 = @CONF_CC_OPTS_STAGE0@
-conf-cc-args-stage1 = @CONF_CC_OPTS_STAGE1@
-conf-cc-args-stage2 = @CONF_CC_OPTS_STAGE2@
-conf-cc-args-stage3 = @CONF_CC_OPTS_STAGE3@
-
-conf-cpp-args-stage0 = @CONF_CPP_OPTS_STAGE0@
-conf-cpp-args-stage1 = @CONF_CPP_OPTS_STAGE1@
-conf-cpp-args-stage2 = @CONF_CPP_OPTS_STAGE2@
-conf-cpp-args-stage3 = @CONF_CPP_OPTS_STAGE3@
-
-conf-gcc-linker-args-stage0 = @CONF_GCC_LINKER_OPTS_STAGE0@
-conf-gcc-linker-args-stage1 = @CONF_GCC_LINKER_OPTS_STAGE1@
-conf-gcc-linker-args-stage2 = @CONF_GCC_LINKER_OPTS_STAGE2@
-conf-gcc-linker-args-stage3 = @CONF_GCC_LINKER_OPTS_STAGE3@
-
-conf-ld-linker-args-stage0 = @CONF_LD_LINKER_OPTS_STAGE0@
-conf-ld-linker-args-stage1 = @CONF_LD_LINKER_OPTS_STAGE1@
-conf-ld-linker-args-stage2 = @CONF_LD_LINKER_OPTS_STAGE2@
-conf-ld-linker-args-stage3 = @CONF_LD_LINKER_OPTS_STAGE3@
-
-conf-merge-objects-args-stage0 = @MergeObjsArgs@
-conf-merge-objects-args-stage1 = @MergeObjsArgs@
-conf-merge-objects-args-stage2 = @MergeObjsArgs@
-conf-merge-objects-args-stage3 = @MergeObjsArgs@
-
-
# Settings:
#==========
diff --git a/hadrian/src/Context.hs b/hadrian/src/Context.hs
index d09228b004..a6ee5c6dc9 100644
--- a/hadrian/src/Context.hs
+++ b/hadrian/src/Context.hs
@@ -3,7 +3,7 @@ module Context (
Context (..), vanillaContext, stageContext,
-- * Expressions
- getStage, getPackage, getWay, getStagedSettingList, getBuildPath, getPackageDbLoc,
+ getStage, getPackage, getWay, getBuildPath, getPackageDbLoc, getStagedTargetConfig,
-- * Paths
contextDir, buildPath, buildDir, pkgInplaceConfig, pkgSetupConfigFile, pkgSetupConfigDir,
@@ -19,6 +19,7 @@ import Context.Type
import Hadrian.Expression
import Hadrian.Haskell.Cabal
import Oracles.Setting
+import GHC.Toolchain.Target (Target)
-- | Most targets are built only one way, hence the notion of 'vanillaContext'.
vanillaContext :: Stage -> Package -> Context
@@ -47,9 +48,9 @@ getPackage = package <$> getContext
getWay :: Expr Context b Way
getWay = way <$> getContext
--- | Get a list of configuration settings for the current stage.
-getStagedSettingList :: (Stage -> SettingList) -> Args Context b
-getStagedSettingList f = getSettingList . f =<< getStage
+-- | Get the 'Target' configuration of the current stage
+getStagedTargetConfig :: Expr Context b Target
+getStagedTargetConfig = expr . targetConfigStage =<< getStage
-- | Path to the directory containing the final artifact in a given 'Context'.
libPath :: Context -> Action FilePath
@@ -95,7 +96,7 @@ pkgSetupConfigFile context = pkgSetupConfigDir context <&> (-/- "setup-config")
-- | Path to the haddock file of a given 'Context', e.g.:
-- @_build/stage1/libraries/array/doc/html/array/array.haddock@.
pkgHaddockFile :: Context -> Action FilePath
-pkgHaddockFile context@Context {..} = do
+pkgHaddockFile Context {..} = do
root <- buildRoot
version <- pkgUnitId stage package
return $ root -/- "doc/html/libraries" -/- version -/- pkgName package <.> "haddock"
@@ -136,7 +137,7 @@ pkgGhciLibraryFile context@Context {..} = do
-- | Path to the configuration file of a given 'Context'.
pkgConfFile :: Context -> Action FilePath
-pkgConfFile context@Context {..} = do
+pkgConfFile Context {..} = do
pid <- pkgUnitId stage package
dbPath <- packageDbPath (PackageDbLoc stage iplace)
return $ dbPath -/- pid <.> "conf"
diff --git a/hadrian/src/Hadrian/Haskell/Hash.hs b/hadrian/src/Hadrian/Haskell/Hash.hs
index ee644168e2..3a40f627e8 100644
--- a/hadrian/src/Hadrian/Haskell/Hash.hs
+++ b/hadrian/src/Hadrian/Haskell/Hash.hs
@@ -31,7 +31,6 @@ import Way
import Packages
import Development.Shake.Classes
import Control.Monad
-import Utilities
import Base
import Context
import System.Directory.Extra (listFilesRecursive)
diff --git a/hadrian/src/Hadrian/Oracles/TextFile.hs b/hadrian/src/Hadrian/Oracles/TextFile.hs
index b0e12930ca..d112e2c636 100644
--- a/hadrian/src/Hadrian/Oracles/TextFile.hs
+++ b/hadrian/src/Hadrian/Oracles/TextFile.hs
@@ -91,6 +91,7 @@ getTargetConfig :: FilePath -> Action Toolchain.Target
getTargetConfig file = askOracle $ TargetFile file
-- | Get the host's target configuration through 'getTarget'
+-- ROMES:TODO: Rename HOST to BUILD
getHostTargetConfig :: Action Toolchain.Target
getHostTargetConfig = getTargetConfig hostTargetFile
-- where
diff --git a/hadrian/src/Oracles/Setting.hs b/hadrian/src/Oracles/Setting.hs
index d784eee497..7380631e6c 100644
--- a/hadrian/src/Oracles/Setting.hs
+++ b/hadrian/src/Oracles/Setting.hs
@@ -1,13 +1,12 @@
module Oracles.Setting (
configFile,
-- * Settings
- Setting (..), SettingList (..), setting, settingList, getSetting,
- getSettingList,
+ Setting (..), setting, getSetting,
ToolchainSetting (..), settingsFileSetting,
-- * Helpers
ghcCanonVersion, cmdLineLengthLimit, hostSupportsRPaths, topDirectory,
- libsuf, ghcVersionStage, bashPath,
+ libsuf, ghcVersionStage, bashPath, targetConfigStage,
-- ** Target platform things
anyTargetPlatform, anyTargetOs, anyTargetArch, anyHostOs,
@@ -85,23 +84,6 @@ data Setting = BuildArch
| TargetWordSize
| BourneShell
--- TODO: Reduce the variety of similar flags (e.g. CPP and non-CPP versions).
--- | Each 'SettingList' comes from the file @hadrian/cfg/system.config@,
--- generated by the @configure@ script from the input file
--- @hadrian/cfg/system.config.in@. For example, the line
---
--- > hs-cpp-args = -E -undef -traditional
---
--- sets the value of 'HsCppArgs'. The action 'settingList' 'HsCppArgs' looks up
--- the value of the setting and returns the list of strings
--- @["-E", "-undef", "-traditional"]@, tracking the result in the Shake database.
-data SettingList = ConfCcArgs Stage
- | ConfCppArgs Stage
- | ConfGccLinkerArgs Stage
- | ConfLdLinkerArgs Stage
- | ConfMergeObjectsArgs Stage
- | HsCppArgs
-
-- TODO compute solely in Hadrian, removing these variables' definitions
-- from aclocal.m4 whenever they can be calculated from other variables
-- already fed into Hadrian.
@@ -194,21 +176,6 @@ setting key = case key of
archStr = stringEncodeArch . archOS_arch . tgtArchOs
osStr = stringEncodeOS . archOS_OS . tgtArchOs
-bootIsStage0 :: Stage -> Stage
-bootIsStage0 (Stage0 {}) = Stage0 InTreeLibs
-bootIsStage0 s = s
-
--- | Look up the value of a 'SettingList' in @cfg/system.config@, tracking the
--- result.
-settingList :: SettingList -> Action [String]
-settingList key = fmap words $ lookupSystemConfig $ case key of
- ConfCcArgs stage -> "conf-cc-args-" ++ stageString (bootIsStage0 stage)
- ConfCppArgs stage -> "conf-cpp-args-" ++ stageString (bootIsStage0 stage)
- ConfGccLinkerArgs stage -> "conf-gcc-linker-args-" ++ stageString (bootIsStage0 stage)
- ConfLdLinkerArgs stage -> "conf-ld-linker-args-" ++ stageString (bootIsStage0 stage)
- ConfMergeObjectsArgs stage -> "conf-merge-objects-args-" ++ stageString (bootIsStage0 stage)
- HsCppArgs -> "hs-cpp-args"
-
-- | Look up the value of a 'SettingList' in @cfg/system.config@, tracking the
-- result.
-- See Note [tooldir: How GHC finds mingw on Windows]
@@ -252,11 +219,6 @@ getSetting = expr . setting
bashPath :: Action FilePath
bashPath = setting BourneShell
--- | An expression that looks up the value of a 'SettingList' in
--- @cfg/system.config@, tracking the result.
-getSettingList :: SettingList -> Args c b
-getSettingList = expr . settingList
-
-- | Check whether the value of a 'Setting' matches one of the given strings.
matchSetting :: Setting -> [String] -> Action Bool
matchSetting key values = (`elem` values) <$> setting key
@@ -371,3 +333,11 @@ libsuf st way
version <- ghcVersionStage st -- e.g. 8.4.4 or 8.9.xxxx
let suffix = waySuffix (removeWayUnit Dynamic way)
return (suffix ++ "-ghc" ++ version ++ extension)
+
+targetConfigStage :: Stage -> Action Target
+-- ROMES:TODO: First iteration, only make it work for BUILD=HOST=TARGET
+targetConfigStage (Stage0 {}) = getHostTargetConfig
+targetConfigStage (Stage1 {}) = getHostTargetConfig
+targetConfigStage (Stage2 {}) = getHostTargetConfig
+targetConfigStage (Stage3 {}) = getHostTargetConfig
+
diff --git a/hadrian/src/Rules/BinaryDist.hs b/hadrian/src/Rules/BinaryDist.hs
index cca28c10f4..7c84bf73e8 100644
--- a/hadrian/src/Rules/BinaryDist.hs
+++ b/hadrian/src/Rules/BinaryDist.hs
@@ -15,6 +15,8 @@ import Target
import Utilities
import qualified System.Directory.Extra as IO
import Data.Either
+import GHC.Toolchain (ccProgram, tgtCCompiler, ccLinkProgram, tgtCCompilerLink)
+import GHC.Toolchain.Program (prgFlags)
{-
Note [Binary distributions]
@@ -418,11 +420,11 @@ commonWrapper = pure $ "exec \"$executablename\" ${1+\"$@\"}\n"
-- echo 'HSC2HS_EXTRA="$(addprefix --cflag=,$(CONF_CC_OPTS_STAGE1)) $(addprefix --lflag=,$(CONF_GCC_LINKER_OPTS_STAGE1))"' >> "$(WRAPPER)"
hsc2hsWrapper :: Action String
hsc2hsWrapper = do
- ccArgs <- map ("--cflag=" <>) <$> settingList (ConfCcArgs Stage1)
- ldFlags <- map ("--lflag=" <>) <$> settingList (ConfGccLinkerArgs Stage1)
+ ccArgs <- map ("--cflag=" <>) . prgFlags . ccProgram . tgtCCompiler <$> targetConfigStage Stage1
+ linkFlags <- map ("--lflag=" <>) . prgFlags . ccLinkProgram . tgtCCompilerLink <$> targetConfigStage Stage1
wrapper <- drop 4 . lines <$> liftIO (readFile "utils/hsc2hs/hsc2hs.wrapper")
return $ unlines
- ( "HSC2HS_EXTRA=\"" <> unwords (ccArgs ++ ldFlags) <> "\""
+ ( "HSC2HS_EXTRA=\"" <> unwords (ccArgs ++ linkFlags) <> "\""
: "tflag=\"--template=$libdir/template-hsc.h\""
: "Iflag=\"-I$includedir/\""
: wrapper )
diff --git a/hadrian/src/Rules/Gmp.hs b/hadrian/src/Rules/Gmp.hs
index f6222a6643..60db9c9017 100644
--- a/hadrian/src/Rules/Gmp.hs
+++ b/hadrian/src/Rules/Gmp.hs
@@ -12,6 +12,8 @@ import Utilities
import Hadrian.BuildPath
import Hadrian.Expression
import Settings.Builders.Common (cArgs)
+import GHC.Toolchain (ccProgram, tgtCCompiler)
+import GHC.Toolchain.Program
-- | Build in-tree GMP library objects (if GmpInTree flag is set) and return
-- their paths.
@@ -122,7 +124,7 @@ gmpRules = do
let gmpBuildP = takeDirectory mk
gmpP = takeDirectory gmpBuildP
ctx <- makeGmpPathContext gmpP
- cFlags <- interpretInContext ctx $ mconcat [ cArgs, getStagedSettingList ConfCcArgs ]
+ cFlags <- interpretInContext ctx $ mconcat [ cArgs, prgFlags . ccProgram . tgtCCompiler <$> getStagedTargetConfig ]
env <- sequence
[ builderEnvironment "CC" $ Cc CompileC (stage ctx)
, return . AddEnv "CFLAGS" $ unwords cFlags
diff --git a/hadrian/src/Rules/Libffi.hs b/hadrian/src/Rules/Libffi.hs
index ee19b198cf..209ef6b320 100644
--- a/hadrian/src/Rules/Libffi.hs
+++ b/hadrian/src/Rules/Libffi.hs
@@ -12,6 +12,8 @@ import Packages
import Settings.Builders.Common
import Target
import Utilities
+import GHC.Toolchain (ccProgram, tgtCCompiler)
+import GHC.Toolchain.Program
{- Note [Libffi indicating inputs]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -131,7 +133,7 @@ configureEnvironment stage = do
context <- libffiContext stage
cFlags <- interpretInContext context $ mconcat
[ cArgs
- , getStagedSettingList ConfCcArgs ]
+ , prgFlags . ccProgram . tgtCCompiler <$> getStagedTargetConfig ]
ldFlags <- interpretInContext context ldArgs
sequence [ builderEnvironment "CC" $ Cc CompileC stage
, builderEnvironment "CXX" $ Cc CompileC stage
diff --git a/hadrian/src/Settings/Builders/Cabal.hs b/hadrian/src/Settings/Builders/Cabal.hs
index 75eb78ccd8..41badaf562 100644
--- a/hadrian/src/Settings/Builders/Cabal.hs
+++ b/hadrian/src/Settings/Builders/Cabal.hs
@@ -13,6 +13,8 @@ import Control.Exception (assert)
import qualified Data.Set as Set
import System.Directory
import Settings.Program (programContext)
+import GHC.Toolchain (ccProgram, tgtCCompiler, ccLinkProgram, tgtCCompilerLink)
+import GHC.Toolchain.Program (prgFlags)
cabalBuilderArgs :: Args
cabalBuilderArgs = cabalSetupArgs <> cabalInstallArgs
@@ -166,9 +168,9 @@ libraryArgs = do
-- | Configure args with stage/lib specific include directories and settings
configureStageArgs :: Args
configureStageArgs = do
- let cFlags = getStagedSettingList ConfCcArgs
- ldFlags = getStagedSettingList ConfGccLinkerArgs
- mconcat [ configureArgs cFlags ldFlags
+ let cFlags = prgFlags . ccProgram . tgtCCompiler <$> getStagedTargetConfig
+ linkFlags = prgFlags . ccLinkProgram . tgtCCompilerLink <$> getStagedTargetConfig
+ mconcat [ configureArgs cFlags linkFlags
, notStage0 ? arg "--ghc-option=-ghcversion-file=rts/include/ghcversion.h"
]
@@ -184,7 +186,7 @@ configureArgs cFlags' ldFlags' = do
not (null values) ?
arg ("--configure-option=" ++ key ++ "=" ++ values)
cFlags = mconcat [ remove ["-Werror"] cArgs
- , getStagedSettingList ConfCcArgs
+ , prgFlags . ccProgram . tgtCCompiler <$> getStagedTargetConfig
-- See https://github.com/snowleopard/hadrian/issues/523
, arg $ "-iquote"
diff --git a/hadrian/src/Settings/Builders/Cc.hs b/hadrian/src/Settings/Builders/Cc.hs
index f7bf215f26..30e41d963d 100644
--- a/hadrian/src/Settings/Builders/Cc.hs
+++ b/hadrian/src/Settings/Builders/Cc.hs
@@ -2,13 +2,15 @@ module Settings.Builders.Cc (ccBuilderArgs) where
import Hadrian.Haskell.Cabal.Type
import Settings.Builders.Common
+import GHC.Toolchain (tgtCCompiler, ccProgram)
+import GHC.Toolchain.Program
ccBuilderArgs :: Args
ccBuilderArgs = do
way <- getWay
builder Cc ? mconcat
[ getContextData ccOpts
- , getStagedSettingList ConfCcArgs
+ , prgFlags . ccProgram . tgtCCompiler <$> getStagedTargetConfig
, builder (Cc CompileC) ? mconcat
[ arg "-Wall"
diff --git a/hadrian/src/Settings/Builders/DeriveConstants.hs b/hadrian/src/Settings/Builders/DeriveConstants.hs
index b2ecb0488f..d210b2815e 100644
--- a/hadrian/src/Settings/Builders/DeriveConstants.hs
+++ b/hadrian/src/Settings/Builders/DeriveConstants.hs
@@ -5,6 +5,8 @@ module Settings.Builders.DeriveConstants (
import Builder
import Packages
import Settings.Builders.Common
+import GHC.Toolchain (tgtCCompiler, ccProgram)
+import GHC.Toolchain.Program
deriveConstantsPairs :: [(String, String)]
deriveConstantsPairs =
@@ -41,7 +43,7 @@ includeCcArgs = do
rtsPath <- expr $ rtsBuildPath stage
mconcat [ cArgs
, cWarnings
- , getSettingList $ ConfCcArgs Stage1
+ , prgFlags . ccProgram . tgtCCompiler <$> expr (targetConfigStage Stage1)
, flag GhcUnregisterised ? arg "-DUSE_MINIINTERPRETER"
, arg "-Irts"
, arg "-Irts/include"
diff --git a/hadrian/src/Settings/Builders/Ghc.hs b/hadrian/src/Settings/Builders/Ghc.hs
index 2e5a15cee5..3957ccd5d5 100644
--- a/hadrian/src/Settings/Builders/Ghc.hs
+++ b/hadrian/src/Settings/Builders/Ghc.hs
@@ -14,6 +14,8 @@ import Rules.Libffi (libffiName)
import qualified Data.Set as Set
import System.Directory
import Data.Version.Extra
+import GHC.Toolchain (ccProgram, tgtCCompiler, cppProgram, tgtCPreprocessor)
+import GHC.Toolchain.Program
ghcBuilderArgs :: Args
ghcBuilderArgs = mconcat
@@ -36,8 +38,8 @@ toolArgs = do
builder (Ghc ToolArgs) ? mconcat
[ packageGhcArgs
, includeGhcArgs
- , map ("-optc" ++) <$> getStagedSettingList ConfCcArgs
- , map ("-optP" ++) <$> getStagedSettingList ConfCppArgs
+ , map ("-optc" ++) <$> getStagedCCFlags
+ , map ("-optP" ++) <$> getStagedCPPFlags
, map ("-optP" ++) <$> getContextData cppOpts
, getContextData hcOpts
]
@@ -69,7 +71,7 @@ compileC :: Args
compileC = builder (Ghc CompileCWithGhc) ? do
way <- getWay
let ccArgs = [ getContextData ccOpts
- , getStagedSettingList ConfCcArgs
+ , getStagedCCFlags
, cIncludeArgs
, Dynamic `wayUnit` way ? pure [ "-fPIC", "-DDYNAMIC" ] ]
mconcat [ arg "-Wall"
@@ -86,7 +88,7 @@ compileCxx :: Args
compileCxx = builder (Ghc CompileCppWithGhc) ? do
way <- getWay
let ccArgs = [ getContextData cxxOpts
- , getStagedSettingList ConfCcArgs
+ , getStagedCCFlags
, cIncludeArgs
, Dynamic `wayUnit` way ? pure [ "-fPIC", "-DDYNAMIC" ] ]
mconcat [ arg "-Wall"
@@ -216,8 +218,8 @@ commonGhcArgs = do
-- to the @ghc-version@ file, to prevent GHC from trying to open the
-- RTS package in the package database and failing.
, package rts ? notStage0 ? arg "-ghcversion-file=rts/include/ghcversion.h"
- , map ("-optc" ++) <$> getStagedSettingList ConfCcArgs
- , map ("-optP" ++) <$> getStagedSettingList ConfCppArgs
+ , map ("-optc" ++) <$> getStagedCCFlags
+ , map ("-optP" ++) <$> getStagedCPPFlags
, map ("-optP" ++) <$> getContextData cppOpts
, arg "-outputdir", arg path
-- we need to enable color explicitly because the output is
@@ -290,3 +292,10 @@ includeGhcArgs = do
, pure [ "-i" ++ d | d <- abSrcDirs ]
, cIncludeArgs
, pure ["-optP-include", "-optP" ++ cabalMacros] ]
+
+-- Utilities
+getStagedCCFlags :: Args
+getStagedCCFlags = prgFlags . ccProgram . tgtCCompiler <$> getStagedTargetConfig
+
+getStagedCPPFlags :: Args
+getStagedCPPFlags = prgFlags . cppProgram . tgtCPreprocessor <$> getStagedTargetConfig
diff --git a/hadrian/src/Settings/Builders/HsCpp.hs b/hadrian/src/Settings/Builders/HsCpp.hs
index e77833e758..72fe67a128 100644
--- a/hadrian/src/Settings/Builders/HsCpp.hs
+++ b/hadrian/src/Settings/Builders/HsCpp.hs
@@ -2,12 +2,14 @@ module Settings.Builders.HsCpp (hsCppBuilderArgs) where
import Packages
import Settings.Builders.Common
+import GHC.Toolchain
+import GHC.Toolchain.Program
hsCppBuilderArgs :: Args
hsCppBuilderArgs = builder HsCpp ? do
stage <- getStage
ghcPath <- expr $ buildPath (vanillaContext stage compiler)
- mconcat [ getSettingList HsCppArgs
+ mconcat [ prgFlags . cppProgram . tgtCPreprocessor <$> getStagedTargetConfig -- ROMES:TODO: HsCppArgs, not CppArgs, make sure this is the case
, arg "-P"
, arg "-Irts/include"
, arg $ "-I" ++ ghcPath
diff --git a/hadrian/src/Settings/Builders/Hsc2Hs.hs b/hadrian/src/Settings/Builders/Hsc2Hs.hs
index 7492f6e29a..921f3e770b 100644
--- a/hadrian/src/Settings/Builders/Hsc2Hs.hs
+++ b/hadrian/src/Settings/Builders/Hsc2Hs.hs
@@ -5,6 +5,8 @@ import Hadrian.Haskell.Cabal.Type
import Builder
import Packages
import Settings.Builders.Common
+import GHC.Toolchain (tgtCCompiler, ccProgram, tgtCPreprocessor, cppProgram, tgtCCompilerLink, ccLinkProgram)
+import GHC.Toolchain.Program
hsc2hsBuilderArgs :: Args
hsc2hsBuilderArgs = builder Hsc2Hs ? do
@@ -49,8 +51,8 @@ getCFlags = do
autogen <- expr $ autogenPath context
let cabalMacros = autogen -/- "cabal_macros.h"
expr $ need [cabalMacros]
- mconcat [ remove ["-O"] (cArgs <> getStagedSettingList ConfCcArgs)
- , getStagedSettingList ConfCppArgs
+ mconcat [ remove ["-O"] (cArgs <> (prgFlags . ccProgram . tgtCCompiler <$> getStagedTargetConfig))
+ , prgFlags . cppProgram . tgtCPreprocessor <$> getStagedTargetConfig -- ROMES:TODO: CppArgs, not HsCppArgs, make sure this is the case
, cIncludeArgs
, getContextData ccOpts
-- we might be able to leave out cppOpts, to be investigated.
@@ -61,7 +63,7 @@ getCFlags = do
getLFlags :: Expr [String]
getLFlags =
- mconcat [ getStagedSettingList ConfGccLinkerArgs
+ mconcat [ prgFlags . ccLinkProgram . tgtCCompilerLink <$> getStagedTargetConfig
, ldArgs
, getContextData ldOpts
, getContextData depLdOpts ]
diff --git a/hadrian/src/Settings/Builders/Ld.hs b/hadrian/src/Settings/Builders/Ld.hs
index c0c6a7083b..ed1a7ec214 100644
--- a/hadrian/src/Settings/Builders/Ld.hs
+++ b/hadrian/src/Settings/Builders/Ld.hs
@@ -1,8 +1,10 @@
module Settings.Builders.Ld (ldBuilderArgs) where
import Settings.Builders.Common
+import GHC.Toolchain
+import GHC.Toolchain.Program
ldBuilderArgs :: Args
-ldBuilderArgs = builder Ld ? mconcat [ getStagedSettingList ConfLdLinkerArgs
+ldBuilderArgs = builder Ld ? mconcat [ prgFlags . ccLinkProgram . tgtCCompilerLink <$> getStagedTargetConfig
, arg "-o", arg =<< getOutput
, getInputs ]
diff --git a/hadrian/src/Settings/Builders/MergeObjects.hs b/hadrian/src/Settings/Builders/MergeObjects.hs
index f5467b43ea..1dcff674b5 100644
--- a/hadrian/src/Settings/Builders/MergeObjects.hs
+++ b/hadrian/src/Settings/Builders/MergeObjects.hs
@@ -1,9 +1,11 @@
module Settings.Builders.MergeObjects (mergeObjectsBuilderArgs) where
import Settings.Builders.Common
+import GHC.Toolchain
+import GHC.Toolchain.Program
mergeObjectsBuilderArgs :: Args
mergeObjectsBuilderArgs = builder MergeObjects ? mconcat
- [ getStagedSettingList ConfMergeObjectsArgs
+ [ (maybe [] (prgFlags . mergeObjsProgram) . tgtMergeObjs) <$> getStagedTargetConfig
, arg "-o", arg =<< getOutput
, getInputs ]