
Rodrigo Mesquita pushed to branch wip/romes/26227 at Glasgow Haskell Compiler / GHC Commits: 1170bbe9 by Rodrigo Mesquita at 2025-08-01T13:49:10+01:00 Drop "Use interpreter" from settings The inaptly named "Use interpreter" entry in `lib/settings` recorded whether GHC had been compiled with the internal interpreter. However, that is a static property of the build, and therefore GHC should simply fix at compile time whether it is compiled with the internal interpreter by checking the HAVE_INTERNAL_INTERPRETER macro. Towards #26227 - - - - - 98cb9766 by Rodrigo Mesquita at 2025-08-01T13:49:10+01:00 Drop "unlit command" from settings The `unlit` program is a binary distributed with ghc. Its location is hardcoded to a path relative to its `$topdir`. It's unnecessary and confusing to write this into a global or per-target settings file since we don't allow it to be configured (except at runtime with -pgmL). Towards #26227 - - - - - 4 changed files: - compiler/GHC/Driver/Session.hs - compiler/GHC/Settings/IO.hs - hadrian/bindist/Makefile - hadrian/src/Rules/Generate.hs Changes: ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3502,6 +3502,7 @@ compilerInfo dflags ("target has .ident directive", queryBool tgtSupportsIdentDirective), ("target has subsections via symbols", queryBool tgtSupportsSubsectionsViaSymbols), ("target RTS linker only supports shared libraries", queryBool tgtRTSLinkerOnlySupportsSharedLibs), + ("unlit command", toolSettings_pgm_L (toolSettings dflags)), ("Unregisterised", queryBool tgtUnregisterised), ("LLVM target", query tgtLlvmTarget), ("LLVM llc command", queryCmdMaybe id tgtLlc), @@ -3528,6 +3529,10 @@ compilerInfo dflags ("target os string", stringEncodeOS (platformOS (targetPlatform dflags))), ("target arch string", stringEncodeArch (platformArch (targetPlatform dflags))), ("target word size in bits", show (platformWordSizeInBits (targetPlatform dflags))), + -- keep "duplicate" of "Have interpreter" for backwards compatibility, + -- since we used to show both... + -- These should really be called "Has internal interpreter" + ("Use interpreter", showBool $ platformMisc_ghcWithInterpreter $ platformMisc dflags), ("Have interpreter", showBool $ platformMisc_ghcWithInterpreter $ platformMisc dflags), ("Object splitting supported", showBool False), ("Have native code generator", showBool $ platformNcgSupported platform), ===================================== compiler/GHC/Settings/IO.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE ScopedTypeVariables #-} @@ -130,12 +131,8 @@ initSettings top_dir = do let ghc_usage_msg_path = installed "ghc-usage.txt" ghci_usage_msg_path = installed "ghci-usage.txt" - -- For all systems, unlit, split, mangle are GHC utilities - -- architecture-specific stuff is done when building Config.hs - unlit_path <- getToolSetting "unlit command" - - -- Other things being equal, 'as' is simply 'gcc' - let (cc_link, cc_link_args) = getTool (ccLinkProgram . tgtCCompilerLink) + -- Other things being equal, 'as' is simply 'gcc' + (cc_link, cc_link_args) = getTool (ccLinkProgram . tgtCCompilerLink) as_prog = cc_prog as_args = map Option cc_args ld_prog = cc_link @@ -145,8 +142,9 @@ initSettings top_dir = do let (ld_r_path, ld_r_args) = getTool (mergeObjsProgram . const ld_r_prog) pure (ld_r_path, map Option ld_r_args) iserv_prog = libexec "ghc-iserv" - - ghcWithInterpreter <- getBooleanSetting "Use interpreter" + unlit_prog = libexec (if tgtLocallyExecutable + then "unlit" -- not a cross compiler + else targetPlatformTriple target ++ "-unlit") baseUnitId <- getSetting_raw "base unit-id" @@ -181,7 +179,7 @@ initSettings top_dir = do , toolSettings_arSupportsDashL = arSupportsDashL $ tgtAr target , toolSettings_cmmCppSupportsG0 = cmmCppSupportsG0 $ tgtCmmCPreprocessor target - , toolSettings_pgm_L = unlit_path + , toolSettings_pgm_L = unlit_prog , toolSettings_pgm_P = (hs_cpp_prog, map Option hs_cpp_args) , toolSettings_pgm_JSP = (js_cpp_prog, map Option js_cpp_args) , toolSettings_pgm_CmmP = (cmmCpp_prog, map Option cmmCpp_args) @@ -227,7 +225,7 @@ initSettings top_dir = do , sTargetPlatform = platform , sPlatformMisc = PlatformMisc { platformMisc_targetPlatformString = targetPlatformTriple target - , platformMisc_ghcWithInterpreter = ghcWithInterpreter + , platformMisc_ghcWithInterpreter = ghcWithInternalInterpreter , platformMisc_libFFI = tgtUseLibffiForAdjustors target , platformMisc_llvmTarget = tgtLlvmTarget target , platformMisc_targetRTSLinkerOnlySupportsSharedLibs = tgtRTSLinkerOnlySupportsSharedLibs target @@ -253,3 +251,13 @@ getTargetPlatform Target{..} = Platform , platformHasLibm = tgtHasLibm , platform_constants = Nothing -- will be filled later when loading (or building) the RTS unit } + + +-- | Do we have an internal interpreter? +ghcWithInternalInterpreter :: Bool +#if defined(HAVE_INTERNAL_INTERPRETER) +ghcWithInternalInterpreter = True +#else +ghcWithInternalInterpreter = False +#endif + ===================================== hadrian/bindist/Makefile ===================================== @@ -85,9 +85,7 @@ WrapperBinsDir=${bindir} # N.B. this is duplicated from includes/ghc.mk. lib/settings : config.mk @rm -f $@ - @echo '[("unlit command", "$$topdir/../bin/$(CrossCompilePrefix)unlit")' >> $@ - @echo ',("Use interpreter", "$(GhcWithInterpreter)")' >> $@ - @echo ',("RTS ways", "$(GhcRTSWays)")' >> $@ + @echo '[("RTS ways", "$(GhcRTSWays)")' >> $@ @echo ',("Relative Global Package DB", "package.conf.d")' >> $@ @echo ',("base unit-id", "$(BaseUnitId)")' >> $@ @echo "]" >> $@ ===================================== hadrian/src/Rules/Generate.hs ===================================== @@ -8,7 +8,6 @@ import Development.Shake.FilePath import Data.Char (isSpace) import qualified Data.Set as Set import Base -import qualified Context import Expression import Hadrian.Oracles.TextFile (lookupSystemConfig, getTargetTarget) import Oracles.Flag hiding (arSupportsAtFile, arSupportsDashL) @@ -25,7 +24,6 @@ import Utilities import GHC.Toolchain as Toolchain hiding (HsCpp(HsCpp)) import GHC.Platform.ArchOS -import Settings.Program (ghcWithInterpreter) -- | Track this file to rebuild generated files whenever it changes. trackGenerateHs :: Expr () @@ -461,7 +459,6 @@ ghcWrapper stage = do generateSettings :: FilePath -> Expr String generateSettings settingsFile = do - ctx <- getContext stage <- getStage package_db_path <- expr $ do @@ -483,9 +480,7 @@ generateSettings settingsFile = do let rel_pkg_db = makeRelativeNoSysLink (dropFileName settingsFile) package_db_path settings <- traverse sequence $ - [ ("unlit command", ("$topdir/../bin/" <>) <$> expr (programName (ctx { Context.package = unlit }))) - , ("Use interpreter", expr $ yesNo <$> ghcWithInterpreter (predStage stage)) - , ("RTS ways", escapeArgs . map show . Set.toList <$> getRtsWays) + [ ("RTS ways", escapeArgs . map show . Set.toList <$> getRtsWays) , ("Relative Global Package DB", pure rel_pkg_db) , ("base unit-id", pure base_unit_id) ] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/debc35861fa8244a45aa3c6d4aae1c5... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/debc35861fa8244a45aa3c6d4aae1c5... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Rodrigo Mesquita (@alt-romes)