[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: testsuite: Use ghci_ways to set ways in PackedDataCon/UnboxedTuples/UnliftedDataTypeInterp tests
by Marge Bot (@marge-bot) 06 Oct '25
by Marge Bot (@marge-bot) 06 Oct '25
06 Oct '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
1275d360 by Matthew Pickering at 2025-10-03T06:05:56-04:00
testsuite: Use ghci_ways to set ways in PackedDataCon/UnboxedTuples/UnliftedDataTypeInterp tests
These tests reimplemented the logic from `valid_way` in order to
determine what ways to run. It's easier to use this combination of
`only_ways` and `extra_ways` to only run in GHCi ways and always run in
GHCi ways.
- - - - -
c06b534b by Matthew Pickering at 2025-10-03T06:06:40-04:00
Rename interpreterBackend to bytecodeBackend
This is preparation for creating bytecode files.
The "interpreter" is one way in which we can run bytecode objects. It is
more accurate to describe that the backend produces bytecode, rather
than the means by which the code will eventually run.
The "interpreterBackend" binding is left as a deprecated alias.
- - - - -
5f2b2004 by Andreas Klebinger at 2025-10-06T11:34:12-04:00
Add a perf test for #26425
- - - - -
64f8ecd6 by Andreas Klebinger at 2025-10-06T11:34:12-04:00
Testsuite: Silence warnings about Wx-partial in concprog001
- - - - -
22 changed files:
- compiler/GHC.hs
- compiler/GHC/Driver/Backend.hs
- compiler/GHC/Driver/Backend/Internal.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Session.hs
- docs/users_guide/extending_ghc.rst
- ghc/Main.hs
- testsuite/driver/testglobals.py
- testsuite/driver/testlib.py
- testsuite/tests/concurrent/prog001/all.T
- testsuite/tests/driver/T5313.hs
- testsuite/tests/ghc-api/T10052/T10052.hs
- testsuite/tests/ghc-api/T8639_api.hs
- testsuite/tests/ghc-api/apirecomp001/myghc.hs
- testsuite/tests/ghci-wasm/T26431.hs
- testsuite/tests/ghci/linking/dyn/T3372.hs
- testsuite/tests/ghci/should_run/PackedDataCon/packeddatacon.T
- testsuite/tests/ghci/should_run/UnboxedTuples/unboxedtuples.T
- testsuite/tests/ghci/should_run/UnliftedDataTypeInterp/unlifteddatatypeinterp.T
- + testsuite/tests/perf/compiler/T26425.hs
- testsuite/tests/perf/compiler/all.T
Changes:
=====================================
compiler/GHC.hs
=====================================
@@ -30,7 +30,7 @@ module GHC (
-- * Flags and settings
DynFlags(..), GeneralFlag(..), Severity(..), Backend, gopt,
- ncgBackend, llvmBackend, viaCBackend, interpreterBackend, noBackend,
+ ncgBackend, llvmBackend, viaCBackend, bytecodeBackend, interpreterBackend, noBackend,
GhcMode(..), GhcLink(..),
parseDynamicFlags, parseTargetFiles,
getSessionDynFlags,
=====================================
compiler/GHC/Driver/Backend.hs
=====================================
@@ -47,6 +47,7 @@ module GHC.Driver.Backend
, llvmBackend
, jsBackend
, viaCBackend
+ , bytecodeBackend
, interpreterBackend
, noBackend
, allBackends
@@ -252,7 +253,7 @@ instance Show Backend where
show = backendDescription
-ncgBackend, llvmBackend, viaCBackend, interpreterBackend, jsBackend, noBackend
+ncgBackend, llvmBackend, viaCBackend, bytecodeBackend, interpreterBackend, jsBackend, noBackend
:: Backend
-- | The native code generator.
@@ -310,7 +311,11 @@ viaCBackend = Named ViaC
-- (foreign primops).
--
-- See "GHC.StgToByteCode"
-interpreterBackend = Named Interpreter
+bytecodeBackend = Named Bytecode
+
+{-# DEPRECATED interpreterBackend "Renamed to bytecodeBackend" #-}
+interpreterBackend = bytecodeBackend
+
-- | A dummy back end that generates no code.
--
@@ -419,7 +424,7 @@ backendDescription (Named NCG) = "native code generator"
backendDescription (Named LLVM) = "LLVM"
backendDescription (Named ViaC) = "compiling via C"
backendDescription (Named JavaScript) = "compiling to JavaScript"
-backendDescription (Named Interpreter) = "byte-code interpreter"
+backendDescription (Named Bytecode) = "byte-code interpreter"
backendDescription (Named NoBackend) = "no code generated"
-- | This flag tells the compiler driver whether the back
@@ -431,7 +436,7 @@ backendWritesFiles (Named NCG) = True
backendWritesFiles (Named LLVM) = True
backendWritesFiles (Named ViaC) = True
backendWritesFiles (Named JavaScript) = True
-backendWritesFiles (Named Interpreter) = False
+backendWritesFiles (Named Bytecode) = False
backendWritesFiles (Named NoBackend) = False
-- | When the back end does write files, this value tells
@@ -442,7 +447,7 @@ backendPipelineOutput (Named NCG) = Persistent
backendPipelineOutput (Named LLVM) = Persistent
backendPipelineOutput (Named ViaC) = Persistent
backendPipelineOutput (Named JavaScript) = Persistent
-backendPipelineOutput (Named Interpreter) = NoOutputFile
+backendPipelineOutput (Named Bytecode) = NoOutputFile
backendPipelineOutput (Named NoBackend) = NoOutputFile
-- | This flag tells the driver whether the back end can
@@ -453,7 +458,7 @@ backendCanReuseLoadedCode (Named NCG) = False
backendCanReuseLoadedCode (Named LLVM) = False
backendCanReuseLoadedCode (Named ViaC) = False
backendCanReuseLoadedCode (Named JavaScript) = False
-backendCanReuseLoadedCode (Named Interpreter) = True
+backendCanReuseLoadedCode (Named Bytecode) = True
backendCanReuseLoadedCode (Named NoBackend) = False
-- | It is is true of every back end except @-fno-code@
@@ -478,7 +483,7 @@ backendGeneratesCode (Named NCG) = True
backendGeneratesCode (Named LLVM) = True
backendGeneratesCode (Named ViaC) = True
backendGeneratesCode (Named JavaScript) = True
-backendGeneratesCode (Named Interpreter) = True
+backendGeneratesCode (Named Bytecode) = True
backendGeneratesCode (Named NoBackend) = False
backendGeneratesCodeForHsBoot :: Backend -> Bool
@@ -486,7 +491,7 @@ backendGeneratesCodeForHsBoot (Named NCG) = True
backendGeneratesCodeForHsBoot (Named LLVM) = True
backendGeneratesCodeForHsBoot (Named ViaC) = True
backendGeneratesCodeForHsBoot (Named JavaScript) = True
-backendGeneratesCodeForHsBoot (Named Interpreter) = False
+backendGeneratesCodeForHsBoot (Named Bytecode) = False
backendGeneratesCodeForHsBoot (Named NoBackend) = False
-- | When set, this flag turns on interface writing for
@@ -498,7 +503,7 @@ backendSupportsInterfaceWriting (Named NCG) = True
backendSupportsInterfaceWriting (Named LLVM) = True
backendSupportsInterfaceWriting (Named ViaC) = True
backendSupportsInterfaceWriting (Named JavaScript) = True
-backendSupportsInterfaceWriting (Named Interpreter) = True
+backendSupportsInterfaceWriting (Named Bytecode) = True
backendSupportsInterfaceWriting (Named NoBackend) = False
-- | When preparing code for this back end, the type
@@ -510,7 +515,7 @@ backendRespectsSpecialise (Named NCG) = True
backendRespectsSpecialise (Named LLVM) = True
backendRespectsSpecialise (Named ViaC) = True
backendRespectsSpecialise (Named JavaScript) = True
-backendRespectsSpecialise (Named Interpreter) = False
+backendRespectsSpecialise (Named Bytecode) = False
backendRespectsSpecialise (Named NoBackend) = False
-- | This back end wants the `mi_top_env` field of a
@@ -522,7 +527,7 @@ backendWantsGlobalBindings (Named LLVM) = False
backendWantsGlobalBindings (Named ViaC) = False
backendWantsGlobalBindings (Named JavaScript) = False
backendWantsGlobalBindings (Named NoBackend) = False
-backendWantsGlobalBindings (Named Interpreter) = True
+backendWantsGlobalBindings (Named Bytecode) = True
-- | The back end targets a technology that implements
-- `switch` natively. (For example, LLVM or C.) Therefore
@@ -534,7 +539,7 @@ backendHasNativeSwitch (Named NCG) = False
backendHasNativeSwitch (Named LLVM) = True
backendHasNativeSwitch (Named ViaC) = True
backendHasNativeSwitch (Named JavaScript) = True
-backendHasNativeSwitch (Named Interpreter) = False
+backendHasNativeSwitch (Named Bytecode) = False
backendHasNativeSwitch (Named NoBackend) = False
-- | As noted in the documentation for
@@ -548,7 +553,7 @@ backendPrimitiveImplementation (Named NCG) = NcgPrimitives
backendPrimitiveImplementation (Named LLVM) = LlvmPrimitives
backendPrimitiveImplementation (Named JavaScript) = JSPrimitives
backendPrimitiveImplementation (Named ViaC) = GenericPrimitives
-backendPrimitiveImplementation (Named Interpreter) = GenericPrimitives
+backendPrimitiveImplementation (Named Bytecode) = GenericPrimitives
backendPrimitiveImplementation (Named NoBackend) = GenericPrimitives
-- | When this value is `IsValid`, the back end is
@@ -560,7 +565,7 @@ backendSimdValidity (Named NCG) = IsValid
backendSimdValidity (Named LLVM) = IsValid
backendSimdValidity (Named ViaC) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
backendSimdValidity (Named JavaScript) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
-backendSimdValidity (Named Interpreter) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
+backendSimdValidity (Named Bytecode) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
backendSimdValidity (Named NoBackend) = NotValid $ unlines ["SIMD vector instructions require using the NCG or the LLVM backend."]
-- | This flag says whether the back end supports large
@@ -571,7 +576,7 @@ backendSupportsEmbeddedBlobs (Named NCG) = True
backendSupportsEmbeddedBlobs (Named LLVM) = False
backendSupportsEmbeddedBlobs (Named ViaC) = False
backendSupportsEmbeddedBlobs (Named JavaScript) = False
-backendSupportsEmbeddedBlobs (Named Interpreter) = False
+backendSupportsEmbeddedBlobs (Named Bytecode) = False
backendSupportsEmbeddedBlobs (Named NoBackend) = False
-- | This flag tells the compiler driver that the back end
@@ -586,7 +591,7 @@ backendNeedsPlatformNcgSupport (Named NCG) = True
backendNeedsPlatformNcgSupport (Named LLVM) = False
backendNeedsPlatformNcgSupport (Named ViaC) = False
backendNeedsPlatformNcgSupport (Named JavaScript) = False
-backendNeedsPlatformNcgSupport (Named Interpreter) = False
+backendNeedsPlatformNcgSupport (Named Bytecode) = False
backendNeedsPlatformNcgSupport (Named NoBackend) = False
-- | This flag is set if the back end can generate code
@@ -598,7 +603,7 @@ backendSupportsUnsplitProcPoints (Named NCG) = True
backendSupportsUnsplitProcPoints (Named LLVM) = False
backendSupportsUnsplitProcPoints (Named ViaC) = False
backendSupportsUnsplitProcPoints (Named JavaScript) = False
-backendSupportsUnsplitProcPoints (Named Interpreter) = False
+backendSupportsUnsplitProcPoints (Named Bytecode) = False
backendSupportsUnsplitProcPoints (Named NoBackend) = False
-- | This flag guides the driver in resolving issues about
@@ -616,7 +621,7 @@ backendSwappableWithViaC (Named NCG) = True
backendSwappableWithViaC (Named LLVM) = True
backendSwappableWithViaC (Named ViaC) = False
backendSwappableWithViaC (Named JavaScript) = False
-backendSwappableWithViaC (Named Interpreter) = False
+backendSwappableWithViaC (Named Bytecode) = False
backendSwappableWithViaC (Named NoBackend) = False
-- | This flag is true if the back end works *only* with
@@ -626,7 +631,7 @@ backendUnregisterisedAbiOnly (Named NCG) = False
backendUnregisterisedAbiOnly (Named LLVM) = False
backendUnregisterisedAbiOnly (Named ViaC) = True
backendUnregisterisedAbiOnly (Named JavaScript) = False
-backendUnregisterisedAbiOnly (Named Interpreter) = False
+backendUnregisterisedAbiOnly (Named Bytecode) = False
backendUnregisterisedAbiOnly (Named NoBackend) = False
-- | This flag is set if the back end generates C code in
@@ -637,7 +642,7 @@ backendGeneratesHc (Named NCG) = False
backendGeneratesHc (Named LLVM) = False
backendGeneratesHc (Named ViaC) = True
backendGeneratesHc (Named JavaScript) = False
-backendGeneratesHc (Named Interpreter) = False
+backendGeneratesHc (Named Bytecode) = False
backendGeneratesHc (Named NoBackend) = False
-- | This flag says whether SPT (static pointer table)
@@ -649,7 +654,7 @@ backendSptIsDynamic (Named NCG) = False
backendSptIsDynamic (Named LLVM) = False
backendSptIsDynamic (Named ViaC) = False
backendSptIsDynamic (Named JavaScript) = False
-backendSptIsDynamic (Named Interpreter) = True
+backendSptIsDynamic (Named Bytecode) = True
backendSptIsDynamic (Named NoBackend) = False
-- | If this flag is unset, then the driver ignores the flag @-fbreak-points@,
@@ -660,7 +665,7 @@ backendSupportsBreakpoints = \case
Named LLVM -> False
Named ViaC -> False
Named JavaScript -> False
- Named Interpreter -> True
+ Named Bytecode -> True
Named NoBackend -> False
-- | If this flag is set, then the driver forces the
@@ -671,7 +676,7 @@ backendForcesOptimization0 (Named NCG) = False
backendForcesOptimization0 (Named LLVM) = False
backendForcesOptimization0 (Named ViaC) = False
backendForcesOptimization0 (Named JavaScript) = False
-backendForcesOptimization0 (Named Interpreter) = True
+backendForcesOptimization0 (Named Bytecode) = True
backendForcesOptimization0 (Named NoBackend) = False
-- | I don't understand exactly how this works. But if
@@ -683,7 +688,7 @@ backendNeedsFullWays (Named NCG) = False
backendNeedsFullWays (Named LLVM) = False
backendNeedsFullWays (Named ViaC) = False
backendNeedsFullWays (Named JavaScript) = False
-backendNeedsFullWays (Named Interpreter) = True
+backendNeedsFullWays (Named Bytecode) = True
backendNeedsFullWays (Named NoBackend) = False
-- | This flag is also special for the interpreter: if a
@@ -695,7 +700,7 @@ backendSpecialModuleSource (Named NCG) = const Nothing
backendSpecialModuleSource (Named LLVM) = const Nothing
backendSpecialModuleSource (Named ViaC) = const Nothing
backendSpecialModuleSource (Named JavaScript) = const Nothing
-backendSpecialModuleSource (Named Interpreter) = \b -> if b then Just "interpreted" else Nothing
+backendSpecialModuleSource (Named Bytecode) = \b -> if b then Just "interpreted" else Nothing
backendSpecialModuleSource (Named NoBackend) = const (Just "nothing")
-- | This flag says whether the back end supports Haskell
@@ -707,7 +712,7 @@ backendSupportsHpc (Named NCG) = True
backendSupportsHpc (Named LLVM) = True
backendSupportsHpc (Named ViaC) = True
backendSupportsHpc (Named JavaScript) = False
-backendSupportsHpc (Named Interpreter) = False
+backendSupportsHpc (Named Bytecode) = False
backendSupportsHpc (Named NoBackend) = True
-- | This flag says whether the back end supports foreign
@@ -718,7 +723,7 @@ backendSupportsCImport (Named NCG) = True
backendSupportsCImport (Named LLVM) = True
backendSupportsCImport (Named ViaC) = True
backendSupportsCImport (Named JavaScript) = True
-backendSupportsCImport (Named Interpreter) = True
+backendSupportsCImport (Named Bytecode) = True
backendSupportsCImport (Named NoBackend) = True
-- | This flag says whether the back end supports foreign
@@ -728,7 +733,7 @@ backendSupportsCExport (Named NCG) = True
backendSupportsCExport (Named LLVM) = True
backendSupportsCExport (Named ViaC) = True
backendSupportsCExport (Named JavaScript) = True
-backendSupportsCExport (Named Interpreter) = False
+backendSupportsCExport (Named Bytecode) = False
backendSupportsCExport (Named NoBackend) = True
-- | When using this back end, it may be necessary or
@@ -749,7 +754,7 @@ backendCDefs (Named NCG) = NoCDefs
backendCDefs (Named LLVM) = LlvmCDefs
backendCDefs (Named ViaC) = NoCDefs
backendCDefs (Named JavaScript) = NoCDefs
-backendCDefs (Named Interpreter) = NoCDefs
+backendCDefs (Named Bytecode) = NoCDefs
backendCDefs (Named NoBackend) = NoCDefs
-- | This (defunctionalized) function generates code and
@@ -768,7 +773,7 @@ backendCodeOutput (Named NCG) = NcgCodeOutput
backendCodeOutput (Named LLVM) = LlvmCodeOutput
backendCodeOutput (Named ViaC) = ViaCCodeOutput
backendCodeOutput (Named JavaScript) = JSCodeOutput
-backendCodeOutput (Named Interpreter) = panic "backendCodeOutput: interpreterBackend"
+backendCodeOutput (Named Bytecode) = panic "backendCodeOutput: bytecodeBackend"
backendCodeOutput (Named NoBackend) = panic "backendCodeOutput: noBackend"
backendUseJSLinker :: Backend -> Bool
@@ -776,7 +781,7 @@ backendUseJSLinker (Named NCG) = False
backendUseJSLinker (Named LLVM) = False
backendUseJSLinker (Named ViaC) = False
backendUseJSLinker (Named JavaScript) = True
-backendUseJSLinker (Named Interpreter) = False
+backendUseJSLinker (Named Bytecode) = False
backendUseJSLinker (Named NoBackend) = False
-- | This (defunctionalized) function tells the compiler
@@ -795,7 +800,7 @@ backendPostHscPipeline (Named NCG) = NcgPostHscPipeline
backendPostHscPipeline (Named LLVM) = LlvmPostHscPipeline
backendPostHscPipeline (Named ViaC) = ViaCPostHscPipeline
backendPostHscPipeline (Named JavaScript) = JSPostHscPipeline
-backendPostHscPipeline (Named Interpreter) = NoPostHscPipeline
+backendPostHscPipeline (Named Bytecode) = NoPostHscPipeline
backendPostHscPipeline (Named NoBackend) = NoPostHscPipeline
-- | Somewhere in the compiler driver, when compiling
@@ -809,7 +814,7 @@ backendNormalSuccessorPhase (Named NCG) = As False
backendNormalSuccessorPhase (Named LLVM) = LlvmOpt
backendNormalSuccessorPhase (Named ViaC) = HCc
backendNormalSuccessorPhase (Named JavaScript) = StopLn
-backendNormalSuccessorPhase (Named Interpreter) = StopLn
+backendNormalSuccessorPhase (Named Bytecode) = StopLn
backendNormalSuccessorPhase (Named NoBackend) = StopLn
-- | Name of the back end, if any. Used to migrate legacy
@@ -820,7 +825,7 @@ backendName (Named NCG) = NCG
backendName (Named LLVM) = LLVM
backendName (Named ViaC) = ViaC
backendName (Named JavaScript) = JavaScript
-backendName (Named Interpreter) = Interpreter
+backendName (Named Bytecode) = Bytecode
backendName (Named NoBackend) = NoBackend
@@ -833,7 +838,7 @@ allBackends = [ ncgBackend
, llvmBackend
, viaCBackend
, jsBackend
- , interpreterBackend
+ , bytecodeBackend
, noBackend
]
=====================================
compiler/GHC/Driver/Backend/Internal.hs
=====================================
@@ -28,6 +28,6 @@ data BackendName
| LLVM -- ^ Names the LLVM backend.
| ViaC -- ^ Names the Via-C backend.
| JavaScript -- ^ Names the JS backend.
- | Interpreter -- ^ Names the ByteCode interpreter.
+ | Bytecode -- ^ Names the ByteCode interpreter.
| NoBackend -- ^ Names the `-fno-code` backend.
deriving (Eq, Show)
=====================================
compiler/GHC/Driver/Downsweep.hs
=====================================
@@ -916,7 +916,7 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = do
else (,) <$> (new_temp_file (hiSuf_ dflags) (dynHiSuf_ dflags))
<*> (new_temp_file (objectSuf_ dflags) (dynObjectSuf_ dflags))
let new_dflags = case enable_spec of
- EnableByteCode -> dflags { backend = interpreterBackend }
+ EnableByteCode -> dflags { backend = bytecodeBackend }
EnableObject -> dflags { backend = defaultBackendOf ms }
EnableByteCodeAndObject -> (gopt_set dflags Opt_ByteCodeAndObjectCode) { backend = defaultBackendOf ms}
let ms' = ms
=====================================
compiler/GHC/Driver/Pipeline.hs
=====================================
@@ -281,8 +281,8 @@ compileOne' mHscMessage
-- was set), force it to generate byte-code. This is NOT transitive and
-- only applies to direct targets.
| loadAsByteCode
- = ( interpreterBackend
- , gopt_set (lcl_dflags { backend = interpreterBackend }) Opt_ForceRecomp
+ = ( bytecodeBackend
+ , gopt_set (lcl_dflags { backend = bytecodeBackend }) Opt_ForceRecomp
)
| otherwise
=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -1931,7 +1931,7 @@ dynamic_flags_deps = [
d { ghcLink=NoLink }) >> setBackend noBackend))
, make_ord_flag defFlag "fbyte-code"
(noArgM $ \dflags -> do
- setBackend interpreterBackend
+ setBackend bytecodeBackend
pure $ flip gopt_unset Opt_ByteCodeAndObjectCode (gopt_set dflags Opt_ByteCode))
, make_ord_flag defFlag "fobject-code" $ noArgM $ \dflags -> do
setBackend $ platformDefaultBackend (targetPlatform dflags)
=====================================
docs/users_guide/extending_ghc.rst
=====================================
@@ -1719,7 +1719,7 @@ constructor from version 9.4 with the corresponding value from 9.6:
+-----------------+------------------------+
| ``ViaC`` | ``viaCBackend`` |
+-----------------+------------------------+
-| ``Interpreter`` | ``interpreterBackend`` |
+| ``Interpreter`` | ``bytecodeBackend`` |
+-----------------+------------------------+
| ``NoBackend`` | ``noBackend`` |
+-----------------+------------------------+
=====================================
ghc/Main.hs
=====================================
@@ -169,9 +169,9 @@ main' postLoadMode units dflags0 args flagWarnings = do
let dflt_backend = backend dflags0
(mode, bcknd, link)
= case postLoadMode of
- DoInteractive -> (CompManager, interpreterBackend, LinkInMemory)
- DoEval _ -> (CompManager, interpreterBackend, LinkInMemory)
- DoRun -> (CompManager, interpreterBackend, LinkInMemory)
+ DoInteractive -> (CompManager, bytecodeBackend, LinkInMemory)
+ DoEval _ -> (CompManager, bytecodeBackend, LinkInMemory)
+ DoRun -> (CompManager, bytecodeBackend, LinkInMemory)
DoMake -> (CompManager, dflt_backend, LinkBinary)
DoBackpack -> (CompManager, dflt_backend, LinkBinary)
DoMkDependHS -> (MkDepend, dflt_backend, LinkBinary)
=====================================
testsuite/driver/testglobals.py
=====================================
@@ -136,9 +136,12 @@ class TestConfig:
# Do we have interpreter support?
self.have_interp = False
+ # Do we have external interpreter support?
+ self.have_ext_interp = False
+
# Are we cross-compiling?
self.cross = False
-
+
# Does the RTS linker only support loading shared libraries?
self.interp_force_dyn = False
=====================================
testsuite/driver/testlib.py
=====================================
@@ -549,10 +549,12 @@ only_ghci = only_ways([WayName('ghci'), WayName('ghci-opt')])
# -----
def valid_way( way: WayName ) -> bool:
- if way in {'ghci', 'ghci-opt', 'ghci-ext'}:
+ if way in {'ghci', 'ghci-opt'}:
return config.have_RTS_linker
- if way == 'ghci-ext-prof':
- return config.have_RTS_linker and config.have_profiling
+ if way in {'ghci-ext'}:
+ return config.have_ext_interp
+ if way in {'ghci-ext-prof'}:
+ return config.have_ext_interp and config.have_profiling
return True
def extra_ways( ways: List[WayName] ):
=====================================
testsuite/tests/concurrent/prog001/all.T
=====================================
@@ -16,4 +16,4 @@ test('concprog001', [extra_files(['Arithmetic.hs', 'Converter.hs', 'Mult.hs', 'S
when(fast(), skip), only_ways(['threaded2']),
fragile(16604),
run_timeout_multiplier(2)],
- multimod_compile_and_run, ['Mult', ''])
+ multimod_compile_and_run, ['Mult', '-Wno-x-partial'])
=====================================
testsuite/tests/driver/T5313.hs
=====================================
@@ -7,7 +7,7 @@ main = do
-- begin initialize
df0 <- GHC.getSessionDynFlags
let df1 = df0{GHC.ghcMode = GHC.CompManager,
- GHC.backend = GHC.interpreterBackend,
+ GHC.backend = GHC.bytecodeBackend,
GHC.ghcLink = GHC.LinkInMemory,
GHC.verbosity = 0}
_ <- GHC.setSessionDynFlags df1
=====================================
testsuite/tests/ghc-api/T10052/T10052.hs
=====================================
@@ -24,7 +24,7 @@ runGhc' args act = do
logger <- getLogger
(dflags1, _leftover, _warns) <- parseDynamicFlags logger dflags0 flags
let dflags2 = dflags1 {
- backend = interpreterBackend
+ backend = bytecodeBackend
, ghcLink = LinkInMemory
, verbosity = 1
}
=====================================
testsuite/tests/ghc-api/T8639_api.hs
=====================================
@@ -11,7 +11,7 @@ main
= do { [libdir] <- getArgs
; runGhc (Just libdir) $ do
flags <- getSessionDynFlags
- setSessionDynFlags (flags{ backend = interpreterBackend, ghcLink = LinkInMemory})
+ setSessionDynFlags (flags{ backend = bytecodeBackend, ghcLink = LinkInMemory})
target <- guessTarget "T8639_api_a.hs" Nothing Nothing
setTargets [target]
load LoadAllTargets
=====================================
testsuite/tests/ghc-api/apirecomp001/myghc.hs
=====================================
@@ -37,7 +37,7 @@ main = do
prn "target nothing: ok"
dflags <- getSessionDynFlags
- setSessionDynFlags $ dflags { backend = interpreterBackend }
+ setSessionDynFlags $ dflags { backend = bytecodeBackend }
ok <- load LoadAllTargets
when (failed ok) $ error "Couldn't load A.hs in interpreted mode"
prn "target interpreted: ok"
=====================================
testsuite/tests/ghci-wasm/T26431.hs
=====================================
@@ -16,7 +16,7 @@ main = do
let dflags1 =
dflags0
{ ghcMode = CompManager,
- backend = interpreterBackend,
+ backend = bytecodeBackend,
ghcLink = LinkInMemory
}
logger <- getLogger
=====================================
testsuite/tests/ghci/linking/dyn/T3372.hs
=====================================
@@ -44,7 +44,7 @@ newGhcServer = do (libdir:_) <- getArgs
where ghc action libdir = GHC.runGhc (Just libdir) (init >> action)
init = do df <- GHC.getSessionDynFlags
GHC.setSessionDynFlags df{GHC.ghcMode = GHC.CompManager,
- GHC.backend = GHC.interpreterBackend,
+ GHC.backend = GHC.bytecodeBackend,
GHC.ghcLink = GHC.LinkInMemory,
GHC.verbosity = 0}
=====================================
testsuite/tests/ghci/should_run/PackedDataCon/packeddatacon.T
=====================================
@@ -2,9 +2,8 @@ test('PackedDataCon',
[ extra_files(['Obj.hs', 'ByteCode.hs', 'Types.hs', 'Common.hs-incl']),
req_interp,
req_bco,
- extra_ways(['ghci']),
- when(config.have_ext_interp, extra_ways(['ghci', 'ghci-ext'])),
- when(config.have_ext_interp and config.have_profiling, extra_ways(['ghci', 'ghci-ext', 'ghci-ext-prof']))
+ extra_ways(ghci_ways),
+ only_ways(ghci_ways),
],
compile_and_run,
['']
=====================================
testsuite/tests/ghci/should_run/UnboxedTuples/unboxedtuples.T
=====================================
@@ -2,9 +2,8 @@ test('UnboxedTuples',
[ extra_files(['Obj.hs', 'ByteCode.hs', 'Common.hs-incl']),
req_interp,
req_bco,
- extra_ways(['ghci']),
- when(config.have_ext_interp, extra_ways(['ghci', 'ghci-ext'])),
- when(config.have_ext_interp and config.have_profiling, extra_ways(['ghci', 'ghci-ext', 'ghci-ext-prof']))
+ only_ways(ghci_ways),
+ extra_ways(ghci_ways),
],
compile_and_run,
['']
=====================================
testsuite/tests/ghci/should_run/UnliftedDataTypeInterp/unlifteddatatypeinterp.T
=====================================
@@ -2,9 +2,8 @@ test('UnliftedDataTypeInterp',
[ extra_files(['Obj.hs', 'ByteCode.hs', 'Types.hs', 'Common.hs-incl']),
req_interp,
req_bco,
- extra_ways(['ghci']),
- when(config.have_ext_interp, extra_ways(['ghci', 'ghci-ext'])),
- when(config.have_ext_interp and config.have_profiling, extra_ways(['ghci', 'ghci-ext', 'ghci-ext-prof']))
+ only_ways(ghci_ways),
+ extra_ways(ghci_ways),
],
compile_and_run,
['']
=====================================
testsuite/tests/perf/compiler/T26425.hs
=====================================
@@ -0,0 +1,664 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+module Reproducer (strToInt) where
+
+import qualified Data.Text as T
+
+{- This program results in a nested chain of join points and cases which tests
+ primarily OccAnal and Unfolding performance.
+-}
+
+strToInt :: T.Text -> Maybe Int
+strToInt txt = case txt of
+ "0" -> Just 0
+ "1" -> Just 1
+ "2" -> Just 2
+ "3" -> Just 3
+ "4" -> Just 4
+ "5" -> Just 5
+ "6" -> Just 6
+ "7" -> Just 7
+ "8" -> Just 8
+ "9" -> Just 9
+ "10" -> Just 10
+ "11" -> Just 11
+ "12" -> Just 12
+ "13" -> Just 13
+ "14" -> Just 14
+ "15" -> Just 15
+ "16" -> Just 16
+ "17" -> Just 17
+ "18" -> Just 18
+ "19" -> Just 19
+ "20" -> Just 20
+ "21" -> Just 21
+ "22" -> Just 22
+ "23" -> Just 23
+ "24" -> Just 24
+ "25" -> Just 25
+ "26" -> Just 26
+ "27" -> Just 27
+ "28" -> Just 28
+ "29" -> Just 29
+ "30" -> Just 30
+ "31" -> Just 31
+ "32" -> Just 32
+ "33" -> Just 33
+ "34" -> Just 34
+ "35" -> Just 35
+ "36" -> Just 36
+ "37" -> Just 37
+ "38" -> Just 38
+ "39" -> Just 39
+ "40" -> Just 40
+ "41" -> Just 41
+ "42" -> Just 42
+ "43" -> Just 43
+ "44" -> Just 44
+ "45" -> Just 45
+ "46" -> Just 46
+ "47" -> Just 47
+ "48" -> Just 48
+ "49" -> Just 49
+ "50" -> Just 50
+ "51" -> Just 51
+ "52" -> Just 52
+ "53" -> Just 53
+ "54" -> Just 54
+ "55" -> Just 55
+ "56" -> Just 56
+ "57" -> Just 57
+ "58" -> Just 58
+ "59" -> Just 59
+ "60" -> Just 60
+ "61" -> Just 61
+ "62" -> Just 62
+ "63" -> Just 63
+ "64" -> Just 64
+ "65" -> Just 65
+ "66" -> Just 66
+ "67" -> Just 67
+ "68" -> Just 68
+ "69" -> Just 69
+ "70" -> Just 70
+ "71" -> Just 71
+ "72" -> Just 72
+ "73" -> Just 73
+ "74" -> Just 74
+ "75" -> Just 75
+ "76" -> Just 76
+ "77" -> Just 77
+ "78" -> Just 78
+ "79" -> Just 79
+ "80" -> Just 80
+ "81" -> Just 81
+ "82" -> Just 82
+ "83" -> Just 83
+ "84" -> Just 84
+ "85" -> Just 85
+ "86" -> Just 86
+ "87" -> Just 87
+ "88" -> Just 88
+ "89" -> Just 89
+ "90" -> Just 90
+ "91" -> Just 91
+ "92" -> Just 92
+ "93" -> Just 93
+ "94" -> Just 94
+ "95" -> Just 95
+ "96" -> Just 96
+ "97" -> Just 97
+ "98" -> Just 98
+ "99" -> Just 99
+ "100" -> Just 100
+ "101" -> Just 101
+ "102" -> Just 102
+ "103" -> Just 103
+ "104" -> Just 104
+ "105" -> Just 105
+ "106" -> Just 106
+ "107" -> Just 107
+ "108" -> Just 108
+ "109" -> Just 109
+ "110" -> Just 110
+ "111" -> Just 111
+ "112" -> Just 112
+ "113" -> Just 113
+ "114" -> Just 114
+ "115" -> Just 115
+ "116" -> Just 116
+ "117" -> Just 117
+ "118" -> Just 118
+ "119" -> Just 119
+ "120" -> Just 120
+ "121" -> Just 121
+ "122" -> Just 122
+ "123" -> Just 123
+ "124" -> Just 124
+ "125" -> Just 125
+ "126" -> Just 126
+ "127" -> Just 127
+ "128" -> Just 128
+ "129" -> Just 129
+ "130" -> Just 130
+ "131" -> Just 131
+ "132" -> Just 132
+ "133" -> Just 133
+ "134" -> Just 134
+ "135" -> Just 135
+ "136" -> Just 136
+ "137" -> Just 137
+ "138" -> Just 138
+ "139" -> Just 139
+ "140" -> Just 140
+ "141" -> Just 141
+ "142" -> Just 142
+ "143" -> Just 143
+ "144" -> Just 144
+ "145" -> Just 145
+ "146" -> Just 146
+ "147" -> Just 147
+ "148" -> Just 148
+ "149" -> Just 149
+ "150" -> Just 150
+ "151" -> Just 151
+ "152" -> Just 152
+ "153" -> Just 153
+ "154" -> Just 154
+ "155" -> Just 155
+ "156" -> Just 156
+ "157" -> Just 157
+ "158" -> Just 158
+ "159" -> Just 159
+ "160" -> Just 160
+ "161" -> Just 161
+ "162" -> Just 162
+ "163" -> Just 163
+ "164" -> Just 164
+ "165" -> Just 165
+ "166" -> Just 166
+ "167" -> Just 167
+ "168" -> Just 168
+ "169" -> Just 169
+ "170" -> Just 170
+ "171" -> Just 171
+ "172" -> Just 172
+ "173" -> Just 173
+ "174" -> Just 174
+ "175" -> Just 175
+ "176" -> Just 176
+ "177" -> Just 177
+ "178" -> Just 178
+ "179" -> Just 179
+ "180" -> Just 180
+ "181" -> Just 181
+ "182" -> Just 182
+ "183" -> Just 183
+ "184" -> Just 184
+ "185" -> Just 185
+ "186" -> Just 186
+ "187" -> Just 187
+ "188" -> Just 188
+ "189" -> Just 189
+ "190" -> Just 190
+ "191" -> Just 191
+ "192" -> Just 192
+ "193" -> Just 193
+ "194" -> Just 194
+ "195" -> Just 195
+ "196" -> Just 196
+ "197" -> Just 197
+ "198" -> Just 198
+ "199" -> Just 199
+ "200" -> Just 200
+ "201" -> Just 201
+ "202" -> Just 202
+ "203" -> Just 203
+ "204" -> Just 204
+ "205" -> Just 205
+ "206" -> Just 206
+ "207" -> Just 207
+ "208" -> Just 208
+ "209" -> Just 209
+ "210" -> Just 210
+ "211" -> Just 211
+ "212" -> Just 212
+ "213" -> Just 213
+ "214" -> Just 214
+ "215" -> Just 215
+ "216" -> Just 216
+ "217" -> Just 217
+ "218" -> Just 218
+ "219" -> Just 219
+ "220" -> Just 220
+ "221" -> Just 221
+ "222" -> Just 222
+ "223" -> Just 223
+ "224" -> Just 224
+ "225" -> Just 225
+ "226" -> Just 226
+ "227" -> Just 227
+ "228" -> Just 228
+ "229" -> Just 229
+ "230" -> Just 230
+ "231" -> Just 231
+ "232" -> Just 232
+ "233" -> Just 233
+ "234" -> Just 234
+ "235" -> Just 235
+ "236" -> Just 236
+ "237" -> Just 237
+ "238" -> Just 238
+ "239" -> Just 239
+ "240" -> Just 240
+ "241" -> Just 241
+ "242" -> Just 242
+ "243" -> Just 243
+ "244" -> Just 244
+ "245" -> Just 245
+ "246" -> Just 246
+ "247" -> Just 247
+ "248" -> Just 248
+ "249" -> Just 249
+ "250" -> Just 250
+ "251" -> Just 251
+ "252" -> Just 252
+ "253" -> Just 253
+ "254" -> Just 254
+ "255" -> Just 255
+ "256" -> Just 256
+ "257" -> Just 257
+ "258" -> Just 258
+ "259" -> Just 259
+ "260" -> Just 260
+ "261" -> Just 261
+ "262" -> Just 262
+ "263" -> Just 263
+ "264" -> Just 264
+ "265" -> Just 265
+ "266" -> Just 266
+ "267" -> Just 267
+ "268" -> Just 268
+ "269" -> Just 269
+ "270" -> Just 270
+ "271" -> Just 271
+ "272" -> Just 272
+ "273" -> Just 273
+ "274" -> Just 274
+ "275" -> Just 275
+ "276" -> Just 276
+ "277" -> Just 277
+ "278" -> Just 278
+ "279" -> Just 279
+ "280" -> Just 280
+ "281" -> Just 281
+ "282" -> Just 282
+ "283" -> Just 283
+ "284" -> Just 284
+ "285" -> Just 285
+ "286" -> Just 286
+ "287" -> Just 287
+ "288" -> Just 288
+ "289" -> Just 289
+ "290" -> Just 290
+ "291" -> Just 291
+ "292" -> Just 292
+ "293" -> Just 293
+ "294" -> Just 294
+ "295" -> Just 295
+ "296" -> Just 296
+ "297" -> Just 297
+ "298" -> Just 298
+ "299" -> Just 299
+ "300" -> Just 300
+ "301" -> Just 301
+ "302" -> Just 302
+ "303" -> Just 303
+ "304" -> Just 304
+ "305" -> Just 305
+ "306" -> Just 306
+ "307" -> Just 307
+ "308" -> Just 308
+ "309" -> Just 309
+ "310" -> Just 310
+ "311" -> Just 311
+ "312" -> Just 312
+ "313" -> Just 313
+ "314" -> Just 314
+ "315" -> Just 315
+ "316" -> Just 316
+ "317" -> Just 317
+ "318" -> Just 318
+ "319" -> Just 319
+ "320" -> Just 320
+ "321" -> Just 321
+ "322" -> Just 322
+ "323" -> Just 323
+ "324" -> Just 324
+ "325" -> Just 325
+ "326" -> Just 326
+ "327" -> Just 327
+ "328" -> Just 328
+ "329" -> Just 329
+ "330" -> Just 330
+ "331" -> Just 331
+ "332" -> Just 332
+ "333" -> Just 333
+ "334" -> Just 334
+ "335" -> Just 335
+ "336" -> Just 336
+ "337" -> Just 337
+ "338" -> Just 338
+ "339" -> Just 339
+ "340" -> Just 340
+ "341" -> Just 341
+ "342" -> Just 342
+ "343" -> Just 343
+ "344" -> Just 344
+ "345" -> Just 345
+ "346" -> Just 346
+ "347" -> Just 347
+ "348" -> Just 348
+ "349" -> Just 349
+ "350" -> Just 350
+ "351" -> Just 351
+ "352" -> Just 352
+ "353" -> Just 353
+ "354" -> Just 354
+ "355" -> Just 355
+ "356" -> Just 356
+ "357" -> Just 357
+ "358" -> Just 358
+ "359" -> Just 359
+ "360" -> Just 360
+ "361" -> Just 361
+ "362" -> Just 362
+ "363" -> Just 363
+ "364" -> Just 364
+ "365" -> Just 365
+ "366" -> Just 366
+ "367" -> Just 367
+ "368" -> Just 368
+ "369" -> Just 369
+ "370" -> Just 370
+ "371" -> Just 371
+ "372" -> Just 372
+ "373" -> Just 373
+ "374" -> Just 374
+ "375" -> Just 375
+ "376" -> Just 376
+ "377" -> Just 377
+ "378" -> Just 378
+ "379" -> Just 379
+ "380" -> Just 380
+ "381" -> Just 381
+ "382" -> Just 382
+ "383" -> Just 383
+ "384" -> Just 384
+ "385" -> Just 385
+ "386" -> Just 386
+ "387" -> Just 387
+ "388" -> Just 388
+ "389" -> Just 389
+ "390" -> Just 390
+ "391" -> Just 391
+ "392" -> Just 392
+ "393" -> Just 393
+ "394" -> Just 394
+ "395" -> Just 395
+ "396" -> Just 396
+ "397" -> Just 397
+ "398" -> Just 398
+ "399" -> Just 399
+ "400" -> Just 400
+ "401" -> Just 401
+ "402" -> Just 402
+ "403" -> Just 403
+ "404" -> Just 404
+ "405" -> Just 405
+ "406" -> Just 406
+ "407" -> Just 407
+ "408" -> Just 408
+ "409" -> Just 409
+ "410" -> Just 410
+ "411" -> Just 411
+ "412" -> Just 412
+ "413" -> Just 413
+ "414" -> Just 414
+ "415" -> Just 415
+ "416" -> Just 416
+ "417" -> Just 417
+ "418" -> Just 418
+ "419" -> Just 419
+ "420" -> Just 420
+ "421" -> Just 421
+ "422" -> Just 422
+ "423" -> Just 423
+ "424" -> Just 424
+ "425" -> Just 425
+ "426" -> Just 426
+ "427" -> Just 427
+ "428" -> Just 428
+ "429" -> Just 429
+ "430" -> Just 430
+ "431" -> Just 431
+ "432" -> Just 432
+ "433" -> Just 433
+ "434" -> Just 434
+ "435" -> Just 435
+ "436" -> Just 436
+ "437" -> Just 437
+ "438" -> Just 438
+ "439" -> Just 439
+ "440" -> Just 440
+ "441" -> Just 441
+ "442" -> Just 442
+ "443" -> Just 443
+ "444" -> Just 444
+ "445" -> Just 445
+ "446" -> Just 446
+ "447" -> Just 447
+ "448" -> Just 448
+ "449" -> Just 449
+ "450" -> Just 450
+ "451" -> Just 451
+ "452" -> Just 452
+ "453" -> Just 453
+ "454" -> Just 454
+ "455" -> Just 455
+ "456" -> Just 456
+ "457" -> Just 457
+ "458" -> Just 458
+ "459" -> Just 459
+ "460" -> Just 460
+ "461" -> Just 461
+ "462" -> Just 462
+ "463" -> Just 463
+ "464" -> Just 464
+ "465" -> Just 465
+ "466" -> Just 466
+ "467" -> Just 467
+ "468" -> Just 468
+ "469" -> Just 469
+ "470" -> Just 470
+ "471" -> Just 471
+ "472" -> Just 472
+ "473" -> Just 473
+ "474" -> Just 474
+ "475" -> Just 475
+ "476" -> Just 476
+ "477" -> Just 477
+ "478" -> Just 478
+ "479" -> Just 479
+ "480" -> Just 480
+ "481" -> Just 481
+ "482" -> Just 482
+ "483" -> Just 483
+ "484" -> Just 484
+ "485" -> Just 485
+ "486" -> Just 486
+ "487" -> Just 487
+ "488" -> Just 488
+ "489" -> Just 489
+ "490" -> Just 490
+ "491" -> Just 491
+ "492" -> Just 492
+ "493" -> Just 493
+ "494" -> Just 494
+ "495" -> Just 495
+ "496" -> Just 496
+ "497" -> Just 497
+ "498" -> Just 498
+ "499" -> Just 499
+ "500" -> Just 500
+ "501" -> Just 501
+ "502" -> Just 502
+ "503" -> Just 503
+ "504" -> Just 504
+ "505" -> Just 505
+ "506" -> Just 506
+ "507" -> Just 507
+ "508" -> Just 508
+ "509" -> Just 509
+ "510" -> Just 510
+ "511" -> Just 511
+ "512" -> Just 512
+ "513" -> Just 513
+ "514" -> Just 514
+ "515" -> Just 515
+ "516" -> Just 516
+ "517" -> Just 517
+ "518" -> Just 518
+ "519" -> Just 519
+ "520" -> Just 520
+ "521" -> Just 521
+ "522" -> Just 522
+ "523" -> Just 523
+ "524" -> Just 524
+ "525" -> Just 525
+ "526" -> Just 526
+ "527" -> Just 527
+ "528" -> Just 528
+ "529" -> Just 529
+ "530" -> Just 530
+ "531" -> Just 531
+ "532" -> Just 532
+ "533" -> Just 533
+ "534" -> Just 534
+ "535" -> Just 535
+ "536" -> Just 536
+ "537" -> Just 537
+ "538" -> Just 538
+ "539" -> Just 539
+ "540" -> Just 540
+ "541" -> Just 541
+ "542" -> Just 542
+ "543" -> Just 543
+ "544" -> Just 544
+ "545" -> Just 545
+ "546" -> Just 546
+ "547" -> Just 547
+ "548" -> Just 548
+ "549" -> Just 549
+ "550" -> Just 550
+ "551" -> Just 551
+ "552" -> Just 552
+ "553" -> Just 553
+ "554" -> Just 554
+ "555" -> Just 555
+ "556" -> Just 556
+ "557" -> Just 557
+ "558" -> Just 558
+ "559" -> Just 559
+ "560" -> Just 560
+ "561" -> Just 561
+ "562" -> Just 562
+ "563" -> Just 563
+ "564" -> Just 564
+ "565" -> Just 565
+ "566" -> Just 566
+ "567" -> Just 567
+ "568" -> Just 568
+ "569" -> Just 569
+ "570" -> Just 570
+ "571" -> Just 571
+ "572" -> Just 572
+ "573" -> Just 573
+ "574" -> Just 574
+ "575" -> Just 575
+ "576" -> Just 576
+ "577" -> Just 577
+ "578" -> Just 578
+ "579" -> Just 579
+ "580" -> Just 580
+ "581" -> Just 581
+ "582" -> Just 582
+ "583" -> Just 583
+ "584" -> Just 584
+ "585" -> Just 585
+ "586" -> Just 586
+ "587" -> Just 587
+ "588" -> Just 588
+ "589" -> Just 589
+ "590" -> Just 590
+ "591" -> Just 591
+ "592" -> Just 592
+ "593" -> Just 593
+ "594" -> Just 594
+ "595" -> Just 595
+ "596" -> Just 596
+ "597" -> Just 597
+ "598" -> Just 598
+ "599" -> Just 599
+ "600" -> Just 600
+ "601" -> Just 601
+ "602" -> Just 602
+ "603" -> Just 603
+ "604" -> Just 604
+ "605" -> Just 605
+ "606" -> Just 606
+ "607" -> Just 607
+ "608" -> Just 608
+ "609" -> Just 609
+ "610" -> Just 610
+ "611" -> Just 611
+ "612" -> Just 612
+ "613" -> Just 613
+ "614" -> Just 614
+ "615" -> Just 615
+ "616" -> Just 616
+ "617" -> Just 617
+ "618" -> Just 618
+ "619" -> Just 619
+ "620" -> Just 620
+ "621" -> Just 621
+ "622" -> Just 622
+ "623" -> Just 623
+ "624" -> Just 624
+ "625" -> Just 625
+ "626" -> Just 626
+ "627" -> Just 627
+ "628" -> Just 628
+ "629" -> Just 629
+ "630" -> Just 630
+ "631" -> Just 631
+ "632" -> Just 632
+ "633" -> Just 633
+ "634" -> Just 634
+ "635" -> Just 635
+ "636" -> Just 636
+ "637" -> Just 637
+ "638" -> Just 638
+ "639" -> Just 639
+ "640" -> Just 640
+ "641" -> Just 641
+ "642" -> Just 642
+ "643" -> Just 643
+ "644" -> Just 644
+ "645" -> Just 645
+ "646" -> Just 646
+ "647" -> Just 647
+ "648" -> Just 648
+ "649" -> Just 649
+ "650" -> Just 650
+ _ -> Nothing
=====================================
testsuite/tests/perf/compiler/all.T
=====================================
@@ -792,3 +792,8 @@ test('interpreter_steplocal',
],
ghci_script,
['interpreter_steplocal.script'])
+
+test ('T26425',
+ [ collect_compiler_stats('all',5) ],
+ compile,
+ ['-O'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f26568c2199d59b90eec7961be7d54…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f26568c2199d59b90eec7961be7d54…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
06 Oct '25
Ben Gamari pushed to branch ghc-9.14 at Glasgow Haskell Compiler / GHC
Commits:
c3bd6bc4 by Ben Gamari at 2025-10-06T11:11:10-04:00
gitlab-ci: Make RELEASE_JOB an input
Rather than an undocumented variable.
- - - - -
1 changed file:
- .gitlab-ci.yml
Changes:
=====================================
.gitlab-ci.yml
=====================================
@@ -1,3 +1,11 @@
+spec:
+ inputs:
+ release:
+ default: "no"
+ options: [ "yes", "no" ]
+
+---
+
variables:
GIT_SSL_NO_VERIFY: "1"
@@ -28,6 +36,8 @@ variables:
# Makes ci.sh isolate CABAL_DIR
HERMETIC: "YES"
+ RELEASE_JOB: $[[ inputs.release ]]
+
# Reduce XZ compression level for regular jobs (it is bumped to 9 for releases
# and nightly jobs). In my experiments I've got the following bindist size in
# the given time for each compression level (with the quick flavour):
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c3bd6bc49d5292a4c9a436d34ed529e…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c3bd6bc49d5292a4c9a436d34ed529e…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/ci-inputs] gitlab-ci: Make RELEASE_JOB an input
by Ben Gamari (@bgamari) 06 Oct '25
by Ben Gamari (@bgamari) 06 Oct '25
06 Oct '25
Ben Gamari pushed to branch wip/ci-inputs at Glasgow Haskell Compiler / GHC
Commits:
5916b6bd by Ben Gamari at 2025-10-06T11:08:53-04:00
gitlab-ci: Make RELEASE_JOB an input
Rather than an undocumented variable.
- - - - -
1 changed file:
- .gitlab-ci.yml
Changes:
=====================================
.gitlab-ci.yml
=====================================
@@ -1,3 +1,12 @@
+spec:
+ inputs:
+ release:
+ default: "no"
+ description: Release pipeline
+ options: [ "yes", "no" ]
+
+---
+
variables:
GIT_SSL_NO_VERIFY: "1"
@@ -28,6 +37,8 @@ variables:
# Makes ci.sh isolate CABAL_DIR
HERMETIC: "YES"
+ RELEASE_JOB: $[[ inputs.release ]]
+
# Reduce XZ compression level for regular jobs (it is bumped to 9 for releases
# and nightly jobs). In my experiments I've got the following bindist size in
# the given time for each compression level (with the quick flavour):
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5916b6bd5440b345b1c15d50700c149…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5916b6bd5440b345b1c15d50700c149…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/ci-inputs] gitlab-ci: Make RELEASE_JOB an input
by Ben Gamari (@bgamari) 06 Oct '25
by Ben Gamari (@bgamari) 06 Oct '25
06 Oct '25
Ben Gamari pushed to branch wip/ci-inputs at Glasgow Haskell Compiler / GHC
Commits:
3c692bba by Ben Gamari at 2025-10-06T11:05:50-04:00
gitlab-ci: Make RELEASE_JOB an input
Rather than an undocumented variable.
- - - - -
1 changed file:
- .gitlab-ci.yml
Changes:
=====================================
.gitlab-ci.yml
=====================================
@@ -1,3 +1,11 @@
+spec:
+ inputs:
+ release_job:
+ default: "no"
+ options: [ "yes", "no" ]
+
+---
+
variables:
GIT_SSL_NO_VERIFY: "1"
@@ -28,6 +36,8 @@ variables:
# Makes ci.sh isolate CABAL_DIR
HERMETIC: "YES"
+ RELEASE_JOB: $[[ inputs.release_job ]]
+
# Reduce XZ compression level for regular jobs (it is bumped to 9 for releases
# and nightly jobs). In my experiments I've got the following bindist size in
# the given time for each compression level (with the quick flavour):
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3c692bbaa472431b792e3c080d26126…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3c692bbaa472431b792e3c080d26126…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
06 Oct '25
Ben Gamari pushed to branch ghc-9.14 at Glasgow Haskell Compiler / GHC
Commits:
6be7cb39 by Ben Gamari at 2025-10-06T11:02:17-04:00
gitlab-ci: Make RELEASE_JOB an input
Rather than an undocumented variable.
- - - - -
1 changed file:
- .gitlab-ci.yml
Changes:
=====================================
.gitlab-ci.yml
=====================================
@@ -1,3 +1,11 @@
+spec:
+ inputs:
+ RELEASE_JOB:
+ default: "no"
+ options: [ "yes", "no" ]
+
+---
+
variables:
GIT_SSL_NO_VERIFY: "1"
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6be7cb39f0e4c7177b01df3725ccb9e…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6be7cb39f0e4c7177b01df3725ccb9e…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
06 Oct '25
Rodrigo Mesquita pushed new branch wip/romes/T26478 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/T26478
You're receiving this email because of your account on gitlab.haskell.org.
1
0
06 Oct '25
Rodrigo Mesquita pushed new branch wip/romes/26478-2 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/26478-2
You're receiving this email because of your account on gitlab.haskell.org.
1
0
06 Oct '25
Rodrigo Mesquita pushed new branch wip/romes/26478 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/26478
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Ben Gamari deleted branch wip/backports-9.14 at Glasgow Haskell Compiler / GHC
--
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][ghc-9.14] 55 commits: rts/Disassembler: Fix spacing of BRK_FUN
by Ben Gamari (@bgamari) 06 Oct '25
by Ben Gamari (@bgamari) 06 Oct '25
06 Oct '25
Ben Gamari pushed to branch ghc-9.14 at Glasgow Haskell Compiler / GHC
Commits:
4e77883f by Rodrigo Mesquita at 2025-10-04T21:49:06-04:00
rts/Disassembler: Fix spacing of BRK_FUN
(cherry picked from commit 53da94ff72f63b6ac09ecd16493a321843ea2c69)
- - - - -
cea17f11 by Rodrigo Mesquita at 2025-10-04T21:52:53-04:00
cleanup: Move dehydrateCgBreakInfo to Stg2Bc
This no longer has anything to do with Core.
(cherry picked from commit 79816cc4071d281d6893ad3df4c06e9cf51daee7)
- - - - -
82a5c088 by Rodrigo Mesquita at 2025-10-04T21:52:56-04:00
debugger: Fix bciPtr in Step-out
We need to use `BCO_NEXT` to move bciPtr to ix=1, because ix=0 points to
the instruction itself!
I do not understand how this didn't crash before.
(cherry picked from commit 08c0cf85abdd0cf63c64f9819cd34b42d437d114)
- - - - -
05aaaee8 by Rodrigo Mesquita at 2025-10-04T21:52:56-04:00
debugger: Allow BRK_FUNs to head case continuation BCOs
When we start executing a BCO, we may want to yield to the scheduler:
this may be triggered by a heap/stack check, context switch, or a
breakpoint. To yield, we need to put the stack in a state such that
when execution is resumed we are back to where we yielded from.
Previously, a BKR_FUN could only head a function BCO because we only
knew how to construct a valid stack for yielding from one -- simply add
`apply_interp_info` + the BCO to resume executing. This is valid because
the stack at the start of run_BCO is headed by that BCO's arguments.
However, in case continuation BCOs (as per Note [Case continuation BCOs]),
we couldn't easily reconstruct a valid stack that could be resumed
because we dropped too soon the stack frames regarding the value
returned (stg_ret) and received (stg_ctoi) by that continuation.
This is especially tricky because of the variable type and size return
frames (e.g. pointer ret_p/ctoi_R1p vs a tuple ret_t/ctoi_t2).
The trick to being able to yield from a BRK_FUN at the start of a case
cont BCO is to stop removing the ret frame headers eagerly and instead
keep them until the BCO starts executing. The new layout at the start of
a case cont. BCO is described by the new Note [Stack layout when entering run_BCO].
Now, we keep the ret_* and ctoi_* frames when entering run_BCO.
A BRK_FUN is then executed if found, and the stack is yielded as-is with
the preserved ret and ctoi frames.
Then, a case cont BCO's instructions always SLIDE off the headers of the
ret and ctoi frames, in StgToByteCode.doCase, turning a stack like
| .... |
+---------------+
| fv2 |
+---------------+
| fv1 |
+---------------+
| BCO |
+---------------+
| stg_ctoi_ret_ |
+---------------+
| retval |
+---------------+
| stg_ret_..... |
+---------------+
into
| .... |
+---------------+
| fv2 |
+---------------+
| fv1 |
+---------------+
| retval |
+---------------+
for the remainder of the BCO.
Moreover, this more uniform approach of keeping the ret and ctoi frames
means we need less ad-hoc logic concerning the variable size of
ret_tuple vs ret_p/np frames in the code generator and interpreter:
Always keep the return to cont. stack intact at the start of run_BCO,
and the statically generated instructions will take care of adjusting
it.
Unlocks BRK_FUNs at the start of case cont. BCOs which will enable a
better user-facing step-out (#26042) which is free of the bugs the
current BRK_ALTS implementation suffers from (namely, using BRK_FUN
rather than BRK_ALTS in a case cont. means we'll never accidentally end
up in a breakpoint "deeper" than the continuation, because we stop at
the case cont itself rather than on the first breakpoint we evaluate
after it).
(cherry picked from commit e7e021fa8ebb847823d2cc6c2a1ae73b94cd6fd8)
- - - - -
8b958d0d by Rodrigo Mesquita at 2025-10-04T21:53:14-04:00
BRK_FUN with InternalBreakLocs for code-generation time breakpoints
At the start of a case continuation BCO, place a BRK_FUN.
This BRK_FUN uses the new "internal breakpoint location" -- allowing us
to come up with a valid source location for this breakpoint that is not associated with a source-level tick.
For case continuation BCOs, we use the last tick seen before it as the
source location. The reasoning is described in Note [Debugger: Stepout internal break locs].
Note how T26042c, which was broken because it displayed the incorrect
behavior of the previous step out when we'd end up at a deeper level
than the one from which we initiated step-out, is now fixed.
As of this commit, BRK_ALTS is now dead code and is thus dropped.
Note [Debugger: Stepout internal break locs]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Step-out tells the interpreter to run until the current function
returns to where it was called from, and stop there.
This is achieved by enabling the BRK_FUN found on the first RET_BCO
frame on the stack (See [Note Debugger: Step-out]).
Case continuation BCOs (which select an alternative branch) must
therefore be headed by a BRK_FUN. An example:
f x = case g x of <--- end up here
1 -> ...
2 -> ...
g y = ... <--- step out from here
- `g` will return a value to the case continuation BCO in `f`
- The case continuation BCO will receive the value returned from g
- Match on it and push the alternative continuation for that branch
- And then enter that alternative.
If we step-out of `g`, the first RET_BCO on the stack is the case
continuation of `f` -- execution should stop at its start, before
selecting an alternative. (One might ask, "why not enable the breakpoint
in the alternative instead?", because the alternative continuation is
only pushed to the stack *after* it is selected by the case cont. BCO)
However, the case cont. BCO is not associated with any source-level
tick, it is merely the glue code which selects alternatives which do
have source level ticks. Therefore, we have to come up at code
generation time with a breakpoint location ('InternalBreakLoc') to
display to the user when it is stopped there.
Our solution is to use the last tick seen just before reaching the case
continuation. This is robust because a case continuation will thus
always have a relevant breakpoint location:
- The source location will be the last source-relevant expression
executed before the continuation is pushed
- So the source location will point to the thing you've just stepped
out of
- Doing :step-local from there will put you on the selected
alternative (which at the source level may also be the e.g. next
line in a do-block)
Examples, using angle brackets (<<...>>) to denote the breakpoint span:
f x = case <<g x>> {- step in here -} of
1 -> ...
2 -> ...>
g y = <<...>> <--- step out from here
...
f x = <<case g x of <--- end up here, whole case highlighted
1 -> ...
2 -> ...>>
doing :step-local ...
f x = case g x of
1 -> <<...>> <--- stop in the alternative
2 -> ...
A second example based on T26042d2, where the source is a do-block IO
action, optimised to a chain of `case expressions`.
main = do
putStrLn "hello1"
<<f>> <--- step-in here
putStrLn "hello3"
putStrLn "hello4"
f = do
<<putStrLn "hello2.1">> <--- step-out from here
putStrLn "hello2.2"
...
main = do
putStrLn "hello1"
<<f>> <--- end up here again, the previously executed expression
putStrLn "hello3"
putStrLn "hello4"
doing step/step-local ...
main = do
putStrLn "hello1"
f
<<putStrLn "hello3">> <--- straight to the next line
putStrLn "hello4"
Finishes #26042
(cherry picked from commit ade3c1e60025c1f2e389742b526a141e5346c6b1)
- - - - -
fce53506 by Rodrigo Mesquita at 2025-10-04T21:53:15-04:00
debugger: Re-use the last BreakpointId whole in step-out
Previously, to come up with a location to stop at for `:stepout`, we
would store the location of the last BreakpointId surrounding the
continuation, as described by Note [Debugger: Stepout internal break locs].
However, re-using just the location from the last source breakpoint
isn't sufficient to provide the necessary information in the break
location. Specifically, it wouldn't bind any variables at that location.
Really, there is no reason not to re-use the last breakpoint wholesale,
and re-use all the information we had there. Step-out should behave just
as if we had stopped at the call, but s.t. continuing will not
re-execute the call.
This commit updates the CgBreakInfo to always store a BreakpointId, be
it the original one or the one we're emulating (for step-out).
It makes variable bindings on :stepout work
(cherry picked from commit c66910c06d63c1fe0b1c87d42a0cac8c1db260eb)
- - - - -
33da3a6a by Ben Gamari at 2025-10-04T21:53:56-04:00
docs: Further release notes clean-ups
- - - - -
49e39957 by Ben Gamari at 2025-10-04T21:53:56-04:00
users-guide: Add missing libraries to release notes
Fixes #26421.
- - - - -
d329b8a2 by sheaf at 2025-10-04T21:53:56-04:00
Revert "Remove hptAllFamInstances usage during upsweep"
This reverts commit 3bf6720eff5e86e673568e756161e6d6150eb440.
(cherry picked from commit 0975d2b6c0747cd40abb4e881b2fb086cbc93726)
- - - - -
9fe605b3 by soulomoon at 2025-10-04T21:53:56-04:00
Family consistency checks: add test for #26154
This commit adds the test T26154, to make sure that GHC doesn't crash
when performing type family consistency checks. This test case
was extracted from Agda.
Fixes #26154
(cherry picked from commit 0cf341761fa2b506868a62a0e20a6214eb275be0)
- - - - -
4e74eaf3 by Simon Peyton Jones at 2025-10-05T08:16:06-04:00
Report solid equality errors before custom errors
This MR fixes #26255 by
* Reporting solid equality errors like
Int ~ Bool
before "custom type errors". See comments in `report1` in
`reportWanteds`
* Suppressing errors that arise from superclasses of
Wanteds. See (SCE1) in Note [Suppressing confusing errors]
More details in #26255.
(cherry picked from commit ba210d981b0812aea604f884d3c0aada4c8ca75c)
- - - - -
6b12b03b by Simon Peyton Jones at 2025-10-05T08:16:06-04:00
Fix a scoping error in Specialise
This small patch fixes #26329, which triggered a scoping error.
Test is in T21391, with -fpolymorphic-specialisation enabled
(cherry picked from commit b62491405ae851ae514afe18d51f0fe7fbefebf3)
- - - - -
d9d6ddaf by Ben Gamari at 2025-10-05T08:16:06-04:00
Add primop to annotate the call stack with arbitrary data
We introduce a new primop `annotateStack#` which allows us to push
arbitrary data onto the call-stack.
This allows us to extract the data later when decoding the stack, for
example when an exception is thrown, showing more information to the
user without having to annotate the full call-stack with `HasCallStack`
constraints.
A new stack frame value is introduced `AnnFrame`, which consists of
nothing but a generic payload.
The primop has a small wrapper API that allows users to annotate their
call-stack in programs.
There is a pure API and an IO-based one. The former is a little bit
dubious, as it affects the evaluation of a program, so use with care.
The latter is "safe", as it doesn't change the evaluation of the
program.
The stack annotation mechanism is similarly implemented to the
`ExceptionAnnotation` and `Exception`, there is a typeclass to indicate
something can be pushed onto the call-stack and all values are wrapped
in the existential `SomeStackAnnotation`, which recover the type of the
annotation payload.
There is currently no builtin way to show the stack annotations when
`Backtraces` are displayed (i.e., when showing stack traces to the user),
which we will address in a follow-up MR.
-------------------------
Metric Increase:
ghc_experimental_so
-------------------------
We increase the size of the package, so this is not unreasonable.
Co-Authored-By: fendor <fendor(a)posteo.de>
Co-Authored-By: Ben Gamari <bgamari.foss(a)gmail.com>
(cherry picked from commit 774fec37d37fd9f31a3742f684b2b5621628f5bf)
- - - - -
299095a8 by Rodrigo Mesquita at 2025-10-05T08:16:06-04:00
bytecode: Use 32bits for breakpoint index
Fixes #26325
(cherry picked from commit e368e24779f8a7bf110a025383db23521b313407)
- - - - -
152c335a by fendor at 2025-10-05T08:16:06-04:00
Move stack decoding logic from ghc-heap to ghc-internal
The stack decoding logic in `ghc-heap` is more sophisticated than the one
currently employed in `CloneStack`. We want to use the stack decoding
implementation from `ghc-heap` in `base`.
We cannot simply depend on `ghc-heap` in `base` due do bootstrapping
issues.
Thus, we move the code that is necessary to implement stack decoding to
`ghc-internal`. This is the right location, as we don't want to add a
new API to `base`.
Moving the stack decoding logic and re-exposing it in ghc-heap is
insufficient, though, as we have a dependency cycle between.
* ghc-heap depends on stage1:ghc-internal
* stage0:ghc depends on stage0:ghc-heap
To fix this, we remove ghc-heap from the set of `stage0` dependencies.
This is not entirely straight-forward, as a couple of boot dependencies,
such as `ghci` depend on `ghc-heap`.
Luckily, the boot compiler of GHC is now >=9.10, so we can migrate `ghci`
to use `ghc-internal` instead of `ghc-heap`, which already exports the
relevant modules.
However, we cannot 100% remove ghc's dependency on `ghc-heap`, since
when we compile `stage0:ghc`, `stage1:ghc-internal` is not yet
available.
Thus, when we compile with the boot-compiler, we still depend on an
older version of `ghc-heap`, and only use the modules from `ghc-internal`,
if the `ghc-internal` version is recent enough.
-------------------------
Metric Increase:
T24602_perf_size
T25046_perf_size_gzip
T25046_perf_size_unicode
T25046_perf_size_unicode_gzip
size_hello_artifact
size_hello_artifact_gzip
size_hello_unicode
size_hello_unicode_gzip
-------------------------
These metric increases are unfortunate, they are most likely caused by
the larger (literally in terms of lines of code) stack decoder implementation
that are now linked into hello-word binaries.
On linux, it is almost a 10% increase, which is considerable.
(cherry picked from commit 26dbcf616378afed9da9d50b5357786f3bd7ff9d)
- - - - -
b965fa76 by Ben Gamari at 2025-10-05T08:16:06-04:00
ghci: Fix CPP guarding Binary HalfWord instance
- - - - -
766a1060 by fendor at 2025-10-05T08:16:06-04:00
Implement `decode` in terms of `decodeStackWithIpe`
Uses the more efficient stack decoder implementation.
(cherry picked from commit bd80bb7013b1c2446557a56779c88e7ad1a06259)
- - - - -
45b1a0e4 by fendor at 2025-10-05T08:16:06-04:00
Remove stg_decodeStackzh
(cherry picked from commit 2444116517515ce7bc6bf7ac8479e919d945ed6a)
- - - - -
ec5b08f4 by fendor at 2025-10-05T08:16:06-04:00
Expose Stack Annotation frames in IPE backtraces by default
When decoding the Haskell-native call stack and displaying the IPE information
for the stack frames, we print the `StackAnnotation` of the `AnnFrame` by default.
This means, when an exception is thrown, any intermediate stack annotations will
be displayed in the `IPE Backtrace`.
Example backtrace:
```
Exception: ghc-internal:GHC.Internal.Exception.ErrorCall:
Oh no!
IPE backtrace:
annotateCallStackIO, called at app/Main.hs:48:10 in backtrace-0.1.0.0-inplace-server:Main
annotateCallStackIO, called at app/Main.hs:46:13 in backtrace-0.1.0.0-inplace-server:Main
Main.handler (app/Main.hs:(46,1)-(49,30))
Main.liftIO (src/Servant/Server/Internal/Handler.hs:30:36-42)
Servant.Server.Internal.Delayed.runHandler' (src/Servant/Server/Internal/Handler.hs:27:31-41)
Control.Monad.Trans.Resource.runResourceT (./Control/Monad/Trans/Resource.hs:(192,14)-(197,18))
Network.Wai.Handler.Warp.HTTP1.processRequest (./Network/Wai/Handler/Warp/HTTP1.hs:195:20-22)
Network.Wai.Handler.Warp.HTTP1.processRequest (./Network/Wai/Handler/Warp/HTTP1.hs:(195,5)-(203,31))
Network.Wai.Handler.Warp.HTTP1.http1server.loop (./Network/Wai/Handler/Warp/HTTP1.hs:(141,9)-(157,42))
HasCallStack backtrace:
error, called at app/Main.hs:48:32 in backtrace-0.1.0.0-inplace-server:Main
```
The first two entries have been added by `annotateCallStackIO`, defined in `annotateCallStackIO`.
(cherry picked from commit 26e0db16365059f0fdfe63b773852df45ebda913)
- - - - -
97ae7bed by Moritz Angermann at 2025-10-05T08:16:06-04:00
Improve mach-o relocation information
This change adds more information about the symbol and addresses
we try to relocate in the linker. This significantly helps when
deubbging relocation issues reported by users.
(cherry picked from commit 1537784bd4928f5ae60504e8ef467279fe541875)
- - - - -
e4ebc0a8 by Moritz Angermann at 2025-10-05T08:16:06-04:00
test.mk expect GhcLeadingUnderscore, not LeadingUnderscore (in line with the other Ghc prefixed variables.
(cherry picked from commit 4e67855b01853bc4a23810b361061eceb1c49efd)
- - - - -
14f3fb70 by Moritz Angermann at 2025-10-05T08:16:06-04:00
testsuite: Fix broken exec_signals_child.c
There is no signal 0. The signal mask is 1-32.
(cherry picked from commit c1cdd26507fa0b7cb7585af5a7b2ec5b1422d385)
- - - - -
10813ad9 by Moritz Angermann at 2025-10-05T08:16:06-04:00
testsuite: clarify Windows/Darwin locale rationale for skipping T6037 T2507 T8959a
(cherry picked from commit 99ac335c54b648d04ced28e2a4d3840871bf9d15)
- - - - -
8a3dd374 by Moritz Angermann at 2025-10-05T08:16:06-04:00
Skip broken tests on macOS (due to leading underscore not handled properly in the expected output.)
(cherry picked from commit 0e8fa77a72c601c9f4ee661bb9f335fff245885a)
- - - - -
f20ac762 by Cheng Shao at 2025-10-05T08:16:07-04:00
rel-eng: update alpine images to 3.22
This patch is a part of #25876 and updates alpine images to 3.22,
while still retaining 3.12 for x86_64 fully_static bindists.
-------------------------
Metric Decrease:
MultiComponentModulesRecomp
-------------------------
(cherry picked from commit d17257edc178c66b930ba279133f462962702470)
- - - - -
8229bb71 by Sylvain Henry at 2025-10-05T08:16:07-04:00
T16180: indicate that the stack isn't executable
(cherry picked from commit db3276bb5a2597bcaf8f830926298935066aeee6)
- - - - -
13c6e587 by Sylvain Henry at 2025-10-05T08:16:07-04:00
Fix some tests (statically linked GHC vs libc)
When GHC is linked statically, the stdout C global variable that GHC uses
isn't shared with the stdout C global variable used by loaded code.
As a consequence, the latter must be explicitly flushed because GHC
won't flush it before exiting.
(cherry picked from commit 11eeeba7dd50d16c8c7d62165d006bba8fa339a9)
- - - - -
4c46a989 by Sylvain Henry at 2025-10-05T08:16:07-04:00
Testsuite: fix debug_rts detection
Running the testsuite without Hadrian should set config.debug_rts
correctly too.
(cherry picked from commit 80a07571623a6fe7692c08dbdee440ff90ce98c2)
- - - - -
cbc1317d by Simon Peyton Jones at 2025-10-05T08:16:07-04:00
Solve forall-constraints via an implication, again
In this earlier commit:
commit 953fd8f1dc080f1c56e3a60b4b7157456949be29
Author: Simon Peyton Jones <simon.peytonjones(a)gmail.com>
Date: Mon Jul 21 10:06:43 2025 +0100
Solve forall-constraints immediately, or not at all
I used a all-or-nothing strategy for quantified constraints
(aka forall-constraints). But alas that fell foul of #26315,
and #26376.
So this MR goes back to solving a quantified constraint by
turning it into an implication; UNLESS we are simplifying
constraints from a SPECIALISE pragma, in which case the
all-or-nothing strategy is great. See:
Note [Solving a Wanted forall-constraint]
Other stuff in this MR:
* TcSMode becomes a record of flags, rather than an enumeration
type; much nicer.
* Some fancy footwork to avoid error messages worsening again
(The above MR made them better; we want to retain that.)
See `GHC.Tc.Errors.Ppr.pprQCOriginExtra`.
-------------------------
Metric Decrease:
T24471
-------------------------
(cherry picked from commit 14123ee646f2b9738a917b7cec30f9d3941c13de)
- - - - -
3046e8fe by Simon Peyton Jones at 2025-10-05T08:16:07-04:00
Add a test case for #26396
...same bug ast #26315
(cherry picked from commit e6c192e2ccdc6e7ac939ea70d891f176109c60e2)
- - - - -
98006796 by Cheng Shao at 2025-10-05T08:16:07-04:00
Revert "wasm: add brotli compression for ghci browser mode"
This reverts commit 731217ce68a1093b5f9e26a07d5bd2cdade2b352.
Benchmarks show non-negligible overhead when browser runs on the same
host, which is the majority of actual use cases.
(cherry picked from commit 42a189603e2e768795cb1684e1aa53ca840c0907)
- - - - -
2649aeea by Cheng Shao at 2025-10-05T08:16:07-04:00
wasm: remove etag logic in ghci browser mode web server
This commit removes the etag logic in dyld script's ghci browser mode
web server. It was meant to support caching logic of wasm shared
libraries, but even if the port is manually specified to make caching
even relevant, for localhost the extra overhead around etag logic is
simply not worth it according to benchmarks.
(cherry picked from commit e6755b9fd10708057dfe1e52a931a579c417c3cf)
- - - - -
4400bfd4 by Sylvain Henry at 2025-10-05T08:16:07-04:00
Print fully qualified unit names in name mismatch
It's more user-friendly to directly print the right thing instead of
requiring the user to retry with the additional `-dppr-debug` flag.
(cherry picked from commit 54b5950ebfed24429fae5111896ffc1f10750d08)
- - - - -
e75d8269 by Stefan Schulze Frielinghaus at 2025-10-05T08:16:07-04:00
rts: Fix alignment for gen_workspace #26334
After a0fa4941903272c48b050d24e93eec819eff51bd bootstrap is broken on
s390x and errors out with
rts/sm/GCThread.h:207:5: error:
error: alignment of array elements is greater than element size
207 | gen_workspace gens[];
| ^~~~~~~~~~~~~
The alignment constraint is applied via the attribute to the type
gen_workspace and leaves the underlying type struct gen_workspace_
untouched. On Aarch64, x86, and s390x the struct has a size of 128
bytes. On Aarch64 and x86 the alignments of 128 and 64 are divisors of
the size, respectively, which is why the type is a viable member type
for an array. However, on s390x, the alignment is 256 and therefore is
not a divisor of the size and hence cannot be used for arrays.
Basically I see two fixes here. Either decrease the alignment
requirement on s390x, or by applying the alignment constraint on the
struct itself. The former might affect performance as noted in
a0fa4941903272c48b050d24e93eec819eff51bd. The latter introduces padding
bits whenever necessary in order to ensure that
sizeof(gen_workspace[N])==N*sizeof(gen_workspace) holds which is done by
this patch.
(cherry picked from commit 6f63f57b86fffc8a9102b91a18a6de5bb4f8b7f0)
- - - - -
cd181042 by Cheng Shao at 2025-10-05T08:16:07-04:00
ghc-internal: fix codepages program
codepages was not properly updated during the base -> ghc-internal
migration, this commit fixes it.
(cherry picked from commit a4ff12bb8657c291a36f09bf2ee6a3798366cbb3)
- - - - -
278e19b5 by Cheng Shao at 2025-10-05T08:16:07-04:00
ghc-internal: relax ucd2haskell cabal upper bounds
This commit relaxes ucd2haskell cabal upper bounds to make it runnable
via ghc 9.12/9.14.
(cherry picked from commit 7e094def054d4a283e55f96167b3ab9eb8c3b4ea)
- - - - -
066e3321 by Cheng Shao at 2025-10-05T08:16:07-04:00
ghc-internal: update to unicode 17.0.0
This commit updates the generated code in ghc-internal to match
unicode 17.0.0.
(cherry picked from commit 7077c9f76ebadedefd763078e7f7c42201b8a4b4)
- - - - -
03b86511 by sheaf at 2025-10-05T08:16:07-04:00
Bad record update msg: allow out-of-scope datacons
This commit ensures that, when we encounter an invalid record update
(because no constructor exists which contains all of the record fields
mentioned in the record update), we graciously handle the situation in
which the constructors themselves are not in scope. In that case,
instead of looking up the constructors in the GlobalRdrEnv, directly
look up their GREInfo using the lookupGREInfo function.
Fixes #26391
(cherry picked from commit cef8938f3c0d22583f01d5ea29e6109bccd36040)
- - - - -
5500a1c5 by sheaf at 2025-10-05T08:16:07-04:00
Improve Notes about disambiguating record updates
This commit updates the notes [Disambiguating record updates] and
[Type-directed record disambiguation], in particular adding more
information about the deprecation status of type-directed disambiguation
of record updates.
(cherry picked from commit a2d9d7c2073867ee0cabb8d49f93246d95ec0b09)
- - - - -
b9d0cc95 by Ben Gamari at 2025-10-05T08:16:07-04:00
StgToByteCode: Don't assume that data con workers are nullary
Previously StgToByteCode assumed that all data-con workers were of a
nullary representation. This is not a valid assumption, as seen
in #23210, where an unsaturated application of a unary data
constructor's worker resulted in invalid bytecode. Sadly, I have not yet
been able to reduce a minimal testcase for this.
Fixes #23210.
(cherry picked from commit d1d9e39ec293cd1d2b539b8246a349b539c6a61a)
- - - - -
cfbf5c16 by Ben Gamari at 2025-10-05T08:16:07-04:00
testsuite: Mark T23146* as unbroken
(cherry picked from commit 3eeecd508ef80812bc8ee84ab83f496f5030d59b)
- - - - -
77eec87a by Cheng Shao at 2025-10-05T08:16:07-04:00
rts: remove obsolete CC_SUPPORTS_TLS logic
This patch removes obsolete CC_SUPPORTS_TLS logic throughout the rts,
given __thread is now uniformly supported by C toolchains of all
platforms we currently support.
(cherry picked from commit 0f034942724233e1457549123b46880f7b93e805)
- - - - -
b97f8f28 by Cheng Shao at 2025-10-05T08:16:07-04:00
rts: remove obsolete HAS_VISIBILITY_HIDDEN logic
This patch removes obsolete HAS_VISIBILITY_HIDDEN logic throughout the
rts, given __attribute__((visibility("hidden"))) is uniformly
supported by C toolchains of all platforms we currently support.
(cherry picked from commit ef7056554df5603ec4d1e33193abe953970e6ab3)
- - - - -
e020642e by Cheng Shao at 2025-10-05T08:16:07-04:00
rts: remove -O3 pragma hack in Hash.c
This patch removes an obsolete gcc pragma to specify -O3 in Hash.c.
Hadrian already passes the right flag.
(cherry picked from commit 9fdc1f7d855cc61f90de909875f6ae0d6798dca7)
- - - - -
7830b7c0 by Cheng Shao at 2025-10-05T08:16:07-04:00
rts: remove obsolete COMPILING_WINDOWS_DLL logic
This patch removes obsolete COMPILING_WINDOWS_DLL logic throughout the
rts. They were once used for compiling to win32 DLLs, but we haven't
been able to compile Haskell units to win32 DLLs for many years now,
due to PE format's restriction of no more than 65536 exported symbols
in a single DLL.
(cherry picked from commit b8cfa8f741729ef123569fb321c4b2ab4a1a941c)
- - - - -
e0837350 by Cheng Shao at 2025-10-05T08:16:07-04:00
wasm: bump browser_wasi_shim to 0.4.2
This patch bumps the browser_wasi_shim dependency of wasm dyld script
to 0.4.2.
(cherry picked from commit bb760611630402a1349b1952e345d879f83e4821)
- - - - -
ef990096 by Vladislav Zavialov at 2025-10-05T08:16:07-04:00
Fix keyword in ExplicitNamespaces error message (#26418)
Consider this module header and the resulting error:
{-# LANGUAGE NoExplicitNamespaces #-}
module T26418 (data HeadC) where
-- error: [GHC-47007]
-- Illegal keyword 'type'
Previously, the error message would mention 'type' (as shown above),
even though the user wrote 'data'. This has now been fixed.
The error location has also been corrected: it is now reported at the
keyword position rather than at the position of the associated
import/export item.
(cherry picked from commit 4a8fed75e2094f9ae2af27bf86298873316c3acb)
- - - - -
621dcf5e by Cheng Shao at 2025-10-05T08:16:07-04:00
wasm: fix dyld handling for forward declared GOT.func items
This patch fixes wasm shared linker's handling of forward declared
GOT.func items, see linked issue for details. Also adds T26430 test to
witness the fix. Fixes #26430.
Co-authored-by: Codex <codex(a)openai.com>
(cherry picked from commit 867c26755e8855c6df949e65df0c2aebc9da64c3)
- - - - -
cca7277a by Cheng Shao at 2025-10-05T08:16:07-04:00
rts: remove obsolete __GNUC__ related logic
This patch removes obsolete `__GNUC__` related logic, given on any
currently supported platform and toolchain, `__GNUC__ >= 4` is
universally true. Also pulls some other weeds and most notably, use
`__builtin___clear_cache` for clang as well, since clang has supported
this gcc intrinsic since 2014, see
https://github.com/llvm/llvm-project/commit/c491a8d4577052bc6b3b4c72a7db6a7….
(cherry picked from commit 67de53a6ced23caad640d2c7421089242f0dfb76)
- - - - -
ab7da811 by Brandon Chinn at 2025-10-05T08:16:07-04:00
Fix tabs in string gaps (#26415)
Tabs in string gaps were broken in bb030d0d because previously, string gaps were manually parsed, but now it's lexed by the usual Alex grammar and post-processed after successful lexing.
It broke because of a discrepancy between GHC's lexer grammar and the Haskell Report. The Haskell Report includes tabs in whitechar:
whitechar → newline | vertab | space | tab | uniWhite
$whitechar used to include tabs until 18 years ago, when it was removed in order to exclude tabs from $white_no_nl in order to warn on tabs: 6e202120. In this MR, I'm adding \t back into $whitechar, and explicitly excluding \t from the $white_no_nl+ rule ignoring all whitespace in source code, which more accurately colocates the "ignore all whitespace except tabs, which is handled in the next line" logic.
As a side effect of this MR, tabs are now allowed in pragmas; currently, a pragma written as {-# \t LANGUAGE ... #-} is interpreted as the tab character being the pragma name, and GHC warns "Unrecognized pragma". With this change, tabs are ignored as whitespace, which more closely matches the Report anyway.
(cherry picked from commit e9c5e46ffdb3cd8725e2ffdc2c440ea57af97bac)
- - - - -
5f02a002 by Cheng Shao at 2025-10-05T08:16:07-04:00
hadrian: fix GHC.Platform.Host generation for cross stage1
This patch fixes incorrectly GHC.Platform.Host generation logic for
cross stage1 in hadrian (#26449). Also adds T26449 test case to
witness the fix.
Co-authored-by: Codex <codex(a)openai.com>
(cherry picked from commit 8cbe006ad09d5a64e4a3cdf4c91a8b81ff1511be)
- - - - -
d3d7df72 by Ben Gamari at 2025-10-05T08:16:07-04:00
base: Update changelog to reflect timing of IOPort# removal
This change will make 9.14 afterall.
(cherry picked from commit e05c496cf44c0cc86dcfa8ad8c5b024e44d8e4b4)
- - - - -
e299eac9 by Simon Peyton Jones at 2025-10-05T08:16:08-04:00
Fix buglet in GHC.Core.Unify.uVarOrFam
We were failing to match two totally-equal types!
This led to #26457.
(cherry picked from commit 9c293544a8b127aef3b4089f7e5cc21cb51a9946)
- - - - -
a42cb5d7 by Cheng Shao at 2025-10-05T08:16:08-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.
(cherry picked from commit 6992ac097b9da989f125f896afe21b75dba8b4c9)
- - - - -
d5836f95 by Ben Gamari at 2025-10-05T08:16:08-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.
(cherry picked from commit 39eaaaba5356e3fc9218d8e27375d6de24778cbc)
- - - - -
283 changed files:
- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Breakpoints.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Pmc/Solver.hs
- compiler/GHC/Iface/Errors/Ppr.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/Lexer/String.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/Types.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Heap/Inspect.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/Tc/Deriv/Utils.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Instance/Family.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/Solver/Solve.hs-boot
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Zonk/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Unit/Home/Graph.hs
- compiler/GHC/Unit/Home/PackageTable.hs
- compiler/GHC/Unit/State.hs
- compiler/ghc.cabal.in
- docs/users_guide/9.14.1-notes.rst
- ghc/GHCi/UI.hs
- hadrian/src/Oracles/TestSettings.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Rules/ToolArgs.hs
- hadrian/src/Settings/Default.hs
- libraries/base/changelog.md
- libraries/base/src/GHC/Stack/CloneStack.hs
- libraries/base/tests/unicode002.stdout
- libraries/base/tests/unicode003.stdout
- libraries/ghc-experimental/ghc-experimental.cabal.in
- + libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs
- libraries/ghc-heap/GHC/Exts/Heap/ClosureTypes.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- + libraries/ghc-heap/GHC/Exts/Heap/Constants.hs
- + libraries/ghc-heap/GHC/Exts/Heap/InfoTable.hs
- + libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hs
- + libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hs
- libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs
- libraries/ghc-heap/GHC/Exts/Stack.hs
- + libraries/ghc-heap/GHC/Exts/Stack/Constants.hs
- libraries/ghc-heap/GHC/Exts/Stack/Decode.hs
- libraries/ghc-heap/ghc-heap.cabal.in
- libraries/ghc-heap/cbits/HeapPrim.cmm → libraries/ghc-internal/cbits/HeapPrim.cmm
- libraries/ghc-heap/cbits/Stack.cmm → libraries/ghc-internal/cbits/Stack.cmm
- libraries/ghc-internal/cbits/StackCloningDecoding.cmm
- libraries/ghc-heap/cbits/Stack_c.c → libraries/ghc-internal/cbits/Stack_c.c
- libraries/ghc-internal/cbits/atomic.c
- libraries/ghc-internal/cbits/ctz.c
- libraries/ghc-internal/codepages/MakeTable.hs
- libraries/ghc-internal/codepages/Makefile
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/jsbits/base.js
- libraries/ghc-internal/src/GHC/Internal/ClosureTypes.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- + libraries/ghc-internal/src/GHC/Internal/Heap/Closures.hs
- libraries/ghc-heap/GHC/Exts/Heap/Constants.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/Constants.hsc
- libraries/ghc-heap/GHC/Exts/Heap/InfoTable.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/InfoTable.hsc
- libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/InfoTable/Types.hsc
- libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/InfoTableProf.hsc
- + libraries/ghc-internal/src/GHC/Internal/Heap/ProfInfo/Types.hs
- + libraries/ghc-internal/src/GHC/Internal/Stack/Annotation.hs
- libraries/ghc-internal/src/GHC/Internal/Stack/CloneStack.hs
- libraries/ghc-heap/GHC/Exts/Stack/Constants.hsc → libraries/ghc-internal/src/GHC/Internal/Stack/Constants.hsc
- + libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs
- libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs
- + libraries/ghc-internal/tests/stack-annotation/Makefile
- + libraries/ghc-internal/tests/stack-annotation/TestUtils.hs
- + libraries/ghc-internal/tests/stack-annotation/all.T
- + libraries/ghc-internal/tests/stack-annotation/ann_frame001.hs
- + libraries/ghc-internal/tests/stack-annotation/ann_frame001.stdout
- + libraries/ghc-internal/tests/stack-annotation/ann_frame002.hs
- + libraries/ghc-internal/tests/stack-annotation/ann_frame002.stdout
- + libraries/ghc-internal/tests/stack-annotation/ann_frame003.hs
- + libraries/ghc-internal/tests/stack-annotation/ann_frame003.stdout
- + libraries/ghc-internal/tests/stack-annotation/ann_frame004.hs
- + libraries/ghc-internal/tests/stack-annotation/ann_frame004.stdout
- libraries/ghc-internal/tools/ucd2haskell/ucd.sh
- libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal
- libraries/ghc-internal/tools/ucd2haskell/unicode_version
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- libraries/ghci/ghci.cabal.in
- − m4/fp_visibility_hidden.m4
- rts/BeginPrivate.h
- + rts/BuiltinClosures.c
- + rts/BuiltinClosures.h
- rts/CloneStack.c
- rts/CloneStack.h
- rts/ClosureFlags.c
- rts/Disassembler.c
- rts/EndPrivate.h
- rts/Hash.c
- rts/Interpreter.c
- rts/LdvProfile.c
- rts/PrimOps.cmm
- rts/Printer.c
- rts/Profiling.c
- rts/RetainerProfile.c
- − rts/RtsDllMain.c
- − rts/RtsDllMain.h
- rts/RtsStartup.c
- rts/RtsSymbols.c
- rts/StgMiscClosures.cmm
- rts/Task.c
- rts/Task.h
- rts/TraverseHeap.c
- rts/configure.ac
- rts/include/Rts.h
- rts/include/RtsAPI.h
- rts/include/Stg.h
- rts/include/rts/Bytecodes.h
- rts/include/rts/Constants.h
- rts/include/rts/OSThreads.h
- rts/include/rts/Types.h
- rts/include/rts/storage/ClosureTypes.h
- rts/include/rts/storage/Closures.h
- rts/include/stg/DLL.h
- rts/include/stg/MiscClosures.h
- rts/js/profiling.js
- rts/linker/MachO.c
- rts/posix/OSThreads.c
- rts/rts.cabal
- rts/sm/BlockAlloc.c
- rts/sm/Compact.c
- rts/sm/Evac.c
- rts/sm/Evac.h
- rts/sm/GCTDecl.h
- rts/sm/GCThread.h
- rts/sm/NonMovingMark.c
- rts/sm/Sanity.c
- rts/sm/Scav.c
- rts/sm/Storage.c
- rts/win32/OSThreads.c
- testsuite/ghc-config/ghc-config.hs
- testsuite/mk/test.mk
- testsuite/tests/backpack/should_fail/bkpfail11.stderr
- testsuite/tests/backpack/should_fail/bkpfail43.stderr
- testsuite/tests/codeGen/should_run/T23146/all.T
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- + testsuite/tests/cross/should_run/T26449.hs
- + testsuite/tests/cross/should_run/all.T
- + testsuite/tests/deriving/should_compile/T26396.hs
- testsuite/tests/deriving/should_compile/all.T
- testsuite/tests/deriving/should_fail/T12768.stderr
- testsuite/tests/deriving/should_fail/T1496.stderr
- testsuite/tests/deriving/should_fail/T21302.stderr
- testsuite/tests/deriving/should_fail/T22696b.stderr
- testsuite/tests/deriving/should_fail/T5498.stderr
- testsuite/tests/deriving/should_fail/T7148.stderr
- testsuite/tests/deriving/should_fail/T7148a.stderr
- testsuite/tests/driver/all.T
- testsuite/tests/ffi/should_run/T1288_c.c
- testsuite/tests/ffi/should_run/T1288_ghci_c.c
- testsuite/tests/ffi/should_run/T2276_c.c
- testsuite/tests/ffi/should_run/T2276_ghci_c.c
- + testsuite/tests/ghci-wasm/Makefile
- + testsuite/tests/ghci-wasm/T26430.hs
- + testsuite/tests/ghci-wasm/T26430A.c
- + testsuite/tests/ghci-wasm/T26430B.c
- + testsuite/tests/ghci-wasm/all.T
- testsuite/tests/ghci.debugger/scripts/T26042b.script
- testsuite/tests/ghci.debugger/scripts/T26042b.stdout
- testsuite/tests/ghci.debugger/scripts/T26042c.script
- testsuite/tests/ghci.debugger/scripts/T26042c.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042d2.hs
- + testsuite/tests/ghci.debugger/scripts/T26042d2.script
- + testsuite/tests/ghci.debugger/scripts/T26042d2.stdout
- testsuite/tests/ghci.debugger/scripts/T26042e.stdout
- testsuite/tests/ghci.debugger/scripts/T26042f.script
- testsuite/tests/ghci.debugger/scripts/T26042f1.stdout
- testsuite/tests/ghci.debugger/scripts/T26042f2.stdout
- testsuite/tests/ghci.debugger/scripts/T26042g.stdout
- testsuite/tests/ghci.debugger/scripts/all.T
- testsuite/tests/ghci/scripts/T7388.hs
- testsuite/tests/ghci/scripts/T7388.script
- testsuite/tests/impredicative/T17332.stderr
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- testsuite/tests/interface-stability/ghc-prim-exports.stdout
- testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32
- + testsuite/tests/overloadedrecflds/should_fail/T26391.hs
- + testsuite/tests/overloadedrecflds/should_fail/T26391.stderr
- testsuite/tests/overloadedrecflds/should_fail/all.T
- testsuite/tests/parser/should_fail/T16270h.stderr
- + testsuite/tests/parser/should_fail/T26418.hs
- + testsuite/tests/parser/should_fail/T26418.stderr
- testsuite/tests/parser/should_fail/all.T
- + testsuite/tests/parser/should_run/T26415.hs
- + testsuite/tests/parser/should_run/T26415.stdout
- testsuite/tests/parser/should_run/all.T
- − testsuite/tests/process/process010.stdout-i386-unknown-solaris2
- testsuite/tests/quantified-constraints/T19690.stderr
- testsuite/tests/quantified-constraints/T19921.stderr
- testsuite/tests/quantified-constraints/T21006.stderr
- testsuite/tests/roles/should_fail/RolesIArray.stderr
- testsuite/tests/rts/exec_signals_child.c
- − 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/linker/T11223/all.T
- − testsuite/tests/rts/outofmem.stderr-i386-apple-darwin
- − testsuite/tests/rts/outofmem.stderr-i386-unknown-mingw32
- − testsuite/tests/rts/outofmem.stderr-powerpc-apple-darwin
- testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs
- testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr
- testsuite/tests/th/T16180.hs
- testsuite/tests/typecheck/should_compile/T14434.hs
- + testsuite/tests/typecheck/should_compile/T26154.hs
- + testsuite/tests/typecheck/should_compile/T26154_A.hs
- + testsuite/tests/typecheck/should_compile/T26154_B.hs
- + testsuite/tests/typecheck/should_compile/T26154_B.hs-boot
- + testsuite/tests/typecheck/should_compile/T26154_Other.hs
- + testsuite/tests/typecheck/should_compile/T26376.hs
- + testsuite/tests/typecheck/should_compile/T26457.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/T15801.stderr
- testsuite/tests/typecheck/should_fail/T18851.hs
- testsuite/tests/typecheck/should_fail/T19627.stderr
- testsuite/tests/typecheck/should_fail/T20666.stderr
- testsuite/tests/typecheck/should_fail/T20666a.stderr
- testsuite/tests/typecheck/should_fail/T20666b.stderr
- testsuite/tests/typecheck/should_fail/T22912.stderr
- testsuite/tests/typecheck/should_fail/T23427.stderr
- + testsuite/tests/typecheck/should_fail/T26255a.hs
- + testsuite/tests/typecheck/should_fail/T26255a.stderr
- + testsuite/tests/typecheck/should_fail/T26255b.hs
- + testsuite/tests/typecheck/should_fail/T26255b.stderr
- + testsuite/tests/typecheck/should_fail/T26255c.hs
- + testsuite/tests/typecheck/should_fail/T26255c.stderr
- testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr
- testsuite/tests/typecheck/should_fail/all.T
- utils/deriveConstants/Main.hs
- utils/jsffi/dyld.mjs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8b9feeefbf5a78dc939045c90f8453…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8b9feeefbf5a78dc939045c90f8453…
You're receiving this email because of your account on gitlab.haskell.org.
1
0