[Git][ghc/ghc][wip/romes/hadrian-cross-stage2-rebase_SVEN_FIXED] Fix libffi configuration
Sven Tennie pushed to branch wip/romes/hadrian-cross-stage2-rebase_SVEN_FIXED at Glasgow Haskell Compiler / GHC Commits: 0b73a45a by Sven Tennie at 2025-09-20T20:41:30+02:00 Fix libffi configuration Libffi needs to be built with the config of the successor stage. - - - - - 7 changed files: - hadrian/src/Builder.hs - hadrian/src/Context.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Libffi.hs - hadrian/src/Rules/Rts.hs - hadrian/src/Settings/Builders/Ghc.hs - hadrian/src/Settings/Packages.hs Changes: ===================================== hadrian/src/Builder.hs ===================================== @@ -241,7 +241,7 @@ instance H.Builder Builder where distro_mingw <- lookupStageBuildConfig "settings-use-distro-mingw" st -- TODO: Check this is the right stage libffi_adjustors <- targetUseLibffiForAdjustors st - use_system_ffi <- buildFlag UseSystemFfi st + use_system_ffi <- buildFlag UseSystemFfi (succStage st) return $ [ unlitPath ] ++ [ root -/- mingwStamp | windowsHost, distro_mingw == "NO" ] ===================================== hadrian/src/Context.hs ===================================== @@ -3,7 +3,7 @@ module Context ( Context (..), vanillaContext, stageContext, -- * Expressions - getStage, staged, getPackage, getWay, getBuildPath, getHieBuildPath, getPackageDbLoc, getStagedTarget, + getStage, staged, succStaged, getPackage, getWay, getBuildPath, getHieBuildPath, getPackageDbLoc, getStagedTarget, -- * Paths contextDir, buildPath, buildDir, pkgInplaceConfig, pkgSetupConfigFile, pkgSetupConfigDir, @@ -32,6 +32,9 @@ getStage = stage <$> getContext staged :: (Stage -> Action a) -> Expr Context b a staged f = getStage >>= \stage -> expr (f stage) +succStaged :: (Stage -> Action a) -> Expr Context b a +succStaged f = getStage >>= \stage -> expr (f (succStage stage)) + getInplace :: Expr Context b Inplace getInplace = iplace <$> getContext ===================================== hadrian/src/Rules/Generate.hs ===================================== @@ -55,7 +55,7 @@ rtsDependencies :: Expr [FilePath] rtsDependencies = do rtsPath <- staged rtsBuildPath jsTarget <- staged isJsTarget - useSystemFfi <- staged (buildFlag UseSystemFfi) + useSystemFfi <- succStaged (buildFlag UseSystemFfi) let -- headers common to native and JS RTS common_headers = ===================================== hadrian/src/Rules/Libffi.hs ===================================== @@ -69,7 +69,7 @@ dynLibManifest = dynLibManifest' buildRoot -- | Need the (locally built) libffi library. needLibffi :: Stage -> Action () needLibffi stage = do - jsTarget <- isJsTarget stage + jsTarget <- isJsTarget (succStage stage) unless jsTarget $ do manifest <- dynLibManifest stage need [manifest] @@ -87,7 +87,7 @@ libffiContext stage = do -- | The name of the library libffiName :: Expr String libffiName = do - useSystemFfi <- staged (buildFlag UseSystemFfi) + useSystemFfi <- succStaged (buildFlag UseSystemFfi) if useSystemFfi then pure "ffi" else libffiLocalName Nothing @@ -159,7 +159,7 @@ libffiRules :: Rules () libffiRules = do _ <- addOracleCache $ \ (LibffiDynLibs stage) -> do - jsTarget <- isJsTarget stage + jsTarget <- isJsTarget (succStage stage) if jsTarget then return [] else readFileLines =<< dynLibManifest stage ===================================== hadrian/src/Rules/Rts.hs ===================================== @@ -33,7 +33,7 @@ rtsRules = priority 3 $ do -- Header files -- See Note [Packaging libffi headers] in GHC.Driver.CodeOutput. forM_ libffiHeaderFiles $ \header -> - buildPath -/- "include" -/- header %> copyLibffiHeader stage + buildPath -/- "include" -/- header %> copyLibffiHeader (succStage stage) -- Static libraries. buildPath -/- "libCffi*.a" %> copyLibffiStatic stage @@ -54,7 +54,7 @@ withLibffi stage action = needLibffi stage -- See Note [Packaging libffi headers] in GHC.Driver.CodeOutput. copyLibffiHeader :: Stage -> FilePath -> Action () copyLibffiHeader stage header = do - useSystemFfi <- buildFlag UseSystemFfi stage + useSystemFfi <- buildFlag UseSystemFfi (succStage stage) (fromStr, headerDir) <- if useSystemFfi then ("system",) <$> libffiSystemHeaderDir stage else needLibffi stage @@ -129,7 +129,7 @@ rtsLibffiLibrary stage way = do needRtsLibffiTargets :: Stage -> Action [FilePath] needRtsLibffiTargets stage = do rtsPath <- rtsBuildPath stage - useSystemFfi <- buildFlag UseSystemFfi stage + useSystemFfi <- buildFlag UseSystemFfi (succStage stage) jsTarget <- isJsTarget stage -- Header files (in the rts build dir). ===================================== hadrian/src/Settings/Builders/Ghc.hs ===================================== @@ -107,7 +107,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do context <- getContext distPath <- expr (Context.distDynDir context) - useSystemFfi <- staged (buildFlag UseSystemFfi) + useSystemFfi <- succStaged (buildFlag UseSystemFfi) buildPath <- getBuildPath libffiName' <- libffiName debugged <- buildingCompilerStage' . ghcDebugged =<< expr flavour ===================================== hadrian/src/Settings/Packages.hs ===================================== @@ -298,7 +298,7 @@ rtsPackageArgs = package rts ? do way <- getWay path <- getBuildPath top <- expr topDirectory - useSystemFfi <- staged (buildFlag UseSystemFfi) + useSystemFfi <- succStaged (buildFlag UseSystemFfi) ffiIncludeDir <- staged (buildSetting FfiIncludeDir) ffiLibraryDir <- staged (buildSetting FfiLibDir) libdwIncludeDir <- staged (\s -> queryTargetTarget s (Lib.includePath <=< tgtRTSWithLibdw)) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0b73a45ab14cf4dddc8c359ca6694d91... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0b73a45ab14cf4dddc8c359ca6694d91... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Sven Tennie (@supersven)