Teo Camarasu pushed to branch wip/T26226 at Glasgow Haskell Compiler / GHC
Commits:
-
846ab130
by Teo Camarasu at 2025-07-25T21:35:00+01:00
-
14a6e7d6
by Teo Camarasu at 2025-07-25T21:35:00+01:00
-
260db985
by Teo Camarasu at 2025-07-25T21:35:00+01:00
9 changed files:
- cabal.project-reinstall
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Utils/Constants.hs
- ghc/GHC/Driver/Session/Mode.hs
- ghc/Main.hs
- ghc/ghc-bin.cabal.in
- hadrian/src/Settings/Packages.hs
- libraries/ghci/GHCi/Run.hs
- libraries/ghci/ghci.cabal.in
Changes:
| ... | ... | @@ -56,7 +56,7 @@ packages: ./compiler |
| 56 | 56 | ./linters/**/*.cabal
|
| 57 | 57 | |
| 58 | 58 | constraints: ghc +internal-interpreter +dynamic-system-linke,
|
| 59 | - ghc-bin +internal-interpreter +threaded,
|
|
| 59 | + ghc-bin +ghci +threaded,
|
|
| 60 | 60 | ghci +internal-interpreter,
|
| 61 | 61 | haddock +in-ghc-tree,
|
| 62 | 62 | any.array installed,
|
| ... | ... | @@ -1010,7 +1010,7 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = do |
| 1010 | 1010 | -- #16331 - when no "internal interpreter" is available but we
|
| 1011 | 1011 | -- need to process some TemplateHaskell or QuasiQuotes, we automatically
|
| 1012 | 1012 | -- turn on -fexternal-interpreter.
|
| 1013 | - ext_interp_enable ms = not ghciSupported && internalInterpreter
|
|
| 1013 | + ext_interp_enable ms = not internalInterpreterSupported && internalInterpreter
|
|
| 1014 | 1014 | where
|
| 1015 | 1015 | lcl_dflags = ms_hspp_opts ms
|
| 1016 | 1016 | internalInterpreter = not (gopt Opt_ExternalInterpreter lcl_dflags)
|
| ... | ... | @@ -2,7 +2,7 @@ |
| 2 | 2 | |
| 3 | 3 | module GHC.Utils.Constants
|
| 4 | 4 | ( debugIsOn
|
| 5 | - , ghciSupported
|
|
| 5 | + , internalInterpreterSupported
|
|
| 6 | 6 | , isWindowsHost
|
| 7 | 7 | , isDarwinHost
|
| 8 | 8 | )
|
| ... | ... | @@ -22,11 +22,11 @@ branch of the conditional, thereby dropping debug code altogether when |
| 22 | 22 | the flags are off.
|
| 23 | 23 | -}
|
| 24 | 24 | |
| 25 | -ghciSupported :: Bool
|
|
| 25 | +internalInterpreterSupported :: Bool
|
|
| 26 | 26 | #if defined(HAVE_INTERNAL_INTERPRETER)
|
| 27 | -ghciSupported = True
|
|
| 27 | +internalInterpreterSupported = True
|
|
| 28 | 28 | #else
|
| 29 | -ghciSupported = False
|
|
| 29 | +internalInterpreterSupported = False
|
|
| 30 | 30 | #endif
|
| 31 | 31 | |
| 32 | 32 | debugIsOn :: Bool
|
| ... | ... | @@ -134,7 +134,7 @@ isDoEvalMode :: Mode -> Bool |
| 134 | 134 | isDoEvalMode (Right (Right (DoEval _))) = True
|
| 135 | 135 | isDoEvalMode _ = False
|
| 136 | 136 | |
| 137 | -#if defined(HAVE_INTERNAL_INTERPRETER)
|
|
| 137 | +#if defined(HAVE_GHCI)
|
|
| 138 | 138 | isInteractiveMode :: PostLoadMode -> Bool
|
| 139 | 139 | isInteractiveMode DoInteractive = True
|
| 140 | 140 | isInteractiveMode _ = False
|
| ... | ... | @@ -37,7 +37,7 @@ import GHC.Driver.Config.Diagnostic |
| 37 | 37 | import GHC.Platform
|
| 38 | 38 | import GHC.Platform.Host
|
| 39 | 39 | |
| 40 | -#if defined(HAVE_INTERNAL_INTERPRETER)
|
|
| 40 | +#if defined(HAVE_GHCI)
|
|
| 41 | 41 | import GHCi.UI ( interactiveUI, ghciWelcomeMsg, defaultGhciSettings )
|
| 42 | 42 | #endif
|
| 43 | 43 | |
| ... | ... | @@ -289,7 +289,7 @@ doRun units srcs args = do |
| 289 | 289 | args' = drop 1 $ dropWhile (/= "--") $ map unLoc args
|
| 290 | 290 | |
| 291 | 291 | ghciUI :: [String] -> [(FilePath, Maybe Phase)] -> Maybe [String] -> Ghc ()
|
| 292 | -#if !defined(HAVE_INTERNAL_INTERPRETER)
|
|
| 292 | +#if !defined(HAVE_GHCI)
|
|
| 293 | 293 | ghciUI _ _ _ =
|
| 294 | 294 | throwGhcException (CmdLineError "not built for interactive use")
|
| 295 | 295 | #else
|
| ... | ... | @@ -333,7 +333,7 @@ showBanner :: PostLoadMode -> DynFlags -> IO () |
| 333 | 333 | showBanner _postLoadMode dflags = do
|
| 334 | 334 | let verb = verbosity dflags
|
| 335 | 335 | |
| 336 | -#if defined(HAVE_INTERNAL_INTERPRETER)
|
|
| 336 | +#if defined(HAVE_GHCI)
|
|
| 337 | 337 | -- Show the GHCi banner
|
| 338 | 338 | when (isInteractiveMode _postLoadMode && verb >= 1) $ putStrLn ghciWelcomeMsg
|
| 339 | 339 | #endif
|
| ... | ... | @@ -17,8 +17,8 @@ Category: Development |
| 17 | 17 | Build-Type: Simple
|
| 18 | 18 | Cabal-Version: >=1.10
|
| 19 | 19 | |
| 20 | -Flag internal-interpreter
|
|
| 21 | - Description: Build with internal interpreter support.
|
|
| 20 | +Flag ghci
|
|
| 21 | + Description: Build with support for GHCi.
|
|
| 22 | 22 | Default: False
|
| 23 | 23 | Manual: True
|
| 24 | 24 | |
| ... | ... | @@ -56,7 +56,7 @@ Executable ghc |
| 56 | 56 | -rtsopts=all
|
| 57 | 57 | "-with-rtsopts=-K512M -H -I5 -T"
|
| 58 | 58 | |
| 59 | - if flag(internal-interpreter)
|
|
| 59 | + if flag(ghci)
|
|
| 60 | 60 | -- NB: this is never built by the bootstrapping GHC+libraries
|
| 61 | 61 | Build-depends:
|
| 62 | 62 | deepseq >= 1.4 && < 1.6,
|
| ... | ... | @@ -65,7 +65,7 @@ Executable ghc |
| 65 | 65 | haskeline == 0.8.*,
|
| 66 | 66 | exceptions == 0.10.*,
|
| 67 | 67 | time >= 1.8 && < 1.15
|
| 68 | - CPP-Options: -DHAVE_INTERNAL_INTERPRETER
|
|
| 68 | + CPP-Options: -DHAVE_GHCI
|
|
| 69 | 69 | Other-Modules:
|
| 70 | 70 | GHCi.Leak
|
| 71 | 71 | GHCi.UI
|
| ... | ... | @@ -25,10 +25,6 @@ packageArgs = do |
| 25 | 25 | -- See: https://gitlab.haskell.org/ghc/ghc/issues/16809.
|
| 26 | 26 | cross = flag CrossCompiling
|
| 27 | 27 | |
| 28 | - -- Check if the bootstrap compiler has the same version as the one we
|
|
| 29 | - -- are building. This is used to build cross-compilers
|
|
| 30 | - bootCross = (==) <$> ghcVersionStage (stage0InTree) <*> ghcVersionStage Stage1
|
|
| 31 | - |
|
| 32 | 28 | compilerStageOption f = buildingCompilerStage' . f =<< expr flavour
|
| 33 | 29 | |
| 34 | 30 | cursesIncludeDir <- getSetting CursesIncludeDir
|
| ... | ... | @@ -128,39 +124,9 @@ packageArgs = do |
| 128 | 124 | |
| 129 | 125 | --------------------------------- ghci ---------------------------------
|
| 130 | 126 | , package ghci ? mconcat
|
| 131 | - [
|
|
| 132 | - -- The use case here is that we want to build @iserv-proxy@ for the
|
|
| 133 | - -- cross compiler. That one needs to be compiled by the bootstrap
|
|
| 134 | - -- compiler as it needs to run on the host. Hence @iserv@ needs
|
|
| 135 | - -- @GHCi.TH@, @GHCi.Message@, @GHCi.Run@, and @GHCi.Server@ from
|
|
| 136 | - -- @ghci@. And those are behind the @-finternal-interpreter@ flag.
|
|
| 137 | - --
|
|
| 138 | - -- But it may not build if we have made some changes to ghci's
|
|
| 139 | - -- dependencies (see #16051).
|
|
| 140 | - --
|
|
| 141 | - -- To fix this properly Hadrian would need to:
|
|
| 142 | - -- * first build a compiler for the build platform (stage1 is enough)
|
|
| 143 | - -- * use it as a bootstrap compiler to build the stage1 cross-compiler
|
|
| 144 | - --
|
|
| 145 | - -- The issue is that "configure" would have to be executed twice (for
|
|
| 146 | - -- the build platform and for the cross-platform) and Hadrian would
|
|
| 147 | - -- need to be fixed to support two different stage1 compilers.
|
|
| 148 | - --
|
|
| 149 | - -- The workaround we use is to check if the bootstrap compiler has
|
|
| 150 | - -- the same version as the one we are building. In this case we can
|
|
| 151 | - -- avoid the first step above and directly build with
|
|
| 152 | - -- `-finternal-interpreter`.
|
|
| 153 | - --
|
|
| 154 | - -- TODO: Note that in that case we also do not need to build most of
|
|
| 155 | - -- the Stage1 libraries, as we already know that the bootstrap
|
|
| 156 | - -- compiler comes with the same versions as the one we are building.
|
|
| 157 | - --
|
|
| 158 | - builder (Cabal Setup) ? cabalExtraDirs ffiIncludeDir ffiLibraryDir
|
|
| 127 | + [ builder (Cabal Setup) ? cabalExtraDirs ffiIncludeDir ffiLibraryDir
|
|
| 159 | 128 | , builder (Cabal Flags) ? mconcat
|
| 160 | - [ ifM stage0
|
|
| 161 | - (andM [cross, bootCross] `cabalFlag` "internal-interpreter")
|
|
| 162 | - (arg "internal-interpreter")
|
|
| 163 | - , stage0 `cabalFlag` "bootstrap"
|
|
| 129 | + [ stage0 `cabalFlag` "bootstrap"
|
|
| 164 | 130 | ]
|
| 165 | 131 | |
| 166 | 132 | ]
|
| ... | ... | @@ -260,7 +260,11 @@ sandboxIO opts io = do |
| 260 | 260 | --
|
| 261 | 261 | rethrow :: EvalOpts -> IO a -> IO a
|
| 262 | 262 | rethrow EvalOpts{..} io =
|
| 263 | +#if MIN_VERSION_base(4,21,0)
|
|
| 263 | 264 | catchNoPropagate io $ \(ExceptionWithContext cx se) -> do
|
| 265 | +#else
|
|
| 266 | + catch io $ \se -> do
|
|
| 267 | +#endif
|
|
| 264 | 268 | -- If -fbreak-on-error, we break unconditionally,
|
| 265 | 269 | -- but with care of not breaking twice
|
| 266 | 270 | if breakOnError && not breakOnException
|
| ... | ... | @@ -271,7 +275,11 @@ rethrow EvalOpts{..} io = |
| 271 | 275 | Just UserInterrupt -> return ()
|
| 272 | 276 | -- In any other case, we don't want to break
|
| 273 | 277 | _ -> poke exceptionFlag 0
|
| 278 | +#if MIN_VERSION_base(4,21,0)
|
|
| 274 | 279 | rethrowIO (ExceptionWithContext cx se)
|
| 280 | +#else
|
|
| 281 | + throwIO se
|
|
| 282 | +#endif
|
|
| 275 | 283 | |
| 276 | 284 | --
|
| 277 | 285 | -- While we're waiting for the sandbox thread to return a result, if
|
| ... | ... | @@ -17,11 +17,6 @@ cabal-version: >=1.10 |
| 17 | 17 | build-type: Simple
|
| 18 | 18 | extra-source-files: changelog.md
|
| 19 | 19 | |
| 20 | -Flag internal-interpreter
|
|
| 21 | - Description: Build with internal interpreter support.
|
|
| 22 | - Default: False
|
|
| 23 | - Manual: True
|
|
| 24 | - |
|
| 25 | 20 | Flag bootstrap
|
| 26 | 21 | Description:
|
| 27 | 22 | Enabled when building the stage1 compiler in order to vendor the in-tree
|
| ... | ... | @@ -56,23 +51,19 @@ library |
| 56 | 51 | TupleSections
|
| 57 | 52 | UnboxedTuples
|
| 58 | 53 | |
| 59 | - if flag(internal-interpreter)
|
|
| 60 | - CPP-Options: -DHAVE_INTERNAL_INTERPRETER
|
|
| 54 | + if !arch(javascript)
|
|
| 61 | 55 | exposed-modules:
|
| 62 | - GHCi.Run
|
|
| 63 | - GHCi.Debugger
|
|
| 64 | - GHCi.CreateBCO
|
|
| 65 | - GHCi.ObjLink
|
|
| 66 | - GHCi.Signals
|
|
| 67 | - GHCi.StaticPtrTable
|
|
| 68 | - GHCi.TH
|
|
| 69 | - GHCi.Server
|
|
| 70 | - |
|
| 71 | - if !arch(javascript)
|
|
| 72 | - exposed-modules:
|
|
| 73 | - GHCi.InfoTable
|
|
| 56 | + GHCi.InfoTable
|
|
| 74 | 57 | |
| 75 | 58 | exposed-modules:
|
| 59 | + GHCi.Run
|
|
| 60 | + GHCi.Debugger
|
|
| 61 | + GHCi.CreateBCO
|
|
| 62 | + GHCi.ObjLink
|
|
| 63 | + GHCi.Signals
|
|
| 64 | + GHCi.StaticPtrTable
|
|
| 65 | + GHCi.TH
|
|
| 66 | + GHCi.Server
|
|
| 76 | 67 | GHCi.BreakArray
|
| 77 | 68 | GHCi.BinaryArray
|
| 78 | 69 | GHCi.Message
|