[Git][ghc/ghc][master] compiler: remove iserv and only use on-demand external interpreter
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: c94aaacd by Cheng Shao at 2026-01-13T12:42:44-05:00 compiler: remove iserv and only use on-demand external interpreter This patch removes `iserv` from the tree completely. Hadrian would no longer build or distribute `iserv`, and the GHC driver would use the on-demand external interpreter by default when invoked with `-fexternal-interpreter`, without needing to specify `-pgmi ""`. This has multiple benefits: - It allows cleanup of a lot of legacy hacks in the hadrian codebase. - It paves the way for running cross ghc's iserv via cross emulator (#25523), fixing TH/ghci support for cross targets other than wasm/js. - - - - - 20 changed files: - CODEOWNERS - cabal.project-reinstall - compiler/GHC/Runtime/Interpreter/Init.hs - compiler/GHC/Settings/IO.hs - docs/users_guide/ghci.rst - docs/users_guide/phases.rst - hadrian/doc/user-settings.md - hadrian/src/Packages.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/CabalReinstall.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Program.hs - hadrian/src/Rules/Test.hs - hadrian/src/Settings/Builders/Ghc.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Packages.hs - − testsuite/tests/driver/T24731.hs - testsuite/tests/driver/all.T - − utils/iserv/iserv.cabal.in - − utils/iserv/src/Main.hs Changes: ===================================== CODEOWNERS ===================================== @@ -66,7 +66,6 @@ [Internal utilities and libraries] /utils/iserv-proxy/ @angerman @simonmar -/utils/iserv/ @angerman @simonmar /utils/fs/ @Phyx /utils/jsffi @TerrorJack /utils/haddock @Kleidukos ===================================== cabal.project-reinstall ===================================== @@ -52,7 +52,6 @@ packages: ./compiler ./utils/hsc2hs ./utils/runghc ./utils/unlit - ./utils/iserv ./linters/**/*.cabal constraints: ghc +internal-interpreter +dynamic-system-linke, ===================================== compiler/GHC/Runtime/Interpreter/Init.hs ===================================== @@ -128,13 +128,7 @@ initInterpreter dflags tmpfs logger platform finder_cache unit_env opts = do prog <- case interpProg opts of -- build iserv program if none specified "" -> generateIservC dflags logger tmpfs (interpExecutableLinkOpts opts) unit_env - _ -> pure (interpProg opts ++ flavour) - where - flavour - | profiled && dynamic = "-prof-dyn" - | profiled = "-prof" - | dynamic = "-dyn" - | otherwise = "" + _ -> pure $ interpProg opts let msg = text "Starting " <> text prog tr <- if interpVerbosity opts >= 3 then return (logInfo logger $ withPprStyle defaultDumpStyle msg) ===================================== compiler/GHC/Settings/IO.hs ===================================== @@ -41,8 +41,6 @@ initSettings initSettings top_dir = do let installed :: FilePath -> FilePath installed file = top_dir > file - libexec :: FilePath -> FilePath - libexec file = top_dir > ".." > "bin" > file settingsFile = installed "settings" targetFile = installed $ "targets" > "default.target" @@ -142,7 +140,9 @@ initSettings top_dir = do ld_r_prog <- tgtMergeObjs target 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" + -- Default to the on-demand external interpreter. A non-empty value can + -- be provided via -pgmi to use a custom external interpreter. + iserv_prog = "" ghcWithInterpreter <- getBooleanSetting "Use interpreter" ===================================== docs/users_guide/ghci.rst ===================================== @@ -3560,15 +3560,18 @@ default in future releases. Building an external interpreter ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -The source code for the external interpreter program is in `utils/iserv`. It is -very simple because most of the heavy lifting code is from the `ghci` library. +When :ghc-flag:`-fexternal-interpreter` is enabled, GHC builds a small external +interpreter executable on demand using the installed `ghci` library and runs it +directly. There is no longer a dedicated `utils/iserv` program in the tree. It is sometimes desirable to customize the external interpreter program. For example, it is possible to add symbols to the RTS linker used by the external interpreter. This is done simply at link time by linking an additional `.o` that defines a `rtsExtraSyms` function returning the extra symbols. Doing it this way avoids the need to recompile the RTS with symbols added to its built-in list. -A typical C file would look like this: +Build your custom interpreter (using `ghci:GHCi.Server.defaultServer` as the +entry point) and point :ghc-flag:`-pgmi ⟨cmd⟩` at it. A typical C file would +look like this: .. code:: C ===================================== docs/users_guide/phases.rst ===================================== @@ -151,16 +151,10 @@ given compilation phase: :category: phase-programs Use ⟨cmd⟩ as the external interpreter command (see - :ref:`external-interpreter`). Default: ``ghc-iserv-prof`` if - :ghc-flag:`-prof` is enabled, ``ghc-iserv-dyn`` if :ghc-flag:`-dynamic` is - enabled, or ``ghc-iserv`` otherwise. - - If <cmd> is the empty string then GHC will try to build an appropriate iserv - program for the target platform. It does this by looking for the installed - ``ghci`` unit and by building an executable program that uses - ``ghci:GHCi.Server.defaultServer`` as an entry point. Note that it doesn't - work when cross-compiling: the cross-compiled ``iserv`` program (if it can - be built) can't be run on the build platform. + :ref:`external-interpreter`). By default GHC builds an on-demand external + interpreter using the installed ``ghci`` unit and runs it directly. This + requires that target executables can run on the build host; when + cross-compiling, pass ``-pgmi`` to use a proxy such as ``iserv-proxy``. .. _forcing-options-through: ===================================== hadrian/doc/user-settings.md ===================================== @@ -238,7 +238,7 @@ quickDebug = quickFlavour { name = "dbg", ghcDebugged = const True } ``` Running `build --flavour=dbg` will build a `quick`-flavoured GHC and link -GHC, iserv, iserv-proxy and remote-iserv against the debugged RTS, by passing +GHC, iserv-proxy and remote-iserv against the debugged RTS, by passing `-debug` to the commands that link those executables. More generally, a predicate on `Stage` can be provided to specify which stages should be built debugged. For example, setting `ghcDebugged = (>= Stage2)` will build a debugged compiler at stage 2 or higher, but not stage 1. ===================================== hadrian/src/Packages.hs ===================================== @@ -7,7 +7,7 @@ module Packages ( exceptions, filepath, fileio, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh, ghcBootThNext, ghcPlatform, ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghcInternal, ghci, ghciWrapper, ghcPkg, ghcPrim, ghcToolchain, ghcToolchainBin, haddockApi, haddockLibrary, haddock, haskeline, - hsc2hs, hp2ps, hpc, hpcBin, integerGmp, iserv, iservProxy, + hsc2hs, hp2ps, hpc, hpcBin, integerGmp, iservProxy, libffi, mtl, osString, parsec, pretty, primitive, process, remoteIserv, rts, runGhc, semaphoreCompat, stm, templateHaskell, thLift, thQuasiquoter, terminfo, text, time, timeout, transformers, unlit, unix, win32, xhtml, @@ -38,7 +38,7 @@ ghcPackages = , exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh, ghcBootThNext, ghcPlatform , ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghcInternal, ghci, ghciWrapper, ghcPkg, ghcPrim , ghcToolchain, ghcToolchainBin, haddockApi, haddockLibrary, haddock, haskeline, hsc2hs - , hp2ps, hpc, hpcBin, integerGmp, iserv, libffi, mtl, osString + , hp2ps, hpc, hpcBin, integerGmp, libffi, mtl, osString , parsec, pretty, process, rts, runGhc, stm, semaphoreCompat, templateHaskell, thLift, thQuasiquoter , terminfo, text, time, transformers, unlit, unix, win32, xhtml, fileio , timeout @@ -55,7 +55,7 @@ array, base, binary, bytestring, cabalSyntax, cabal, checkPpr, checkExact, count exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh, ghcBootThNext, ghcPlatform, ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghci, ghcInternal, ghciWrapper, ghcPkg, ghcPrim, ghcToolchain, ghcToolchainBin, haddockLibrary, haddockApi, haddock, haskeline, hsc2hs, - hp2ps, hpc, hpcBin, integerGmp, iserv, iservProxy, remoteIserv, libffi, mtl, + hp2ps, hpc, hpcBin, integerGmp, iservProxy, remoteIserv, libffi, mtl, osString, parsec, pretty, primitive, process, rts, runGhc, semaphoreCompat, stm, templateHaskell, thLift, thQuasiquoter, terminfo, text, time, transformers, unlit, unix, win32, xhtml, timeout, @@ -109,7 +109,6 @@ hp2ps = util "hp2ps" hpc = lib "hpc" hpcBin = util "hpc-bin" `setPath` "utils/hpc" integerGmp = lib "integer-gmp" -iserv = util "iserv" iservProxy = util "iserv-proxy" libffi = top "libffi" mtl = lib "mtl" @@ -182,24 +181,12 @@ programName :: Context -> Action String programName Context {..} = do prefix <- crossPrefix -- TODO: Can we extract this information from Cabal files? - -- Alp: We could, but then the iserv package would have to - -- use Cabal conditionals + a 'profiling' flag - -- to declare the executable name, and I'm not sure - -- this is allowed (or desired for that matter). return $ prefix ++ basename where basename | package == ghc = "ghc" | package == ghciWrapper = "ghci" -- See Note [Hadrian's ghci-wrapper package] | package == hpcBin = "hpc" - | package == iserv = "ghc-iserv" ++ concat [ - if wayUnit' `wayUnit` way - then suffix - else "" - | (wayUnit', suffix) <- [ - (Profiling, "-prof"), - (Dynamic, "-dyn") - ]] | otherwise = pkgName package -- | The 'FilePath' to a program executable in a given 'Context'. ===================================== hadrian/src/Rules/BinaryDist.hs ===================================== @@ -5,7 +5,6 @@ import CommandLine import Context import Expression import Oracles.Setting -import Oracles.Flag import Packages import Settings import Settings.Program (programContext) @@ -154,10 +153,7 @@ bindistRules = do -- We 'need' all binaries and libraries all_pkgs <- stagePackages Stage1 (lib_targets, bin_targets) <- partitionEithers <$> mapM pkgTarget all_pkgs - cross <- flag CrossCompiling - iserv_targets <- if cross then pure [] else iservBins - - let lib_exe_targets = (lib_targets ++ (map (\(_, p) -> p) (bin_targets ++ iserv_targets))) + let lib_exe_targets = lib_targets ++ map snd bin_targets let doc_target = ["docs"] @@ -173,7 +169,7 @@ bindistRules = do createDirectory (bindistFilesDir -/- "bin") createDirectory (bindistFilesDir -/- "lib") -- Also create wrappers with version suffixes (#20074) - forM_ (bin_targets ++ iserv_targets) $ \(pkg, prog_path) -> do + forM_ bin_targets $ \(pkg, prog_path) -> do let orig_filename = takeFileName prog_path (name, ext) = splitExtensions orig_filename suffix = if useGhcPrefix pkg @@ -481,20 +477,6 @@ ghciScriptWrapper = do [ "executable=\"$bindir/" ++ prefix ++ "ghc-" ++ version ++ "\"" , "exec $executable --interactive \"$@\"" ] --- | When not on Windows, we want to ship the 3 flavours of the iserv program --- in binary distributions. This isn't easily achievable by just asking for --- the package to be built, since here we're generating 3 different --- executables out of just one package, so we need to specify all 3 contexts --- explicitly and 'need' the result of building them. -iservBins :: Action [(Package, FilePath)] -iservBins = do - rtsways <- interpretInContext (vanillaContext Stage1 ghc) getRtsWays - traverse (fmap (\p -> (iserv, p)) . programPath) - [ Context Stage1 iserv w Final - | w <- [vanilla, profiling, dynamic] - , w `elem` rtsways - ] - -- Version wrapper scripts -- See Note [Two Types of Wrappers] ===================================== hadrian/src/Rules/CabalReinstall.hs ===================================== @@ -2,7 +2,6 @@ module Rules.CabalReinstall where import Context import Expression -import Oracles.Flag import Packages import Settings import Target @@ -48,9 +47,7 @@ cabalBuildRules = do -- We 'need' all binaries and libraries all_pkgs <- stagePackages Stage1 (lib_targets, bin_targets) <- partitionEithers <$> mapM pkgTarget all_pkgs - cross <- flag CrossCompiling - iserv_targets <- if cross then pure [] else iservBins - need (lib_targets ++ (map (\(_, p) -> p) (bin_targets ++ iserv_targets))) + need (lib_targets ++ map snd bin_targets) distDir <- Context.distDir (vanillaContext Stage1 rts) let rtsIncludeDir = distDir -/- "include" @@ -69,7 +66,7 @@ cabalBuildRules = do let cabal_package_db = cwd -/- root -/- "stage-cabal" -/- "dist-newstyle" -/- "packagedb" -/- "ghc-" ++ version - forM_ (filter ((/= iserv) . fst) bin_targets) $ \(bin_pkg,_bin_path) -> do + forM_ bin_targets $ \(bin_pkg,_bin_path) -> do let pgmName pkg | pkg == ghc = "ghc" | pkg == hpcBin = "hpc" @@ -92,14 +89,4 @@ cabalBuildRules = do makeExecutable output_file pure () - -- Just symlink these for now - -- TODO: build these with cabal as well - forM_ iserv_targets $ \(_bin_pkg,bin_path') -> do - bin_path <- liftIO $ makeAbsolute bin_path' - let orig_filename = takeFileName bin_path - output_file = outputDir -/- orig_filename - liftIO $ do - IO.removeFile output_file <|> pure () - IO.createFileLink bin_path output_file - pure () writeFile' stamp "OK" ===================================== hadrian/src/Rules/Generate.hs ===================================== @@ -351,7 +351,6 @@ templateRules = do templateRule "compiler/ghc.cabal" $ projectVersion templateRule "driver/ghci/ghci-wrapper.cabal" $ projectVersion templateRule "ghc/ghc-bin.cabal" $ projectVersion - templateRule "utils/iserv/iserv.cabal" $ projectVersion templateRule "utils/remote-iserv/remote-iserv.cabal" $ projectVersion templateRule "utils/runghc/runghc.cabal" $ projectVersion templateRule "libraries/ghc-boot/ghc-boot.cabal" $ projectVersion ===================================== hadrian/src/Rules/Program.hs ===================================== @@ -53,27 +53,10 @@ getProgramContexts stage = do -- TODO: Shall we use Stage2 for testsuite packages instead? let allPackages = sPackages ++ tPackages - fmap concat . forM allPackages $ \pkg -> do - -- the iserv pkg results in three different programs at - -- the moment, ghc-iserv (built the vanilla way), - -- ghc-iserv-prof (built the profiling way), - -- ghc-iserv-dyn (built the dynamic way), and - -- ghc-iserv-prof-dyn (built the profiling+dynamic way). - -- The testsuite requires all to be present, so we - -- make sure that we cover these - -- "prof-build-under-other-name" cases. - -- iserv gets its names from Packages.hs:programName + forM allPackages $ \pkg -> do ctx <- programContext stage pkg -- TODO: see todo on programContext. - let allCtxs = if pkg == iserv - then [ vanillaContext stage pkg - , Context stage pkg profiling Final - , Context stage pkg dynamic Final - , Context stage pkg profilingDynamic Final - ] - else [ ctx ] - forM allCtxs $ \ctx -> do - name <- programName ctx - return (name <.> exe, ctx) + name <- programName ctx + return (name <.> exe, ctx) lookupProgramContext :: FilePath -> [(FilePath, Context)] -> Maybe Context lookupProgramContext wholePath progs = lookup (takeFileName wholePath) progs ===================================== hadrian/src/Rules/Test.hs ===================================== @@ -17,7 +17,6 @@ import Settings.Builders.RunTest import Settings.Program (programContext) import Target import Utilities -import Context.Type import qualified System.Directory as IO import GHC.Toolchain as Toolchain @@ -320,11 +319,9 @@ needTestsuitePackages stg = do -- This is a hack, but a major usecase for testing the stage1 compiler is -- so that we can use it even if ghc stage2 fails to build -- Unfortunately, we still need the liba - let pkgs = filter (\(_,p) -> not $ "iserv" `isInfixOf` pkgName p || ((pkgName p `elem` ["ghc", "Cabal"]) && isStage0 stg)) + let pkgs = filter (\(_,p) -> not $ (pkgName p `elem` ["ghc", "Cabal"]) && isStage0 stg) (libpkgs ++ exepkgs ++ [ (stg,timeout) | windowsHost ]) need =<< mapM (uncurry pkgFile) pkgs - cross <- flag CrossCompiling - when (not cross) $ needIservBins stg -- stage 1 ghc lives under stage0/bin, -- stage 2 ghc lives under stage1/bin, etc @@ -334,28 +331,6 @@ stageOf "stage2" = Just Stage1 stageOf "stage3" = Just Stage2 stageOf _ = Nothing -needIservBins :: Stage -> Action () -needIservBins stg = do - let ws = [vanilla, profiling, dynamic] - progs <- catMaybes <$> mapM (canBuild stg) ws - need progs - where - -- Only build iserv binaries if all dependencies are built the right - -- way already. In particular this fixes the case of no_profiled_libs - -- not working with the testsuite, see #19624 - canBuild (Stage0 {}) _ = pure Nothing - canBuild stg w = do - contextDeps <- contextDependencies (Context stg iserv w Final) - ws <- forM contextDeps $ \c -> - interpretInContext c (getLibraryWays <> - if Context.Type.package c == rts - then getRtsWays - else mempty) - if (all (w `elem`) ws) - then Just <$> programPath (Context stg iserv w Final) - else return Nothing - - pkgFile :: Stage -> Package -> Action FilePath pkgFile stage pkg | isLibrary pkg = pkgConfFile (Context stage pkg profilingDynamic Final) ===================================== hadrian/src/Settings/Builders/Ghc.hs ===================================== @@ -168,7 +168,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do , pure [ "-L" ++ libDir | libDir <- libDirs ] , rtsFfiArg , osxTarget ? pure (concat [ ["-framework", fmwk] | fmwk <- fmwks ]) - , debugged ? packageOneOf [ghc, iservProxy, iserv, remoteIserv] ? + , debugged ? packageOneOf [ghc, iservProxy, remoteIserv] ? arg "-debug" ] ===================================== hadrian/src/Settings/Default.hs ===================================== @@ -183,7 +183,6 @@ stage1Packages = do ] , when (not cross) [ hpcBin - , iserv , runGhc , ghcToolchainBin ] ===================================== hadrian/src/Settings/Packages.hs ===================================== @@ -41,8 +41,6 @@ packageArgs = do libzstdLibraryDir <- getSetting LibZstdLibDir stageVersion <- readVersion <$> (expr $ ghcVersionStage stage) - rtsWays <- getRtsWays - mconcat --------------------------------- base --------------------------------- [ package base ? mconcat @@ -179,23 +177,6 @@ packageArgs = do , package directory ? builder (Cabal Flags) ? arg "+os-string" , package win32 ? builder (Cabal Flags) ? arg "+os-string" - --------------------------------- iserv -------------------------------- - -- Add -Wl,--export-dynamic enables GHCi to load dynamic objects that - -- refer to the RTS. This is harmless if you don't use it (adds a bit - -- of overhead to startup and increases the binary sizes) but if you - -- need it there's no alternative. - -- - -- The Solaris linker does not support --export-dynamic option. It also - -- does not need it since it exports all dynamic symbols by default - , package iserv ? mconcat [ - expr isElfTarget - ? notM (expr $ anyTargetOs [OSFreeBSD, OSSolaris2])? mconcat - [ builder (Ghc LinkHs) ? arg "-optl-Wl,--export-dynamic" ] - - -- Link iserv with -threaded if possible - , builder (Cabal Flags) ? any (wayUnit Threaded) rtsWays `cabalFlag` "threaded" - ] - -------------------------------- haddock ------------------------------- , package haddockApi ? builder (Cabal Flags) ? arg "in-ghc-tree" ===================================== testsuite/tests/driver/T24731.hs deleted ===================================== @@ -1,5 +0,0 @@ -{-# LANGUAGE TemplateHaskell #-} -module T24731 where - -foo :: Int -foo = $([|10|]) ===================================== testsuite/tests/driver/all.T ===================================== @@ -333,4 +333,3 @@ test('T25382', normal, makefile_test, []) test('T26018', req_c, makefile_test, []) test('T24120', normal, compile, ['-Wunused-packages -hide-all-packages -package base -package system-cxx-std-lib']) test('T26551', [extra_files(['T26551.hs'])], makefile_test, []) -test('T24731', [only_ways(['ext-interp'])], compile, ['-fexternal-interpreter -pgmi ""']) ===================================== utils/iserv/iserv.cabal.in deleted ===================================== @@ -1,43 +0,0 @@ --- WARNING: iserv.cabal is automatically generated from iserv.cabal.in by --- ../../configure. Make sure you are editing iserv.cabal.in, not --- iserv.cabal. - -Name: iserv -Version: @ProjectVersion@ -Copyright: XXX -License: BSD3 --- XXX License-File: LICENSE -Author: XXX -Maintainer: XXX -Synopsis: iserv allows GHC to delegate Template Haskell computations -Description: - GHC can be provided with a path to the iserv binary with - @-pgmi=/path/to/iserv-bin@, and will in combination with - @-fexternal-interpreter@, compile Template Haskell though the - @iserv-bin@ delegate. This is very similar to how ghcjs has been - compiling Template Haskell, by spawning a separate delegate (so - called runner on the javascript vm) and evaluating the splices - there. - -Category: Development -build-type: Simple -cabal-version: >=1.10 - -Flag threaded - Description: Link the iserv executable against the threaded RTS - Default: True - Manual: True - -Executable iserv - Default-Language: Haskell2010 - -- We never know what symbols GHC will look up in the future, so we - -- must retain CAFs for running interpreted code. - ghc-options: -fkeep-cafs -rtsopts - if flag(threaded) - ghc-options: -threaded - Main-Is: Main.hs - Hs-Source-Dirs: src - include-dirs: . - Build-Depends: - base >= 4 && < 5, - ghci == @ProjectVersionMunged@ ===================================== utils/iserv/src/Main.hs deleted ===================================== @@ -1,12 +0,0 @@ --- | --- The Remote GHCi server. --- --- For details on Remote GHCi, see Note [Remote GHCi] in --- compiler/GHC/Runtime/Interpreter.hs. --- -module Main (main) where - -import GHCi.Server (defaultServer) - -main :: IO () -main = defaultServer View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c94aaacd4c4e31a2fe2cb8dadcdd14c7... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c94aaacd4c4e31a2fe2cb8dadcdd14c7... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)