[Git][ghc/ghc][wip/hadrian-cross-stage2] fix
Matthew Pickering (@mpickering)
gitlab at gitlab.haskell.org
Thu Sep 21 15:37:09 UTC 2023
Matthew Pickering pushed to branch wip/hadrian-cross-stage2 at Glasgow Haskell Compiler / GHC
Commits:
25360e01 by Matthew Pickering at 2023-09-21T16:37:01+01:00
fix
- - - - -
3 changed files:
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Packages.hs
- hadrian/src/Settings/Builders/RunTest.hs
Changes:
=====================================
hadrian/src/Oracles/Setting.hs
=====================================
@@ -6,7 +6,7 @@ module Oracles.Setting (
-- * Helpers
ghcCanonVersion, cmdLineLengthLimit, hostSupportsRPaths, topDirectory,
- libsuf, ghcVersionStage, bashPath, targetStage, queryTarget, queryTargetTarget,
+ libsuf, ghcVersionStage, bashPath, targetStage, crossStage, queryTarget, queryTargetTarget,
-- ** Target platform things
anyTargetOs, anyTargetArch, anyHostOs,
@@ -264,3 +264,10 @@ queryTarget s f = expr (f <$> targetStage s)
queryTargetTarget :: Stage -> (Target -> a) -> Action a
queryTargetTarget s f = f <$> targetStage s
+-- | Whether the StageN compiler is a cross-compiler or not.
+crossStage :: Stage -> Action Bool
+crossStage st = do
+ st_target <- targetStage st
+ st_host <- targetStage (predStage st)
+ return (targetPlatformTriple st_target /= targetPlatformTriple st_host)
+
=====================================
hadrian/src/Packages.hs
=====================================
@@ -165,12 +165,6 @@ linter name = program name ("linters" -/- name)
setPath :: Package -> FilePath -> Package
setPath pkg path = pkg { pkgPath = path }
--- | Whether the StageN compiler is a cross-compiler or not.
-crossStage :: Stage -> Action Bool
-crossStage st = do
- st_target <- targetStage st
- st_host <- targetStage (predStage st)
- return (targetPlatformTriple st_target /= targetPlatformTriple st_host)
-- | Target prefix to prepend to executable names.
=====================================
hadrian/src/Settings/Builders/RunTest.hs
=====================================
@@ -322,13 +322,14 @@ runTestBuilderArgs = builder Testsuite ? do
-- | Command line arguments for running GHC's test script.
getTestArgs :: Args
getTestArgs = do
+ stage <- getStage
-- targets specified in the TEST env var
testEnvTargets <- maybe [] words <$> expr (liftIO $ lookupEnv "TEST")
args <- expr $ userSetting defaultTestArgs
bindir <- expr $ getBinaryDirectory (testCompiler args)
compiler <- expr $ getCompilerPath (testCompiler args)
globalVerbosity <- shakeVerbosity <$> expr getShakeOptions
- cross_prefix <- expr crossPrefix
+ cross_prefix <- expr (crossPrefix (succStage stage))
-- the testsuite driver will itself tell us if we need to generate the docs target
-- So we always pass the haddock path if the hadrian configuration allows us to build
-- docs
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/25360e01ab155f59bf993779d337f6b66791bc6f
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/25360e01ab155f59bf993779d337f6b66791bc6f
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230921/49f9490e/attachment-0001.html>
More information about the ghc-commits
mailing list