[Git][ghc/ghc][wip/fix-packedcons-ways] testsuite: Use ghci_ways to set ways in PackedDataCon/UnboxedTuples/UnliftedDataTypeInterp tests
by Matthew Pickering (@mpickering) 02 Oct '25
by Matthew Pickering (@mpickering) 02 Oct '25
02 Oct '25
Matthew Pickering pushed to branch wip/fix-packedcons-ways at Glasgow Haskell Compiler / GHC
Commits:
7a30b545 by Matthew Pickering at 2025-10-02T15:09:31+01: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/7a30b545a13565831bca5a2fd9c4378…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7a30b545a13565831bca5a2fd9c4378…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/rename-bytecode] Rename interpreterBackend to bytecodeBackend
by Matthew Pickering (@mpickering) 02 Oct '25
by Matthew Pickering (@mpickering) 02 Oct '25
02 Oct '25
Matthew Pickering pushed to branch wip/rename-bytecode at Glasgow Haskell Compiler / GHC
Commits:
120cdc9b by Matthew Pickering at 2025-10-02T15:05:22+01: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/120cdc9b0651bba5396ebf554abb302…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/120cdc9b0651bba5396ebf554abb302…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/gbc-files] Add support for generating bytecode objects
by Matthew Pickering (@mpickering) 02 Oct '25
by Matthew Pickering (@mpickering) 02 Oct '25
02 Oct '25
Matthew Pickering pushed to branch wip/gbc-files at Glasgow Haskell Compiler / GHC
Commits:
e8c5b20d by Matthew Pickering at 2025-10-02T14:11:10+01:00
Add support for generating bytecode objects
This commit adds the `-fwrite-byte-code` option which makes GHC emit a
`.gbc` file which contains a serialised representation of bytecode.
The bytecode can be loaded by the compiler to avoid having to
reinterpret a module when using the bytecode interpreter (for example,
in GHCi).
There are also the new options:
* -gbcdir=<DIR>: Specify the directory to place the gbc files
* -gbcsuf=<suffix>: Specify the suffix for gbc files
The option `-fbyte-code-and-object-code` now implies
`-fwrite-byte-code`.
These performance tests fail due to https://github.com/haskell/directory/issues/204
-------------------------
Metric Increase:
MultiComponentModules
MultiComponentModulesRecomp
MultiLayerModulesRecomp
MultiLayerModulesTH_Make
MultiLayerModulesTH_OneShot
T13701
-------------------------
- - - - -
59 changed files:
- compiler/GHC/ByteCode/Serialize.hs
- compiler/GHC/Driver/Backend.hs
- compiler/GHC/Driver/Backpack.hs
- + compiler/GHC/Driver/ByteCode.hs
- compiler/GHC/Driver/Config/Finder.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Messager.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/HsToCore/Usage.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Types/SptEntry.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Unit/Module/Location.hs
- compiler/GHC/Unit/Module/ModSummary.hs
- compiler/GHC/Unit/Module/WholeCoreBindings.hs
- compiler/GHC/Utils/Binary.hs
- compiler/ghc.cabal.in
- docs/users_guide/phases.rst
- docs/users_guide/separate_compilation.rst
- testsuite/tests/bytecode/T24634/T24634a.stdout
- testsuite/tests/bytecode/T24634/T24634b.stdout
- + testsuite/tests/driver/bytecode-object/A.hs
- + testsuite/tests/driver/bytecode-object/BytecodeForeign.c
- + testsuite/tests/driver/bytecode-object/BytecodeForeign.hs
- + testsuite/tests/driver/bytecode-object/BytecodeMain.hs
- + testsuite/tests/driver/bytecode-object/BytecodeTest.hs
- + testsuite/tests/driver/bytecode-object/Makefile
- + testsuite/tests/driver/bytecode-object/all.T
- + testsuite/tests/driver/bytecode-object/bytecode_object12.stderr
- + testsuite/tests/driver/bytecode-object/bytecode_object13.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object14.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object15.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object16.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object17.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object18.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object19.script
- + testsuite/tests/driver/bytecode-object/bytecode_object19.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object25.script
- + testsuite/tests/driver/bytecode-object/bytecode_object25.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object4.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object5.stdout
- + testsuite/tests/driver/bytecode-object/bytecode_object6.stdout
- testsuite/tests/driver/fat-iface/T22405/T22405.stdout
- testsuite/tests/driver/fat-iface/T22405/T22405b.stdout
- testsuite/tests/driver/fat-iface/fat011.stderr
- testsuite/tests/perf/compiler/Makefile
- + testsuite/tests/perf/compiler/MultiLayerModulesDefsGhciWithBytecodeFiles.script
- testsuite/tests/perf/compiler/all.T
- testsuite/tests/simplStg/should_compile/T22840.stderr
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e8c5b20d92eb210081f5b9fcae3f99f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e8c5b20d92eb210081f5b9fcae3f99f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/rename-bytecode] Rename interpreterBackend to bytecodeBackend
by Matthew Pickering (@mpickering) 02 Oct '25
by Matthew Pickering (@mpickering) 02 Oct '25
02 Oct '25
Matthew Pickering pushed to branch wip/rename-bytecode at Glasgow Haskell Compiler / GHC
Commits:
96f05756 by Matthew Pickering at 2025-10-02T14:06:11+01: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.
- - - - -
12 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
- 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/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: interpreterBackend"
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)
=====================================
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/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/96f057562332b8a17ef6818b7fa28f7…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/96f057562332b8a17ef6818b7fa28f7…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] compiler: only invoke keepCAFsForGHCi if internal-interpreter is enabled
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:
c254c54b by Cheng Shao at 2025-10-02T07:29:33-04:00
compiler: only invoke keepCAFsForGHCi if internal-interpreter is enabled
This patch makes the ghc library only invoke keepCAFsForGHCi if
internal-interpreter is enabled. For cases when it's not (e.g. the
host build of a cross ghc), this avoids unnecessarily retaining all
CAFs in the heap. Also fixes the type signature of c_keepCAFsForGHCi
to match the C ABI.
- - - - -
3 changed files:
- compiler/GHC.hs
- compiler/cbits/keepCAFsForGHCi.c
- compiler/ghc.cabal.in
Changes:
=====================================
compiler/GHC.hs
=====================================
@@ -463,6 +463,9 @@ import System.Exit ( exitWith, ExitCode(..) )
import System.FilePath
import System.IO.Error ( isDoesNotExistError )
+#if defined(HAVE_INTERNAL_INTERPRETER)
+import Foreign.C
+#endif
-- %************************************************************************
-- %* *
@@ -597,12 +600,12 @@ withCleanupSession ghc = ghc `MC.finally` cleanup
initGhcMonad :: GhcMonad m => Maybe FilePath -> m ()
initGhcMonad mb_top_dir = setSession =<< liftIO ( do
-#if !defined(javascript_HOST_ARCH)
+#if defined(HAVE_INTERNAL_INTERPRETER)
-- The call to c_keepCAFsForGHCi must not be optimized away. Even in non-debug builds.
-- So we can't use assertM here.
-- See Note [keepCAFsForGHCi] in keepCAFsForGHCi.c for details about why.
!keep_cafs <- c_keepCAFsForGHCi
- massert keep_cafs
+ massert $ keep_cafs /= 0
#endif
initHscEnv mb_top_dir
)
@@ -2092,7 +2095,7 @@ mkApiErr :: DynFlags -> SDoc -> GhcApiError
mkApiErr dflags msg = GhcApiError (showSDoc dflags msg)
-#if !defined(javascript_HOST_ARCH)
+#if defined(HAVE_INTERNAL_INTERPRETER)
foreign import ccall unsafe "keepCAFsForGHCi"
- c_keepCAFsForGHCi :: IO Bool
+ c_keepCAFsForGHCi :: IO CBool
#endif
=====================================
compiler/cbits/keepCAFsForGHCi.c
=====================================
@@ -21,7 +21,7 @@
// the constructor to be run, allowing the assertion to succeed in the first place
// as keepCAFs will have been set already during initialization of constructors.
-
+#if defined(HAVE_INTERNAL_INTERPRETER)
bool keepCAFsForGHCi(void) __attribute__((constructor));
@@ -32,4 +32,4 @@ bool keepCAFsForGHCi(void)
return was_set;
}
-
+#endif
=====================================
compiler/ghc.cabal.in
=====================================
@@ -156,6 +156,7 @@ Library
if flag(internal-interpreter)
CPP-Options: -DHAVE_INTERNAL_INTERPRETER
+ cc-options: -DHAVE_INTERNAL_INTERPRETER
-- if no dynamic system linker is available, don't try DLLs.
if flag(dynamic-system-linker)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c254c54b3b4354722172c2c91c4ccc0…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c254c54b3b4354722172c2c91c4ccc0…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] rts: Dynamically initialize built-in closures
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:
39eaaaba by Ben Gamari at 2025-10-02T07:28:45-04:00
rts: Dynamically initialize built-in closures
To resolve #26166 we need to eliminate references to undefined symbols
in the runtime system. One such source of these is the runtime's
static references to `I#` and `C#` due the `stg_INTLIKE` and
`stg_CHARLIKE` arrays.
To avoid this we make these dynamic, initializing them during RTS
start-up.
- - - - -
7 changed files:
- + rts/BuiltinClosures.c
- + rts/BuiltinClosures.h
- rts/RtsStartup.c
- rts/StgMiscClosures.cmm
- rts/include/rts/Constants.h
- rts/include/stg/MiscClosures.h
- rts/rts.cabal
Changes:
=====================================
rts/BuiltinClosures.c
=====================================
@@ -0,0 +1,30 @@
+#include "Rts.h"
+#include "Prelude.h"
+#include "BuiltinClosures.h"
+
+/*
+ * Note [CHARLIKE and INTLIKE closures]
+ * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+ * These are static representations of Chars and small Ints, so that
+ * we can remove dynamic Chars and Ints during garbage collection and
+ * replace them with references to the static objects.
+ */
+
+StgIntCharlikeClosure stg_INTLIKE_closure[MAX_INTLIKE - MIN_INTLIKE + 1];
+StgIntCharlikeClosure stg_CHARLIKE_closure[MAX_CHARLIKE - MIN_CHARLIKE + 1];
+
+void initBuiltinClosures(void) {
+ // INTLIKE closures
+ for (int i = MIN_INTLIKE; i <= MAX_INTLIKE; i++) {
+ StgIntCharlikeClosure *c = &stg_INTLIKE_closure[i - MIN_INTLIKE];
+ SET_HDR((StgClosure* ) c, Izh_con_info, CCS_SYSTEM_OR_NULL);
+ c->data = i;
+ }
+
+ // CHARLIKE closures
+ for (int i = MIN_CHARLIKE; i <= MAX_CHARLIKE; i++) {
+ StgIntCharlikeClosure *c = &stg_CHARLIKE_closure[i - MIN_CHARLIKE];
+ SET_HDR((StgClosure* ) c, Czh_con_info, CCS_SYSTEM_OR_NULL);
+ c->data = i;
+ }
+}
=====================================
rts/BuiltinClosures.h
=====================================
@@ -0,0 +1,14 @@
+/*
+ * (c) The GHC Team, 2025-2026
+ *
+ * RTS/ghc-internal interface
+ *
+ */
+
+#pragma once
+
+#include "BeginPrivate.h"
+
+void initBuiltinClosures(void);
+
+#include "EndPrivate.h"
=====================================
rts/RtsStartup.c
=====================================
@@ -14,6 +14,7 @@
#include "linker/MMap.h"
#include "RtsFlags.h"
#include "RtsUtils.h"
+#include "BuiltinClosures.h"
#include "Prelude.h"
#include "Printer.h" /* DEBUG_LoadSymbols */
#include "Schedule.h" /* initScheduler */
@@ -373,6 +374,9 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config)
traceInitEvent(traceOSProcessInfo);
flushTrace();
+ /* initialize INTLIKE and CHARLIKE closures */
+ initBuiltinClosures();
+
/* initialize the storage manager */
initStorage();
=====================================
rts/StgMiscClosures.cmm
=====================================
@@ -13,8 +13,6 @@
#include "Cmm.h"
import pthread_mutex_lock;
-import ghczminternal_GHCziInternalziTypes_Czh_info;
-import ghczminternal_GHCziInternalziTypes_Izh_info;
import AcquireSRWLockExclusive;
import ReleaseSRWLockExclusive;
@@ -23,7 +21,6 @@ import whitehole_lockClosure_spin;
import whitehole_lockClosure_yield;
#endif
-
#if !defined(UnregisterisedCompiler)
import CLOSURE CCS_SYSTEM;
import CLOSURE ENT_DYN_IND_ctr;
@@ -1031,554 +1028,3 @@ INFO_TABLE_CONSTR(stg_ASYNCIO_LIVE0,0,0,0,CONSTR_NOCAF,"ASYNCIO_LIVE0","ASYNCIO_
{ foreign "C" barf("ASYNCIO_LIVE0 object (%p) entered!", R1) never returns; }
CLOSURE(stg_ASYNCIO_LIVE0_closure,stg_ASYNCIO_LIVE0);
-
-/* ----------------------------------------------------------------------------
- Note [CHARLIKE and INTLIKE closures]
- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
- These are static representations of Chars and small Ints, so that
- we can remove dynamic Chars and Ints during garbage collection and
- replace them with references to the static objects.
- ------------------------------------------------------------------------- */
-
-#define Char_hash_con_info ghczminternal_GHCziInternalziTypes_Czh_con_info
-#define Int_hash_con_info ghczminternal_GHCziInternalziTypes_Izh_con_info
-
-#define CHARLIKE_HDR(n) CLOSURE(Char_hash_con_info, n)
-#define INTLIKE_HDR(n) CLOSURE(Int_hash_con_info, n)
-
-section "data" {
- stg_CHARLIKE_closure:
- CHARLIKE_HDR(0)
- CHARLIKE_HDR(1)
- CHARLIKE_HDR(2)
- CHARLIKE_HDR(3)
- CHARLIKE_HDR(4)
- CHARLIKE_HDR(5)
- CHARLIKE_HDR(6)
- CHARLIKE_HDR(7)
- CHARLIKE_HDR(8)
- CHARLIKE_HDR(9)
- CHARLIKE_HDR(10)
- CHARLIKE_HDR(11)
- CHARLIKE_HDR(12)
- CHARLIKE_HDR(13)
- CHARLIKE_HDR(14)
- CHARLIKE_HDR(15)
- CHARLIKE_HDR(16)
- CHARLIKE_HDR(17)
- CHARLIKE_HDR(18)
- CHARLIKE_HDR(19)
- CHARLIKE_HDR(20)
- CHARLIKE_HDR(21)
- CHARLIKE_HDR(22)
- CHARLIKE_HDR(23)
- CHARLIKE_HDR(24)
- CHARLIKE_HDR(25)
- CHARLIKE_HDR(26)
- CHARLIKE_HDR(27)
- CHARLIKE_HDR(28)
- CHARLIKE_HDR(29)
- CHARLIKE_HDR(30)
- CHARLIKE_HDR(31)
- CHARLIKE_HDR(32)
- CHARLIKE_HDR(33)
- CHARLIKE_HDR(34)
- CHARLIKE_HDR(35)
- CHARLIKE_HDR(36)
- CHARLIKE_HDR(37)
- CHARLIKE_HDR(38)
- CHARLIKE_HDR(39)
- CHARLIKE_HDR(40)
- CHARLIKE_HDR(41)
- CHARLIKE_HDR(42)
- CHARLIKE_HDR(43)
- CHARLIKE_HDR(44)
- CHARLIKE_HDR(45)
- CHARLIKE_HDR(46)
- CHARLIKE_HDR(47)
- CHARLIKE_HDR(48)
- CHARLIKE_HDR(49)
- CHARLIKE_HDR(50)
- CHARLIKE_HDR(51)
- CHARLIKE_HDR(52)
- CHARLIKE_HDR(53)
- CHARLIKE_HDR(54)
- CHARLIKE_HDR(55)
- CHARLIKE_HDR(56)
- CHARLIKE_HDR(57)
- CHARLIKE_HDR(58)
- CHARLIKE_HDR(59)
- CHARLIKE_HDR(60)
- CHARLIKE_HDR(61)
- CHARLIKE_HDR(62)
- CHARLIKE_HDR(63)
- CHARLIKE_HDR(64)
- CHARLIKE_HDR(65)
- CHARLIKE_HDR(66)
- CHARLIKE_HDR(67)
- CHARLIKE_HDR(68)
- CHARLIKE_HDR(69)
- CHARLIKE_HDR(70)
- CHARLIKE_HDR(71)
- CHARLIKE_HDR(72)
- CHARLIKE_HDR(73)
- CHARLIKE_HDR(74)
- CHARLIKE_HDR(75)
- CHARLIKE_HDR(76)
- CHARLIKE_HDR(77)
- CHARLIKE_HDR(78)
- CHARLIKE_HDR(79)
- CHARLIKE_HDR(80)
- CHARLIKE_HDR(81)
- CHARLIKE_HDR(82)
- CHARLIKE_HDR(83)
- CHARLIKE_HDR(84)
- CHARLIKE_HDR(85)
- CHARLIKE_HDR(86)
- CHARLIKE_HDR(87)
- CHARLIKE_HDR(88)
- CHARLIKE_HDR(89)
- CHARLIKE_HDR(90)
- CHARLIKE_HDR(91)
- CHARLIKE_HDR(92)
- CHARLIKE_HDR(93)
- CHARLIKE_HDR(94)
- CHARLIKE_HDR(95)
- CHARLIKE_HDR(96)
- CHARLIKE_HDR(97)
- CHARLIKE_HDR(98)
- CHARLIKE_HDR(99)
- CHARLIKE_HDR(100)
- CHARLIKE_HDR(101)
- CHARLIKE_HDR(102)
- CHARLIKE_HDR(103)
- CHARLIKE_HDR(104)
- CHARLIKE_HDR(105)
- CHARLIKE_HDR(106)
- CHARLIKE_HDR(107)
- CHARLIKE_HDR(108)
- CHARLIKE_HDR(109)
- CHARLIKE_HDR(110)
- CHARLIKE_HDR(111)
- CHARLIKE_HDR(112)
- CHARLIKE_HDR(113)
- CHARLIKE_HDR(114)
- CHARLIKE_HDR(115)
- CHARLIKE_HDR(116)
- CHARLIKE_HDR(117)
- CHARLIKE_HDR(118)
- CHARLIKE_HDR(119)
- CHARLIKE_HDR(120)
- CHARLIKE_HDR(121)
- CHARLIKE_HDR(122)
- CHARLIKE_HDR(123)
- CHARLIKE_HDR(124)
- CHARLIKE_HDR(125)
- CHARLIKE_HDR(126)
- CHARLIKE_HDR(127)
- CHARLIKE_HDR(128)
- CHARLIKE_HDR(129)
- CHARLIKE_HDR(130)
- CHARLIKE_HDR(131)
- CHARLIKE_HDR(132)
- CHARLIKE_HDR(133)
- CHARLIKE_HDR(134)
- CHARLIKE_HDR(135)
- CHARLIKE_HDR(136)
- CHARLIKE_HDR(137)
- CHARLIKE_HDR(138)
- CHARLIKE_HDR(139)
- CHARLIKE_HDR(140)
- CHARLIKE_HDR(141)
- CHARLIKE_HDR(142)
- CHARLIKE_HDR(143)
- CHARLIKE_HDR(144)
- CHARLIKE_HDR(145)
- CHARLIKE_HDR(146)
- CHARLIKE_HDR(147)
- CHARLIKE_HDR(148)
- CHARLIKE_HDR(149)
- CHARLIKE_HDR(150)
- CHARLIKE_HDR(151)
- CHARLIKE_HDR(152)
- CHARLIKE_HDR(153)
- CHARLIKE_HDR(154)
- CHARLIKE_HDR(155)
- CHARLIKE_HDR(156)
- CHARLIKE_HDR(157)
- CHARLIKE_HDR(158)
- CHARLIKE_HDR(159)
- CHARLIKE_HDR(160)
- CHARLIKE_HDR(161)
- CHARLIKE_HDR(162)
- CHARLIKE_HDR(163)
- CHARLIKE_HDR(164)
- CHARLIKE_HDR(165)
- CHARLIKE_HDR(166)
- CHARLIKE_HDR(167)
- CHARLIKE_HDR(168)
- CHARLIKE_HDR(169)
- CHARLIKE_HDR(170)
- CHARLIKE_HDR(171)
- CHARLIKE_HDR(172)
- CHARLIKE_HDR(173)
- CHARLIKE_HDR(174)
- CHARLIKE_HDR(175)
- CHARLIKE_HDR(176)
- CHARLIKE_HDR(177)
- CHARLIKE_HDR(178)
- CHARLIKE_HDR(179)
- CHARLIKE_HDR(180)
- CHARLIKE_HDR(181)
- CHARLIKE_HDR(182)
- CHARLIKE_HDR(183)
- CHARLIKE_HDR(184)
- CHARLIKE_HDR(185)
- CHARLIKE_HDR(186)
- CHARLIKE_HDR(187)
- CHARLIKE_HDR(188)
- CHARLIKE_HDR(189)
- CHARLIKE_HDR(190)
- CHARLIKE_HDR(191)
- CHARLIKE_HDR(192)
- CHARLIKE_HDR(193)
- CHARLIKE_HDR(194)
- CHARLIKE_HDR(195)
- CHARLIKE_HDR(196)
- CHARLIKE_HDR(197)
- CHARLIKE_HDR(198)
- CHARLIKE_HDR(199)
- CHARLIKE_HDR(200)
- CHARLIKE_HDR(201)
- CHARLIKE_HDR(202)
- CHARLIKE_HDR(203)
- CHARLIKE_HDR(204)
- CHARLIKE_HDR(205)
- CHARLIKE_HDR(206)
- CHARLIKE_HDR(207)
- CHARLIKE_HDR(208)
- CHARLIKE_HDR(209)
- CHARLIKE_HDR(210)
- CHARLIKE_HDR(211)
- CHARLIKE_HDR(212)
- CHARLIKE_HDR(213)
- CHARLIKE_HDR(214)
- CHARLIKE_HDR(215)
- CHARLIKE_HDR(216)
- CHARLIKE_HDR(217)
- CHARLIKE_HDR(218)
- CHARLIKE_HDR(219)
- CHARLIKE_HDR(220)
- CHARLIKE_HDR(221)
- CHARLIKE_HDR(222)
- CHARLIKE_HDR(223)
- CHARLIKE_HDR(224)
- CHARLIKE_HDR(225)
- CHARLIKE_HDR(226)
- CHARLIKE_HDR(227)
- CHARLIKE_HDR(228)
- CHARLIKE_HDR(229)
- CHARLIKE_HDR(230)
- CHARLIKE_HDR(231)
- CHARLIKE_HDR(232)
- CHARLIKE_HDR(233)
- CHARLIKE_HDR(234)
- CHARLIKE_HDR(235)
- CHARLIKE_HDR(236)
- CHARLIKE_HDR(237)
- CHARLIKE_HDR(238)
- CHARLIKE_HDR(239)
- CHARLIKE_HDR(240)
- CHARLIKE_HDR(241)
- CHARLIKE_HDR(242)
- CHARLIKE_HDR(243)
- CHARLIKE_HDR(244)
- CHARLIKE_HDR(245)
- CHARLIKE_HDR(246)
- CHARLIKE_HDR(247)
- CHARLIKE_HDR(248)
- CHARLIKE_HDR(249)
- CHARLIKE_HDR(250)
- CHARLIKE_HDR(251)
- CHARLIKE_HDR(252)
- CHARLIKE_HDR(253)
- CHARLIKE_HDR(254)
- CHARLIKE_HDR(255)
-}
-
-section "data" {
- stg_INTLIKE_closure:
- INTLIKE_HDR(-16) /* MIN_INTLIKE == -16 */
- INTLIKE_HDR(-15)
- INTLIKE_HDR(-14)
- INTLIKE_HDR(-13)
- INTLIKE_HDR(-12)
- INTLIKE_HDR(-11)
- INTLIKE_HDR(-10)
- INTLIKE_HDR(-9)
- INTLIKE_HDR(-8)
- INTLIKE_HDR(-7)
- INTLIKE_HDR(-6)
- INTLIKE_HDR(-5)
- INTLIKE_HDR(-4)
- INTLIKE_HDR(-3)
- INTLIKE_HDR(-2)
- INTLIKE_HDR(-1)
- INTLIKE_HDR(0)
- INTLIKE_HDR(1)
- INTLIKE_HDR(2)
- INTLIKE_HDR(3)
- INTLIKE_HDR(4)
- INTLIKE_HDR(5)
- INTLIKE_HDR(6)
- INTLIKE_HDR(7)
- INTLIKE_HDR(8)
- INTLIKE_HDR(9)
- INTLIKE_HDR(10)
- INTLIKE_HDR(11)
- INTLIKE_HDR(12)
- INTLIKE_HDR(13)
- INTLIKE_HDR(14)
- INTLIKE_HDR(15)
- INTLIKE_HDR(16)
- INTLIKE_HDR(17)
- INTLIKE_HDR(18)
- INTLIKE_HDR(19)
- INTLIKE_HDR(20)
- INTLIKE_HDR(21)
- INTLIKE_HDR(22)
- INTLIKE_HDR(23)
- INTLIKE_HDR(24)
- INTLIKE_HDR(25)
- INTLIKE_HDR(26)
- INTLIKE_HDR(27)
- INTLIKE_HDR(28)
- INTLIKE_HDR(29)
- INTLIKE_HDR(30)
- INTLIKE_HDR(31)
- INTLIKE_HDR(32)
- INTLIKE_HDR(33)
- INTLIKE_HDR(34)
- INTLIKE_HDR(35)
- INTLIKE_HDR(36)
- INTLIKE_HDR(37)
- INTLIKE_HDR(38)
- INTLIKE_HDR(39)
- INTLIKE_HDR(40)
- INTLIKE_HDR(41)
- INTLIKE_HDR(42)
- INTLIKE_HDR(43)
- INTLIKE_HDR(44)
- INTLIKE_HDR(45)
- INTLIKE_HDR(46)
- INTLIKE_HDR(47)
- INTLIKE_HDR(48)
- INTLIKE_HDR(49)
- INTLIKE_HDR(50)
- INTLIKE_HDR(51)
- INTLIKE_HDR(52)
- INTLIKE_HDR(53)
- INTLIKE_HDR(54)
- INTLIKE_HDR(55)
- INTLIKE_HDR(56)
- INTLIKE_HDR(57)
- INTLIKE_HDR(58)
- INTLIKE_HDR(59)
- INTLIKE_HDR(60)
- INTLIKE_HDR(61)
- INTLIKE_HDR(62)
- INTLIKE_HDR(63)
- INTLIKE_HDR(64)
- INTLIKE_HDR(65)
- INTLIKE_HDR(66)
- INTLIKE_HDR(67)
- INTLIKE_HDR(68)
- INTLIKE_HDR(69)
- INTLIKE_HDR(70)
- INTLIKE_HDR(71)
- INTLIKE_HDR(72)
- INTLIKE_HDR(73)
- INTLIKE_HDR(74)
- INTLIKE_HDR(75)
- INTLIKE_HDR(76)
- INTLIKE_HDR(77)
- INTLIKE_HDR(78)
- INTLIKE_HDR(79)
- INTLIKE_HDR(80)
- INTLIKE_HDR(81)
- INTLIKE_HDR(82)
- INTLIKE_HDR(83)
- INTLIKE_HDR(84)
- INTLIKE_HDR(85)
- INTLIKE_HDR(86)
- INTLIKE_HDR(87)
- INTLIKE_HDR(88)
- INTLIKE_HDR(89)
- INTLIKE_HDR(90)
- INTLIKE_HDR(91)
- INTLIKE_HDR(92)
- INTLIKE_HDR(93)
- INTLIKE_HDR(94)
- INTLIKE_HDR(95)
- INTLIKE_HDR(96)
- INTLIKE_HDR(97)
- INTLIKE_HDR(98)
- INTLIKE_HDR(99)
- INTLIKE_HDR(100)
- INTLIKE_HDR(101)
- INTLIKE_HDR(102)
- INTLIKE_HDR(103)
- INTLIKE_HDR(104)
- INTLIKE_HDR(105)
- INTLIKE_HDR(106)
- INTLIKE_HDR(107)
- INTLIKE_HDR(108)
- INTLIKE_HDR(109)
- INTLIKE_HDR(110)
- INTLIKE_HDR(111)
- INTLIKE_HDR(112)
- INTLIKE_HDR(113)
- INTLIKE_HDR(114)
- INTLIKE_HDR(115)
- INTLIKE_HDR(116)
- INTLIKE_HDR(117)
- INTLIKE_HDR(118)
- INTLIKE_HDR(119)
- INTLIKE_HDR(120)
- INTLIKE_HDR(121)
- INTLIKE_HDR(122)
- INTLIKE_HDR(123)
- INTLIKE_HDR(124)
- INTLIKE_HDR(125)
- INTLIKE_HDR(126)
- INTLIKE_HDR(127)
- INTLIKE_HDR(128)
- INTLIKE_HDR(129)
- INTLIKE_HDR(130)
- INTLIKE_HDR(131)
- INTLIKE_HDR(132)
- INTLIKE_HDR(133)
- INTLIKE_HDR(134)
- INTLIKE_HDR(135)
- INTLIKE_HDR(136)
- INTLIKE_HDR(137)
- INTLIKE_HDR(138)
- INTLIKE_HDR(139)
- INTLIKE_HDR(140)
- INTLIKE_HDR(141)
- INTLIKE_HDR(142)
- INTLIKE_HDR(143)
- INTLIKE_HDR(144)
- INTLIKE_HDR(145)
- INTLIKE_HDR(146)
- INTLIKE_HDR(147)
- INTLIKE_HDR(148)
- INTLIKE_HDR(149)
- INTLIKE_HDR(150)
- INTLIKE_HDR(151)
- INTLIKE_HDR(152)
- INTLIKE_HDR(153)
- INTLIKE_HDR(154)
- INTLIKE_HDR(155)
- INTLIKE_HDR(156)
- INTLIKE_HDR(157)
- INTLIKE_HDR(158)
- INTLIKE_HDR(159)
- INTLIKE_HDR(160)
- INTLIKE_HDR(161)
- INTLIKE_HDR(162)
- INTLIKE_HDR(163)
- INTLIKE_HDR(164)
- INTLIKE_HDR(165)
- INTLIKE_HDR(166)
- INTLIKE_HDR(167)
- INTLIKE_HDR(168)
- INTLIKE_HDR(169)
- INTLIKE_HDR(170)
- INTLIKE_HDR(171)
- INTLIKE_HDR(172)
- INTLIKE_HDR(173)
- INTLIKE_HDR(174)
- INTLIKE_HDR(175)
- INTLIKE_HDR(176)
- INTLIKE_HDR(177)
- INTLIKE_HDR(178)
- INTLIKE_HDR(179)
- INTLIKE_HDR(180)
- INTLIKE_HDR(181)
- INTLIKE_HDR(182)
- INTLIKE_HDR(183)
- INTLIKE_HDR(184)
- INTLIKE_HDR(185)
- INTLIKE_HDR(186)
- INTLIKE_HDR(187)
- INTLIKE_HDR(188)
- INTLIKE_HDR(189)
- INTLIKE_HDR(190)
- INTLIKE_HDR(191)
- INTLIKE_HDR(192)
- INTLIKE_HDR(193)
- INTLIKE_HDR(194)
- INTLIKE_HDR(195)
- INTLIKE_HDR(196)
- INTLIKE_HDR(197)
- INTLIKE_HDR(198)
- INTLIKE_HDR(199)
- INTLIKE_HDR(200)
- INTLIKE_HDR(201)
- INTLIKE_HDR(202)
- INTLIKE_HDR(203)
- INTLIKE_HDR(204)
- INTLIKE_HDR(205)
- INTLIKE_HDR(206)
- INTLIKE_HDR(207)
- INTLIKE_HDR(208)
- INTLIKE_HDR(209)
- INTLIKE_HDR(210)
- INTLIKE_HDR(211)
- INTLIKE_HDR(212)
- INTLIKE_HDR(213)
- INTLIKE_HDR(214)
- INTLIKE_HDR(215)
- INTLIKE_HDR(216)
- INTLIKE_HDR(217)
- INTLIKE_HDR(218)
- INTLIKE_HDR(219)
- INTLIKE_HDR(220)
- INTLIKE_HDR(221)
- INTLIKE_HDR(222)
- INTLIKE_HDR(223)
- INTLIKE_HDR(224)
- INTLIKE_HDR(225)
- INTLIKE_HDR(226)
- INTLIKE_HDR(227)
- INTLIKE_HDR(228)
- INTLIKE_HDR(229)
- INTLIKE_HDR(230)
- INTLIKE_HDR(231)
- INTLIKE_HDR(232)
- INTLIKE_HDR(233)
- INTLIKE_HDR(234)
- INTLIKE_HDR(235)
- INTLIKE_HDR(236)
- INTLIKE_HDR(237)
- INTLIKE_HDR(238)
- INTLIKE_HDR(239)
- INTLIKE_HDR(240)
- INTLIKE_HDR(241)
- INTLIKE_HDR(242)
- INTLIKE_HDR(243)
- INTLIKE_HDR(244)
- INTLIKE_HDR(245)
- INTLIKE_HDR(246)
- INTLIKE_HDR(247)
- INTLIKE_HDR(248)
- INTLIKE_HDR(249)
- INTLIKE_HDR(250)
- INTLIKE_HDR(251)
- INTLIKE_HDR(252)
- INTLIKE_HDR(253)
- INTLIKE_HDR(254)
- INTLIKE_HDR(255) /* MAX_INTLIKE == 255
- See #16961 for why 255 */
-}
=====================================
rts/include/rts/Constants.h
=====================================
@@ -57,11 +57,12 @@
#define MAX_SPEC_CONSTR_SIZE 2
/* Range of built-in table of static small int-like and char-like closures.
+ * Range is inclusive of both minimum and maximum.
*
* NB. This corresponds with the number of actual INTLIKE/CHARLIKE
* closures defined in rts/StgMiscClosures.cmm.
*/
-#define MAX_INTLIKE 255
+#define MAX_INTLIKE 255 /* See #16961 for why 255 */
#define MIN_INTLIKE (-16)
#define MAX_CHARLIKE 255
=====================================
rts/include/stg/MiscClosures.h
=====================================
@@ -277,8 +277,8 @@ RTS_ENTRY(stg_NO_FINALIZER);
extern StgWordArray stg_CHARLIKE_closure;
extern StgWordArray stg_INTLIKE_closure;
#else
-extern StgIntCharlikeClosure stg_CHARLIKE_closure[];
-extern StgIntCharlikeClosure stg_INTLIKE_closure[];
+extern StgIntCharlikeClosure stg_CHARLIKE_closure[MAX_CHARLIKE - MIN_CHARLIKE + 1];
+extern StgIntCharlikeClosure stg_INTLIKE_closure[MAX_INTLIKE - MIN_INTLIKE + 1];
#endif
/* StgStartup */
=====================================
rts/rts.cabal
=====================================
@@ -403,6 +403,7 @@ library
adjustor/AdjustorPool.c
ExecPage.c
Arena.c
+ BuiltinClosures.c
Capability.c
CheckUnload.c
CheckVectorSupport.c
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/39eaaaba5356e3fc9218d8e27375d6d…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/39eaaaba5356e3fc9218d8e27375d6d…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] testsuite: remove unused expected output files
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:
6992ac09 by Cheng Shao at 2025-10-02T07:27:55-04:00
testsuite: remove unused expected output files
This patch removes unused expected output files in the testsuites on
platforms that we no longer support.
- - - - -
6 changed files:
- − testsuite/tests/process/process010.stdout-i386-unknown-solaris2
- − testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32
- − testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-32-mingw32
- − testsuite/tests/rts/outofmem.stderr-i386-apple-darwin
- − testsuite/tests/rts/outofmem.stderr-i386-unknown-mingw32
- − testsuite/tests/rts/outofmem.stderr-powerpc-apple-darwin
Changes:
=====================================
testsuite/tests/process/process010.stdout-i386-unknown-solaris2 deleted
=====================================
@@ -1,4 +0,0 @@
-ExitSuccess
-ExitFailure 255
-Exc: /non/existent: rawSystem: runInteractiveProcess: exec: does not exist (No such file or directory)
-Done
=====================================
testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32 deleted
=====================================
@@ -1,25 +0,0 @@
-GHC runtime linker: fatal error: I found a duplicate definition for symbol
- _a
-whilst processing object file
- E:\ghc-dev\msys64\home\Tamar\ghc\testsuite\tests\rts\T11223\T11223_link_order_a_b_2_fail.run\libfoo_link_lib_3.a
-The symbol was previously defined in
- E:\ghc-dev\msys64\home\Tamar\ghc\testsuite\tests\rts\T11223\T11223_link_order_a_b_2_fail.run\libbar_link_lib_3.a(#3:bar_link_lib_3.o)
-This could be caused by:
- * Loading two different object files which export the same symbol
- * Specifying the same object file twice on the GHCi command line
- * An incorrect `package.conf' entry, causing some object to be
- loaded twice.
-ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above. You might consider using --optimistic-linking
-
-
-GHC.ByteCode.Linker: can't find label
-During interactive linking, GHCi couldn't find the following symbol:
- c
-This may be due to you not asking GHCi to load extra object files,
-archives or DLLs needed by your current session. Restart GHCi, specifying
-the missing library using the -L/path/to/object/dir and -lmissinglibname
-flags, or simply by naming the relevant files on the GHCi command line.
-Alternatively, this link failure might indicate a bug in GHCi.
-If you suspect the latter, please report this as a GHC bug:
- https://www.haskell.org/ghc/reportabug
-
=====================================
testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-32-mingw32 deleted
=====================================
@@ -1,25 +0,0 @@
-GHC runtime linker: fatal error: I found a duplicate definition for symbol
- _a
-whilst processing object file
- E:\ghc-dev\msys64\home\Tamar\ghc\testsuite\tests\rts\T11223\T11223_simple_duplicate_lib.run\libfoo_dup_lib.a
-The symbol was previously defined in
- E:\ghc-dev\msys64\home\Tamar\ghc\testsuite\tests\rts\T11223\T11223_simple_duplicate_lib.run\bar_dup_lib.o
-This could be caused by:
- * Loading two different object files which export the same symbol
- * Specifying the same object file twice on the GHCi command line
- * An incorrect `package.conf' entry, causing some object to be
- loaded twice.
-ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above. You might consider using --optimistic-linking
-
-
-GHC.ByteCode.Linker: can't find label
-During interactive linking, GHCi couldn't find the following symbol:
- c
-This may be due to you not asking GHCi to load extra object files,
-archives or DLLs needed by your current session. Restart GHCi, specifying
-the missing library using the -L/path/to/object/dir and -lmissinglibname
-flags, or simply by naming the relevant files on the GHCi command line.
-Alternatively, this link failure might indicate a bug in GHCi.
-If you suspect the latter, please report this as a GHC bug:
- https://www.haskell.org/ghc/reportabug
-
=====================================
testsuite/tests/rts/outofmem.stderr-i386-apple-darwin deleted
=====================================
@@ -1 +0,0 @@
-outofmem: memory allocation failed (requested 1074790400 bytes)
=====================================
testsuite/tests/rts/outofmem.stderr-i386-unknown-mingw32 deleted
=====================================
@@ -1 +0,0 @@
-outofmem.exe: Out of memory
=====================================
testsuite/tests/rts/outofmem.stderr-powerpc-apple-darwin deleted
=====================================
@@ -1 +0,0 @@
-outofmem: memory allocation failed (requested 1074790400 bytes)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6992ac097b9da989f125f896afe21b7…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6992ac097b9da989f125f896afe21b7…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/26435] compiler: Warn when -finfo-table-map is used with -fllvm
by Zubin (@wz1000) 02 Oct '25
by Zubin (@wz1000) 02 Oct '25
02 Oct '25
Zubin pushed to branch wip/26435 at Glasgow Haskell Compiler / GHC
Commits:
0bf564ee by Zubin Duggal at 2025-10-02T14:07:00+05:30
compiler: Warn when -finfo-table-map is used with -fllvm
These are currently not supported together.
Fixes #26435
- - - - -
6 changed files:
- compiler/GHC/Driver/Session.hs
- docs/users_guide/debug-info.rst
- + testsuite/tests/driver/T26435.ghc.stderr
- + testsuite/tests/driver/T26435.hs
- + testsuite/tests/driver/T26435.stdout
- testsuite/tests/driver/all.T
Changes:
=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -3784,6 +3784,11 @@ makeDynFlagsConsistent dflags
hostFullWays
in dflags_c
+ | gopt Opt_InfoTableMap dflags
+ , LlvmCodeOutput <- backendCodeOutput (backend dflags)
+ = loop (gopt_unset dflags Opt_InfoTableMap)
+ "-finfo-table-map is incompatible with -fllvm and is disabled (See #26435)"
+
| otherwise = (dflags, mempty, mempty)
where loc = mkGeneralSrcSpan (fsLit "when making flags consistent")
loop updated_dflags warning
=====================================
docs/users_guide/debug-info.rst
=====================================
@@ -370,6 +370,11 @@ to a source location. This lookup table is generated by using the ``-finfo-table
also want more precise information about constructor info tables then you
should also use :ghc-flag:`-fdistinct-constructor-tables`.
+ .. note::
+ This flag is incompatible with :ghc-flag:`-fllvm`. If both flags are
+ enabled, GHC will emit a warning and :ghc-flag:`-finfo-table-map` will
+ have no effect.
+
The :ghc-flag:`-finfo-table-map` flag will increase the binary size by quite
a lot, depending on how big your project is. For compiling a project the
size of GHC the overhead was about 200 megabytes.
=====================================
testsuite/tests/driver/T26435.ghc.stderr
=====================================
@@ -0,0 +1,5 @@
+when making flags consistent: warning: [GHC-74335] [-Winconsistent-flags (in -Wdefault)]
+ -finfo-table-map is incompatible with -fllvm and is disabled (See #26435)
+
+[1 of 2] Compiling Main ( T26435.hs, T26435.o )
+[2 of 2] Linking T26435
=====================================
testsuite/tests/driver/T26435.hs
=====================================
@@ -0,0 +1,5 @@
+module Main where
+import GHC.InfoProv
+
+main :: IO ()
+main = print =<< whereFrom main
=====================================
testsuite/tests/driver/T26435.stdout
=====================================
@@ -0,0 +1 @@
+Nothing
=====================================
testsuite/tests/driver/all.T
=====================================
@@ -331,3 +331,4 @@ test('T24839', [unless(arch('x86_64') or arch('aarch64'), skip), extra_files(["t
test('t25150', [extra_files(["t25150"])], multimod_compile, ['Main.hs', '-v0 -working-dir t25150/dir a.c'])
test('T25382', normal, makefile_test, [])
test('T26018', req_c, makefile_test, [])
+test('T26435', normal, warn_and_run, ['-finfo-table-map -fllvm'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0bf564eed9691767d097169f8740b82…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0bf564eed9691767d097169f8740b82…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: cleanup: Drop obsolete comment about HsConDetails
by Marge Bot (@marge-bot) 01 Oct '25
by Marge Bot (@marge-bot) 01 Oct '25
01 Oct '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
554487a7 by Rodrigo Mesquita at 2025-10-01T23:04:43-04:00
cleanup: Drop obsolete comment about HsConDetails
HsConDetails used to have an argument representing the type of the
tyargs in a list:
data HsConDetails tyarg arg rec
= PrefixCon [tyarg] [arg]
This datatype was shared across 3 synonyms: HsConPatDetails,
HsConDeclH98Details, HsPatSynDetails. In the latter two cases, `tyarg`
was instanced to `Void` meaning the list was always empty for these
cases.
In 7b84c58867edca57a45945a20a9391724db6d9e4, this was refactored such
that HsConDetails no longer needs a type of tyargs by construction. The
first case now represents the type arguments in the args type itself,
with something like:
ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2]
So the deleted comment really is just obsolete.
Fixes #26461
- - - - -
eccf0e38 by Cheng Shao at 2025-10-01T23:37:01-04:00
testsuite: remove unused expected output files
This patch removes unused expected output files in the testsuites on
platforms that we no longer support.
- - - - -
7445c498 by Ben Gamari at 2025-10-01T23:37:02-04:00
rts: Dynamically initialize built-in closures
To resolve #26166 we need to eliminate references to undefined symbols
in the runtime system. One such source of these is the runtime's
static references to `I#` and `C#` due the `stg_INTLIKE` and
`stg_CHARLIKE` arrays.
To avoid this we make these dynamic, initializing them during RTS
start-up.
- - - - -
911b0177 by Cheng Shao at 2025-10-01T23:37:03-04:00
compiler: only invoke keepCAFsForGHCi if internal-interpreter is enabled
This patch makes the ghc library only invoke keepCAFsForGHCi if
internal-interpreter is enabled. For cases when it's not (e.g. the
host build of a cross ghc), this avoids unnecessarily retaining all
CAFs in the heap. Also fixes the type signature of c_keepCAFsForGHCi
to match the C ABI.
- - - - -
17 changed files:
- compiler/GHC.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/cbits/keepCAFsForGHCi.c
- compiler/ghc.cabal.in
- + rts/BuiltinClosures.c
- + rts/BuiltinClosures.h
- rts/RtsStartup.c
- rts/StgMiscClosures.cmm
- rts/include/rts/Constants.h
- rts/include/stg/MiscClosures.h
- rts/rts.cabal
- − testsuite/tests/process/process010.stdout-i386-unknown-solaris2
- − testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32
- − testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-32-mingw32
- − testsuite/tests/rts/outofmem.stderr-i386-apple-darwin
- − testsuite/tests/rts/outofmem.stderr-i386-unknown-mingw32
- − testsuite/tests/rts/outofmem.stderr-powerpc-apple-darwin
Changes:
=====================================
compiler/GHC.hs
=====================================
@@ -463,6 +463,9 @@ import System.Exit ( exitWith, ExitCode(..) )
import System.FilePath
import System.IO.Error ( isDoesNotExistError )
+#if defined(HAVE_INTERNAL_INTERPRETER)
+import Foreign.C
+#endif
-- %************************************************************************
-- %* *
@@ -597,12 +600,12 @@ withCleanupSession ghc = ghc `MC.finally` cleanup
initGhcMonad :: GhcMonad m => Maybe FilePath -> m ()
initGhcMonad mb_top_dir = setSession =<< liftIO ( do
-#if !defined(javascript_HOST_ARCH)
+#if defined(HAVE_INTERNAL_INTERPRETER)
-- The call to c_keepCAFsForGHCi must not be optimized away. Even in non-debug builds.
-- So we can't use assertM here.
-- See Note [keepCAFsForGHCi] in keepCAFsForGHCi.c for details about why.
!keep_cafs <- c_keepCAFsForGHCi
- massert keep_cafs
+ massert $ keep_cafs /= 0
#endif
initHscEnv mb_top_dir
)
@@ -2092,7 +2095,7 @@ mkApiErr :: DynFlags -> SDoc -> GhcApiError
mkApiErr dflags msg = GhcApiError (showSDoc dflags msg)
-#if !defined(javascript_HOST_ARCH)
+#if defined(HAVE_INTERNAL_INTERPRETER)
foreign import ccall unsafe "keepCAFsForGHCi"
- c_keepCAFsForGHCi :: IO Bool
+ c_keepCAFsForGHCi :: IO CBool
#endif
=====================================
compiler/Language/Haskell/Syntax/Decls.hs
=====================================
@@ -1120,8 +1120,6 @@ or contexts in two parts:
-- | The arguments in a Haskell98-style data constructor.
type HsConDeclH98Details pass
= HsConDetails (HsConDeclField pass) (XRec pass [LHsConDeclRecField pass])
--- The Void argument to HsConDetails here is a reflection of the fact that
--- type applications are not allowed in data constructor declarations.
-- | The arguments in a GADT constructor. Unlike Haskell98-style constructors,
-- GADT constructors cannot be declared with infix syntax. As a result, we do
=====================================
compiler/cbits/keepCAFsForGHCi.c
=====================================
@@ -21,7 +21,7 @@
// the constructor to be run, allowing the assertion to succeed in the first place
// as keepCAFs will have been set already during initialization of constructors.
-
+#if defined(HAVE_INTERNAL_INTERPRETER)
bool keepCAFsForGHCi(void) __attribute__((constructor));
@@ -32,4 +32,4 @@ bool keepCAFsForGHCi(void)
return was_set;
}
-
+#endif
=====================================
compiler/ghc.cabal.in
=====================================
@@ -156,6 +156,7 @@ Library
if flag(internal-interpreter)
CPP-Options: -DHAVE_INTERNAL_INTERPRETER
+ cc-options: -DHAVE_INTERNAL_INTERPRETER
-- if no dynamic system linker is available, don't try DLLs.
if flag(dynamic-system-linker)
=====================================
rts/BuiltinClosures.c
=====================================
@@ -0,0 +1,30 @@
+#include "Rts.h"
+#include "Prelude.h"
+#include "BuiltinClosures.h"
+
+/*
+ * Note [CHARLIKE and INTLIKE closures]
+ * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+ * These are static representations of Chars and small Ints, so that
+ * we can remove dynamic Chars and Ints during garbage collection and
+ * replace them with references to the static objects.
+ */
+
+StgIntCharlikeClosure stg_INTLIKE_closure[MAX_INTLIKE - MIN_INTLIKE + 1];
+StgIntCharlikeClosure stg_CHARLIKE_closure[MAX_CHARLIKE - MIN_CHARLIKE + 1];
+
+void initBuiltinClosures(void) {
+ // INTLIKE closures
+ for (int i = MIN_INTLIKE; i <= MAX_INTLIKE; i++) {
+ StgIntCharlikeClosure *c = &stg_INTLIKE_closure[i - MIN_INTLIKE];
+ SET_HDR((StgClosure* ) c, Izh_con_info, CCS_SYSTEM_OR_NULL);
+ c->data = i;
+ }
+
+ // CHARLIKE closures
+ for (int i = MIN_CHARLIKE; i <= MAX_CHARLIKE; i++) {
+ StgIntCharlikeClosure *c = &stg_CHARLIKE_closure[i - MIN_CHARLIKE];
+ SET_HDR((StgClosure* ) c, Czh_con_info, CCS_SYSTEM_OR_NULL);
+ c->data = i;
+ }
+}
=====================================
rts/BuiltinClosures.h
=====================================
@@ -0,0 +1,14 @@
+/*
+ * (c) The GHC Team, 2025-2026
+ *
+ * RTS/ghc-internal interface
+ *
+ */
+
+#pragma once
+
+#include "BeginPrivate.h"
+
+void initBuiltinClosures(void);
+
+#include "EndPrivate.h"
=====================================
rts/RtsStartup.c
=====================================
@@ -14,6 +14,7 @@
#include "linker/MMap.h"
#include "RtsFlags.h"
#include "RtsUtils.h"
+#include "BuiltinClosures.h"
#include "Prelude.h"
#include "Printer.h" /* DEBUG_LoadSymbols */
#include "Schedule.h" /* initScheduler */
@@ -373,6 +374,9 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config)
traceInitEvent(traceOSProcessInfo);
flushTrace();
+ /* initialize INTLIKE and CHARLIKE closures */
+ initBuiltinClosures();
+
/* initialize the storage manager */
initStorage();
=====================================
rts/StgMiscClosures.cmm
=====================================
@@ -13,8 +13,6 @@
#include "Cmm.h"
import pthread_mutex_lock;
-import ghczminternal_GHCziInternalziTypes_Czh_info;
-import ghczminternal_GHCziInternalziTypes_Izh_info;
import AcquireSRWLockExclusive;
import ReleaseSRWLockExclusive;
@@ -23,7 +21,6 @@ import whitehole_lockClosure_spin;
import whitehole_lockClosure_yield;
#endif
-
#if !defined(UnregisterisedCompiler)
import CLOSURE CCS_SYSTEM;
import CLOSURE ENT_DYN_IND_ctr;
@@ -1031,554 +1028,3 @@ INFO_TABLE_CONSTR(stg_ASYNCIO_LIVE0,0,0,0,CONSTR_NOCAF,"ASYNCIO_LIVE0","ASYNCIO_
{ foreign "C" barf("ASYNCIO_LIVE0 object (%p) entered!", R1) never returns; }
CLOSURE(stg_ASYNCIO_LIVE0_closure,stg_ASYNCIO_LIVE0);
-
-/* ----------------------------------------------------------------------------
- Note [CHARLIKE and INTLIKE closures]
- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
- These are static representations of Chars and small Ints, so that
- we can remove dynamic Chars and Ints during garbage collection and
- replace them with references to the static objects.
- ------------------------------------------------------------------------- */
-
-#define Char_hash_con_info ghczminternal_GHCziInternalziTypes_Czh_con_info
-#define Int_hash_con_info ghczminternal_GHCziInternalziTypes_Izh_con_info
-
-#define CHARLIKE_HDR(n) CLOSURE(Char_hash_con_info, n)
-#define INTLIKE_HDR(n) CLOSURE(Int_hash_con_info, n)
-
-section "data" {
- stg_CHARLIKE_closure:
- CHARLIKE_HDR(0)
- CHARLIKE_HDR(1)
- CHARLIKE_HDR(2)
- CHARLIKE_HDR(3)
- CHARLIKE_HDR(4)
- CHARLIKE_HDR(5)
- CHARLIKE_HDR(6)
- CHARLIKE_HDR(7)
- CHARLIKE_HDR(8)
- CHARLIKE_HDR(9)
- CHARLIKE_HDR(10)
- CHARLIKE_HDR(11)
- CHARLIKE_HDR(12)
- CHARLIKE_HDR(13)
- CHARLIKE_HDR(14)
- CHARLIKE_HDR(15)
- CHARLIKE_HDR(16)
- CHARLIKE_HDR(17)
- CHARLIKE_HDR(18)
- CHARLIKE_HDR(19)
- CHARLIKE_HDR(20)
- CHARLIKE_HDR(21)
- CHARLIKE_HDR(22)
- CHARLIKE_HDR(23)
- CHARLIKE_HDR(24)
- CHARLIKE_HDR(25)
- CHARLIKE_HDR(26)
- CHARLIKE_HDR(27)
- CHARLIKE_HDR(28)
- CHARLIKE_HDR(29)
- CHARLIKE_HDR(30)
- CHARLIKE_HDR(31)
- CHARLIKE_HDR(32)
- CHARLIKE_HDR(33)
- CHARLIKE_HDR(34)
- CHARLIKE_HDR(35)
- CHARLIKE_HDR(36)
- CHARLIKE_HDR(37)
- CHARLIKE_HDR(38)
- CHARLIKE_HDR(39)
- CHARLIKE_HDR(40)
- CHARLIKE_HDR(41)
- CHARLIKE_HDR(42)
- CHARLIKE_HDR(43)
- CHARLIKE_HDR(44)
- CHARLIKE_HDR(45)
- CHARLIKE_HDR(46)
- CHARLIKE_HDR(47)
- CHARLIKE_HDR(48)
- CHARLIKE_HDR(49)
- CHARLIKE_HDR(50)
- CHARLIKE_HDR(51)
- CHARLIKE_HDR(52)
- CHARLIKE_HDR(53)
- CHARLIKE_HDR(54)
- CHARLIKE_HDR(55)
- CHARLIKE_HDR(56)
- CHARLIKE_HDR(57)
- CHARLIKE_HDR(58)
- CHARLIKE_HDR(59)
- CHARLIKE_HDR(60)
- CHARLIKE_HDR(61)
- CHARLIKE_HDR(62)
- CHARLIKE_HDR(63)
- CHARLIKE_HDR(64)
- CHARLIKE_HDR(65)
- CHARLIKE_HDR(66)
- CHARLIKE_HDR(67)
- CHARLIKE_HDR(68)
- CHARLIKE_HDR(69)
- CHARLIKE_HDR(70)
- CHARLIKE_HDR(71)
- CHARLIKE_HDR(72)
- CHARLIKE_HDR(73)
- CHARLIKE_HDR(74)
- CHARLIKE_HDR(75)
- CHARLIKE_HDR(76)
- CHARLIKE_HDR(77)
- CHARLIKE_HDR(78)
- CHARLIKE_HDR(79)
- CHARLIKE_HDR(80)
- CHARLIKE_HDR(81)
- CHARLIKE_HDR(82)
- CHARLIKE_HDR(83)
- CHARLIKE_HDR(84)
- CHARLIKE_HDR(85)
- CHARLIKE_HDR(86)
- CHARLIKE_HDR(87)
- CHARLIKE_HDR(88)
- CHARLIKE_HDR(89)
- CHARLIKE_HDR(90)
- CHARLIKE_HDR(91)
- CHARLIKE_HDR(92)
- CHARLIKE_HDR(93)
- CHARLIKE_HDR(94)
- CHARLIKE_HDR(95)
- CHARLIKE_HDR(96)
- CHARLIKE_HDR(97)
- CHARLIKE_HDR(98)
- CHARLIKE_HDR(99)
- CHARLIKE_HDR(100)
- CHARLIKE_HDR(101)
- CHARLIKE_HDR(102)
- CHARLIKE_HDR(103)
- CHARLIKE_HDR(104)
- CHARLIKE_HDR(105)
- CHARLIKE_HDR(106)
- CHARLIKE_HDR(107)
- CHARLIKE_HDR(108)
- CHARLIKE_HDR(109)
- CHARLIKE_HDR(110)
- CHARLIKE_HDR(111)
- CHARLIKE_HDR(112)
- CHARLIKE_HDR(113)
- CHARLIKE_HDR(114)
- CHARLIKE_HDR(115)
- CHARLIKE_HDR(116)
- CHARLIKE_HDR(117)
- CHARLIKE_HDR(118)
- CHARLIKE_HDR(119)
- CHARLIKE_HDR(120)
- CHARLIKE_HDR(121)
- CHARLIKE_HDR(122)
- CHARLIKE_HDR(123)
- CHARLIKE_HDR(124)
- CHARLIKE_HDR(125)
- CHARLIKE_HDR(126)
- CHARLIKE_HDR(127)
- CHARLIKE_HDR(128)
- CHARLIKE_HDR(129)
- CHARLIKE_HDR(130)
- CHARLIKE_HDR(131)
- CHARLIKE_HDR(132)
- CHARLIKE_HDR(133)
- CHARLIKE_HDR(134)
- CHARLIKE_HDR(135)
- CHARLIKE_HDR(136)
- CHARLIKE_HDR(137)
- CHARLIKE_HDR(138)
- CHARLIKE_HDR(139)
- CHARLIKE_HDR(140)
- CHARLIKE_HDR(141)
- CHARLIKE_HDR(142)
- CHARLIKE_HDR(143)
- CHARLIKE_HDR(144)
- CHARLIKE_HDR(145)
- CHARLIKE_HDR(146)
- CHARLIKE_HDR(147)
- CHARLIKE_HDR(148)
- CHARLIKE_HDR(149)
- CHARLIKE_HDR(150)
- CHARLIKE_HDR(151)
- CHARLIKE_HDR(152)
- CHARLIKE_HDR(153)
- CHARLIKE_HDR(154)
- CHARLIKE_HDR(155)
- CHARLIKE_HDR(156)
- CHARLIKE_HDR(157)
- CHARLIKE_HDR(158)
- CHARLIKE_HDR(159)
- CHARLIKE_HDR(160)
- CHARLIKE_HDR(161)
- CHARLIKE_HDR(162)
- CHARLIKE_HDR(163)
- CHARLIKE_HDR(164)
- CHARLIKE_HDR(165)
- CHARLIKE_HDR(166)
- CHARLIKE_HDR(167)
- CHARLIKE_HDR(168)
- CHARLIKE_HDR(169)
- CHARLIKE_HDR(170)
- CHARLIKE_HDR(171)
- CHARLIKE_HDR(172)
- CHARLIKE_HDR(173)
- CHARLIKE_HDR(174)
- CHARLIKE_HDR(175)
- CHARLIKE_HDR(176)
- CHARLIKE_HDR(177)
- CHARLIKE_HDR(178)
- CHARLIKE_HDR(179)
- CHARLIKE_HDR(180)
- CHARLIKE_HDR(181)
- CHARLIKE_HDR(182)
- CHARLIKE_HDR(183)
- CHARLIKE_HDR(184)
- CHARLIKE_HDR(185)
- CHARLIKE_HDR(186)
- CHARLIKE_HDR(187)
- CHARLIKE_HDR(188)
- CHARLIKE_HDR(189)
- CHARLIKE_HDR(190)
- CHARLIKE_HDR(191)
- CHARLIKE_HDR(192)
- CHARLIKE_HDR(193)
- CHARLIKE_HDR(194)
- CHARLIKE_HDR(195)
- CHARLIKE_HDR(196)
- CHARLIKE_HDR(197)
- CHARLIKE_HDR(198)
- CHARLIKE_HDR(199)
- CHARLIKE_HDR(200)
- CHARLIKE_HDR(201)
- CHARLIKE_HDR(202)
- CHARLIKE_HDR(203)
- CHARLIKE_HDR(204)
- CHARLIKE_HDR(205)
- CHARLIKE_HDR(206)
- CHARLIKE_HDR(207)
- CHARLIKE_HDR(208)
- CHARLIKE_HDR(209)
- CHARLIKE_HDR(210)
- CHARLIKE_HDR(211)
- CHARLIKE_HDR(212)
- CHARLIKE_HDR(213)
- CHARLIKE_HDR(214)
- CHARLIKE_HDR(215)
- CHARLIKE_HDR(216)
- CHARLIKE_HDR(217)
- CHARLIKE_HDR(218)
- CHARLIKE_HDR(219)
- CHARLIKE_HDR(220)
- CHARLIKE_HDR(221)
- CHARLIKE_HDR(222)
- CHARLIKE_HDR(223)
- CHARLIKE_HDR(224)
- CHARLIKE_HDR(225)
- CHARLIKE_HDR(226)
- CHARLIKE_HDR(227)
- CHARLIKE_HDR(228)
- CHARLIKE_HDR(229)
- CHARLIKE_HDR(230)
- CHARLIKE_HDR(231)
- CHARLIKE_HDR(232)
- CHARLIKE_HDR(233)
- CHARLIKE_HDR(234)
- CHARLIKE_HDR(235)
- CHARLIKE_HDR(236)
- CHARLIKE_HDR(237)
- CHARLIKE_HDR(238)
- CHARLIKE_HDR(239)
- CHARLIKE_HDR(240)
- CHARLIKE_HDR(241)
- CHARLIKE_HDR(242)
- CHARLIKE_HDR(243)
- CHARLIKE_HDR(244)
- CHARLIKE_HDR(245)
- CHARLIKE_HDR(246)
- CHARLIKE_HDR(247)
- CHARLIKE_HDR(248)
- CHARLIKE_HDR(249)
- CHARLIKE_HDR(250)
- CHARLIKE_HDR(251)
- CHARLIKE_HDR(252)
- CHARLIKE_HDR(253)
- CHARLIKE_HDR(254)
- CHARLIKE_HDR(255)
-}
-
-section "data" {
- stg_INTLIKE_closure:
- INTLIKE_HDR(-16) /* MIN_INTLIKE == -16 */
- INTLIKE_HDR(-15)
- INTLIKE_HDR(-14)
- INTLIKE_HDR(-13)
- INTLIKE_HDR(-12)
- INTLIKE_HDR(-11)
- INTLIKE_HDR(-10)
- INTLIKE_HDR(-9)
- INTLIKE_HDR(-8)
- INTLIKE_HDR(-7)
- INTLIKE_HDR(-6)
- INTLIKE_HDR(-5)
- INTLIKE_HDR(-4)
- INTLIKE_HDR(-3)
- INTLIKE_HDR(-2)
- INTLIKE_HDR(-1)
- INTLIKE_HDR(0)
- INTLIKE_HDR(1)
- INTLIKE_HDR(2)
- INTLIKE_HDR(3)
- INTLIKE_HDR(4)
- INTLIKE_HDR(5)
- INTLIKE_HDR(6)
- INTLIKE_HDR(7)
- INTLIKE_HDR(8)
- INTLIKE_HDR(9)
- INTLIKE_HDR(10)
- INTLIKE_HDR(11)
- INTLIKE_HDR(12)
- INTLIKE_HDR(13)
- INTLIKE_HDR(14)
- INTLIKE_HDR(15)
- INTLIKE_HDR(16)
- INTLIKE_HDR(17)
- INTLIKE_HDR(18)
- INTLIKE_HDR(19)
- INTLIKE_HDR(20)
- INTLIKE_HDR(21)
- INTLIKE_HDR(22)
- INTLIKE_HDR(23)
- INTLIKE_HDR(24)
- INTLIKE_HDR(25)
- INTLIKE_HDR(26)
- INTLIKE_HDR(27)
- INTLIKE_HDR(28)
- INTLIKE_HDR(29)
- INTLIKE_HDR(30)
- INTLIKE_HDR(31)
- INTLIKE_HDR(32)
- INTLIKE_HDR(33)
- INTLIKE_HDR(34)
- INTLIKE_HDR(35)
- INTLIKE_HDR(36)
- INTLIKE_HDR(37)
- INTLIKE_HDR(38)
- INTLIKE_HDR(39)
- INTLIKE_HDR(40)
- INTLIKE_HDR(41)
- INTLIKE_HDR(42)
- INTLIKE_HDR(43)
- INTLIKE_HDR(44)
- INTLIKE_HDR(45)
- INTLIKE_HDR(46)
- INTLIKE_HDR(47)
- INTLIKE_HDR(48)
- INTLIKE_HDR(49)
- INTLIKE_HDR(50)
- INTLIKE_HDR(51)
- INTLIKE_HDR(52)
- INTLIKE_HDR(53)
- INTLIKE_HDR(54)
- INTLIKE_HDR(55)
- INTLIKE_HDR(56)
- INTLIKE_HDR(57)
- INTLIKE_HDR(58)
- INTLIKE_HDR(59)
- INTLIKE_HDR(60)
- INTLIKE_HDR(61)
- INTLIKE_HDR(62)
- INTLIKE_HDR(63)
- INTLIKE_HDR(64)
- INTLIKE_HDR(65)
- INTLIKE_HDR(66)
- INTLIKE_HDR(67)
- INTLIKE_HDR(68)
- INTLIKE_HDR(69)
- INTLIKE_HDR(70)
- INTLIKE_HDR(71)
- INTLIKE_HDR(72)
- INTLIKE_HDR(73)
- INTLIKE_HDR(74)
- INTLIKE_HDR(75)
- INTLIKE_HDR(76)
- INTLIKE_HDR(77)
- INTLIKE_HDR(78)
- INTLIKE_HDR(79)
- INTLIKE_HDR(80)
- INTLIKE_HDR(81)
- INTLIKE_HDR(82)
- INTLIKE_HDR(83)
- INTLIKE_HDR(84)
- INTLIKE_HDR(85)
- INTLIKE_HDR(86)
- INTLIKE_HDR(87)
- INTLIKE_HDR(88)
- INTLIKE_HDR(89)
- INTLIKE_HDR(90)
- INTLIKE_HDR(91)
- INTLIKE_HDR(92)
- INTLIKE_HDR(93)
- INTLIKE_HDR(94)
- INTLIKE_HDR(95)
- INTLIKE_HDR(96)
- INTLIKE_HDR(97)
- INTLIKE_HDR(98)
- INTLIKE_HDR(99)
- INTLIKE_HDR(100)
- INTLIKE_HDR(101)
- INTLIKE_HDR(102)
- INTLIKE_HDR(103)
- INTLIKE_HDR(104)
- INTLIKE_HDR(105)
- INTLIKE_HDR(106)
- INTLIKE_HDR(107)
- INTLIKE_HDR(108)
- INTLIKE_HDR(109)
- INTLIKE_HDR(110)
- INTLIKE_HDR(111)
- INTLIKE_HDR(112)
- INTLIKE_HDR(113)
- INTLIKE_HDR(114)
- INTLIKE_HDR(115)
- INTLIKE_HDR(116)
- INTLIKE_HDR(117)
- INTLIKE_HDR(118)
- INTLIKE_HDR(119)
- INTLIKE_HDR(120)
- INTLIKE_HDR(121)
- INTLIKE_HDR(122)
- INTLIKE_HDR(123)
- INTLIKE_HDR(124)
- INTLIKE_HDR(125)
- INTLIKE_HDR(126)
- INTLIKE_HDR(127)
- INTLIKE_HDR(128)
- INTLIKE_HDR(129)
- INTLIKE_HDR(130)
- INTLIKE_HDR(131)
- INTLIKE_HDR(132)
- INTLIKE_HDR(133)
- INTLIKE_HDR(134)
- INTLIKE_HDR(135)
- INTLIKE_HDR(136)
- INTLIKE_HDR(137)
- INTLIKE_HDR(138)
- INTLIKE_HDR(139)
- INTLIKE_HDR(140)
- INTLIKE_HDR(141)
- INTLIKE_HDR(142)
- INTLIKE_HDR(143)
- INTLIKE_HDR(144)
- INTLIKE_HDR(145)
- INTLIKE_HDR(146)
- INTLIKE_HDR(147)
- INTLIKE_HDR(148)
- INTLIKE_HDR(149)
- INTLIKE_HDR(150)
- INTLIKE_HDR(151)
- INTLIKE_HDR(152)
- INTLIKE_HDR(153)
- INTLIKE_HDR(154)
- INTLIKE_HDR(155)
- INTLIKE_HDR(156)
- INTLIKE_HDR(157)
- INTLIKE_HDR(158)
- INTLIKE_HDR(159)
- INTLIKE_HDR(160)
- INTLIKE_HDR(161)
- INTLIKE_HDR(162)
- INTLIKE_HDR(163)
- INTLIKE_HDR(164)
- INTLIKE_HDR(165)
- INTLIKE_HDR(166)
- INTLIKE_HDR(167)
- INTLIKE_HDR(168)
- INTLIKE_HDR(169)
- INTLIKE_HDR(170)
- INTLIKE_HDR(171)
- INTLIKE_HDR(172)
- INTLIKE_HDR(173)
- INTLIKE_HDR(174)
- INTLIKE_HDR(175)
- INTLIKE_HDR(176)
- INTLIKE_HDR(177)
- INTLIKE_HDR(178)
- INTLIKE_HDR(179)
- INTLIKE_HDR(180)
- INTLIKE_HDR(181)
- INTLIKE_HDR(182)
- INTLIKE_HDR(183)
- INTLIKE_HDR(184)
- INTLIKE_HDR(185)
- INTLIKE_HDR(186)
- INTLIKE_HDR(187)
- INTLIKE_HDR(188)
- INTLIKE_HDR(189)
- INTLIKE_HDR(190)
- INTLIKE_HDR(191)
- INTLIKE_HDR(192)
- INTLIKE_HDR(193)
- INTLIKE_HDR(194)
- INTLIKE_HDR(195)
- INTLIKE_HDR(196)
- INTLIKE_HDR(197)
- INTLIKE_HDR(198)
- INTLIKE_HDR(199)
- INTLIKE_HDR(200)
- INTLIKE_HDR(201)
- INTLIKE_HDR(202)
- INTLIKE_HDR(203)
- INTLIKE_HDR(204)
- INTLIKE_HDR(205)
- INTLIKE_HDR(206)
- INTLIKE_HDR(207)
- INTLIKE_HDR(208)
- INTLIKE_HDR(209)
- INTLIKE_HDR(210)
- INTLIKE_HDR(211)
- INTLIKE_HDR(212)
- INTLIKE_HDR(213)
- INTLIKE_HDR(214)
- INTLIKE_HDR(215)
- INTLIKE_HDR(216)
- INTLIKE_HDR(217)
- INTLIKE_HDR(218)
- INTLIKE_HDR(219)
- INTLIKE_HDR(220)
- INTLIKE_HDR(221)
- INTLIKE_HDR(222)
- INTLIKE_HDR(223)
- INTLIKE_HDR(224)
- INTLIKE_HDR(225)
- INTLIKE_HDR(226)
- INTLIKE_HDR(227)
- INTLIKE_HDR(228)
- INTLIKE_HDR(229)
- INTLIKE_HDR(230)
- INTLIKE_HDR(231)
- INTLIKE_HDR(232)
- INTLIKE_HDR(233)
- INTLIKE_HDR(234)
- INTLIKE_HDR(235)
- INTLIKE_HDR(236)
- INTLIKE_HDR(237)
- INTLIKE_HDR(238)
- INTLIKE_HDR(239)
- INTLIKE_HDR(240)
- INTLIKE_HDR(241)
- INTLIKE_HDR(242)
- INTLIKE_HDR(243)
- INTLIKE_HDR(244)
- INTLIKE_HDR(245)
- INTLIKE_HDR(246)
- INTLIKE_HDR(247)
- INTLIKE_HDR(248)
- INTLIKE_HDR(249)
- INTLIKE_HDR(250)
- INTLIKE_HDR(251)
- INTLIKE_HDR(252)
- INTLIKE_HDR(253)
- INTLIKE_HDR(254)
- INTLIKE_HDR(255) /* MAX_INTLIKE == 255
- See #16961 for why 255 */
-}
=====================================
rts/include/rts/Constants.h
=====================================
@@ -57,11 +57,12 @@
#define MAX_SPEC_CONSTR_SIZE 2
/* Range of built-in table of static small int-like and char-like closures.
+ * Range is inclusive of both minimum and maximum.
*
* NB. This corresponds with the number of actual INTLIKE/CHARLIKE
* closures defined in rts/StgMiscClosures.cmm.
*/
-#define MAX_INTLIKE 255
+#define MAX_INTLIKE 255 /* See #16961 for why 255 */
#define MIN_INTLIKE (-16)
#define MAX_CHARLIKE 255
=====================================
rts/include/stg/MiscClosures.h
=====================================
@@ -277,8 +277,8 @@ RTS_ENTRY(stg_NO_FINALIZER);
extern StgWordArray stg_CHARLIKE_closure;
extern StgWordArray stg_INTLIKE_closure;
#else
-extern StgIntCharlikeClosure stg_CHARLIKE_closure[];
-extern StgIntCharlikeClosure stg_INTLIKE_closure[];
+extern StgIntCharlikeClosure stg_CHARLIKE_closure[MAX_CHARLIKE - MIN_CHARLIKE + 1];
+extern StgIntCharlikeClosure stg_INTLIKE_closure[MAX_INTLIKE - MIN_INTLIKE + 1];
#endif
/* StgStartup */
=====================================
rts/rts.cabal
=====================================
@@ -403,6 +403,7 @@ library
adjustor/AdjustorPool.c
ExecPage.c
Arena.c
+ BuiltinClosures.c
Capability.c
CheckUnload.c
CheckVectorSupport.c
=====================================
testsuite/tests/process/process010.stdout-i386-unknown-solaris2 deleted
=====================================
@@ -1,4 +0,0 @@
-ExitSuccess
-ExitFailure 255
-Exc: /non/existent: rawSystem: runInteractiveProcess: exec: does not exist (No such file or directory)
-Done
=====================================
testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32 deleted
=====================================
@@ -1,25 +0,0 @@
-GHC runtime linker: fatal error: I found a duplicate definition for symbol
- _a
-whilst processing object file
- E:\ghc-dev\msys64\home\Tamar\ghc\testsuite\tests\rts\T11223\T11223_link_order_a_b_2_fail.run\libfoo_link_lib_3.a
-The symbol was previously defined in
- E:\ghc-dev\msys64\home\Tamar\ghc\testsuite\tests\rts\T11223\T11223_link_order_a_b_2_fail.run\libbar_link_lib_3.a(#3:bar_link_lib_3.o)
-This could be caused by:
- * Loading two different object files which export the same symbol
- * Specifying the same object file twice on the GHCi command line
- * An incorrect `package.conf' entry, causing some object to be
- loaded twice.
-ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above. You might consider using --optimistic-linking
-
-
-GHC.ByteCode.Linker: can't find label
-During interactive linking, GHCi couldn't find the following symbol:
- c
-This may be due to you not asking GHCi to load extra object files,
-archives or DLLs needed by your current session. Restart GHCi, specifying
-the missing library using the -L/path/to/object/dir and -lmissinglibname
-flags, or simply by naming the relevant files on the GHCi command line.
-Alternatively, this link failure might indicate a bug in GHCi.
-If you suspect the latter, please report this as a GHC bug:
- https://www.haskell.org/ghc/reportabug
-
=====================================
testsuite/tests/rts/linker/T11223/T11223_simple_duplicate_lib.stderr-ws-32-mingw32 deleted
=====================================
@@ -1,25 +0,0 @@
-GHC runtime linker: fatal error: I found a duplicate definition for symbol
- _a
-whilst processing object file
- E:\ghc-dev\msys64\home\Tamar\ghc\testsuite\tests\rts\T11223\T11223_simple_duplicate_lib.run\libfoo_dup_lib.a
-The symbol was previously defined in
- E:\ghc-dev\msys64\home\Tamar\ghc\testsuite\tests\rts\T11223\T11223_simple_duplicate_lib.run\bar_dup_lib.o
-This could be caused by:
- * Loading two different object files which export the same symbol
- * Specifying the same object file twice on the GHCi command line
- * An incorrect `package.conf' entry, causing some object to be
- loaded twice.
-ghc-stage2.exe: ^^ Could not load '_c', dependency unresolved. See top entry above. You might consider using --optimistic-linking
-
-
-GHC.ByteCode.Linker: can't find label
-During interactive linking, GHCi couldn't find the following symbol:
- c
-This may be due to you not asking GHCi to load extra object files,
-archives or DLLs needed by your current session. Restart GHCi, specifying
-the missing library using the -L/path/to/object/dir and -lmissinglibname
-flags, or simply by naming the relevant files on the GHCi command line.
-Alternatively, this link failure might indicate a bug in GHCi.
-If you suspect the latter, please report this as a GHC bug:
- https://www.haskell.org/ghc/reportabug
-
=====================================
testsuite/tests/rts/outofmem.stderr-i386-apple-darwin deleted
=====================================
@@ -1 +0,0 @@
-outofmem: memory allocation failed (requested 1074790400 bytes)
=====================================
testsuite/tests/rts/outofmem.stderr-i386-unknown-mingw32 deleted
=====================================
@@ -1 +0,0 @@
-outofmem.exe: Out of memory
=====================================
testsuite/tests/rts/outofmem.stderr-powerpc-apple-darwin deleted
=====================================
@@ -1 +0,0 @@
-outofmem: memory allocation failed (requested 1074790400 bytes)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d21638e35db5a32a9420b691c5244f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d21638e35db5a32a9420b691c5244f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
01 Oct '25
Simon Hengel pushed new branch wip/sol/master-patch-68692 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/sol/master-patch-68692
You're receiving this email because of your account on gitlab.haskell.org.
1
0