[Git][ghc/ghc][master] Rename interpreterBackend to bytecodeBackend
by Marge Bot (@marge-bot) 03 Oct '25
by Marge Bot (@marge-bot) 03 Oct '25
03 Oct '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
c06b534b by Matthew Pickering at 2025-10-03T06:06:40-04:00
Rename interpreterBackend to bytecodeBackend
This is preparation for creating bytecode files.
The "interpreter" is one way in which we can run bytecode objects. It is
more accurate to describe that the backend produces bytecode, rather
than the means by which the code will eventually run.
The "interpreterBackend" binding is left as a deprecated alias.
- - - - -
14 changed files:
- compiler/GHC.hs
- compiler/GHC/Driver/Backend.hs
- compiler/GHC/Driver/Backend/Internal.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Session.hs
- docs/users_guide/extending_ghc.rst
- ghc/Main.hs
- testsuite/tests/driver/T5313.hs
- testsuite/tests/ghc-api/T10052/T10052.hs
- testsuite/tests/ghc-api/T8639_api.hs
- testsuite/tests/ghc-api/apirecomp001/myghc.hs
- testsuite/tests/ghci-wasm/T26431.hs
- testsuite/tests/ghci/linking/dyn/T3372.hs
Changes:
=====================================
compiler/GHC.hs
=====================================
@@ -30,7 +30,7 @@ module GHC (
-- * Flags and settings
DynFlags(..), GeneralFlag(..), Severity(..), Backend, gopt,
- ncgBackend, llvmBackend, viaCBackend, interpreterBackend, noBackend,
+ ncgBackend, llvmBackend, viaCBackend, bytecodeBackend, interpreterBackend, noBackend,
GhcMode(..), GhcLink(..),
parseDynamicFlags, parseTargetFiles,
getSessionDynFlags,
=====================================
compiler/GHC/Driver/Backend.hs
=====================================
@@ -47,6 +47,7 @@ module GHC.Driver.Backend
, llvmBackend
, jsBackend
, viaCBackend
+ , bytecodeBackend
, interpreterBackend
, noBackend
, allBackends
@@ -252,7 +253,7 @@ instance Show Backend where
show = backendDescription
-ncgBackend, llvmBackend, viaCBackend, interpreterBackend, jsBackend, noBackend
+ncgBackend, llvmBackend, viaCBackend, bytecodeBackend, interpreterBackend, jsBackend, noBackend
:: Backend
-- | The native code generator.
@@ -310,7 +311,11 @@ viaCBackend = Named ViaC
-- (foreign primops).
--
-- See "GHC.StgToByteCode"
-interpreterBackend = Named Interpreter
+bytecodeBackend = Named Bytecode
+
+{-# DEPRECATED interpreterBackend "Renamed to bytecodeBackend" #-}
+interpreterBackend = bytecodeBackend
+
-- | A dummy back end that generates no code.
--
@@ -419,7 +424,7 @@ backendDescription (Named NCG) = "native code generator"
backendDescription (Named LLVM) = "LLVM"
backendDescription (Named ViaC) = "compiling via C"
backendDescription (Named JavaScript) = "compiling to JavaScript"
-backendDescription (Named Interpreter) = "byte-code interpreter"
+backendDescription (Named Bytecode) = "byte-code interpreter"
backendDescription (Named NoBackend) = "no code generated"
-- | This flag tells the compiler driver whether the back
@@ -431,7 +436,7 @@ backendWritesFiles (Named NCG) = True
backendWritesFiles (Named LLVM) = True
backendWritesFiles (Named ViaC) = True
backendWritesFiles (Named JavaScript) = True
-backendWritesFiles (Named Interpreter) = False
+backendWritesFiles (Named Bytecode) = False
backendWritesFiles (Named NoBackend) = False
-- | When the back end does write files, this value tells
@@ -442,7 +447,7 @@ backendPipelineOutput (Named NCG) = Persistent
backendPipelineOutput (Named LLVM) = Persistent
backendPipelineOutput (Named ViaC) = Persistent
backendPipelineOutput (Named JavaScript) = Persistent
-backendPipelineOutput (Named Interpreter) = NoOutputFile
+backendPipelineOutput (Named Bytecode) = NoOutputFile
backendPipelineOutput (Named NoBackend) = NoOutputFile
-- | This flag tells the driver whether the back end can
@@ -453,7 +458,7 @@ backendCanReuseLoadedCode (Named NCG) = False
backendCanReuseLoadedCode (Named LLVM) = False
backendCanReuseLoadedCode (Named ViaC) = False
backendCanReuseLoadedCode (Named JavaScript) = False
-backendCanReuseLoadedCode (Named Interpreter) = True
+backendCanReuseLoadedCode (Named Bytecode) = True
backendCanReuseLoadedCode (Named NoBackend) = False
-- | It is is true of every back end except @-fno-code@
@@ -478,7 +483,7 @@ backendGeneratesCode (Named NCG) = True
backendGeneratesCode (Named LLVM) = True
backendGeneratesCode (Named ViaC) = True
backendGeneratesCode (Named JavaScript) = True
-backendGeneratesCode (Named Interpreter) = True
+backendGeneratesCode (Named Bytecode) = True
backendGeneratesCode (Named NoBackend) = False
backendGeneratesCodeForHsBoot :: Backend -> Bool
@@ -486,7 +491,7 @@ backendGeneratesCodeForHsBoot (Named NCG) = True
backendGeneratesCodeForHsBoot (Named LLVM) = True
backendGeneratesCodeForHsBoot (Named ViaC) = True
backendGeneratesCodeForHsBoot (Named JavaScript) = True
-backendGeneratesCodeForHsBoot (Named Interpreter) = False
+backendGeneratesCodeForHsBoot (Named Bytecode) = False
backendGeneratesCodeForHsBoot (Named NoBackend) = False
-- | When set, this flag turns on interface writing for
@@ -498,7 +503,7 @@ backendSupportsInterfaceWriting (Named NCG) = True
backendSupportsInterfaceWriting (Named LLVM) = True
backendSupportsInterfaceWriting (Named ViaC) = True
backendSupportsInterfaceWriting (Named JavaScript) = True
-backendSupportsInterfaceWriting (Named Interpreter) = True
+backendSupportsInterfaceWriting (Named Bytecode) = True
backendSupportsInterfaceWriting (Named NoBackend) = False
-- | When preparing code for this back end, the type
@@ -510,7 +515,7 @@ backendRespectsSpecialise (Named NCG) = True
backendRespectsSpecialise (Named LLVM) = True
backendRespectsSpecialise (Named ViaC) = True
backendRespectsSpecialise (Named JavaScript) = True
-backendRespectsSpecialise (Named Interpreter) = False
+backendRespectsSpecialise (Named Bytecode) = False
backendRespectsSpecialise (Named NoBackend) = False
-- | This back end wants the `mi_top_env` field of a
@@ -522,7 +527,7 @@ backendWantsGlobalBindings (Named LLVM) = False
backendWantsGlobalBindings (Named ViaC) = False
backendWantsGlobalBindings (Named JavaScript) = False
backendWantsGlobalBindings (Named NoBackend) = False
-backendWantsGlobalBindings (Named Interpreter) = True
+backendWantsGlobalBindings (Named Bytecode) = True
-- | The back end targets a technology that implements
-- `switch` natively. (For example, LLVM or C.) Therefore
@@ -534,7 +539,7 @@ backendHasNativeSwitch (Named NCG) = False
backendHasNativeSwitch (Named LLVM) = True
backendHasNativeSwitch (Named ViaC) = True
backendHasNativeSwitch (Named JavaScript) = True
-backendHasNativeSwitch (Named Interpreter) = False
+backendHasNativeSwitch (Named Bytecode) = False
backendHasNativeSwitch (Named NoBackend) = False
-- | As noted in the documentation for
@@ -548,7 +553,7 @@ backendPrimitiveImplementation (Named NCG) = NcgPrimitives
backendPrimitiveImplementation (Named LLVM) = LlvmPrimitives
backendPrimitiveImplementation (Named JavaScript) = JSPrimitives
backendPrimitiveImplementation (Named ViaC) = GenericPrimitives
-backendPrimitiveImplementation (Named Interpreter) = GenericPrimitives
+backendPrimitiveImplementation (Named Bytecode) = GenericPrimitives
backendPrimitiveImplementation (Named NoBackend) = GenericPrimitives
-- | When this value is `IsValid`, the back end is
@@ -560,7 +565,7 @@ backendSimdValidity (Named NCG) = IsValid
backendSimdValidity (Named LLVM) = IsValid
backendSimdValidity (Named ViaC) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
backendSimdValidity (Named JavaScript) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
-backendSimdValidity (Named Interpreter) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
+backendSimdValidity (Named Bytecode) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
backendSimdValidity (Named NoBackend) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
-- | This flag says whether the back end supports large
@@ -571,7 +576,7 @@ backendSupportsEmbeddedBlobs (Named NCG) = True
backendSupportsEmbeddedBlobs (Named LLVM) = False
backendSupportsEmbeddedBlobs (Named ViaC) = False
backendSupportsEmbeddedBlobs (Named JavaScript) = False
-backendSupportsEmbeddedBlobs (Named Interpreter) = False
+backendSupportsEmbeddedBlobs (Named Bytecode) = False
backendSupportsEmbeddedBlobs (Named NoBackend) = False
-- | This flag tells the compiler driver that the back end
@@ -586,7 +591,7 @@ backendNeedsPlatformNcgSupport (Named NCG) = True
backendNeedsPlatformNcgSupport (Named LLVM) = False
backendNeedsPlatformNcgSupport (Named ViaC) = False
backendNeedsPlatformNcgSupport (Named JavaScript) = False
-backendNeedsPlatformNcgSupport (Named Interpreter) = False
+backendNeedsPlatformNcgSupport (Named Bytecode) = False
backendNeedsPlatformNcgSupport (Named NoBackend) = False
-- | This flag is set if the back end can generate code
@@ -598,7 +603,7 @@ backendSupportsUnsplitProcPoints (Named NCG) = True
backendSupportsUnsplitProcPoints (Named LLVM) = False
backendSupportsUnsplitProcPoints (Named ViaC) = False
backendSupportsUnsplitProcPoints (Named JavaScript) = False
-backendSupportsUnsplitProcPoints (Named Interpreter) = False
+backendSupportsUnsplitProcPoints (Named Bytecode) = False
backendSupportsUnsplitProcPoints (Named NoBackend) = False
-- | This flag guides the driver in resolving issues about
@@ -616,7 +621,7 @@ backendSwappableWithViaC (Named NCG) = True
backendSwappableWithViaC (Named LLVM) = True
backendSwappableWithViaC (Named ViaC) = False
backendSwappableWithViaC (Named JavaScript) = False
-backendSwappableWithViaC (Named Interpreter) = False
+backendSwappableWithViaC (Named Bytecode) = False
backendSwappableWithViaC (Named NoBackend) = False
-- | This flag is true if the back end works *only* with
@@ -626,7 +631,7 @@ backendUnregisterisedAbiOnly (Named NCG) = False
backendUnregisterisedAbiOnly (Named LLVM) = False
backendUnregisterisedAbiOnly (Named ViaC) = True
backendUnregisterisedAbiOnly (Named JavaScript) = False
-backendUnregisterisedAbiOnly (Named Interpreter) = False
+backendUnregisterisedAbiOnly (Named Bytecode) = False
backendUnregisterisedAbiOnly (Named NoBackend) = False
-- | This flag is set if the back end generates C code in
@@ -637,7 +642,7 @@ backendGeneratesHc (Named NCG) = False
backendGeneratesHc (Named LLVM) = False
backendGeneratesHc (Named ViaC) = True
backendGeneratesHc (Named JavaScript) = False
-backendGeneratesHc (Named Interpreter) = False
+backendGeneratesHc (Named Bytecode) = False
backendGeneratesHc (Named NoBackend) = False
-- | This flag says whether SPT (static pointer table)
@@ -649,7 +654,7 @@ backendSptIsDynamic (Named NCG) = False
backendSptIsDynamic (Named LLVM) = False
backendSptIsDynamic (Named ViaC) = False
backendSptIsDynamic (Named JavaScript) = False
-backendSptIsDynamic (Named Interpreter) = True
+backendSptIsDynamic (Named Bytecode) = True
backendSptIsDynamic (Named NoBackend) = False
-- | If this flag is unset, then the driver ignores the flag @-fbreak-points@,
@@ -660,7 +665,7 @@ backendSupportsBreakpoints = \case
Named LLVM -> False
Named ViaC -> False
Named JavaScript -> False
- Named Interpreter -> True
+ Named Bytecode -> True
Named NoBackend -> False
-- | If this flag is set, then the driver forces the
@@ -671,7 +676,7 @@ backendForcesOptimization0 (Named NCG) = False
backendForcesOptimization0 (Named LLVM) = False
backendForcesOptimization0 (Named ViaC) = False
backendForcesOptimization0 (Named JavaScript) = False
-backendForcesOptimization0 (Named Interpreter) = True
+backendForcesOptimization0 (Named Bytecode) = True
backendForcesOptimization0 (Named NoBackend) = False
-- | I don't understand exactly how this works. But if
@@ -683,7 +688,7 @@ backendNeedsFullWays (Named NCG) = False
backendNeedsFullWays (Named LLVM) = False
backendNeedsFullWays (Named ViaC) = False
backendNeedsFullWays (Named JavaScript) = False
-backendNeedsFullWays (Named Interpreter) = True
+backendNeedsFullWays (Named Bytecode) = True
backendNeedsFullWays (Named NoBackend) = False
-- | This flag is also special for the interpreter: if a
@@ -695,7 +700,7 @@ backendSpecialModuleSource (Named NCG) = const Nothing
backendSpecialModuleSource (Named LLVM) = const Nothing
backendSpecialModuleSource (Named ViaC) = const Nothing
backendSpecialModuleSource (Named JavaScript) = const Nothing
-backendSpecialModuleSource (Named Interpreter) = \b -> if b then Just "interpreted" else Nothing
+backendSpecialModuleSource (Named Bytecode) = \b -> if b then Just "interpreted" else Nothing
backendSpecialModuleSource (Named NoBackend) = const (Just "nothing")
-- | This flag says whether the back end supports Haskell
@@ -707,7 +712,7 @@ backendSupportsHpc (Named NCG) = True
backendSupportsHpc (Named LLVM) = True
backendSupportsHpc (Named ViaC) = True
backendSupportsHpc (Named JavaScript) = False
-backendSupportsHpc (Named Interpreter) = False
+backendSupportsHpc (Named Bytecode) = False
backendSupportsHpc (Named NoBackend) = True
-- | This flag says whether the back end supports foreign
@@ -718,7 +723,7 @@ backendSupportsCImport (Named NCG) = True
backendSupportsCImport (Named LLVM) = True
backendSupportsCImport (Named ViaC) = True
backendSupportsCImport (Named JavaScript) = True
-backendSupportsCImport (Named Interpreter) = True
+backendSupportsCImport (Named Bytecode) = True
backendSupportsCImport (Named NoBackend) = True
-- | This flag says whether the back end supports foreign
@@ -728,7 +733,7 @@ backendSupportsCExport (Named NCG) = True
backendSupportsCExport (Named LLVM) = True
backendSupportsCExport (Named ViaC) = True
backendSupportsCExport (Named JavaScript) = True
-backendSupportsCExport (Named Interpreter) = False
+backendSupportsCExport (Named Bytecode) = False
backendSupportsCExport (Named NoBackend) = True
-- | When using this back end, it may be necessary or
@@ -749,7 +754,7 @@ backendCDefs (Named NCG) = NoCDefs
backendCDefs (Named LLVM) = LlvmCDefs
backendCDefs (Named ViaC) = NoCDefs
backendCDefs (Named JavaScript) = NoCDefs
-backendCDefs (Named Interpreter) = NoCDefs
+backendCDefs (Named Bytecode) = NoCDefs
backendCDefs (Named NoBackend) = NoCDefs
-- | This (defunctionalized) function generates code and
@@ -768,7 +773,7 @@ backendCodeOutput (Named NCG) = NcgCodeOutput
backendCodeOutput (Named LLVM) = LlvmCodeOutput
backendCodeOutput (Named ViaC) = ViaCCodeOutput
backendCodeOutput (Named JavaScript) = JSCodeOutput
-backendCodeOutput (Named Interpreter) = panic "backendCodeOutput: interpreterBackend"
+backendCodeOutput (Named Bytecode) = panic "backendCodeOutput: bytecodeBackend"
backendCodeOutput (Named NoBackend) = panic "backendCodeOutput: noBackend"
backendUseJSLinker :: Backend -> Bool
@@ -776,7 +781,7 @@ backendUseJSLinker (Named NCG) = False
backendUseJSLinker (Named LLVM) = False
backendUseJSLinker (Named ViaC) = False
backendUseJSLinker (Named JavaScript) = True
-backendUseJSLinker (Named Interpreter) = False
+backendUseJSLinker (Named Bytecode) = False
backendUseJSLinker (Named NoBackend) = False
-- | This (defunctionalized) function tells the compiler
@@ -795,7 +800,7 @@ backendPostHscPipeline (Named NCG) = NcgPostHscPipeline
backendPostHscPipeline (Named LLVM) = LlvmPostHscPipeline
backendPostHscPipeline (Named ViaC) = ViaCPostHscPipeline
backendPostHscPipeline (Named JavaScript) = JSPostHscPipeline
-backendPostHscPipeline (Named Interpreter) = NoPostHscPipeline
+backendPostHscPipeline (Named Bytecode) = NoPostHscPipeline
backendPostHscPipeline (Named NoBackend) = NoPostHscPipeline
-- | Somewhere in the compiler driver, when compiling
@@ -809,7 +814,7 @@ backendNormalSuccessorPhase (Named NCG) = As False
backendNormalSuccessorPhase (Named LLVM) = LlvmOpt
backendNormalSuccessorPhase (Named ViaC) = HCc
backendNormalSuccessorPhase (Named JavaScript) = StopLn
-backendNormalSuccessorPhase (Named Interpreter) = StopLn
+backendNormalSuccessorPhase (Named Bytecode) = StopLn
backendNormalSuccessorPhase (Named NoBackend) = StopLn
-- | Name of the back end, if any. Used to migrate legacy
@@ -820,7 +825,7 @@ backendName (Named NCG) = NCG
backendName (Named LLVM) = LLVM
backendName (Named ViaC) = ViaC
backendName (Named JavaScript) = JavaScript
-backendName (Named Interpreter) = Interpreter
+backendName (Named Bytecode) = Bytecode
backendName (Named NoBackend) = NoBackend
@@ -833,7 +838,7 @@ allBackends = [ ncgBackend
, llvmBackend
, viaCBackend
, jsBackend
- , interpreterBackend
+ , bytecodeBackend
, noBackend
]
=====================================
compiler/GHC/Driver/Backend/Internal.hs
=====================================
@@ -28,6 +28,6 @@ data BackendName
| LLVM -- ^ Names the LLVM backend.
| ViaC -- ^ Names the Via-C backend.
| JavaScript -- ^ Names the JS backend.
- | Interpreter -- ^ Names the ByteCode interpreter.
+ | Bytecode -- ^ Names the ByteCode interpreter.
| NoBackend -- ^ Names the `-fno-code` backend.
deriving (Eq, Show)
=====================================
compiler/GHC/Driver/Downsweep.hs
=====================================
@@ -916,7 +916,7 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = do
else (,) <$> (new_temp_file (hiSuf_ dflags) (dynHiSuf_ dflags))
<*> (new_temp_file (objectSuf_ dflags) (dynObjectSuf_ dflags))
let new_dflags = case enable_spec of
- EnableByteCode -> dflags { backend = interpreterBackend }
+ EnableByteCode -> dflags { backend = bytecodeBackend }
EnableObject -> dflags { backend = defaultBackendOf ms }
EnableByteCodeAndObject -> (gopt_set dflags Opt_ByteCodeAndObjectCode) { backend = defaultBackendOf ms}
let ms' = ms
=====================================
compiler/GHC/Driver/Pipeline.hs
=====================================
@@ -281,8 +281,8 @@ compileOne' mHscMessage
-- was set), force it to generate byte-code. This is NOT transitive and
-- only applies to direct targets.
| loadAsByteCode
- = ( interpreterBackend
- , gopt_set (lcl_dflags { backend = interpreterBackend }) Opt_ForceRecomp
+ = ( bytecodeBackend
+ , gopt_set (lcl_dflags { backend = bytecodeBackend }) Opt_ForceRecomp
)
| otherwise
=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -1931,7 +1931,7 @@ dynamic_flags_deps = [
d { ghcLink=NoLink }) >> setBackend noBackend))
, make_ord_flag defFlag "fbyte-code"
(noArgM $ \dflags -> do
- setBackend interpreterBackend
+ setBackend bytecodeBackend
pure $ flip gopt_unset Opt_ByteCodeAndObjectCode (gopt_set dflags Opt_ByteCode))
, make_ord_flag defFlag "fobject-code" $ noArgM $ \dflags -> do
setBackend $ platformDefaultBackend (targetPlatform dflags)
=====================================
docs/users_guide/extending_ghc.rst
=====================================
@@ -1719,7 +1719,7 @@ constructor from version 9.4 with the corresponding value from 9.6:
+-----------------+------------------------+
| ``ViaC`` | ``viaCBackend`` |
+-----------------+------------------------+
-| ``Interpreter`` | ``interpreterBackend`` |
+| ``Interpreter`` | ``bytecodeBackend`` |
+-----------------+------------------------+
| ``NoBackend`` | ``noBackend`` |
+-----------------+------------------------+
=====================================
ghc/Main.hs
=====================================
@@ -169,9 +169,9 @@ main' postLoadMode units dflags0 args flagWarnings = do
let dflt_backend = backend dflags0
(mode, bcknd, link)
= case postLoadMode of
- DoInteractive -> (CompManager, interpreterBackend, LinkInMemory)
- DoEval _ -> (CompManager, interpreterBackend, LinkInMemory)
- DoRun -> (CompManager, interpreterBackend, LinkInMemory)
+ DoInteractive -> (CompManager, bytecodeBackend, LinkInMemory)
+ DoEval _ -> (CompManager, bytecodeBackend, LinkInMemory)
+ DoRun -> (CompManager, bytecodeBackend, LinkInMemory)
DoMake -> (CompManager, dflt_backend, LinkBinary)
DoBackpack -> (CompManager, dflt_backend, LinkBinary)
DoMkDependHS -> (MkDepend, dflt_backend, LinkBinary)
=====================================
testsuite/tests/driver/T5313.hs
=====================================
@@ -7,7 +7,7 @@ main = do
-- begin initialize
df0 <- GHC.getSessionDynFlags
let df1 = df0{GHC.ghcMode = GHC.CompManager,
- GHC.backend = GHC.interpreterBackend,
+ GHC.backend = GHC.bytecodeBackend,
GHC.ghcLink = GHC.LinkInMemory,
GHC.verbosity = 0}
_ <- GHC.setSessionDynFlags df1
=====================================
testsuite/tests/ghc-api/T10052/T10052.hs
=====================================
@@ -24,7 +24,7 @@ runGhc' args act = do
logger <- getLogger
(dflags1, _leftover, _warns) <- parseDynamicFlags logger dflags0 flags
let dflags2 = dflags1 {
- backend = interpreterBackend
+ backend = bytecodeBackend
, ghcLink = LinkInMemory
, verbosity = 1
}
=====================================
testsuite/tests/ghc-api/T8639_api.hs
=====================================
@@ -11,7 +11,7 @@ main
= do { [libdir] <- getArgs
; runGhc (Just libdir) $ do
flags <- getSessionDynFlags
- setSessionDynFlags (flags{ backend = interpreterBackend, ghcLink = LinkInMemory})
+ setSessionDynFlags (flags{ backend = bytecodeBackend, ghcLink = LinkInMemory})
target <- guessTarget "T8639_api_a.hs" Nothing Nothing
setTargets [target]
load LoadAllTargets
=====================================
testsuite/tests/ghc-api/apirecomp001/myghc.hs
=====================================
@@ -37,7 +37,7 @@ main = do
prn "target nothing: ok"
dflags <- getSessionDynFlags
- setSessionDynFlags $ dflags { backend = interpreterBackend }
+ setSessionDynFlags $ dflags { backend = bytecodeBackend }
ok <- load LoadAllTargets
when (failed ok) $ error "Couldn't load A.hs in interpreted mode"
prn "target interpreted: ok"
=====================================
testsuite/tests/ghci-wasm/T26431.hs
=====================================
@@ -16,7 +16,7 @@ main = do
let dflags1 =
dflags0
{ ghcMode = CompManager,
- backend = interpreterBackend,
+ backend = bytecodeBackend,
ghcLink = LinkInMemory
}
logger <- getLogger
=====================================
testsuite/tests/ghci/linking/dyn/T3372.hs
=====================================
@@ -44,7 +44,7 @@ newGhcServer = do (libdir:_) <- getArgs
where ghc action libdir = GHC.runGhc (Just libdir) (init >> action)
init = do df <- GHC.getSessionDynFlags
GHC.setSessionDynFlags df{GHC.ghcMode = GHC.CompManager,
- GHC.backend = GHC.interpreterBackend,
+ GHC.backend = GHC.bytecodeBackend,
GHC.ghcLink = GHC.LinkInMemory,
GHC.verbosity = 0}
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c06b534bbd6dbb570b760f2e82b3e37…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c06b534bbd6dbb570b760f2e82b3e37…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] testsuite: Use ghci_ways to set ways in PackedDataCon/UnboxedTuples/UnliftedDataTypeInterp tests
by Marge Bot (@marge-bot) 03 Oct '25
by Marge Bot (@marge-bot) 03 Oct '25
03 Oct '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
1275d360 by Matthew Pickering at 2025-10-03T06:05:56-04:00
testsuite: Use ghci_ways to set ways in PackedDataCon/UnboxedTuples/UnliftedDataTypeInterp tests
These tests reimplemented the logic from `valid_way` in order to
determine what ways to run. It's easier to use this combination of
`only_ways` and `extra_ways` to only run in GHCi ways and always run in
GHCi ways.
- - - - -
5 changed files:
- testsuite/driver/testglobals.py
- testsuite/driver/testlib.py
- testsuite/tests/ghci/should_run/PackedDataCon/packeddatacon.T
- testsuite/tests/ghci/should_run/UnboxedTuples/unboxedtuples.T
- testsuite/tests/ghci/should_run/UnliftedDataTypeInterp/unlifteddatatypeinterp.T
Changes:
=====================================
testsuite/driver/testglobals.py
=====================================
@@ -136,9 +136,12 @@ class TestConfig:
# Do we have interpreter support?
self.have_interp = False
+ # Do we have external interpreter support?
+ self.have_ext_interp = False
+
# Are we cross-compiling?
self.cross = False
-
+
# Does the RTS linker only support loading shared libraries?
self.interp_force_dyn = False
=====================================
testsuite/driver/testlib.py
=====================================
@@ -549,10 +549,12 @@ only_ghci = only_ways([WayName('ghci'), WayName('ghci-opt')])
# -----
def valid_way( way: WayName ) -> bool:
- if way in {'ghci', 'ghci-opt', 'ghci-ext'}:
+ if way in {'ghci', 'ghci-opt'}:
return config.have_RTS_linker
- if way == 'ghci-ext-prof':
- return config.have_RTS_linker and config.have_profiling
+ if way in {'ghci-ext'}:
+ return config.have_ext_interp
+ if way in {'ghci-ext-prof'}:
+ return config.have_ext_interp and config.have_profiling
return True
def extra_ways( ways: List[WayName] ):
=====================================
testsuite/tests/ghci/should_run/PackedDataCon/packeddatacon.T
=====================================
@@ -2,9 +2,8 @@ test('PackedDataCon',
[ extra_files(['Obj.hs', 'ByteCode.hs', 'Types.hs', 'Common.hs-incl']),
req_interp,
req_bco,
- extra_ways(['ghci']),
- when(config.have_ext_interp, extra_ways(['ghci', 'ghci-ext'])),
- when(config.have_ext_interp and config.have_profiling, extra_ways(['ghci', 'ghci-ext', 'ghci-ext-prof']))
+ extra_ways(ghci_ways),
+ only_ways(ghci_ways),
],
compile_and_run,
['']
=====================================
testsuite/tests/ghci/should_run/UnboxedTuples/unboxedtuples.T
=====================================
@@ -2,9 +2,8 @@ test('UnboxedTuples',
[ extra_files(['Obj.hs', 'ByteCode.hs', 'Common.hs-incl']),
req_interp,
req_bco,
- extra_ways(['ghci']),
- when(config.have_ext_interp, extra_ways(['ghci', 'ghci-ext'])),
- when(config.have_ext_interp and config.have_profiling, extra_ways(['ghci', 'ghci-ext', 'ghci-ext-prof']))
+ only_ways(ghci_ways),
+ extra_ways(ghci_ways),
],
compile_and_run,
['']
=====================================
testsuite/tests/ghci/should_run/UnliftedDataTypeInterp/unlifteddatatypeinterp.T
=====================================
@@ -2,9 +2,8 @@ test('UnliftedDataTypeInterp',
[ extra_files(['Obj.hs', 'ByteCode.hs', 'Types.hs', 'Common.hs-incl']),
req_interp,
req_bco,
- extra_ways(['ghci']),
- when(config.have_ext_interp, extra_ways(['ghci', 'ghci-ext'])),
- when(config.have_ext_interp and config.have_profiling, extra_ways(['ghci', 'ghci-ext', 'ghci-ext-prof']))
+ only_ways(ghci_ways),
+ extra_ways(ghci_ways),
],
compile_and_run,
['']
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1275d3607299734228adbbc47bfb69b…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1275d3607299734228adbbc47bfb69b…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/andreask/t26425_test] Add a perf test for #26425
by Andreas Klebinger (@AndreasK) 03 Oct '25
by Andreas Klebinger (@AndreasK) 03 Oct '25
03 Oct '25
Andreas Klebinger pushed to branch wip/andreask/t26425_test at Glasgow Haskell Compiler / GHC
Commits:
d706155a by Andreas Klebinger at 2025-10-03T11:31:43+02:00
Add a perf test for #26425
- - - - -
2 changed files:
- + testsuite/tests/perf/compiler/T26425.hs
- testsuite/tests/perf/compiler/all.T
Changes:
=====================================
testsuite/tests/perf/compiler/T26425.hs
=====================================
@@ -0,0 +1,1014 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+module Reproducer (strToInt) where
+
+import qualified Data.Text as T
+
+{- This program results in a nested chain of join points and cases which tests
+ primarily OccAnal and Unfolding performance.
+-}
+
+strToInt :: T.Text -> Maybe Int
+strToInt txt = case txt of
+ "0" -> Just 0
+ "1" -> Just 1
+ "2" -> Just 2
+ "3" -> Just 3
+ "4" -> Just 4
+ "5" -> Just 5
+ "6" -> Just 6
+ "7" -> Just 7
+ "8" -> Just 8
+ "9" -> Just 9
+ "10" -> Just 10
+ "11" -> Just 11
+ "12" -> Just 12
+ "13" -> Just 13
+ "14" -> Just 14
+ "15" -> Just 15
+ "16" -> Just 16
+ "17" -> Just 17
+ "18" -> Just 18
+ "19" -> Just 19
+ "20" -> Just 20
+ "21" -> Just 21
+ "22" -> Just 22
+ "23" -> Just 23
+ "24" -> Just 24
+ "25" -> Just 25
+ "26" -> Just 26
+ "27" -> Just 27
+ "28" -> Just 28
+ "29" -> Just 29
+ "30" -> Just 30
+ "31" -> Just 31
+ "32" -> Just 32
+ "33" -> Just 33
+ "34" -> Just 34
+ "35" -> Just 35
+ "36" -> Just 36
+ "37" -> Just 37
+ "38" -> Just 38
+ "39" -> Just 39
+ "40" -> Just 40
+ "41" -> Just 41
+ "42" -> Just 42
+ "43" -> Just 43
+ "44" -> Just 44
+ "45" -> Just 45
+ "46" -> Just 46
+ "47" -> Just 47
+ "48" -> Just 48
+ "49" -> Just 49
+ "50" -> Just 50
+ "51" -> Just 51
+ "52" -> Just 52
+ "53" -> Just 53
+ "54" -> Just 54
+ "55" -> Just 55
+ "56" -> Just 56
+ "57" -> Just 57
+ "58" -> Just 58
+ "59" -> Just 59
+ "60" -> Just 60
+ "61" -> Just 61
+ "62" -> Just 62
+ "63" -> Just 63
+ "64" -> Just 64
+ "65" -> Just 65
+ "66" -> Just 66
+ "67" -> Just 67
+ "68" -> Just 68
+ "69" -> Just 69
+ "70" -> Just 70
+ "71" -> Just 71
+ "72" -> Just 72
+ "73" -> Just 73
+ "74" -> Just 74
+ "75" -> Just 75
+ "76" -> Just 76
+ "77" -> Just 77
+ "78" -> Just 78
+ "79" -> Just 79
+ "80" -> Just 80
+ "81" -> Just 81
+ "82" -> Just 82
+ "83" -> Just 83
+ "84" -> Just 84
+ "85" -> Just 85
+ "86" -> Just 86
+ "87" -> Just 87
+ "88" -> Just 88
+ "89" -> Just 89
+ "90" -> Just 90
+ "91" -> Just 91
+ "92" -> Just 92
+ "93" -> Just 93
+ "94" -> Just 94
+ "95" -> Just 95
+ "96" -> Just 96
+ "97" -> Just 97
+ "98" -> Just 98
+ "99" -> Just 99
+ "100" -> Just 100
+ "101" -> Just 101
+ "102" -> Just 102
+ "103" -> Just 103
+ "104" -> Just 104
+ "105" -> Just 105
+ "106" -> Just 106
+ "107" -> Just 107
+ "108" -> Just 108
+ "109" -> Just 109
+ "110" -> Just 110
+ "111" -> Just 111
+ "112" -> Just 112
+ "113" -> Just 113
+ "114" -> Just 114
+ "115" -> Just 115
+ "116" -> Just 116
+ "117" -> Just 117
+ "118" -> Just 118
+ "119" -> Just 119
+ "120" -> Just 120
+ "121" -> Just 121
+ "122" -> Just 122
+ "123" -> Just 123
+ "124" -> Just 124
+ "125" -> Just 125
+ "126" -> Just 126
+ "127" -> Just 127
+ "128" -> Just 128
+ "129" -> Just 129
+ "130" -> Just 130
+ "131" -> Just 131
+ "132" -> Just 132
+ "133" -> Just 133
+ "134" -> Just 134
+ "135" -> Just 135
+ "136" -> Just 136
+ "137" -> Just 137
+ "138" -> Just 138
+ "139" -> Just 139
+ "140" -> Just 140
+ "141" -> Just 141
+ "142" -> Just 142
+ "143" -> Just 143
+ "144" -> Just 144
+ "145" -> Just 145
+ "146" -> Just 146
+ "147" -> Just 147
+ "148" -> Just 148
+ "149" -> Just 149
+ "150" -> Just 150
+ "151" -> Just 151
+ "152" -> Just 152
+ "153" -> Just 153
+ "154" -> Just 154
+ "155" -> Just 155
+ "156" -> Just 156
+ "157" -> Just 157
+ "158" -> Just 158
+ "159" -> Just 159
+ "160" -> Just 160
+ "161" -> Just 161
+ "162" -> Just 162
+ "163" -> Just 163
+ "164" -> Just 164
+ "165" -> Just 165
+ "166" -> Just 166
+ "167" -> Just 167
+ "168" -> Just 168
+ "169" -> Just 169
+ "170" -> Just 170
+ "171" -> Just 171
+ "172" -> Just 172
+ "173" -> Just 173
+ "174" -> Just 174
+ "175" -> Just 175
+ "176" -> Just 176
+ "177" -> Just 177
+ "178" -> Just 178
+ "179" -> Just 179
+ "180" -> Just 180
+ "181" -> Just 181
+ "182" -> Just 182
+ "183" -> Just 183
+ "184" -> Just 184
+ "185" -> Just 185
+ "186" -> Just 186
+ "187" -> Just 187
+ "188" -> Just 188
+ "189" -> Just 189
+ "190" -> Just 190
+ "191" -> Just 191
+ "192" -> Just 192
+ "193" -> Just 193
+ "194" -> Just 194
+ "195" -> Just 195
+ "196" -> Just 196
+ "197" -> Just 197
+ "198" -> Just 198
+ "199" -> Just 199
+ "200" -> Just 200
+ "201" -> Just 201
+ "202" -> Just 202
+ "203" -> Just 203
+ "204" -> Just 204
+ "205" -> Just 205
+ "206" -> Just 206
+ "207" -> Just 207
+ "208" -> Just 208
+ "209" -> Just 209
+ "210" -> Just 210
+ "211" -> Just 211
+ "212" -> Just 212
+ "213" -> Just 213
+ "214" -> Just 214
+ "215" -> Just 215
+ "216" -> Just 216
+ "217" -> Just 217
+ "218" -> Just 218
+ "219" -> Just 219
+ "220" -> Just 220
+ "221" -> Just 221
+ "222" -> Just 222
+ "223" -> Just 223
+ "224" -> Just 224
+ "225" -> Just 225
+ "226" -> Just 226
+ "227" -> Just 227
+ "228" -> Just 228
+ "229" -> Just 229
+ "230" -> Just 230
+ "231" -> Just 231
+ "232" -> Just 232
+ "233" -> Just 233
+ "234" -> Just 234
+ "235" -> Just 235
+ "236" -> Just 236
+ "237" -> Just 237
+ "238" -> Just 238
+ "239" -> Just 239
+ "240" -> Just 240
+ "241" -> Just 241
+ "242" -> Just 242
+ "243" -> Just 243
+ "244" -> Just 244
+ "245" -> Just 245
+ "246" -> Just 246
+ "247" -> Just 247
+ "248" -> Just 248
+ "249" -> Just 249
+ "250" -> Just 250
+ "251" -> Just 251
+ "252" -> Just 252
+ "253" -> Just 253
+ "254" -> Just 254
+ "255" -> Just 255
+ "256" -> Just 256
+ "257" -> Just 257
+ "258" -> Just 258
+ "259" -> Just 259
+ "260" -> Just 260
+ "261" -> Just 261
+ "262" -> Just 262
+ "263" -> Just 263
+ "264" -> Just 264
+ "265" -> Just 265
+ "266" -> Just 266
+ "267" -> Just 267
+ "268" -> Just 268
+ "269" -> Just 269
+ "270" -> Just 270
+ "271" -> Just 271
+ "272" -> Just 272
+ "273" -> Just 273
+ "274" -> Just 274
+ "275" -> Just 275
+ "276" -> Just 276
+ "277" -> Just 277
+ "278" -> Just 278
+ "279" -> Just 279
+ "280" -> Just 280
+ "281" -> Just 281
+ "282" -> Just 282
+ "283" -> Just 283
+ "284" -> Just 284
+ "285" -> Just 285
+ "286" -> Just 286
+ "287" -> Just 287
+ "288" -> Just 288
+ "289" -> Just 289
+ "290" -> Just 290
+ "291" -> Just 291
+ "292" -> Just 292
+ "293" -> Just 293
+ "294" -> Just 294
+ "295" -> Just 295
+ "296" -> Just 296
+ "297" -> Just 297
+ "298" -> Just 298
+ "299" -> Just 299
+ "300" -> Just 300
+ "301" -> Just 301
+ "302" -> Just 302
+ "303" -> Just 303
+ "304" -> Just 304
+ "305" -> Just 305
+ "306" -> Just 306
+ "307" -> Just 307
+ "308" -> Just 308
+ "309" -> Just 309
+ "310" -> Just 310
+ "311" -> Just 311
+ "312" -> Just 312
+ "313" -> Just 313
+ "314" -> Just 314
+ "315" -> Just 315
+ "316" -> Just 316
+ "317" -> Just 317
+ "318" -> Just 318
+ "319" -> Just 319
+ "320" -> Just 320
+ "321" -> Just 321
+ "322" -> Just 322
+ "323" -> Just 323
+ "324" -> Just 324
+ "325" -> Just 325
+ "326" -> Just 326
+ "327" -> Just 327
+ "328" -> Just 328
+ "329" -> Just 329
+ "330" -> Just 330
+ "331" -> Just 331
+ "332" -> Just 332
+ "333" -> Just 333
+ "334" -> Just 334
+ "335" -> Just 335
+ "336" -> Just 336
+ "337" -> Just 337
+ "338" -> Just 338
+ "339" -> Just 339
+ "340" -> Just 340
+ "341" -> Just 341
+ "342" -> Just 342
+ "343" -> Just 343
+ "344" -> Just 344
+ "345" -> Just 345
+ "346" -> Just 346
+ "347" -> Just 347
+ "348" -> Just 348
+ "349" -> Just 349
+ "350" -> Just 350
+ "351" -> Just 351
+ "352" -> Just 352
+ "353" -> Just 353
+ "354" -> Just 354
+ "355" -> Just 355
+ "356" -> Just 356
+ "357" -> Just 357
+ "358" -> Just 358
+ "359" -> Just 359
+ "360" -> Just 360
+ "361" -> Just 361
+ "362" -> Just 362
+ "363" -> Just 363
+ "364" -> Just 364
+ "365" -> Just 365
+ "366" -> Just 366
+ "367" -> Just 367
+ "368" -> Just 368
+ "369" -> Just 369
+ "370" -> Just 370
+ "371" -> Just 371
+ "372" -> Just 372
+ "373" -> Just 373
+ "374" -> Just 374
+ "375" -> Just 375
+ "376" -> Just 376
+ "377" -> Just 377
+ "378" -> Just 378
+ "379" -> Just 379
+ "380" -> Just 380
+ "381" -> Just 381
+ "382" -> Just 382
+ "383" -> Just 383
+ "384" -> Just 384
+ "385" -> Just 385
+ "386" -> Just 386
+ "387" -> Just 387
+ "388" -> Just 388
+ "389" -> Just 389
+ "390" -> Just 390
+ "391" -> Just 391
+ "392" -> Just 392
+ "393" -> Just 393
+ "394" -> Just 394
+ "395" -> Just 395
+ "396" -> Just 396
+ "397" -> Just 397
+ "398" -> Just 398
+ "399" -> Just 399
+ "400" -> Just 400
+ "401" -> Just 401
+ "402" -> Just 402
+ "403" -> Just 403
+ "404" -> Just 404
+ "405" -> Just 405
+ "406" -> Just 406
+ "407" -> Just 407
+ "408" -> Just 408
+ "409" -> Just 409
+ "410" -> Just 410
+ "411" -> Just 411
+ "412" -> Just 412
+ "413" -> Just 413
+ "414" -> Just 414
+ "415" -> Just 415
+ "416" -> Just 416
+ "417" -> Just 417
+ "418" -> Just 418
+ "419" -> Just 419
+ "420" -> Just 420
+ "421" -> Just 421
+ "422" -> Just 422
+ "423" -> Just 423
+ "424" -> Just 424
+ "425" -> Just 425
+ "426" -> Just 426
+ "427" -> Just 427
+ "428" -> Just 428
+ "429" -> Just 429
+ "430" -> Just 430
+ "431" -> Just 431
+ "432" -> Just 432
+ "433" -> Just 433
+ "434" -> Just 434
+ "435" -> Just 435
+ "436" -> Just 436
+ "437" -> Just 437
+ "438" -> Just 438
+ "439" -> Just 439
+ "440" -> Just 440
+ "441" -> Just 441
+ "442" -> Just 442
+ "443" -> Just 443
+ "444" -> Just 444
+ "445" -> Just 445
+ "446" -> Just 446
+ "447" -> Just 447
+ "448" -> Just 448
+ "449" -> Just 449
+ "450" -> Just 450
+ "451" -> Just 451
+ "452" -> Just 452
+ "453" -> Just 453
+ "454" -> Just 454
+ "455" -> Just 455
+ "456" -> Just 456
+ "457" -> Just 457
+ "458" -> Just 458
+ "459" -> Just 459
+ "460" -> Just 460
+ "461" -> Just 461
+ "462" -> Just 462
+ "463" -> Just 463
+ "464" -> Just 464
+ "465" -> Just 465
+ "466" -> Just 466
+ "467" -> Just 467
+ "468" -> Just 468
+ "469" -> Just 469
+ "470" -> Just 470
+ "471" -> Just 471
+ "472" -> Just 472
+ "473" -> Just 473
+ "474" -> Just 474
+ "475" -> Just 475
+ "476" -> Just 476
+ "477" -> Just 477
+ "478" -> Just 478
+ "479" -> Just 479
+ "480" -> Just 480
+ "481" -> Just 481
+ "482" -> Just 482
+ "483" -> Just 483
+ "484" -> Just 484
+ "485" -> Just 485
+ "486" -> Just 486
+ "487" -> Just 487
+ "488" -> Just 488
+ "489" -> Just 489
+ "490" -> Just 490
+ "491" -> Just 491
+ "492" -> Just 492
+ "493" -> Just 493
+ "494" -> Just 494
+ "495" -> Just 495
+ "496" -> Just 496
+ "497" -> Just 497
+ "498" -> Just 498
+ "499" -> Just 499
+ "500" -> Just 500
+ "501" -> Just 501
+ "502" -> Just 502
+ "503" -> Just 503
+ "504" -> Just 504
+ "505" -> Just 505
+ "506" -> Just 506
+ "507" -> Just 507
+ "508" -> Just 508
+ "509" -> Just 509
+ "510" -> Just 510
+ "511" -> Just 511
+ "512" -> Just 512
+ "513" -> Just 513
+ "514" -> Just 514
+ "515" -> Just 515
+ "516" -> Just 516
+ "517" -> Just 517
+ "518" -> Just 518
+ "519" -> Just 519
+ "520" -> Just 520
+ "521" -> Just 521
+ "522" -> Just 522
+ "523" -> Just 523
+ "524" -> Just 524
+ "525" -> Just 525
+ "526" -> Just 526
+ "527" -> Just 527
+ "528" -> Just 528
+ "529" -> Just 529
+ "530" -> Just 530
+ "531" -> Just 531
+ "532" -> Just 532
+ "533" -> Just 533
+ "534" -> Just 534
+ "535" -> Just 535
+ "536" -> Just 536
+ "537" -> Just 537
+ "538" -> Just 538
+ "539" -> Just 539
+ "540" -> Just 540
+ "541" -> Just 541
+ "542" -> Just 542
+ "543" -> Just 543
+ "544" -> Just 544
+ "545" -> Just 545
+ "546" -> Just 546
+ "547" -> Just 547
+ "548" -> Just 548
+ "549" -> Just 549
+ "550" -> Just 550
+ "551" -> Just 551
+ "552" -> Just 552
+ "553" -> Just 553
+ "554" -> Just 554
+ "555" -> Just 555
+ "556" -> Just 556
+ "557" -> Just 557
+ "558" -> Just 558
+ "559" -> Just 559
+ "560" -> Just 560
+ "561" -> Just 561
+ "562" -> Just 562
+ "563" -> Just 563
+ "564" -> Just 564
+ "565" -> Just 565
+ "566" -> Just 566
+ "567" -> Just 567
+ "568" -> Just 568
+ "569" -> Just 569
+ "570" -> Just 570
+ "571" -> Just 571
+ "572" -> Just 572
+ "573" -> Just 573
+ "574" -> Just 574
+ "575" -> Just 575
+ "576" -> Just 576
+ "577" -> Just 577
+ "578" -> Just 578
+ "579" -> Just 579
+ "580" -> Just 580
+ "581" -> Just 581
+ "582" -> Just 582
+ "583" -> Just 583
+ "584" -> Just 584
+ "585" -> Just 585
+ "586" -> Just 586
+ "587" -> Just 587
+ "588" -> Just 588
+ "589" -> Just 589
+ "590" -> Just 590
+ "591" -> Just 591
+ "592" -> Just 592
+ "593" -> Just 593
+ "594" -> Just 594
+ "595" -> Just 595
+ "596" -> Just 596
+ "597" -> Just 597
+ "598" -> Just 598
+ "599" -> Just 599
+ "600" -> Just 600
+ "601" -> Just 601
+ "602" -> Just 602
+ "603" -> Just 603
+ "604" -> Just 604
+ "605" -> Just 605
+ "606" -> Just 606
+ "607" -> Just 607
+ "608" -> Just 608
+ "609" -> Just 609
+ "610" -> Just 610
+ "611" -> Just 611
+ "612" -> Just 612
+ "613" -> Just 613
+ "614" -> Just 614
+ "615" -> Just 615
+ "616" -> Just 616
+ "617" -> Just 617
+ "618" -> Just 618
+ "619" -> Just 619
+ "620" -> Just 620
+ "621" -> Just 621
+ "622" -> Just 622
+ "623" -> Just 623
+ "624" -> Just 624
+ "625" -> Just 625
+ "626" -> Just 626
+ "627" -> Just 627
+ "628" -> Just 628
+ "629" -> Just 629
+ "630" -> Just 630
+ "631" -> Just 631
+ "632" -> Just 632
+ "633" -> Just 633
+ "634" -> Just 634
+ "635" -> Just 635
+ "636" -> Just 636
+ "637" -> Just 637
+ "638" -> Just 638
+ "639" -> Just 639
+ "640" -> Just 640
+ "641" -> Just 641
+ "642" -> Just 642
+ "643" -> Just 643
+ "644" -> Just 644
+ "645" -> Just 645
+ "646" -> Just 646
+ "647" -> Just 647
+ "648" -> Just 648
+ "649" -> Just 649
+ "650" -> Just 650
+ -- "651" -> Just 651
+ -- "652" -> Just 652
+ -- "653" -> Just 653
+ -- "654" -> Just 654
+ -- "655" -> Just 655
+ -- "656" -> Just 656
+ -- "657" -> Just 657
+ -- "658" -> Just 658
+ -- "659" -> Just 659
+ -- "660" -> Just 660
+ -- "661" -> Just 661
+ -- "662" -> Just 662
+ -- "663" -> Just 663
+ -- "664" -> Just 664
+ -- "665" -> Just 665
+ -- "666" -> Just 666
+ -- "667" -> Just 667
+ -- "668" -> Just 668
+ -- "669" -> Just 669
+ -- "670" -> Just 670
+ -- "671" -> Just 671
+ -- "672" -> Just 672
+ -- "673" -> Just 673
+ -- "674" -> Just 674
+ -- "675" -> Just 675
+ -- "676" -> Just 676
+ -- "677" -> Just 677
+ -- "678" -> Just 678
+ -- "679" -> Just 679
+ -- "680" -> Just 680
+ -- "681" -> Just 681
+ -- "682" -> Just 682
+ -- "683" -> Just 683
+ -- "684" -> Just 684
+ -- "685" -> Just 685
+ -- "686" -> Just 686
+ -- "687" -> Just 687
+ -- "688" -> Just 688
+ -- "689" -> Just 689
+ -- "690" -> Just 690
+ -- "691" -> Just 691
+ -- "692" -> Just 692
+ -- "693" -> Just 693
+ -- "694" -> Just 694
+ -- "695" -> Just 695
+ -- "696" -> Just 696
+ -- "697" -> Just 697
+ -- "698" -> Just 698
+ -- "699" -> Just 699
+ -- "700" -> Just 700
+ -- "701" -> Just 701
+ -- "702" -> Just 702
+ -- "703" -> Just 703
+ -- "704" -> Just 704
+ -- "705" -> Just 705
+ -- "706" -> Just 706
+ -- "707" -> Just 707
+ -- "708" -> Just 708
+ -- "709" -> Just 709
+ -- "710" -> Just 710
+ -- "711" -> Just 711
+ -- "712" -> Just 712
+ -- "713" -> Just 713
+ -- "714" -> Just 714
+ -- "715" -> Just 715
+ -- "716" -> Just 716
+ -- "717" -> Just 717
+ -- "718" -> Just 718
+ -- "719" -> Just 719
+ -- "720" -> Just 720
+ -- "721" -> Just 721
+ -- "722" -> Just 722
+ -- "723" -> Just 723
+ -- "724" -> Just 724
+ -- "725" -> Just 725
+ -- "726" -> Just 726
+ -- "727" -> Just 727
+ -- "728" -> Just 728
+ -- "729" -> Just 729
+ -- "730" -> Just 730
+ -- "731" -> Just 731
+ -- "732" -> Just 732
+ -- "733" -> Just 733
+ -- "734" -> Just 734
+ -- "735" -> Just 735
+ -- "736" -> Just 736
+ -- "737" -> Just 737
+ -- "738" -> Just 738
+ -- "739" -> Just 739
+ -- "740" -> Just 740
+ -- "741" -> Just 741
+ -- "742" -> Just 742
+ -- "743" -> Just 743
+ -- "744" -> Just 744
+ -- "745" -> Just 745
+ -- "746" -> Just 746
+ -- "747" -> Just 747
+ -- "748" -> Just 748
+ -- "749" -> Just 749
+ -- "750" -> Just 750
+ -- "751" -> Just 751
+ -- "752" -> Just 752
+ -- "753" -> Just 753
+ -- "754" -> Just 754
+ -- "755" -> Just 755
+ -- "756" -> Just 756
+ -- "757" -> Just 757
+ -- "758" -> Just 758
+ -- "759" -> Just 759
+ -- "760" -> Just 760
+ -- "761" -> Just 761
+ -- "762" -> Just 762
+ -- "763" -> Just 763
+ -- "764" -> Just 764
+ -- "765" -> Just 765
+ -- "766" -> Just 766
+ -- "767" -> Just 767
+ -- "768" -> Just 768
+ -- "769" -> Just 769
+ -- "770" -> Just 770
+ -- "771" -> Just 771
+ -- "772" -> Just 772
+ -- "773" -> Just 773
+ -- "774" -> Just 774
+ -- "775" -> Just 775
+ -- "776" -> Just 776
+ -- "777" -> Just 777
+ -- "778" -> Just 778
+ -- "779" -> Just 779
+ -- "780" -> Just 780
+ -- "781" -> Just 781
+ -- "782" -> Just 782
+ -- "783" -> Just 783
+ -- "784" -> Just 784
+ -- "785" -> Just 785
+ -- "786" -> Just 786
+ -- "787" -> Just 787
+ -- "788" -> Just 788
+ -- "789" -> Just 789
+ -- "790" -> Just 790
+ -- "791" -> Just 791
+ -- "792" -> Just 792
+ -- "793" -> Just 793
+ -- "794" -> Just 794
+ -- "795" -> Just 795
+ -- "796" -> Just 796
+ -- "797" -> Just 797
+ -- "798" -> Just 798
+ -- "799" -> Just 799
+ -- "800" -> Just 800
+ -- "801" -> Just 801
+ -- "802" -> Just 802
+ -- "803" -> Just 803
+ -- "804" -> Just 804
+ -- "805" -> Just 805
+ -- "806" -> Just 806
+ -- "807" -> Just 807
+ -- "808" -> Just 808
+ -- "809" -> Just 809
+ -- "810" -> Just 810
+ -- "811" -> Just 811
+ -- "812" -> Just 812
+ -- "813" -> Just 813
+ -- "814" -> Just 814
+ -- "815" -> Just 815
+ -- "816" -> Just 816
+ -- "817" -> Just 817
+ -- "818" -> Just 818
+ -- "819" -> Just 819
+ -- "820" -> Just 820
+ -- "821" -> Just 821
+ -- "822" -> Just 822
+ -- "823" -> Just 823
+ -- "824" -> Just 824
+ -- "825" -> Just 825
+ -- "826" -> Just 826
+ -- "827" -> Just 827
+ -- "828" -> Just 828
+ -- "829" -> Just 829
+ -- "830" -> Just 830
+ -- "831" -> Just 831
+ -- "832" -> Just 832
+ -- "833" -> Just 833
+ -- "834" -> Just 834
+ -- "835" -> Just 835
+ -- "836" -> Just 836
+ -- "837" -> Just 837
+ -- "838" -> Just 838
+ -- "839" -> Just 839
+ -- "840" -> Just 840
+ -- "841" -> Just 841
+ -- "842" -> Just 842
+ -- "843" -> Just 843
+ -- "844" -> Just 844
+ -- "845" -> Just 845
+ -- "846" -> Just 846
+ -- "847" -> Just 847
+ -- "848" -> Just 848
+ -- "849" -> Just 849
+ -- "850" -> Just 850
+ -- "851" -> Just 851
+ -- "852" -> Just 852
+ -- "853" -> Just 853
+ -- "854" -> Just 854
+ -- "855" -> Just 855
+ -- "856" -> Just 856
+ -- "857" -> Just 857
+ -- "858" -> Just 858
+ -- "859" -> Just 859
+ -- "860" -> Just 860
+ -- "861" -> Just 861
+ -- "862" -> Just 862
+ -- "863" -> Just 863
+ -- "864" -> Just 864
+ -- "865" -> Just 865
+ -- "866" -> Just 866
+ -- "867" -> Just 867
+ -- "868" -> Just 868
+ -- "869" -> Just 869
+ -- "870" -> Just 870
+ -- "871" -> Just 871
+ -- "872" -> Just 872
+ -- "873" -> Just 873
+ -- "874" -> Just 874
+ -- "875" -> Just 875
+ -- "876" -> Just 876
+ -- "877" -> Just 877
+ -- "878" -> Just 878
+ -- "879" -> Just 879
+ -- "880" -> Just 880
+ -- "881" -> Just 881
+ -- "882" -> Just 882
+ -- "883" -> Just 883
+ -- "884" -> Just 884
+ -- "885" -> Just 885
+ -- "886" -> Just 886
+ -- "887" -> Just 887
+ -- "888" -> Just 888
+ -- "889" -> Just 889
+ -- "890" -> Just 890
+ -- "891" -> Just 891
+ -- "892" -> Just 892
+ -- "893" -> Just 893
+ -- "894" -> Just 894
+ -- "895" -> Just 895
+ -- "896" -> Just 896
+ -- "897" -> Just 897
+ -- "898" -> Just 898
+ -- "899" -> Just 899
+ -- "900" -> Just 900
+ -- "901" -> Just 901
+ -- "902" -> Just 902
+ -- "903" -> Just 903
+ -- "904" -> Just 904
+ -- "905" -> Just 905
+ -- "906" -> Just 906
+ -- "907" -> Just 907
+ -- "908" -> Just 908
+ -- "909" -> Just 909
+ -- "910" -> Just 910
+ -- "911" -> Just 911
+ -- "912" -> Just 912
+ -- "913" -> Just 913
+ -- "914" -> Just 914
+ -- "915" -> Just 915
+ -- "916" -> Just 916
+ -- "917" -> Just 917
+ -- "918" -> Just 918
+ -- "919" -> Just 919
+ -- "920" -> Just 920
+ -- "921" -> Just 921
+ -- "922" -> Just 922
+ -- "923" -> Just 923
+ -- "924" -> Just 924
+ -- "925" -> Just 925
+ -- "926" -> Just 926
+ -- "927" -> Just 927
+ -- "928" -> Just 928
+ -- "929" -> Just 929
+ -- "930" -> Just 930
+ -- "931" -> Just 931
+ -- "932" -> Just 932
+ -- "933" -> Just 933
+ -- "934" -> Just 934
+ -- "935" -> Just 935
+ -- "936" -> Just 936
+ -- "937" -> Just 937
+ -- "938" -> Just 938
+ -- "939" -> Just 939
+ -- "940" -> Just 940
+ -- "941" -> Just 941
+ -- "942" -> Just 942
+ -- "943" -> Just 943
+ -- "944" -> Just 944
+ -- "945" -> Just 945
+ -- "946" -> Just 946
+ -- "947" -> Just 947
+ -- "948" -> Just 948
+ -- "949" -> Just 949
+ -- "950" -> Just 950
+ -- "951" -> Just 951
+ -- "952" -> Just 952
+ -- "953" -> Just 953
+ -- "954" -> Just 954
+ -- "955" -> Just 955
+ -- "956" -> Just 956
+ -- "957" -> Just 957
+ -- "958" -> Just 958
+ -- "959" -> Just 959
+ -- "960" -> Just 960
+ -- "961" -> Just 961
+ -- "962" -> Just 962
+ -- "963" -> Just 963
+ -- "964" -> Just 964
+ -- "965" -> Just 965
+ -- "966" -> Just 966
+ -- "967" -> Just 967
+ -- "968" -> Just 968
+ -- "969" -> Just 969
+ -- "970" -> Just 970
+ -- "971" -> Just 971
+ -- "972" -> Just 972
+ -- "973" -> Just 973
+ -- "974" -> Just 974
+ -- "975" -> Just 975
+ -- "976" -> Just 976
+ -- "977" -> Just 977
+ -- "978" -> Just 978
+ -- "979" -> Just 979
+ -- "980" -> Just 980
+ -- "981" -> Just 981
+ -- "982" -> Just 982
+ -- "983" -> Just 983
+ -- "984" -> Just 984
+ -- "985" -> Just 985
+ -- "986" -> Just 986
+ -- "987" -> Just 987
+ -- "988" -> Just 988
+ -- "989" -> Just 989
+ -- "990" -> Just 990
+ -- "991" -> Just 991
+ -- "992" -> Just 992
+ -- "993" -> Just 993
+ -- "994" -> Just 994
+ -- "995" -> Just 995
+ -- "996" -> Just 996
+ -- "997" -> Just 997
+ -- "998" -> Just 998
+ -- "999" -> Just 999
+ -- "1000" -> Just 1000
+ _ -> Nothing
=====================================
testsuite/tests/perf/compiler/all.T
=====================================
@@ -792,3 +792,8 @@ test('interpreter_steplocal',
],
ghci_script,
['interpreter_steplocal.script'])
+
+test ('T26425',
+ [ collect_compiler_stats('all',5) ],
+ compile,
+ ['-O'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d706155a19005d0bd144928bec4fd92…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d706155a19005d0bd144928bec4fd92…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/gbc-files] Apply 3 suggestion(s) to 2 file(s)
by Matthew Pickering (@mpickering) 03 Oct '25
by Matthew Pickering (@mpickering) 03 Oct '25
03 Oct '25
Matthew Pickering pushed to branch wip/gbc-files at Glasgow Haskell Compiler / GHC
Commits:
57febb55 by Matthew Pickering at 2025-10-03T09:08:21+00:00
Apply 3 suggestion(s) to 2 file(s)
Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita(a)gmail.com>
- - - - -
2 changed files:
- compiler/GHC/ByteCode/Serialize.hs
- compiler/GHC/Driver/Main.hs
Changes:
=====================================
compiler/GHC/ByteCode/Serialize.hs
=====================================
@@ -40,18 +40,11 @@ import System.IO.Unsafe (unsafeInterleaveIO)
{- Note [Overview of persistent bytecode]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-GHC can produce a .gbc file, which is a serialised representation of a bytecode object.
+By default, when using the interpreter, a Haskell module is first compiled to bytecode (which lives in memory) and then executed by the RTS interpreter. However, when dealing with many modules compiling to bytecode from scratch every time is expensive. This is especially relevant for interpreter-heavy workflows on large projects where changes are incremental or non-existent (e.g. running the project in the debugger).
-By passing the flag `-fwrite-bytecode`, then when using the bytecode backend,
-a .gbc file will be written to the output directory.
+In light of this, GHC can produce so-called `.gbc` files, which contain a serialized representation of the bytecode objects in a Haskell module. These files are written by enabling the flag `-fwrite-bytecode` when using the interpreter.
-The primary use case for the file is to avoid having to recompile when using
-GHCi. Instead, the driver will look for the interface and .gbc file and load
-those to avoid recompiling.
-
-* This can save a lot of time if you have many modules. Even compared to `-fwrite-if-simplified-core`.
-* The source code might not be available, but you may still want to run the bytecode rather than
- native object code (for example, for debugging).
+The driver will always look for both the interface and the `.gbc` file and load those to avoid unnecessary recompilation. This can save a lot of time if you have many modules. Even compared to `-fwrite-if-simplified-core`.
.gbc files are standalone, in the sense that they can be loaded into the interpreter
without having the interface file or source files available. In the future you could
=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -877,7 +877,7 @@ hscRecompStatus
, text "BCO core linkable", ppr bc_core_linkable
, text "Object Linkable", ppr obj_linkable])
- let just_o = justObjects <$> obj_linkable
+ let just_o = justObjects <$> obj_linkable
bytecode_or_object_code
| gopt Opt_WriteByteCode lcl_dflags = justBytecode <$> definitely_bc
@@ -2215,7 +2215,7 @@ generateAndWriteByteCode hsc_env cgguts mod_location = do
{-
Note [-fwrite-bytecode is not the default]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
`-fwrite-bytecode` is not enabled by default because previously using `-fbyte-code` would
not write anything at all to disk. For example, GHCi would not write anything to the directory
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/57febb55de1dd512cf3e9dda032a7e6…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/57febb55de1dd512cf3e9dda032a7e6…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc] Pushed new branch wip/andreask/t26425_test
by Andreas Klebinger (@AndreasK) 03 Oct '25
by Andreas Klebinger (@AndreasK) 03 Oct '25
03 Oct '25
Andreas Klebinger pushed new branch wip/andreask/t26425_test at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/t26425_test
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: testsuite: Use ghci_ways to set ways in PackedDataCon/UnboxedTuples/UnliftedDataTypeInterp tests
by Marge Bot (@marge-bot) 03 Oct '25
by Marge Bot (@marge-bot) 03 Oct '25
03 Oct '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
29fa1867 by Matthew Pickering at 2025-10-03T00:15:23-04:00
testsuite: Use ghci_ways to set ways in PackedDataCon/UnboxedTuples/UnliftedDataTypeInterp tests
These tests reimplemented the logic from `valid_way` in order to
determine what ways to run. It's easier to use this combination of
`only_ways` and `extra_ways` to only run in GHCi ways and always run in
GHCi ways.
- - - - -
f26568c2 by Matthew Pickering at 2025-10-03T00:15:24-04:00
Rename interpreterBackend to bytecodeBackend
This is preparation for creating bytecode files.
The "interpreter" is one way in which we can run bytecode objects. It is
more accurate to describe that the backend produces bytecode, rather
than the means by which the code will eventually run.
The "interpreterBackend" binding is left as a deprecated alias.
- - - - -
19 changed files:
- compiler/GHC.hs
- compiler/GHC/Driver/Backend.hs
- compiler/GHC/Driver/Backend/Internal.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Session.hs
- docs/users_guide/extending_ghc.rst
- ghc/Main.hs
- testsuite/driver/testglobals.py
- testsuite/driver/testlib.py
- testsuite/tests/driver/T5313.hs
- testsuite/tests/ghc-api/T10052/T10052.hs
- testsuite/tests/ghc-api/T8639_api.hs
- testsuite/tests/ghc-api/apirecomp001/myghc.hs
- testsuite/tests/ghci-wasm/T26431.hs
- testsuite/tests/ghci/linking/dyn/T3372.hs
- testsuite/tests/ghci/should_run/PackedDataCon/packeddatacon.T
- testsuite/tests/ghci/should_run/UnboxedTuples/unboxedtuples.T
- testsuite/tests/ghci/should_run/UnliftedDataTypeInterp/unlifteddatatypeinterp.T
Changes:
=====================================
compiler/GHC.hs
=====================================
@@ -30,7 +30,7 @@ module GHC (
-- * Flags and settings
DynFlags(..), GeneralFlag(..), Severity(..), Backend, gopt,
- ncgBackend, llvmBackend, viaCBackend, interpreterBackend, noBackend,
+ ncgBackend, llvmBackend, viaCBackend, bytecodeBackend, interpreterBackend, noBackend,
GhcMode(..), GhcLink(..),
parseDynamicFlags, parseTargetFiles,
getSessionDynFlags,
=====================================
compiler/GHC/Driver/Backend.hs
=====================================
@@ -47,6 +47,7 @@ module GHC.Driver.Backend
, llvmBackend
, jsBackend
, viaCBackend
+ , bytecodeBackend
, interpreterBackend
, noBackend
, allBackends
@@ -252,7 +253,7 @@ instance Show Backend where
show = backendDescription
-ncgBackend, llvmBackend, viaCBackend, interpreterBackend, jsBackend, noBackend
+ncgBackend, llvmBackend, viaCBackend, bytecodeBackend, interpreterBackend, jsBackend, noBackend
:: Backend
-- | The native code generator.
@@ -310,7 +311,11 @@ viaCBackend = Named ViaC
-- (foreign primops).
--
-- See "GHC.StgToByteCode"
-interpreterBackend = Named Interpreter
+bytecodeBackend = Named Bytecode
+
+{-# DEPRECATED interpreterBackend "Renamed to bytecodeBackend" #-}
+interpreterBackend = bytecodeBackend
+
-- | A dummy back end that generates no code.
--
@@ -419,7 +424,7 @@ backendDescription (Named NCG) = "native code generator"
backendDescription (Named LLVM) = "LLVM"
backendDescription (Named ViaC) = "compiling via C"
backendDescription (Named JavaScript) = "compiling to JavaScript"
-backendDescription (Named Interpreter) = "byte-code interpreter"
+backendDescription (Named Bytecode) = "byte-code interpreter"
backendDescription (Named NoBackend) = "no code generated"
-- | This flag tells the compiler driver whether the back
@@ -431,7 +436,7 @@ backendWritesFiles (Named NCG) = True
backendWritesFiles (Named LLVM) = True
backendWritesFiles (Named ViaC) = True
backendWritesFiles (Named JavaScript) = True
-backendWritesFiles (Named Interpreter) = False
+backendWritesFiles (Named Bytecode) = False
backendWritesFiles (Named NoBackend) = False
-- | When the back end does write files, this value tells
@@ -442,7 +447,7 @@ backendPipelineOutput (Named NCG) = Persistent
backendPipelineOutput (Named LLVM) = Persistent
backendPipelineOutput (Named ViaC) = Persistent
backendPipelineOutput (Named JavaScript) = Persistent
-backendPipelineOutput (Named Interpreter) = NoOutputFile
+backendPipelineOutput (Named Bytecode) = NoOutputFile
backendPipelineOutput (Named NoBackend) = NoOutputFile
-- | This flag tells the driver whether the back end can
@@ -453,7 +458,7 @@ backendCanReuseLoadedCode (Named NCG) = False
backendCanReuseLoadedCode (Named LLVM) = False
backendCanReuseLoadedCode (Named ViaC) = False
backendCanReuseLoadedCode (Named JavaScript) = False
-backendCanReuseLoadedCode (Named Interpreter) = True
+backendCanReuseLoadedCode (Named Bytecode) = True
backendCanReuseLoadedCode (Named NoBackend) = False
-- | It is is true of every back end except @-fno-code@
@@ -478,7 +483,7 @@ backendGeneratesCode (Named NCG) = True
backendGeneratesCode (Named LLVM) = True
backendGeneratesCode (Named ViaC) = True
backendGeneratesCode (Named JavaScript) = True
-backendGeneratesCode (Named Interpreter) = True
+backendGeneratesCode (Named Bytecode) = True
backendGeneratesCode (Named NoBackend) = False
backendGeneratesCodeForHsBoot :: Backend -> Bool
@@ -486,7 +491,7 @@ backendGeneratesCodeForHsBoot (Named NCG) = True
backendGeneratesCodeForHsBoot (Named LLVM) = True
backendGeneratesCodeForHsBoot (Named ViaC) = True
backendGeneratesCodeForHsBoot (Named JavaScript) = True
-backendGeneratesCodeForHsBoot (Named Interpreter) = False
+backendGeneratesCodeForHsBoot (Named Bytecode) = False
backendGeneratesCodeForHsBoot (Named NoBackend) = False
-- | When set, this flag turns on interface writing for
@@ -498,7 +503,7 @@ backendSupportsInterfaceWriting (Named NCG) = True
backendSupportsInterfaceWriting (Named LLVM) = True
backendSupportsInterfaceWriting (Named ViaC) = True
backendSupportsInterfaceWriting (Named JavaScript) = True
-backendSupportsInterfaceWriting (Named Interpreter) = True
+backendSupportsInterfaceWriting (Named Bytecode) = True
backendSupportsInterfaceWriting (Named NoBackend) = False
-- | When preparing code for this back end, the type
@@ -510,7 +515,7 @@ backendRespectsSpecialise (Named NCG) = True
backendRespectsSpecialise (Named LLVM) = True
backendRespectsSpecialise (Named ViaC) = True
backendRespectsSpecialise (Named JavaScript) = True
-backendRespectsSpecialise (Named Interpreter) = False
+backendRespectsSpecialise (Named Bytecode) = False
backendRespectsSpecialise (Named NoBackend) = False
-- | This back end wants the `mi_top_env` field of a
@@ -522,7 +527,7 @@ backendWantsGlobalBindings (Named LLVM) = False
backendWantsGlobalBindings (Named ViaC) = False
backendWantsGlobalBindings (Named JavaScript) = False
backendWantsGlobalBindings (Named NoBackend) = False
-backendWantsGlobalBindings (Named Interpreter) = True
+backendWantsGlobalBindings (Named Bytecode) = True
-- | The back end targets a technology that implements
-- `switch` natively. (For example, LLVM or C.) Therefore
@@ -534,7 +539,7 @@ backendHasNativeSwitch (Named NCG) = False
backendHasNativeSwitch (Named LLVM) = True
backendHasNativeSwitch (Named ViaC) = True
backendHasNativeSwitch (Named JavaScript) = True
-backendHasNativeSwitch (Named Interpreter) = False
+backendHasNativeSwitch (Named Bytecode) = False
backendHasNativeSwitch (Named NoBackend) = False
-- | As noted in the documentation for
@@ -548,7 +553,7 @@ backendPrimitiveImplementation (Named NCG) = NcgPrimitives
backendPrimitiveImplementation (Named LLVM) = LlvmPrimitives
backendPrimitiveImplementation (Named JavaScript) = JSPrimitives
backendPrimitiveImplementation (Named ViaC) = GenericPrimitives
-backendPrimitiveImplementation (Named Interpreter) = GenericPrimitives
+backendPrimitiveImplementation (Named Bytecode) = GenericPrimitives
backendPrimitiveImplementation (Named NoBackend) = GenericPrimitives
-- | When this value is `IsValid`, the back end is
@@ -560,7 +565,7 @@ backendSimdValidity (Named NCG) = IsValid
backendSimdValidity (Named LLVM) = IsValid
backendSimdValidity (Named ViaC) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
backendSimdValidity (Named JavaScript) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
-backendSimdValidity (Named Interpreter) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
+backendSimdValidity (Named Bytecode) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
backendSimdValidity (Named NoBackend) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
-- | This flag says whether the back end supports large
@@ -571,7 +576,7 @@ backendSupportsEmbeddedBlobs (Named NCG) = True
backendSupportsEmbeddedBlobs (Named LLVM) = False
backendSupportsEmbeddedBlobs (Named ViaC) = False
backendSupportsEmbeddedBlobs (Named JavaScript) = False
-backendSupportsEmbeddedBlobs (Named Interpreter) = False
+backendSupportsEmbeddedBlobs (Named Bytecode) = False
backendSupportsEmbeddedBlobs (Named NoBackend) = False
-- | This flag tells the compiler driver that the back end
@@ -586,7 +591,7 @@ backendNeedsPlatformNcgSupport (Named NCG) = True
backendNeedsPlatformNcgSupport (Named LLVM) = False
backendNeedsPlatformNcgSupport (Named ViaC) = False
backendNeedsPlatformNcgSupport (Named JavaScript) = False
-backendNeedsPlatformNcgSupport (Named Interpreter) = False
+backendNeedsPlatformNcgSupport (Named Bytecode) = False
backendNeedsPlatformNcgSupport (Named NoBackend) = False
-- | This flag is set if the back end can generate code
@@ -598,7 +603,7 @@ backendSupportsUnsplitProcPoints (Named NCG) = True
backendSupportsUnsplitProcPoints (Named LLVM) = False
backendSupportsUnsplitProcPoints (Named ViaC) = False
backendSupportsUnsplitProcPoints (Named JavaScript) = False
-backendSupportsUnsplitProcPoints (Named Interpreter) = False
+backendSupportsUnsplitProcPoints (Named Bytecode) = False
backendSupportsUnsplitProcPoints (Named NoBackend) = False
-- | This flag guides the driver in resolving issues about
@@ -616,7 +621,7 @@ backendSwappableWithViaC (Named NCG) = True
backendSwappableWithViaC (Named LLVM) = True
backendSwappableWithViaC (Named ViaC) = False
backendSwappableWithViaC (Named JavaScript) = False
-backendSwappableWithViaC (Named Interpreter) = False
+backendSwappableWithViaC (Named Bytecode) = False
backendSwappableWithViaC (Named NoBackend) = False
-- | This flag is true if the back end works *only* with
@@ -626,7 +631,7 @@ backendUnregisterisedAbiOnly (Named NCG) = False
backendUnregisterisedAbiOnly (Named LLVM) = False
backendUnregisterisedAbiOnly (Named ViaC) = True
backendUnregisterisedAbiOnly (Named JavaScript) = False
-backendUnregisterisedAbiOnly (Named Interpreter) = False
+backendUnregisterisedAbiOnly (Named Bytecode) = False
backendUnregisterisedAbiOnly (Named NoBackend) = False
-- | This flag is set if the back end generates C code in
@@ -637,7 +642,7 @@ backendGeneratesHc (Named NCG) = False
backendGeneratesHc (Named LLVM) = False
backendGeneratesHc (Named ViaC) = True
backendGeneratesHc (Named JavaScript) = False
-backendGeneratesHc (Named Interpreter) = False
+backendGeneratesHc (Named Bytecode) = False
backendGeneratesHc (Named NoBackend) = False
-- | This flag says whether SPT (static pointer table)
@@ -649,7 +654,7 @@ backendSptIsDynamic (Named NCG) = False
backendSptIsDynamic (Named LLVM) = False
backendSptIsDynamic (Named ViaC) = False
backendSptIsDynamic (Named JavaScript) = False
-backendSptIsDynamic (Named Interpreter) = True
+backendSptIsDynamic (Named Bytecode) = True
backendSptIsDynamic (Named NoBackend) = False
-- | If this flag is unset, then the driver ignores the flag @-fbreak-points@,
@@ -660,7 +665,7 @@ backendSupportsBreakpoints = \case
Named LLVM -> False
Named ViaC -> False
Named JavaScript -> False
- Named Interpreter -> True
+ Named Bytecode -> True
Named NoBackend -> False
-- | If this flag is set, then the driver forces the
@@ -671,7 +676,7 @@ backendForcesOptimization0 (Named NCG) = False
backendForcesOptimization0 (Named LLVM) = False
backendForcesOptimization0 (Named ViaC) = False
backendForcesOptimization0 (Named JavaScript) = False
-backendForcesOptimization0 (Named Interpreter) = True
+backendForcesOptimization0 (Named Bytecode) = True
backendForcesOptimization0 (Named NoBackend) = False
-- | I don't understand exactly how this works. But if
@@ -683,7 +688,7 @@ backendNeedsFullWays (Named NCG) = False
backendNeedsFullWays (Named LLVM) = False
backendNeedsFullWays (Named ViaC) = False
backendNeedsFullWays (Named JavaScript) = False
-backendNeedsFullWays (Named Interpreter) = True
+backendNeedsFullWays (Named Bytecode) = True
backendNeedsFullWays (Named NoBackend) = False
-- | This flag is also special for the interpreter: if a
@@ -695,7 +700,7 @@ backendSpecialModuleSource (Named NCG) = const Nothing
backendSpecialModuleSource (Named LLVM) = const Nothing
backendSpecialModuleSource (Named ViaC) = const Nothing
backendSpecialModuleSource (Named JavaScript) = const Nothing
-backendSpecialModuleSource (Named Interpreter) = \b -> if b then Just "interpreted" else Nothing
+backendSpecialModuleSource (Named Bytecode) = \b -> if b then Just "interpreted" else Nothing
backendSpecialModuleSource (Named NoBackend) = const (Just "nothing")
-- | This flag says whether the back end supports Haskell
@@ -707,7 +712,7 @@ backendSupportsHpc (Named NCG) = True
backendSupportsHpc (Named LLVM) = True
backendSupportsHpc (Named ViaC) = True
backendSupportsHpc (Named JavaScript) = False
-backendSupportsHpc (Named Interpreter) = False
+backendSupportsHpc (Named Bytecode) = False
backendSupportsHpc (Named NoBackend) = True
-- | This flag says whether the back end supports foreign
@@ -718,7 +723,7 @@ backendSupportsCImport (Named NCG) = True
backendSupportsCImport (Named LLVM) = True
backendSupportsCImport (Named ViaC) = True
backendSupportsCImport (Named JavaScript) = True
-backendSupportsCImport (Named Interpreter) = True
+backendSupportsCImport (Named Bytecode) = True
backendSupportsCImport (Named NoBackend) = True
-- | This flag says whether the back end supports foreign
@@ -728,7 +733,7 @@ backendSupportsCExport (Named NCG) = True
backendSupportsCExport (Named LLVM) = True
backendSupportsCExport (Named ViaC) = True
backendSupportsCExport (Named JavaScript) = True
-backendSupportsCExport (Named Interpreter) = False
+backendSupportsCExport (Named Bytecode) = False
backendSupportsCExport (Named NoBackend) = True
-- | When using this back end, it may be necessary or
@@ -749,7 +754,7 @@ backendCDefs (Named NCG) = NoCDefs
backendCDefs (Named LLVM) = LlvmCDefs
backendCDefs (Named ViaC) = NoCDefs
backendCDefs (Named JavaScript) = NoCDefs
-backendCDefs (Named Interpreter) = NoCDefs
+backendCDefs (Named Bytecode) = NoCDefs
backendCDefs (Named NoBackend) = NoCDefs
-- | This (defunctionalized) function generates code and
@@ -768,7 +773,7 @@ backendCodeOutput (Named NCG) = NcgCodeOutput
backendCodeOutput (Named LLVM) = LlvmCodeOutput
backendCodeOutput (Named ViaC) = ViaCCodeOutput
backendCodeOutput (Named JavaScript) = JSCodeOutput
-backendCodeOutput (Named Interpreter) = panic "backendCodeOutput: interpreterBackend"
+backendCodeOutput (Named Bytecode) = panic "backendCodeOutput: bytecodeBackend"
backendCodeOutput (Named NoBackend) = panic "backendCodeOutput: noBackend"
backendUseJSLinker :: Backend -> Bool
@@ -776,7 +781,7 @@ backendUseJSLinker (Named NCG) = False
backendUseJSLinker (Named LLVM) = False
backendUseJSLinker (Named ViaC) = False
backendUseJSLinker (Named JavaScript) = True
-backendUseJSLinker (Named Interpreter) = False
+backendUseJSLinker (Named Bytecode) = False
backendUseJSLinker (Named NoBackend) = False
-- | This (defunctionalized) function tells the compiler
@@ -795,7 +800,7 @@ backendPostHscPipeline (Named NCG) = NcgPostHscPipeline
backendPostHscPipeline (Named LLVM) = LlvmPostHscPipeline
backendPostHscPipeline (Named ViaC) = ViaCPostHscPipeline
backendPostHscPipeline (Named JavaScript) = JSPostHscPipeline
-backendPostHscPipeline (Named Interpreter) = NoPostHscPipeline
+backendPostHscPipeline (Named Bytecode) = NoPostHscPipeline
backendPostHscPipeline (Named NoBackend) = NoPostHscPipeline
-- | Somewhere in the compiler driver, when compiling
@@ -809,7 +814,7 @@ backendNormalSuccessorPhase (Named NCG) = As False
backendNormalSuccessorPhase (Named LLVM) = LlvmOpt
backendNormalSuccessorPhase (Named ViaC) = HCc
backendNormalSuccessorPhase (Named JavaScript) = StopLn
-backendNormalSuccessorPhase (Named Interpreter) = StopLn
+backendNormalSuccessorPhase (Named Bytecode) = StopLn
backendNormalSuccessorPhase (Named NoBackend) = StopLn
-- | Name of the back end, if any. Used to migrate legacy
@@ -820,7 +825,7 @@ backendName (Named NCG) = NCG
backendName (Named LLVM) = LLVM
backendName (Named ViaC) = ViaC
backendName (Named JavaScript) = JavaScript
-backendName (Named Interpreter) = Interpreter
+backendName (Named Bytecode) = Bytecode
backendName (Named NoBackend) = NoBackend
@@ -833,7 +838,7 @@ allBackends = [ ncgBackend
, llvmBackend
, viaCBackend
, jsBackend
- , interpreterBackend
+ , bytecodeBackend
, noBackend
]
=====================================
compiler/GHC/Driver/Backend/Internal.hs
=====================================
@@ -28,6 +28,6 @@ data BackendName
| LLVM -- ^ Names the LLVM backend.
| ViaC -- ^ Names the Via-C backend.
| JavaScript -- ^ Names the JS backend.
- | Interpreter -- ^ Names the ByteCode interpreter.
+ | Bytecode -- ^ Names the ByteCode interpreter.
| NoBackend -- ^ Names the `-fno-code` backend.
deriving (Eq, Show)
=====================================
compiler/GHC/Driver/Downsweep.hs
=====================================
@@ -916,7 +916,7 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = do
else (,) <$> (new_temp_file (hiSuf_ dflags) (dynHiSuf_ dflags))
<*> (new_temp_file (objectSuf_ dflags) (dynObjectSuf_ dflags))
let new_dflags = case enable_spec of
- EnableByteCode -> dflags { backend = interpreterBackend }
+ EnableByteCode -> dflags { backend = bytecodeBackend }
EnableObject -> dflags { backend = defaultBackendOf ms }
EnableByteCodeAndObject -> (gopt_set dflags Opt_ByteCodeAndObjectCode) { backend = defaultBackendOf ms}
let ms' = ms
=====================================
compiler/GHC/Driver/Pipeline.hs
=====================================
@@ -281,8 +281,8 @@ compileOne' mHscMessage
-- was set), force it to generate byte-code. This is NOT transitive and
-- only applies to direct targets.
| loadAsByteCode
- = ( interpreterBackend
- , gopt_set (lcl_dflags { backend = interpreterBackend }) Opt_ForceRecomp
+ = ( bytecodeBackend
+ , gopt_set (lcl_dflags { backend = bytecodeBackend }) Opt_ForceRecomp
)
| otherwise
=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -1931,7 +1931,7 @@ dynamic_flags_deps = [
d { ghcLink=NoLink }) >> setBackend noBackend))
, make_ord_flag defFlag "fbyte-code"
(noArgM $ \dflags -> do
- setBackend interpreterBackend
+ setBackend bytecodeBackend
pure $ flip gopt_unset Opt_ByteCodeAndObjectCode (gopt_set dflags Opt_ByteCode))
, make_ord_flag defFlag "fobject-code" $ noArgM $ \dflags -> do
setBackend $ platformDefaultBackend (targetPlatform dflags)
=====================================
docs/users_guide/extending_ghc.rst
=====================================
@@ -1719,7 +1719,7 @@ constructor from version 9.4 with the corresponding value from 9.6:
+-----------------+------------------------+
| ``ViaC`` | ``viaCBackend`` |
+-----------------+------------------------+
-| ``Interpreter`` | ``interpreterBackend`` |
+| ``Interpreter`` | ``bytecodeBackend`` |
+-----------------+------------------------+
| ``NoBackend`` | ``noBackend`` |
+-----------------+------------------------+
=====================================
ghc/Main.hs
=====================================
@@ -169,9 +169,9 @@ main' postLoadMode units dflags0 args flagWarnings = do
let dflt_backend = backend dflags0
(mode, bcknd, link)
= case postLoadMode of
- DoInteractive -> (CompManager, interpreterBackend, LinkInMemory)
- DoEval _ -> (CompManager, interpreterBackend, LinkInMemory)
- DoRun -> (CompManager, interpreterBackend, LinkInMemory)
+ DoInteractive -> (CompManager, bytecodeBackend, LinkInMemory)
+ DoEval _ -> (CompManager, bytecodeBackend, LinkInMemory)
+ DoRun -> (CompManager, bytecodeBackend, LinkInMemory)
DoMake -> (CompManager, dflt_backend, LinkBinary)
DoBackpack -> (CompManager, dflt_backend, LinkBinary)
DoMkDependHS -> (MkDepend, dflt_backend, LinkBinary)
=====================================
testsuite/driver/testglobals.py
=====================================
@@ -136,9 +136,12 @@ class TestConfig:
# Do we have interpreter support?
self.have_interp = False
+ # Do we have external interpreter support?
+ self.have_ext_interp = False
+
# Are we cross-compiling?
self.cross = False
-
+
# Does the RTS linker only support loading shared libraries?
self.interp_force_dyn = False
=====================================
testsuite/driver/testlib.py
=====================================
@@ -549,10 +549,12 @@ only_ghci = only_ways([WayName('ghci'), WayName('ghci-opt')])
# -----
def valid_way( way: WayName ) -> bool:
- if way in {'ghci', 'ghci-opt', 'ghci-ext'}:
+ if way in {'ghci', 'ghci-opt'}:
return config.have_RTS_linker
- if way == 'ghci-ext-prof':
- return config.have_RTS_linker and config.have_profiling
+ if way in {'ghci-ext'}:
+ return config.have_ext_interp
+ if way in {'ghci-ext-prof'}:
+ return config.have_ext_interp and config.have_profiling
return True
def extra_ways( ways: List[WayName] ):
=====================================
testsuite/tests/driver/T5313.hs
=====================================
@@ -7,7 +7,7 @@ main = do
-- begin initialize
df0 <- GHC.getSessionDynFlags
let df1 = df0{GHC.ghcMode = GHC.CompManager,
- GHC.backend = GHC.interpreterBackend,
+ GHC.backend = GHC.bytecodeBackend,
GHC.ghcLink = GHC.LinkInMemory,
GHC.verbosity = 0}
_ <- GHC.setSessionDynFlags df1
=====================================
testsuite/tests/ghc-api/T10052/T10052.hs
=====================================
@@ -24,7 +24,7 @@ runGhc' args act = do
logger <- getLogger
(dflags1, _leftover, _warns) <- parseDynamicFlags logger dflags0 flags
let dflags2 = dflags1 {
- backend = interpreterBackend
+ backend = bytecodeBackend
, ghcLink = LinkInMemory
, verbosity = 1
}
=====================================
testsuite/tests/ghc-api/T8639_api.hs
=====================================
@@ -11,7 +11,7 @@ main
= do { [libdir] <- getArgs
; runGhc (Just libdir) $ do
flags <- getSessionDynFlags
- setSessionDynFlags (flags{ backend = interpreterBackend, ghcLink = LinkInMemory})
+ setSessionDynFlags (flags{ backend = bytecodeBackend, ghcLink = LinkInMemory})
target <- guessTarget "T8639_api_a.hs" Nothing Nothing
setTargets [target]
load LoadAllTargets
=====================================
testsuite/tests/ghc-api/apirecomp001/myghc.hs
=====================================
@@ -37,7 +37,7 @@ main = do
prn "target nothing: ok"
dflags <- getSessionDynFlags
- setSessionDynFlags $ dflags { backend = interpreterBackend }
+ setSessionDynFlags $ dflags { backend = bytecodeBackend }
ok <- load LoadAllTargets
when (failed ok) $ error "Couldn't load A.hs in interpreted mode"
prn "target interpreted: ok"
=====================================
testsuite/tests/ghci-wasm/T26431.hs
=====================================
@@ -16,7 +16,7 @@ main = do
let dflags1 =
dflags0
{ ghcMode = CompManager,
- backend = interpreterBackend,
+ backend = bytecodeBackend,
ghcLink = LinkInMemory
}
logger <- getLogger
=====================================
testsuite/tests/ghci/linking/dyn/T3372.hs
=====================================
@@ -44,7 +44,7 @@ newGhcServer = do (libdir:_) <- getArgs
where ghc action libdir = GHC.runGhc (Just libdir) (init >> action)
init = do df <- GHC.getSessionDynFlags
GHC.setSessionDynFlags df{GHC.ghcMode = GHC.CompManager,
- GHC.backend = GHC.interpreterBackend,
+ GHC.backend = GHC.bytecodeBackend,
GHC.ghcLink = GHC.LinkInMemory,
GHC.verbosity = 0}
=====================================
testsuite/tests/ghci/should_run/PackedDataCon/packeddatacon.T
=====================================
@@ -2,9 +2,8 @@ test('PackedDataCon',
[ extra_files(['Obj.hs', 'ByteCode.hs', 'Types.hs', 'Common.hs-incl']),
req_interp,
req_bco,
- extra_ways(['ghci']),
- when(config.have_ext_interp, extra_ways(['ghci', 'ghci-ext'])),
- when(config.have_ext_interp and config.have_profiling, extra_ways(['ghci', 'ghci-ext', 'ghci-ext-prof']))
+ extra_ways(ghci_ways),
+ only_ways(ghci_ways),
],
compile_and_run,
['']
=====================================
testsuite/tests/ghci/should_run/UnboxedTuples/unboxedtuples.T
=====================================
@@ -2,9 +2,8 @@ test('UnboxedTuples',
[ extra_files(['Obj.hs', 'ByteCode.hs', 'Common.hs-incl']),
req_interp,
req_bco,
- extra_ways(['ghci']),
- when(config.have_ext_interp, extra_ways(['ghci', 'ghci-ext'])),
- when(config.have_ext_interp and config.have_profiling, extra_ways(['ghci', 'ghci-ext', 'ghci-ext-prof']))
+ only_ways(ghci_ways),
+ extra_ways(ghci_ways),
],
compile_and_run,
['']
=====================================
testsuite/tests/ghci/should_run/UnliftedDataTypeInterp/unlifteddatatypeinterp.T
=====================================
@@ -2,9 +2,8 @@ test('UnliftedDataTypeInterp',
[ extra_files(['Obj.hs', 'ByteCode.hs', 'Types.hs', 'Common.hs-incl']),
req_interp,
req_bco,
- extra_ways(['ghci']),
- when(config.have_ext_interp, extra_ways(['ghci', 'ghci-ext'])),
- when(config.have_ext_interp and config.have_profiling, extra_ways(['ghci', 'ghci-ext', 'ghci-ext-prof']))
+ only_ways(ghci_ways),
+ extra_ways(ghci_ways),
],
compile_and_run,
['']
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/33dd8e8b4b358e973ca228b1c92351…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/33dd8e8b4b358e973ca228b1c92351…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Update copyright in documentation
by Marge Bot (@marge-bot) 02 Oct '25
by Marge Bot (@marge-bot) 02 Oct '25
02 Oct '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
c9ec4d43 by Simon Hengel at 2025-10-02T18:42:20-04:00
Update copyright in documentation
- - - - -
da9633a9 by Matthew Pickering at 2025-10-02T18:43:04-04:00
loader: Unify loadDecls and loadModuleLinkables functions
These two functions nearly did the same thing. I have refactored them so
that `loadDecls` now calls `loadModuleLinkables`.
Fixes #26459
- - - - -
5db98d80 by Simon Hengel at 2025-10-02T18:43:53-04:00
Fix typo
- - - - -
b624481f by Matthew Pickering at 2025-10-02T19:17:52-04:00
testsuite: Use ghci_ways to set ways in PackedDataCon/UnboxedTuples/UnliftedDataTypeInterp tests
These tests reimplemented the logic from `valid_way` in order to
determine what ways to run. It's easier to use this combination of
`only_ways` and `extra_ways` to only run in GHCi ways and always run in
GHCi ways.
- - - - -
33dd8e8b by Matthew Pickering at 2025-10-02T19:17:53-04:00
Rename interpreterBackend to bytecodeBackend
This is preparation for creating bytecode files.
The "interpreter" is one way in which we can run bytecode objects. It is
more accurate to describe that the backend produces bytecode, rather
than the means by which the code will eventually run.
The "interpreterBackend" binding is left as a deprecated alias.
- - - - -
23 changed files:
- compiler/GHC.hs
- compiler/GHC/Driver/Backend.hs
- compiler/GHC/Driver/Backend/Internal.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Parser/PostProcess.hs
- docs/users_guide/conf.py
- docs/users_guide/extending_ghc.rst
- ghc/Main.hs
- testsuite/driver/testglobals.py
- testsuite/driver/testlib.py
- testsuite/tests/driver/T5313.hs
- testsuite/tests/ghc-api/T10052/T10052.hs
- testsuite/tests/ghc-api/T8639_api.hs
- testsuite/tests/ghc-api/apirecomp001/myghc.hs
- testsuite/tests/ghci-wasm/T26431.hs
- testsuite/tests/ghci/linking/dyn/T3372.hs
- testsuite/tests/ghci/should_run/PackedDataCon/packeddatacon.T
- testsuite/tests/ghci/should_run/UnboxedTuples/unboxedtuples.T
- testsuite/tests/ghci/should_run/UnliftedDataTypeInterp/unlifteddatatypeinterp.T
Changes:
=====================================
compiler/GHC.hs
=====================================
@@ -30,7 +30,7 @@ module GHC (
-- * Flags and settings
DynFlags(..), GeneralFlag(..), Severity(..), Backend, gopt,
- ncgBackend, llvmBackend, viaCBackend, interpreterBackend, noBackend,
+ ncgBackend, llvmBackend, viaCBackend, bytecodeBackend, interpreterBackend, noBackend,
GhcMode(..), GhcLink(..),
parseDynamicFlags, parseTargetFiles,
getSessionDynFlags,
=====================================
compiler/GHC/Driver/Backend.hs
=====================================
@@ -47,6 +47,7 @@ module GHC.Driver.Backend
, llvmBackend
, jsBackend
, viaCBackend
+ , bytecodeBackend
, interpreterBackend
, noBackend
, allBackends
@@ -252,7 +253,7 @@ instance Show Backend where
show = backendDescription
-ncgBackend, llvmBackend, viaCBackend, interpreterBackend, jsBackend, noBackend
+ncgBackend, llvmBackend, viaCBackend, bytecodeBackend, interpreterBackend, jsBackend, noBackend
:: Backend
-- | The native code generator.
@@ -310,7 +311,11 @@ viaCBackend = Named ViaC
-- (foreign primops).
--
-- See "GHC.StgToByteCode"
-interpreterBackend = Named Interpreter
+bytecodeBackend = Named Bytecode
+
+{-# DEPRECATED interpreterBackend "Renamed to bytecodeBackend" #-}
+interpreterBackend = bytecodeBackend
+
-- | A dummy back end that generates no code.
--
@@ -419,7 +424,7 @@ backendDescription (Named NCG) = "native code generator"
backendDescription (Named LLVM) = "LLVM"
backendDescription (Named ViaC) = "compiling via C"
backendDescription (Named JavaScript) = "compiling to JavaScript"
-backendDescription (Named Interpreter) = "byte-code interpreter"
+backendDescription (Named Bytecode) = "byte-code interpreter"
backendDescription (Named NoBackend) = "no code generated"
-- | This flag tells the compiler driver whether the back
@@ -431,7 +436,7 @@ backendWritesFiles (Named NCG) = True
backendWritesFiles (Named LLVM) = True
backendWritesFiles (Named ViaC) = True
backendWritesFiles (Named JavaScript) = True
-backendWritesFiles (Named Interpreter) = False
+backendWritesFiles (Named Bytecode) = False
backendWritesFiles (Named NoBackend) = False
-- | When the back end does write files, this value tells
@@ -442,7 +447,7 @@ backendPipelineOutput (Named NCG) = Persistent
backendPipelineOutput (Named LLVM) = Persistent
backendPipelineOutput (Named ViaC) = Persistent
backendPipelineOutput (Named JavaScript) = Persistent
-backendPipelineOutput (Named Interpreter) = NoOutputFile
+backendPipelineOutput (Named Bytecode) = NoOutputFile
backendPipelineOutput (Named NoBackend) = NoOutputFile
-- | This flag tells the driver whether the back end can
@@ -453,7 +458,7 @@ backendCanReuseLoadedCode (Named NCG) = False
backendCanReuseLoadedCode (Named LLVM) = False
backendCanReuseLoadedCode (Named ViaC) = False
backendCanReuseLoadedCode (Named JavaScript) = False
-backendCanReuseLoadedCode (Named Interpreter) = True
+backendCanReuseLoadedCode (Named Bytecode) = True
backendCanReuseLoadedCode (Named NoBackend) = False
-- | It is is true of every back end except @-fno-code@
@@ -478,7 +483,7 @@ backendGeneratesCode (Named NCG) = True
backendGeneratesCode (Named LLVM) = True
backendGeneratesCode (Named ViaC) = True
backendGeneratesCode (Named JavaScript) = True
-backendGeneratesCode (Named Interpreter) = True
+backendGeneratesCode (Named Bytecode) = True
backendGeneratesCode (Named NoBackend) = False
backendGeneratesCodeForHsBoot :: Backend -> Bool
@@ -486,7 +491,7 @@ backendGeneratesCodeForHsBoot (Named NCG) = True
backendGeneratesCodeForHsBoot (Named LLVM) = True
backendGeneratesCodeForHsBoot (Named ViaC) = True
backendGeneratesCodeForHsBoot (Named JavaScript) = True
-backendGeneratesCodeForHsBoot (Named Interpreter) = False
+backendGeneratesCodeForHsBoot (Named Bytecode) = False
backendGeneratesCodeForHsBoot (Named NoBackend) = False
-- | When set, this flag turns on interface writing for
@@ -498,7 +503,7 @@ backendSupportsInterfaceWriting (Named NCG) = True
backendSupportsInterfaceWriting (Named LLVM) = True
backendSupportsInterfaceWriting (Named ViaC) = True
backendSupportsInterfaceWriting (Named JavaScript) = True
-backendSupportsInterfaceWriting (Named Interpreter) = True
+backendSupportsInterfaceWriting (Named Bytecode) = True
backendSupportsInterfaceWriting (Named NoBackend) = False
-- | When preparing code for this back end, the type
@@ -510,7 +515,7 @@ backendRespectsSpecialise (Named NCG) = True
backendRespectsSpecialise (Named LLVM) = True
backendRespectsSpecialise (Named ViaC) = True
backendRespectsSpecialise (Named JavaScript) = True
-backendRespectsSpecialise (Named Interpreter) = False
+backendRespectsSpecialise (Named Bytecode) = False
backendRespectsSpecialise (Named NoBackend) = False
-- | This back end wants the `mi_top_env` field of a
@@ -522,7 +527,7 @@ backendWantsGlobalBindings (Named LLVM) = False
backendWantsGlobalBindings (Named ViaC) = False
backendWantsGlobalBindings (Named JavaScript) = False
backendWantsGlobalBindings (Named NoBackend) = False
-backendWantsGlobalBindings (Named Interpreter) = True
+backendWantsGlobalBindings (Named Bytecode) = True
-- | The back end targets a technology that implements
-- `switch` natively. (For example, LLVM or C.) Therefore
@@ -534,7 +539,7 @@ backendHasNativeSwitch (Named NCG) = False
backendHasNativeSwitch (Named LLVM) = True
backendHasNativeSwitch (Named ViaC) = True
backendHasNativeSwitch (Named JavaScript) = True
-backendHasNativeSwitch (Named Interpreter) = False
+backendHasNativeSwitch (Named Bytecode) = False
backendHasNativeSwitch (Named NoBackend) = False
-- | As noted in the documentation for
@@ -548,7 +553,7 @@ backendPrimitiveImplementation (Named NCG) = NcgPrimitives
backendPrimitiveImplementation (Named LLVM) = LlvmPrimitives
backendPrimitiveImplementation (Named JavaScript) = JSPrimitives
backendPrimitiveImplementation (Named ViaC) = GenericPrimitives
-backendPrimitiveImplementation (Named Interpreter) = GenericPrimitives
+backendPrimitiveImplementation (Named Bytecode) = GenericPrimitives
backendPrimitiveImplementation (Named NoBackend) = GenericPrimitives
-- | When this value is `IsValid`, the back end is
@@ -560,7 +565,7 @@ backendSimdValidity (Named NCG) = IsValid
backendSimdValidity (Named LLVM) = IsValid
backendSimdValidity (Named ViaC) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
backendSimdValidity (Named JavaScript) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
-backendSimdValidity (Named Interpreter) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
+backendSimdValidity (Named Bytecode) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
backendSimdValidity (Named NoBackend) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
-- | This flag says whether the back end supports large
@@ -571,7 +576,7 @@ backendSupportsEmbeddedBlobs (Named NCG) = True
backendSupportsEmbeddedBlobs (Named LLVM) = False
backendSupportsEmbeddedBlobs (Named ViaC) = False
backendSupportsEmbeddedBlobs (Named JavaScript) = False
-backendSupportsEmbeddedBlobs (Named Interpreter) = False
+backendSupportsEmbeddedBlobs (Named Bytecode) = False
backendSupportsEmbeddedBlobs (Named NoBackend) = False
-- | This flag tells the compiler driver that the back end
@@ -586,7 +591,7 @@ backendNeedsPlatformNcgSupport (Named NCG) = True
backendNeedsPlatformNcgSupport (Named LLVM) = False
backendNeedsPlatformNcgSupport (Named ViaC) = False
backendNeedsPlatformNcgSupport (Named JavaScript) = False
-backendNeedsPlatformNcgSupport (Named Interpreter) = False
+backendNeedsPlatformNcgSupport (Named Bytecode) = False
backendNeedsPlatformNcgSupport (Named NoBackend) = False
-- | This flag is set if the back end can generate code
@@ -598,7 +603,7 @@ backendSupportsUnsplitProcPoints (Named NCG) = True
backendSupportsUnsplitProcPoints (Named LLVM) = False
backendSupportsUnsplitProcPoints (Named ViaC) = False
backendSupportsUnsplitProcPoints (Named JavaScript) = False
-backendSupportsUnsplitProcPoints (Named Interpreter) = False
+backendSupportsUnsplitProcPoints (Named Bytecode) = False
backendSupportsUnsplitProcPoints (Named NoBackend) = False
-- | This flag guides the driver in resolving issues about
@@ -616,7 +621,7 @@ backendSwappableWithViaC (Named NCG) = True
backendSwappableWithViaC (Named LLVM) = True
backendSwappableWithViaC (Named ViaC) = False
backendSwappableWithViaC (Named JavaScript) = False
-backendSwappableWithViaC (Named Interpreter) = False
+backendSwappableWithViaC (Named Bytecode) = False
backendSwappableWithViaC (Named NoBackend) = False
-- | This flag is true if the back end works *only* with
@@ -626,7 +631,7 @@ backendUnregisterisedAbiOnly (Named NCG) = False
backendUnregisterisedAbiOnly (Named LLVM) = False
backendUnregisterisedAbiOnly (Named ViaC) = True
backendUnregisterisedAbiOnly (Named JavaScript) = False
-backendUnregisterisedAbiOnly (Named Interpreter) = False
+backendUnregisterisedAbiOnly (Named Bytecode) = False
backendUnregisterisedAbiOnly (Named NoBackend) = False
-- | This flag is set if the back end generates C code in
@@ -637,7 +642,7 @@ backendGeneratesHc (Named NCG) = False
backendGeneratesHc (Named LLVM) = False
backendGeneratesHc (Named ViaC) = True
backendGeneratesHc (Named JavaScript) = False
-backendGeneratesHc (Named Interpreter) = False
+backendGeneratesHc (Named Bytecode) = False
backendGeneratesHc (Named NoBackend) = False
-- | This flag says whether SPT (static pointer table)
@@ -649,7 +654,7 @@ backendSptIsDynamic (Named NCG) = False
backendSptIsDynamic (Named LLVM) = False
backendSptIsDynamic (Named ViaC) = False
backendSptIsDynamic (Named JavaScript) = False
-backendSptIsDynamic (Named Interpreter) = True
+backendSptIsDynamic (Named Bytecode) = True
backendSptIsDynamic (Named NoBackend) = False
-- | If this flag is unset, then the driver ignores the flag @-fbreak-points@,
@@ -660,7 +665,7 @@ backendSupportsBreakpoints = \case
Named LLVM -> False
Named ViaC -> False
Named JavaScript -> False
- Named Interpreter -> True
+ Named Bytecode -> True
Named NoBackend -> False
-- | If this flag is set, then the driver forces the
@@ -671,7 +676,7 @@ backendForcesOptimization0 (Named NCG) = False
backendForcesOptimization0 (Named LLVM) = False
backendForcesOptimization0 (Named ViaC) = False
backendForcesOptimization0 (Named JavaScript) = False
-backendForcesOptimization0 (Named Interpreter) = True
+backendForcesOptimization0 (Named Bytecode) = True
backendForcesOptimization0 (Named NoBackend) = False
-- | I don't understand exactly how this works. But if
@@ -683,7 +688,7 @@ backendNeedsFullWays (Named NCG) = False
backendNeedsFullWays (Named LLVM) = False
backendNeedsFullWays (Named ViaC) = False
backendNeedsFullWays (Named JavaScript) = False
-backendNeedsFullWays (Named Interpreter) = True
+backendNeedsFullWays (Named Bytecode) = True
backendNeedsFullWays (Named NoBackend) = False
-- | This flag is also special for the interpreter: if a
@@ -695,7 +700,7 @@ backendSpecialModuleSource (Named NCG) = const Nothing
backendSpecialModuleSource (Named LLVM) = const Nothing
backendSpecialModuleSource (Named ViaC) = const Nothing
backendSpecialModuleSource (Named JavaScript) = const Nothing
-backendSpecialModuleSource (Named Interpreter) = \b -> if b then Just "interpreted" else Nothing
+backendSpecialModuleSource (Named Bytecode) = \b -> if b then Just "interpreted" else Nothing
backendSpecialModuleSource (Named NoBackend) = const (Just "nothing")
-- | This flag says whether the back end supports Haskell
@@ -707,7 +712,7 @@ backendSupportsHpc (Named NCG) = True
backendSupportsHpc (Named LLVM) = True
backendSupportsHpc (Named ViaC) = True
backendSupportsHpc (Named JavaScript) = False
-backendSupportsHpc (Named Interpreter) = False
+backendSupportsHpc (Named Bytecode) = False
backendSupportsHpc (Named NoBackend) = True
-- | This flag says whether the back end supports foreign
@@ -718,7 +723,7 @@ backendSupportsCImport (Named NCG) = True
backendSupportsCImport (Named LLVM) = True
backendSupportsCImport (Named ViaC) = True
backendSupportsCImport (Named JavaScript) = True
-backendSupportsCImport (Named Interpreter) = True
+backendSupportsCImport (Named Bytecode) = True
backendSupportsCImport (Named NoBackend) = True
-- | This flag says whether the back end supports foreign
@@ -728,7 +733,7 @@ backendSupportsCExport (Named NCG) = True
backendSupportsCExport (Named LLVM) = True
backendSupportsCExport (Named ViaC) = True
backendSupportsCExport (Named JavaScript) = True
-backendSupportsCExport (Named Interpreter) = False
+backendSupportsCExport (Named Bytecode) = False
backendSupportsCExport (Named NoBackend) = True
-- | When using this back end, it may be necessary or
@@ -749,7 +754,7 @@ backendCDefs (Named NCG) = NoCDefs
backendCDefs (Named LLVM) = LlvmCDefs
backendCDefs (Named ViaC) = NoCDefs
backendCDefs (Named JavaScript) = NoCDefs
-backendCDefs (Named Interpreter) = NoCDefs
+backendCDefs (Named Bytecode) = NoCDefs
backendCDefs (Named NoBackend) = NoCDefs
-- | This (defunctionalized) function generates code and
@@ -768,7 +773,7 @@ backendCodeOutput (Named NCG) = NcgCodeOutput
backendCodeOutput (Named LLVM) = LlvmCodeOutput
backendCodeOutput (Named ViaC) = ViaCCodeOutput
backendCodeOutput (Named JavaScript) = JSCodeOutput
-backendCodeOutput (Named Interpreter) = panic "backendCodeOutput: interpreterBackend"
+backendCodeOutput (Named Bytecode) = panic "backendCodeOutput: bytecodeBackend"
backendCodeOutput (Named NoBackend) = panic "backendCodeOutput: noBackend"
backendUseJSLinker :: Backend -> Bool
@@ -776,7 +781,7 @@ backendUseJSLinker (Named NCG) = False
backendUseJSLinker (Named LLVM) = False
backendUseJSLinker (Named ViaC) = False
backendUseJSLinker (Named JavaScript) = True
-backendUseJSLinker (Named Interpreter) = False
+backendUseJSLinker (Named Bytecode) = False
backendUseJSLinker (Named NoBackend) = False
-- | This (defunctionalized) function tells the compiler
@@ -795,7 +800,7 @@ backendPostHscPipeline (Named NCG) = NcgPostHscPipeline
backendPostHscPipeline (Named LLVM) = LlvmPostHscPipeline
backendPostHscPipeline (Named ViaC) = ViaCPostHscPipeline
backendPostHscPipeline (Named JavaScript) = JSPostHscPipeline
-backendPostHscPipeline (Named Interpreter) = NoPostHscPipeline
+backendPostHscPipeline (Named Bytecode) = NoPostHscPipeline
backendPostHscPipeline (Named NoBackend) = NoPostHscPipeline
-- | Somewhere in the compiler driver, when compiling
@@ -809,7 +814,7 @@ backendNormalSuccessorPhase (Named NCG) = As False
backendNormalSuccessorPhase (Named LLVM) = LlvmOpt
backendNormalSuccessorPhase (Named ViaC) = HCc
backendNormalSuccessorPhase (Named JavaScript) = StopLn
-backendNormalSuccessorPhase (Named Interpreter) = StopLn
+backendNormalSuccessorPhase (Named Bytecode) = StopLn
backendNormalSuccessorPhase (Named NoBackend) = StopLn
-- | Name of the back end, if any. Used to migrate legacy
@@ -820,7 +825,7 @@ backendName (Named NCG) = NCG
backendName (Named LLVM) = LLVM
backendName (Named ViaC) = ViaC
backendName (Named JavaScript) = JavaScript
-backendName (Named Interpreter) = Interpreter
+backendName (Named Bytecode) = Bytecode
backendName (Named NoBackend) = NoBackend
@@ -833,7 +838,7 @@ allBackends = [ ncgBackend
, llvmBackend
, viaCBackend
, jsBackend
- , interpreterBackend
+ , bytecodeBackend
, noBackend
]
=====================================
compiler/GHC/Driver/Backend/Internal.hs
=====================================
@@ -28,6 +28,6 @@ data BackendName
| LLVM -- ^ Names the LLVM backend.
| ViaC -- ^ Names the Via-C backend.
| JavaScript -- ^ Names the JS backend.
- | Interpreter -- ^ Names the ByteCode interpreter.
+ | Bytecode -- ^ Names the ByteCode interpreter.
| NoBackend -- ^ Names the `-fno-code` backend.
deriving (Eq, Show)
=====================================
compiler/GHC/Driver/Downsweep.hs
=====================================
@@ -916,7 +916,7 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = do
else (,) <$> (new_temp_file (hiSuf_ dflags) (dynHiSuf_ dflags))
<*> (new_temp_file (objectSuf_ dflags) (dynObjectSuf_ dflags))
let new_dflags = case enable_spec of
- EnableByteCode -> dflags { backend = interpreterBackend }
+ EnableByteCode -> dflags { backend = bytecodeBackend }
EnableObject -> dflags { backend = defaultBackendOf ms }
EnableByteCodeAndObject -> (gopt_set dflags Opt_ByteCodeAndObjectCode) { backend = defaultBackendOf ms}
let ms' = ms
=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -2777,10 +2777,12 @@ hscCompileCoreExpr' hsc_env srcspan ds_expr = do
{- load it -}
bco_time <- getCurrentTime
- (fv_hvs, mods_needed, units_needed) <- loadDecls interp hsc_env srcspan $
+ (mods_needed, units_needed) <- loadDecls interp hsc_env srcspan $
Linkable bco_time this_mod $ NE.singleton $ BCOs bcos
+ -- Get the foreign reference to the name we should have just loaded.
+ mhvs <- lookupFromLoadedEnv interp (idName binding_id)
{- Get the HValue for the root -}
- return (expectJust $ lookup (idName binding_id) fv_hvs, mods_needed, units_needed)
+ return (expectJust mhvs, mods_needed, units_needed)
=====================================
compiler/GHC/Driver/Pipeline.hs
=====================================
@@ -281,8 +281,8 @@ compileOne' mHscMessage
-- was set), force it to generate byte-code. This is NOT transitive and
-- only applies to direct targets.
| loadAsByteCode
- = ( interpreterBackend
- , gopt_set (lcl_dflags { backend = interpreterBackend }) Opt_ForceRecomp
+ = ( bytecodeBackend
+ , gopt_set (lcl_dflags { backend = bytecodeBackend }) Opt_ForceRecomp
)
| otherwise
=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -1931,7 +1931,7 @@ dynamic_flags_deps = [
d { ghcLink=NoLink }) >> setBackend noBackend))
, make_ord_flag defFlag "fbyte-code"
(noArgM $ \dflags -> do
- setBackend interpreterBackend
+ setBackend bytecodeBackend
pure $ flip gopt_unset Opt_ByteCodeAndObjectCode (gopt_set dflags Opt_ByteCode))
, make_ord_flag defFlag "fobject-code" $ noArgM $ \dflags -> do
setBackend $ platformDefaultBackend (targetPlatform dflags)
=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -28,6 +28,7 @@ module GHC.Linker.Loader
, withExtendedLoadedEnv
, extendLoadedEnv
, deleteFromLoadedEnv
+ , lookupFromLoadedEnv
-- * Internals
, allocateBreakArrays
, rmDupLinkables
@@ -213,6 +214,15 @@ deleteFromLoadedEnv interp to_remove =
return $ modifyClosureEnv pls $ \ce ->
delListFromNameEnv ce to_remove
+-- | Have we already loaded a name into the interpreter?
+lookupFromLoadedEnv :: Interp -> Name -> IO (Maybe ForeignHValue)
+lookupFromLoadedEnv interp name = do
+ mstate <- getLoaderState interp
+ return $ do
+ pls <- mstate
+ res <- lookupNameEnv (closure_env (linker_env pls)) name
+ return (snd res)
+
-- | Load the module containing the given Name and get its associated 'HValue'.
--
-- Throws a 'ProgramError' if loading fails or the name cannot be found.
@@ -258,7 +268,7 @@ loadDependencies interp hsc_env pls span needed_mods = do
-- Link the packages and modules required
pls1 <- loadPackages' interp hsc_env (ldUnits deps) pls
- (pls2, succ) <- loadModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps)
+ (pls2, succ) <- loadExternalModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps)
let this_pkgs_loaded = udfmRestrictKeys all_pkgs_loaded $ getUniqDSet trans_pkgs_needed
all_pkgs_loaded = pkgs_loaded pls2
trans_pkgs_needed = unionManyUniqDSets (this_pkgs_needed : [ loaded_pkg_trans_deps pkg
@@ -684,42 +694,23 @@ get_reachable_nodes hsc_env mods
********************************************************************* -}
-loadDecls :: Interp -> HscEnv -> SrcSpan -> Linkable -> IO ([(Name, ForeignHValue)], [Linkable], PkgsLoaded)
+-- | Load the dependencies of a linkable, and then load the linkable itself.
+loadDecls :: Interp -> HscEnv -> SrcSpan -> Linkable -> IO ([Linkable], PkgsLoaded)
loadDecls interp hsc_env span linkable = do
-- Initialise the linker (if it's not been done already)
initLoaderState interp hsc_env
-- Take lock for the actual work.
modifyLoaderState interp $ \pls0 -> do
- -- Link the foreign objects first; BCOs in linkable are ignored here.
- (pls1, objs_ok) <- loadObjects interp hsc_env pls0 [linkable]
- when (failed objs_ok) $ throwGhcExceptionIO $ ProgramError "loadDecls: failed to load foreign objects"
-
-- Link the packages and modules required
- (pls, ok, links_needed, units_needed) <- loadDependencies interp hsc_env pls1 span needed_mods
+ (pls, ok, links_needed, units_needed) <- loadDependencies interp hsc_env pls0 span needed_mods
if failed ok
- then throwGhcExceptionIO (ProgramError "")
+ then throwGhcExceptionIO (ProgramError "could not load dependencies for decls")
else do
- -- Link the expression itself
- let le = linker_env pls
- let lb = linked_breaks pls
- le2_itbl_env <- linkITbls interp (itbl_env le) (concat $ map bc_itbls cbcs)
- le2_addr_env <- foldlM (\env cbc -> allocateTopStrings interp (bc_strs cbc) env) (addr_env le) cbcs
- le2_breakarray_env <- allocateBreakArrays interp (breakarray_env lb) (catMaybes $ map bc_breaks cbcs)
- le2_ccs_env <- allocateCCS interp (ccs_env lb) (catMaybes $ map bc_breaks cbcs)
- let le2 = le { itbl_env = le2_itbl_env
- , addr_env = le2_addr_env }
- let lb2 = lb { breakarray_env = le2_breakarray_env
- , ccs_env = le2_ccs_env }
-
- -- Link the necessary packages and linkables
- new_bindings <- linkSomeBCOs interp (pkgs_loaded pls) le2 lb2 cbcs
- nms_fhvs <- makeForeignNamedHValueRefs interp new_bindings
- let ce2 = extendClosureEnv (closure_env le2) nms_fhvs
- !pls2 = pls { linker_env = le2 { closure_env = ce2 }
- , linked_breaks = lb2 }
- mapM_ (linkSptEntry interp ce2) (concatMap bc_spt_entries cbcs)
- return (pls2, (nms_fhvs, links_needed, units_needed))
+ (pls2, ok2) <- loadInternalModuleLinkables interp hsc_env pls [linkable]
+ when (failed ok2) $
+ throwGhcExceptionIO (ProgramError "could not load linkable for decls")
+ return (pls2, (links_needed, units_needed))
where
cbcs = linkableBCOs linkable
@@ -761,8 +752,29 @@ loadModule interp hsc_env mod = do
********************************************************************* -}
-loadModuleLinkables :: Interp -> HscEnv -> LoaderState -> [Linkable] -> IO (LoaderState, SuccessFlag)
-loadModuleLinkables interp hsc_env pls linkables
+-- | Which closures from a Linkable to add to the 'ClosureEnv' in the 'LoaderState'
+data KeepModuleLinkableDefinitions = KeepAllDefinitions -- ^ Keep all definitions
+ | KeepExternalDefinitions -- ^ Only keep external definitions
+
+-- | Interpret a 'KeepModuleLinkableDefinitions' specification to a predictate on 'Name'
+keepDefinitions :: KeepModuleLinkableDefinitions -> (Name -> Bool)
+keepDefinitions KeepAllDefinitions = const True
+keepDefinitions KeepExternalDefinitions = isExternalName
+
+-- | Load a linkable from a module, and only add externally visible names to the
+-- environment.
+loadExternalModuleLinkables :: Interp -> HscEnv -> LoaderState -> [Linkable] -> IO (LoaderState, SuccessFlag)
+loadExternalModuleLinkables interp hsc_env pls linkables =
+ loadModuleLinkables interp hsc_env pls KeepExternalDefinitions linkables
+
+-- | Load a linkable from a module, and add all the names from the linkable into the
+-- closure environment.
+loadInternalModuleLinkables :: Interp -> HscEnv -> LoaderState -> [Linkable] -> IO (LoaderState, SuccessFlag)
+loadInternalModuleLinkables interp hsc_env pls linkables =
+ loadModuleLinkables interp hsc_env pls KeepAllDefinitions linkables
+
+loadModuleLinkables :: Interp -> HscEnv -> LoaderState -> KeepModuleLinkableDefinitions -> [Linkable] -> IO (LoaderState, SuccessFlag)
+loadModuleLinkables interp hsc_env pls keep_spec linkables
= mask_ $ do -- don't want to be interrupted by ^C in here
debugTraceMsg (hsc_logger hsc_env) 3 $
@@ -777,7 +789,7 @@ loadModuleLinkables interp hsc_env pls linkables
if failed ok_flag then
return (pls1, Failed)
else do
- pls2 <- dynLinkBCOs interp pls1 bcos
+ pls2 <- dynLinkBCOs interp pls1 keep_spec bcos
return (pls2, Succeeded)
where
(objs, bcos) = partitionLinkables linkables
@@ -920,8 +932,8 @@ rmDupLinkables already ls
********************************************************************* -}
-dynLinkBCOs :: Interp -> LoaderState -> [Linkable] -> IO LoaderState
-dynLinkBCOs interp pls bcos = do
+dynLinkBCOs :: Interp -> LoaderState -> KeepModuleLinkableDefinitions -> [Linkable] -> IO LoaderState
+dynLinkBCOs interp pls keep_spec bcos = do
let (bcos_loaded', new_bcos) = rmDupLinkables (bcos_loaded pls) bcos
pls1 = pls { bcos_loaded = bcos_loaded' }
@@ -945,7 +957,7 @@ dynLinkBCOs interp pls bcos = do
names_and_refs <- linkSomeBCOs interp (pkgs_loaded pls) le2 lb2 cbcs
-- We only want to add the external ones to the ClosureEnv
- let (to_add, to_drop) = partition (isExternalName.fst) names_and_refs
+ let (to_add, to_drop) = partition (keepDefinitions keep_spec . fst) names_and_refs
-- Immediately release any HValueRefs we're not going to add
freeHValueRefs interp (map snd to_drop)
=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -2778,7 +2778,7 @@ the appropriate component of the product, discarding the rest:
checkPatOf3 (_, _, p) = p -- interpret as a pattern
We can easily define ambiguities between arbitrary subsets of interpretations.
-For example, when we know ahead of type that only an expression or a command is
+For example, when we know ahead of time that only an expression or a command is
possible, but not a pattern, we can use a smaller type:
type ExpCmd = (PV (LHsExpr GhcPs), PV (LHsCmd GhcPs))
=====================================
docs/users_guide/conf.py
=====================================
@@ -7,6 +7,7 @@
#
import sys
import os
+from datetime import datetime, timezone
# Support for :base-ref:, etc.
sys.path.insert(0, os.path.abspath('.'))
@@ -44,7 +45,7 @@ rst_prolog = """
# General information about the project.
project = u'Glasgow Haskell Compiler'
-copyright = u'2023, GHC Team'
+copyright = f"{datetime.now(timezone.utc).year}, GHC Team"
# N.B. version comes from ghc_config
release = version # The full version, including alpha/beta/rc tags.
=====================================
docs/users_guide/extending_ghc.rst
=====================================
@@ -1719,7 +1719,7 @@ constructor from version 9.4 with the corresponding value from 9.6:
+-----------------+------------------------+
| ``ViaC`` | ``viaCBackend`` |
+-----------------+------------------------+
-| ``Interpreter`` | ``interpreterBackend`` |
+| ``Interpreter`` | ``bytecodeBackend`` |
+-----------------+------------------------+
| ``NoBackend`` | ``noBackend`` |
+-----------------+------------------------+
=====================================
ghc/Main.hs
=====================================
@@ -169,9 +169,9 @@ main' postLoadMode units dflags0 args flagWarnings = do
let dflt_backend = backend dflags0
(mode, bcknd, link)
= case postLoadMode of
- DoInteractive -> (CompManager, interpreterBackend, LinkInMemory)
- DoEval _ -> (CompManager, interpreterBackend, LinkInMemory)
- DoRun -> (CompManager, interpreterBackend, LinkInMemory)
+ DoInteractive -> (CompManager, bytecodeBackend, LinkInMemory)
+ DoEval _ -> (CompManager, bytecodeBackend, LinkInMemory)
+ DoRun -> (CompManager, bytecodeBackend, LinkInMemory)
DoMake -> (CompManager, dflt_backend, LinkBinary)
DoBackpack -> (CompManager, dflt_backend, LinkBinary)
DoMkDependHS -> (MkDepend, dflt_backend, LinkBinary)
=====================================
testsuite/driver/testglobals.py
=====================================
@@ -136,9 +136,12 @@ class TestConfig:
# Do we have interpreter support?
self.have_interp = False
+ # Do we have external interpreter support?
+ self.have_ext_interp = False
+
# Are we cross-compiling?
self.cross = False
-
+
# Does the RTS linker only support loading shared libraries?
self.interp_force_dyn = False
=====================================
testsuite/driver/testlib.py
=====================================
@@ -549,10 +549,12 @@ only_ghci = only_ways([WayName('ghci'), WayName('ghci-opt')])
# -----
def valid_way( way: WayName ) -> bool:
- if way in {'ghci', 'ghci-opt', 'ghci-ext'}:
+ if way in {'ghci', 'ghci-opt'}:
return config.have_RTS_linker
- if way == 'ghci-ext-prof':
- return config.have_RTS_linker and config.have_profiling
+ if way in {'ghci-ext'}:
+ return config.have_ext_interp
+ if way in {'ghci-ext-prof'}:
+ return config.have_ext_interp and config.have_profiling
return True
def extra_ways( ways: List[WayName] ):
=====================================
testsuite/tests/driver/T5313.hs
=====================================
@@ -7,7 +7,7 @@ main = do
-- begin initialize
df0 <- GHC.getSessionDynFlags
let df1 = df0{GHC.ghcMode = GHC.CompManager,
- GHC.backend = GHC.interpreterBackend,
+ GHC.backend = GHC.bytecodeBackend,
GHC.ghcLink = GHC.LinkInMemory,
GHC.verbosity = 0}
_ <- GHC.setSessionDynFlags df1
=====================================
testsuite/tests/ghc-api/T10052/T10052.hs
=====================================
@@ -24,7 +24,7 @@ runGhc' args act = do
logger <- getLogger
(dflags1, _leftover, _warns) <- parseDynamicFlags logger dflags0 flags
let dflags2 = dflags1 {
- backend = interpreterBackend
+ backend = bytecodeBackend
, ghcLink = LinkInMemory
, verbosity = 1
}
=====================================
testsuite/tests/ghc-api/T8639_api.hs
=====================================
@@ -11,7 +11,7 @@ main
= do { [libdir] <- getArgs
; runGhc (Just libdir) $ do
flags <- getSessionDynFlags
- setSessionDynFlags (flags{ backend = interpreterBackend, ghcLink = LinkInMemory})
+ setSessionDynFlags (flags{ backend = bytecodeBackend, ghcLink = LinkInMemory})
target <- guessTarget "T8639_api_a.hs" Nothing Nothing
setTargets [target]
load LoadAllTargets
=====================================
testsuite/tests/ghc-api/apirecomp001/myghc.hs
=====================================
@@ -37,7 +37,7 @@ main = do
prn "target nothing: ok"
dflags <- getSessionDynFlags
- setSessionDynFlags $ dflags { backend = interpreterBackend }
+ setSessionDynFlags $ dflags { backend = bytecodeBackend }
ok <- load LoadAllTargets
when (failed ok) $ error "Couldn't load A.hs in interpreted mode"
prn "target interpreted: ok"
=====================================
testsuite/tests/ghci-wasm/T26431.hs
=====================================
@@ -16,7 +16,7 @@ main = do
let dflags1 =
dflags0
{ ghcMode = CompManager,
- backend = interpreterBackend,
+ backend = bytecodeBackend,
ghcLink = LinkInMemory
}
logger <- getLogger
=====================================
testsuite/tests/ghci/linking/dyn/T3372.hs
=====================================
@@ -44,7 +44,7 @@ newGhcServer = do (libdir:_) <- getArgs
where ghc action libdir = GHC.runGhc (Just libdir) (init >> action)
init = do df <- GHC.getSessionDynFlags
GHC.setSessionDynFlags df{GHC.ghcMode = GHC.CompManager,
- GHC.backend = GHC.interpreterBackend,
+ GHC.backend = GHC.bytecodeBackend,
GHC.ghcLink = GHC.LinkInMemory,
GHC.verbosity = 0}
=====================================
testsuite/tests/ghci/should_run/PackedDataCon/packeddatacon.T
=====================================
@@ -2,9 +2,8 @@ test('PackedDataCon',
[ extra_files(['Obj.hs', 'ByteCode.hs', 'Types.hs', 'Common.hs-incl']),
req_interp,
req_bco,
- extra_ways(['ghci']),
- when(config.have_ext_interp, extra_ways(['ghci', 'ghci-ext'])),
- when(config.have_ext_interp and config.have_profiling, extra_ways(['ghci', 'ghci-ext', 'ghci-ext-prof']))
+ extra_ways(ghci_ways),
+ only_ways(ghci_ways),
],
compile_and_run,
['']
=====================================
testsuite/tests/ghci/should_run/UnboxedTuples/unboxedtuples.T
=====================================
@@ -2,9 +2,8 @@ test('UnboxedTuples',
[ extra_files(['Obj.hs', 'ByteCode.hs', 'Common.hs-incl']),
req_interp,
req_bco,
- extra_ways(['ghci']),
- when(config.have_ext_interp, extra_ways(['ghci', 'ghci-ext'])),
- when(config.have_ext_interp and config.have_profiling, extra_ways(['ghci', 'ghci-ext', 'ghci-ext-prof']))
+ only_ways(ghci_ways),
+ extra_ways(ghci_ways),
],
compile_and_run,
['']
=====================================
testsuite/tests/ghci/should_run/UnliftedDataTypeInterp/unlifteddatatypeinterp.T
=====================================
@@ -2,9 +2,8 @@ test('UnliftedDataTypeInterp',
[ extra_files(['Obj.hs', 'ByteCode.hs', 'Types.hs', 'Common.hs-incl']),
req_interp,
req_bco,
- extra_ways(['ghci']),
- when(config.have_ext_interp, extra_ways(['ghci', 'ghci-ext'])),
- when(config.have_ext_interp and config.have_profiling, extra_ways(['ghci', 'ghci-ext', 'ghci-ext-prof']))
+ only_ways(ghci_ways),
+ extra_ways(ghci_ways),
],
compile_and_run,
['']
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/406b7b232d47e1b3a84cbcdb69fec5…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/406b7b232d47e1b3a84cbcdb69fec5…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
5db98d80 by Simon Hengel at 2025-10-02T18:43:53-04:00
Fix typo
- - - - -
1 changed file:
- compiler/GHC/Parser/PostProcess.hs
Changes:
=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -2778,7 +2778,7 @@ the appropriate component of the product, discarding the rest:
checkPatOf3 (_, _, p) = p -- interpret as a pattern
We can easily define ambiguities between arbitrary subsets of interpretations.
-For example, when we know ahead of type that only an expression or a command is
+For example, when we know ahead of time that only an expression or a command is
possible, but not a pattern, we can use a smaller type:
type ExpCmd = (PV (LHsExpr GhcPs), PV (LHsCmd GhcPs))
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5db98d80d4a64cb866ab4b74acc16a4…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5db98d80d4a64cb866ab4b74acc16a4…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] loader: Unify loadDecls and loadModuleLinkables functions
by Marge Bot (@marge-bot) 02 Oct '25
by Marge Bot (@marge-bot) 02 Oct '25
02 Oct '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
da9633a9 by Matthew Pickering at 2025-10-02T18:43:04-04:00
loader: Unify loadDecls and loadModuleLinkables functions
These two functions nearly did the same thing. I have refactored them so
that `loadDecls` now calls `loadModuleLinkables`.
Fixes #26459
- - - - -
2 changed files:
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Linker/Loader.hs
Changes:
=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -2777,10 +2777,12 @@ hscCompileCoreExpr' hsc_env srcspan ds_expr = do
{- load it -}
bco_time <- getCurrentTime
- (fv_hvs, mods_needed, units_needed) <- loadDecls interp hsc_env srcspan $
+ (mods_needed, units_needed) <- loadDecls interp hsc_env srcspan $
Linkable bco_time this_mod $ NE.singleton $ BCOs bcos
+ -- Get the foreign reference to the name we should have just loaded.
+ mhvs <- lookupFromLoadedEnv interp (idName binding_id)
{- Get the HValue for the root -}
- return (expectJust $ lookup (idName binding_id) fv_hvs, mods_needed, units_needed)
+ return (expectJust mhvs, mods_needed, units_needed)
=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -28,6 +28,7 @@ module GHC.Linker.Loader
, withExtendedLoadedEnv
, extendLoadedEnv
, deleteFromLoadedEnv
+ , lookupFromLoadedEnv
-- * Internals
, allocateBreakArrays
, rmDupLinkables
@@ -213,6 +214,15 @@ deleteFromLoadedEnv interp to_remove =
return $ modifyClosureEnv pls $ \ce ->
delListFromNameEnv ce to_remove
+-- | Have we already loaded a name into the interpreter?
+lookupFromLoadedEnv :: Interp -> Name -> IO (Maybe ForeignHValue)
+lookupFromLoadedEnv interp name = do
+ mstate <- getLoaderState interp
+ return $ do
+ pls <- mstate
+ res <- lookupNameEnv (closure_env (linker_env pls)) name
+ return (snd res)
+
-- | Load the module containing the given Name and get its associated 'HValue'.
--
-- Throws a 'ProgramError' if loading fails or the name cannot be found.
@@ -258,7 +268,7 @@ loadDependencies interp hsc_env pls span needed_mods = do
-- Link the packages and modules required
pls1 <- loadPackages' interp hsc_env (ldUnits deps) pls
- (pls2, succ) <- loadModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps)
+ (pls2, succ) <- loadExternalModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps)
let this_pkgs_loaded = udfmRestrictKeys all_pkgs_loaded $ getUniqDSet trans_pkgs_needed
all_pkgs_loaded = pkgs_loaded pls2
trans_pkgs_needed = unionManyUniqDSets (this_pkgs_needed : [ loaded_pkg_trans_deps pkg
@@ -684,42 +694,23 @@ get_reachable_nodes hsc_env mods
********************************************************************* -}
-loadDecls :: Interp -> HscEnv -> SrcSpan -> Linkable -> IO ([(Name, ForeignHValue)], [Linkable], PkgsLoaded)
+-- | Load the dependencies of a linkable, and then load the linkable itself.
+loadDecls :: Interp -> HscEnv -> SrcSpan -> Linkable -> IO ([Linkable], PkgsLoaded)
loadDecls interp hsc_env span linkable = do
-- Initialise the linker (if it's not been done already)
initLoaderState interp hsc_env
-- Take lock for the actual work.
modifyLoaderState interp $ \pls0 -> do
- -- Link the foreign objects first; BCOs in linkable are ignored here.
- (pls1, objs_ok) <- loadObjects interp hsc_env pls0 [linkable]
- when (failed objs_ok) $ throwGhcExceptionIO $ ProgramError "loadDecls: failed to load foreign objects"
-
-- Link the packages and modules required
- (pls, ok, links_needed, units_needed) <- loadDependencies interp hsc_env pls1 span needed_mods
+ (pls, ok, links_needed, units_needed) <- loadDependencies interp hsc_env pls0 span needed_mods
if failed ok
- then throwGhcExceptionIO (ProgramError "")
+ then throwGhcExceptionIO (ProgramError "could not load dependencies for decls")
else do
- -- Link the expression itself
- let le = linker_env pls
- let lb = linked_breaks pls
- le2_itbl_env <- linkITbls interp (itbl_env le) (concat $ map bc_itbls cbcs)
- le2_addr_env <- foldlM (\env cbc -> allocateTopStrings interp (bc_strs cbc) env) (addr_env le) cbcs
- le2_breakarray_env <- allocateBreakArrays interp (breakarray_env lb) (catMaybes $ map bc_breaks cbcs)
- le2_ccs_env <- allocateCCS interp (ccs_env lb) (catMaybes $ map bc_breaks cbcs)
- let le2 = le { itbl_env = le2_itbl_env
- , addr_env = le2_addr_env }
- let lb2 = lb { breakarray_env = le2_breakarray_env
- , ccs_env = le2_ccs_env }
-
- -- Link the necessary packages and linkables
- new_bindings <- linkSomeBCOs interp (pkgs_loaded pls) le2 lb2 cbcs
- nms_fhvs <- makeForeignNamedHValueRefs interp new_bindings
- let ce2 = extendClosureEnv (closure_env le2) nms_fhvs
- !pls2 = pls { linker_env = le2 { closure_env = ce2 }
- , linked_breaks = lb2 }
- mapM_ (linkSptEntry interp ce2) (concatMap bc_spt_entries cbcs)
- return (pls2, (nms_fhvs, links_needed, units_needed))
+ (pls2, ok2) <- loadInternalModuleLinkables interp hsc_env pls [linkable]
+ when (failed ok2) $
+ throwGhcExceptionIO (ProgramError "could not load linkable for decls")
+ return (pls2, (links_needed, units_needed))
where
cbcs = linkableBCOs linkable
@@ -761,8 +752,29 @@ loadModule interp hsc_env mod = do
********************************************************************* -}
-loadModuleLinkables :: Interp -> HscEnv -> LoaderState -> [Linkable] -> IO (LoaderState, SuccessFlag)
-loadModuleLinkables interp hsc_env pls linkables
+-- | Which closures from a Linkable to add to the 'ClosureEnv' in the 'LoaderState'
+data KeepModuleLinkableDefinitions = KeepAllDefinitions -- ^ Keep all definitions
+ | KeepExternalDefinitions -- ^ Only keep external definitions
+
+-- | Interpret a 'KeepModuleLinkableDefinitions' specification to a predictate on 'Name'
+keepDefinitions :: KeepModuleLinkableDefinitions -> (Name -> Bool)
+keepDefinitions KeepAllDefinitions = const True
+keepDefinitions KeepExternalDefinitions = isExternalName
+
+-- | Load a linkable from a module, and only add externally visible names to the
+-- environment.
+loadExternalModuleLinkables :: Interp -> HscEnv -> LoaderState -> [Linkable] -> IO (LoaderState, SuccessFlag)
+loadExternalModuleLinkables interp hsc_env pls linkables =
+ loadModuleLinkables interp hsc_env pls KeepExternalDefinitions linkables
+
+-- | Load a linkable from a module, and add all the names from the linkable into the
+-- closure environment.
+loadInternalModuleLinkables :: Interp -> HscEnv -> LoaderState -> [Linkable] -> IO (LoaderState, SuccessFlag)
+loadInternalModuleLinkables interp hsc_env pls linkables =
+ loadModuleLinkables interp hsc_env pls KeepAllDefinitions linkables
+
+loadModuleLinkables :: Interp -> HscEnv -> LoaderState -> KeepModuleLinkableDefinitions -> [Linkable] -> IO (LoaderState, SuccessFlag)
+loadModuleLinkables interp hsc_env pls keep_spec linkables
= mask_ $ do -- don't want to be interrupted by ^C in here
debugTraceMsg (hsc_logger hsc_env) 3 $
@@ -777,7 +789,7 @@ loadModuleLinkables interp hsc_env pls linkables
if failed ok_flag then
return (pls1, Failed)
else do
- pls2 <- dynLinkBCOs interp pls1 bcos
+ pls2 <- dynLinkBCOs interp pls1 keep_spec bcos
return (pls2, Succeeded)
where
(objs, bcos) = partitionLinkables linkables
@@ -920,8 +932,8 @@ rmDupLinkables already ls
********************************************************************* -}
-dynLinkBCOs :: Interp -> LoaderState -> [Linkable] -> IO LoaderState
-dynLinkBCOs interp pls bcos = do
+dynLinkBCOs :: Interp -> LoaderState -> KeepModuleLinkableDefinitions -> [Linkable] -> IO LoaderState
+dynLinkBCOs interp pls keep_spec bcos = do
let (bcos_loaded', new_bcos) = rmDupLinkables (bcos_loaded pls) bcos
pls1 = pls { bcos_loaded = bcos_loaded' }
@@ -945,7 +957,7 @@ dynLinkBCOs interp pls bcos = do
names_and_refs <- linkSomeBCOs interp (pkgs_loaded pls) le2 lb2 cbcs
-- We only want to add the external ones to the ClosureEnv
- let (to_add, to_drop) = partition (isExternalName.fst) names_and_refs
+ let (to_add, to_drop) = partition (keepDefinitions keep_spec . fst) names_and_refs
-- Immediately release any HValueRefs we're not going to add
freeHValueRefs interp (map snd to_drop)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/da9633a9009a08132b974b0407c4057…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/da9633a9009a08132b974b0407c4057…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
02 Oct '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
c9ec4d43 by Simon Hengel at 2025-10-02T18:42:20-04:00
Update copyright in documentation
- - - - -
1 changed file:
- docs/users_guide/conf.py
Changes:
=====================================
docs/users_guide/conf.py
=====================================
@@ -7,6 +7,7 @@
#
import sys
import os
+from datetime import datetime, timezone
# Support for :base-ref:, etc.
sys.path.insert(0, os.path.abspath('.'))
@@ -44,7 +45,7 @@ rst_prolog = """
# General information about the project.
project = u'Glasgow Haskell Compiler'
-copyright = u'2023, GHC Team'
+copyright = f"{datetime.now(timezone.utc).year}, GHC Team"
# N.B. version comes from ghc_config
release = version # The full version, including alpha/beta/rc tags.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c9ec4d434d59624905d950e810cc6c0…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c9ec4d434d59624905d950e810cc6c0…
You're receiving this email because of your account on gitlab.haskell.org.
1
0