Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
8cbe006a by Cheng Shao at 2025-09-26T16:01:34-04:00
hadrian: fix GHC.Platform.Host generation for cross stage1
This patch fixes incorrectly GHC.Platform.Host generation logic for
cross stage1 in hadrian (#26449). Also adds T26449 test case to
witness the fix.
Co-authored-by: Codex
- - - - -
3 changed files:
- hadrian/src/Rules/Generate.hs
- + testsuite/tests/cross/should_run/T26449.hs
- + testsuite/tests/cross/should_run/all.T
Changes:
=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -606,8 +606,12 @@ generateVersionHs = do
generatePlatformHostHs :: Expr String
generatePlatformHostHs = do
trackGenerateHs
- cHostPlatformArch <- queryHost (archOS_arch . tgtArchOs)
- cHostPlatformOS <- queryHost (archOS_OS . tgtArchOs)
+ stage <- getStage
+ let chooseHostQuery = case stage of
+ Stage0 {} -> queryHost
+ _ -> queryTarget
+ cHostPlatformArch <- chooseHostQuery (archOS_arch . tgtArchOs)
+ cHostPlatformOS <- chooseHostQuery (archOS_OS . tgtArchOs)
return $ unlines
[ "module GHC.Platform.Host where"
, ""
=====================================
testsuite/tests/cross/should_run/T26449.hs
=====================================
@@ -0,0 +1,16 @@
+import Control.Monad
+import GHC.Platform.ArchOS
+import GHC.Platform.Host
+import System.Info
+
+main :: IO ()
+main =
+ when ((arch, os) /= (arch', os')) $
+ fail $
+ "System.Info says host platform is "
+ <> show (arch, os)
+ <> " but GHC.Platform.Host says "
+ <> show (arch', os')
+ where
+ (arch', os') =
+ (stringEncodeArch hostPlatformArch, stringEncodeOS hostPlatformOS)
=====================================
testsuite/tests/cross/should_run/all.T
=====================================
@@ -0,0 +1 @@
+test('T26449', [], compile_and_run, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8cbe006ad09d5a64e4a3cdf4c91a8b81...
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8cbe006ad09d5a64e4a3cdf4c91a8b81...
You're receiving this email because of your account on gitlab.haskell.org.