[Git][ghc/ghc][wip/romes/hadrian-cross-stage2-rebase_SVEN_FIXED] 2 commits: Rebase fixup: ghcWithInternalInterpreter
Sven Tennie pushed to branch wip/romes/hadrian-cross-stage2-rebase_SVEN_FIXED at Glasgow Haskell Compiler / GHC Commits: 652091c5 by GHC GitLab CI at 2025-11-16T14:35:18+01:00 Rebase fixup: ghcWithInternalInterpreter - - - - - b5ea9968 by GHC GitLab CI at 2025-11-16T14:35:56+01:00 Provide config.cross flag to testsuite - - - - - 5 changed files: - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Settings/Builders/Cabal.hs - hadrian/src/Settings/Builders/RunTest.hs - hadrian/src/Settings/Packages.hs Changes: ===================================== hadrian/src/Oracles/Setting.hs ===================================== @@ -7,7 +7,7 @@ module Oracles.Setting ( -- * Helpers ghcCanonVersion, cmdLineLengthLimit, targetSupportsRPaths, topDirectory, libsuf, ghcVersionStage, bashPath, targetStage, crossStage, queryTarget, queryTargetTarget, - ghcWithInterpreter, isHostStage, + isHostStage, -- ** Target platform things anyTargetOs, anyTargetArch, anyHostOs, @@ -181,22 +181,6 @@ targetSupportsRPaths stage = queryTargetTarget stage (\t -> let os = archOS_OS (tgtArchOs t) in osElfTarget os || osMachOTarget os) --- | Check whether the target supports GHCi. -ghcWithInterpreter :: Stage -> Action Bool -ghcWithInterpreter stage = do - goodOs <- anyTargetOs stage [ OSMinGW32, OSLinux, OSSolaris2 -- TODO "cygwin32"?, - , OSFreeBSD, OSDragonFly, OSNetBSD, OSOpenBSD - , OSDarwin, OSKFreeBSD - , OSWasi ] - goodArch <- (||) <$> - anyTargetArch stage [ ArchX86, ArchX86_64, ArchPPC - , ArchAArch64, ArchS390X - , ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2 - , ArchRISCV64, ArchLoongArch64 - , ArchWasm32 ] - <*> isArmTarget stage - return $ goodOs && goodArch && (stage >= Stage1) - -- | Which variant of the ARM architecture is the target (or 'Nothing' if not -- ARM)? targetArmVersion :: Stage -> Action (Maybe ArmISA) ===================================== hadrian/src/Rules/Generate.hs ===================================== @@ -12,6 +12,7 @@ import Hadrian.Oracles.TextFile (lookupStageBuildConfig) import Oracles.Flag hiding (arSupportsAtFile, arSupportsDashL) import Oracles.ModuleFiles import Oracles.Setting +import Settings.Program (ghcWithInterpreter) import Hadrian.Haskell.Cabal.Type (PackageData(version)) import Hadrian.Haskell.Cabal import Hadrian.Oracles.Cabal (readPackageData) @@ -489,7 +490,7 @@ generateSettings settingsFile = do -- ROMES:TODO: WHERE HAS CROSS COMPILING GONE? -- ("cross compiling", expr $ yesNo <$> crossStage (predStage stage)) [ ("unlit command", ("$topdir/../bin/" <>) <$> expr (programName (ctx { Context.package = unlit, Context.stage = predStage stage }))) - , ("Use interpreter", expr $ yesNo <$> Oracles.Setting.ghcWithInterpreter stage) + , ("Use interpreter", expr $ yesNo <$> ghcWithInterpreter (predStage stage)) -- Hard-coded as Cabal queries these to determine way support and we -- need to always advertise all ways when bootstrapping. -- The settings file is generated at install time when installing a bindist. ===================================== hadrian/src/Settings/Builders/Cabal.hs ===================================== @@ -11,7 +11,7 @@ import Settings.Builders.Common import qualified Settings.Builders.Common as S import Control.Exception (assert) import qualified Data.Set as Set -import Settings.Program (programContext) +import Settings.Program (programContext, ghcWithInterpreter) import GHC.Toolchain (ccLinkProgram, tgtCCompilerLink, targetPlatformTriple) import GHC.Toolchain.Program (prgFlags) @@ -139,7 +139,7 @@ libraryArgs = do contextWay <- getWay package <- getPackage stage <- getStage - withGhci <- expr (ghcWithInterpreter stage) + withGhci <- expr $ ghcWithInterpreter stage dynPrograms <- expr (flavour >>= flip dynamicGhcPrograms stage) ghciObjsSupported <- expr (targetSupportsGhciObjects stage) let ways = Set.insert contextWay flavourWays ===================================== hadrian/src/Settings/Builders/RunTest.hs ===================================== @@ -15,6 +15,7 @@ import CommandLine import Oracles.TestSettings import Packages import Settings.Builders.Common +import Settings.Program (ghcWithInterpreter) import qualified Data.Set as Set import Flavour import qualified Context.Type as C @@ -62,6 +63,7 @@ data TestCompilerArgs = TestCompilerArgs{ , leadingUnderscore :: Bool , withNativeCodeGen :: Bool , withInterpreter :: Bool + , cross :: Bool , interpForceDyn :: Bool , unregisterised :: Bool , tables_next_to_code :: Bool @@ -96,9 +98,9 @@ allowHaveLLVM = not . (`elem` ["wasm32", "javascript"]) -- inTreeCompilerArgs :: Stage -> Action TestCompilerArgs inTreeCompilerArgs stg = do - isCrossStage <- crossStage stg + cross <- crossStage stg let ghcStage = succStage stg - pkgCacheStage = if isCrossStage then ghcStage else stg + pkgCacheStage = if cross then ghcStage else stg (hasDynamicRts, hasThreadedRts) <- do ways <- interpretInContext (vanillaContext ghcStage rts) getRtsWays return (dynamic `elem` ways, threaded `elem` ways) @@ -158,11 +160,11 @@ outOfTreeCompilerArgs = do leadingUnderscore <- getBooleanSetting TestLeadingUnderscore withNativeCodeGen <- getBooleanSetting TestGhcWithNativeCodeGen withInterpreter <- getBooleanSetting TestGhcWithInterpreter + cross <- getBooleanSetting TestGhcCrossCompiling interpForceDyn <- getBooleanSetting TestRTSLinkerForceDyn unregisterised <- getBooleanSetting TestGhcUnregisterised tables_next_to_code <- getBooleanSetting TestGhcTablesNextToCode targetWithSMP <- getBooleanSetting TestGhcWithSMP - debugAssertions <- getBooleanSetting TestGhcDebugAssertions os <- getTestSetting TestHostOS @@ -279,6 +281,7 @@ runTestBuilderArgs = builder Testsuite ? do , arg "-e", arg $ "config.have_interp=" ++ show withInterpreter + , arg "-e", arg $ "config.cross=" ++ show cross , arg "-e", arg $ "config.interp_force_dyn=" ++ show interpForceDyn , arg "-e", arg $ "config.unregisterised=" ++ show unregisterised , arg "-e", arg $ "config.tables_next_to_code=" ++ show tables_next_to_code ===================================== hadrian/src/Settings/Packages.hs ===================================== @@ -8,6 +8,7 @@ import Oracles.Flag import Packages import Settings import Settings.Builders.Common (wayCcArgs) +import Settings.Program (ghcWithInterpreter) import qualified GHC.Toolchain.Library as Lib import GHC.Toolchain.Target @@ -82,16 +83,18 @@ packageArgs = do ] , builder (Cabal Flags) ? mconcat - -- For the ghc library, internal-interpreter only makes - -- sense when we're not cross compiling. For cross GHC, - -- external interpreter is used for loading target code - -- and internal interpreter is supposed to load native - -- code for plugins (!7377), however it's unfinished work - -- (#14335) and completely untested in CI for cross - -- backends at the moment, so we might as well disable it - -- for cross GHC. - -- TODO: MP - [ andM [ghcWithInterpreter stage, notM isCrossStage] `cabalFlag` "internal-interpreter" + -- In order to enable internal-interpreter for the ghc + -- library: + -- + -- 1. ghcWithInterpreter must be True ("Use interpreter" = + -- "YES") + -- 2. For non-cross case it can be enabled + -- 3. For cross case, disable for stage0 since that runs + -- on the host and must rely on external interpreter to + -- load target code, otherwise enable for stage1 since + -- that runs on the target and can use target's own + -- ghci object linker + [ andM [expr (ghcWithInterpreter stage), orM [expr (notM cross), stage2]] `cabalFlag` "internal-interpreter" , orM [ notM cross, haveCurses ] `cabalFlag` "terminfo" , arg "-build-tool-depends" , staged (buildFlag UseLibzstd) `cabalFlag` "with-libzstd" @@ -113,7 +116,7 @@ packageArgs = do , compilerStageOption ghcDebugAssertions ? arg "-DDEBUG" ] , builder (Cabal Flags) ? mconcat - [ andM [ghcWithInterpreter stage, notM isCrossStage] `cabalFlag` "internal-interpreter" + [ (expr (ghcWithInterpreter stage)) `cabalFlag` "internal-interpreter" , ifM stage0 -- We build a threaded stage 1 if the bootstrapping compiler -- supports it. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ca6129780c811d78cfbc04fde5f1ac5... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ca6129780c811d78cfbc04fde5f1ac5... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Sven Tennie (@supersven)