[Git][ghc/ghc][wip/bytecode-library] Fix haddock comments
by Matthew Pickering (@mpickering) 07 Oct '25
by Matthew Pickering (@mpickering) 07 Oct '25
07 Oct '25
Matthew Pickering pushed to branch wip/bytecode-library at Glasgow Haskell Compiler / GHC
Commits:
b186de5f by Matthew Pickering at 2025-10-07T10:54:01+01:00
Fix haddock comments
- - - - -
1 changed file:
- compiler/GHC/Linker/Dynamic.hs
Changes:
=====================================
compiler/GHC/Linker/Dynamic.hs
=====================================
@@ -29,9 +29,9 @@ import GHC.Utils.TmpFs
import Control.Monad (when)
import System.FilePath
-data DynLinkMode = LinkingHomePackage -- | Creating a dynamic library for the home package
+data DynLinkMode = LinkingHomePackage -- ^ Creating a dynamic library for the home package
| LinkingForInterpreter
- -- |^ Creating a shared library which will immediately be loaded by the interpreter
+ -- ^ Creating a shared library which will immediately be loaded by the interpreter
-- this will not pass any package dependencies, and presume that the correct libraries are loaded in
-- the correct order using dlopen.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b186de5fcc0d8da289a05d4e2870d83…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b186de5fcc0d8da289a05d4e2870d83…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/romes/26478] cleanup: Drop obsolete settings from config.mk.in
by Rodrigo Mesquita (@alt-romes) 07 Oct '25
by Rodrigo Mesquita (@alt-romes) 07 Oct '25
07 Oct '25
Rodrigo Mesquita pushed to branch wip/romes/26478 at Glasgow Haskell Compiler / GHC
Commits:
001acdc6 by Rodrigo Mesquita at 2025-10-07T10:29:41+01:00
cleanup: Drop obsolete settings from config.mk.in
These values used to be spliced into the bindist's `config.mk` s.t. when
`make` was run, the values were read and written into the bindist installation `settings` file.
However, we now carry these values to the bindist directly in the
default.target toolchain file, and `make` writes almost nothing to
`settings` now (see #26227)
The entries deleted in this MR were already unused.
Fixes #26478
- - - - -
1 changed file:
- hadrian/bindist/config.mk.in
Changes:
=====================================
hadrian/bindist/config.mk.in
=====================================
@@ -174,34 +174,3 @@ UseLibffiForAdjustors=@UseLibffiForAdjustors@
# rts/Libdw.c:set_initial_registers()
UseLibdw=$(strip $(if $(filter $(TargetArch_CPP),i386 x86_64 s390x),@UseLibdw@,NO))
-#-----------------------------------------------------------------------------
-# Settings
-
-# We are in the process of moving the settings file from being entirely
-# generated by configure, to generated being by the build system. Many of these
-# might become redundant.
-# See Note [tooldir: How GHC finds mingw on Windows]
-
-LdHasFilelist = @LdHasFilelist@
-MergeObjsSupportsResponseFiles = @MergeObjsSupportsResponseFiles@
-LdHasBuildId = @LdHasBuildId@
-LdHasFilelist = @LdHasFilelist@
-LdIsGNULd = @LdIsGNULd@
-LdHasNoCompactUnwind = @LdHasNoCompactUnwind@
-LdHasSingleModule = @LdHasSingleModule@
-ArArgs = @ArArgs@
-ArSupportsAtFile = @ArSupportsAtFile@
-ArSupportsDashL = @ArSupportsDashL@
-HaskellHostOs = @HaskellHostOs@
-HaskellHostArch = @HaskellHostArch@
-HaskellTargetOs = @HaskellTargetOs@
-HaskellTargetArch = @HaskellTargetArch@
-TargetWordSize = @TargetWordSize@
-TargetWordBigEndian = @TargetWordBigEndian@
-TargetHasGnuNonexecStack = @TargetHasGnuNonexecStack@
-TargetHasIdentDirective = @TargetHasIdentDirective@
-TargetHasSubsectionsViaSymbols = @TargetHasSubsectionsViaSymbols@
-TargetHasLibm = @TargetHasLibm@
-TablesNextToCode = @TablesNextToCode@
-LeadingUnderscore = @LeadingUnderscore@
-LlvmTarget = @LlvmTarget@
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/001acdc64bd019b62957bbd73e09ab9…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/001acdc64bd019b62957bbd73e09ab9…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/romes/T26478] cleanup: Drop obsolete settings from config.mk.in
by Rodrigo Mesquita (@alt-romes) 07 Oct '25
by Rodrigo Mesquita (@alt-romes) 07 Oct '25
07 Oct '25
Rodrigo Mesquita pushed to branch wip/romes/T26478 at Glasgow Haskell Compiler / GHC
Commits:
001acdc6 by Rodrigo Mesquita at 2025-10-07T10:29:41+01:00
cleanup: Drop obsolete settings from config.mk.in
These values used to be spliced into the bindist's `config.mk` s.t. when
`make` was run, the values were read and written into the bindist installation `settings` file.
However, we now carry these values to the bindist directly in the
default.target toolchain file, and `make` writes almost nothing to
`settings` now (see #26227)
The entries deleted in this MR were already unused.
Fixes #26478
- - - - -
1 changed file:
- hadrian/bindist/config.mk.in
Changes:
=====================================
hadrian/bindist/config.mk.in
=====================================
@@ -174,34 +174,3 @@ UseLibffiForAdjustors=@UseLibffiForAdjustors@
# rts/Libdw.c:set_initial_registers()
UseLibdw=$(strip $(if $(filter $(TargetArch_CPP),i386 x86_64 s390x),@UseLibdw@,NO))
-#-----------------------------------------------------------------------------
-# Settings
-
-# We are in the process of moving the settings file from being entirely
-# generated by configure, to generated being by the build system. Many of these
-# might become redundant.
-# See Note [tooldir: How GHC finds mingw on Windows]
-
-LdHasFilelist = @LdHasFilelist@
-MergeObjsSupportsResponseFiles = @MergeObjsSupportsResponseFiles@
-LdHasBuildId = @LdHasBuildId@
-LdHasFilelist = @LdHasFilelist@
-LdIsGNULd = @LdIsGNULd@
-LdHasNoCompactUnwind = @LdHasNoCompactUnwind@
-LdHasSingleModule = @LdHasSingleModule@
-ArArgs = @ArArgs@
-ArSupportsAtFile = @ArSupportsAtFile@
-ArSupportsDashL = @ArSupportsDashL@
-HaskellHostOs = @HaskellHostOs@
-HaskellHostArch = @HaskellHostArch@
-HaskellTargetOs = @HaskellTargetOs@
-HaskellTargetArch = @HaskellTargetArch@
-TargetWordSize = @TargetWordSize@
-TargetWordBigEndian = @TargetWordBigEndian@
-TargetHasGnuNonexecStack = @TargetHasGnuNonexecStack@
-TargetHasIdentDirective = @TargetHasIdentDirective@
-TargetHasSubsectionsViaSymbols = @TargetHasSubsectionsViaSymbols@
-TargetHasLibm = @TargetHasLibm@
-TablesNextToCode = @TablesNextToCode@
-LeadingUnderscore = @LeadingUnderscore@
-LlvmTarget = @LlvmTarget@
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/001acdc64bd019b62957bbd73e09ab9…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/001acdc64bd019b62957bbd73e09ab9…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/bytecode-library] 3 commits: Fix recompilation checking
by Matthew Pickering (@mpickering) 07 Oct '25
by Matthew Pickering (@mpickering) 07 Oct '25
07 Oct '25
Matthew Pickering pushed to branch wip/bytecode-library at Glasgow Haskell Compiler / GHC
Commits:
3ea99c4b by Matthew Pickering at 2025-10-06T15:37:25+01:00
Fix recompilation checking
- - - - -
b56d46c6 by Matthew Pickering at 2025-10-06T16:19:27+01:00
proper error message
- - - - -
4663c4e1 by Matthew Pickering at 2025-10-07T09:39:50+01:00
Add bytecodelib docs
- - - - -
8 changed files:
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Linker/ByteCode.hs
- compiler/GHC/Types/Error/Codes.hs
- docs/users_guide/phases.rst
- testsuite/tests/driver/bytecode-object/Makefile
Changes:
=====================================
compiler/GHC/Driver/Errors/Ppr.hs
=====================================
@@ -282,6 +282,10 @@ instance Diagnostic DriverMessage where
++ " and "
++ llvmVersionStr supportedLlvmVersionUpperBound
++ ") and reinstall GHC to ensure -fllvm works")
+ DriverMissingLinkableForModule mods
+ -> mkSimpleDecorated $
+ vcat [ text "The following modules are missing a linkable which is needed for creating a library:"
+ , nest 2 $ hcat (map ppr mods) ]
diagnosticReason = \case
DriverUnknownMessage m
@@ -353,6 +357,8 @@ instance Diagnostic DriverMessage where
-> ErrorWithoutFlag
DriverNoConfiguredLLVMToolchain
-> WarningWithoutFlag
+ DriverMissingLinkableForModule {}
+ -> ErrorWithoutFlag
diagnosticHints = \case
DriverUnknownMessage m
@@ -426,5 +432,7 @@ instance Diagnostic DriverMessage where
-> noHints
DriverNoConfiguredLLVMToolchain
-> noHints
+ DriverMissingLinkableForModule {}
+ -> noHints
diagnosticCode = constructorCode @GHC
=====================================
compiler/GHC/Driver/Errors/Types.hs
=====================================
@@ -412,6 +412,17 @@ data DriverMessage where
-}
DriverNoConfiguredLLVMToolchain :: DriverMessage
+ {- |
+ DriverMissingLinkableForModule is an error that occurs if a module is missing a linkable
+ which is needed for creating a library.
+
+
+ Test cases: bytecode-object22
+
+ -}
+
+ DriverMissingLinkableForModule :: ![Module] -> DriverMessage
+
deriving instance Generic DriverMessage
data DriverMessageOpts =
=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -1840,19 +1840,20 @@ Also closely related are
-}
executeLinkNode :: HomeUnitGraph -> (Int, Int) -> UnitId -> [NodeKey] -> RunMakeM ()
-executeLinkNode hug kn uid deps = do
+executeLinkNode hug kn@(k, _) uid deps = do
withCurrentUnit uid $ do
- MakeEnv{..} <- ask
+ make_env@MakeEnv{..} <- ask
let dflags = hsc_dflags hsc_env
- let hsc_env' = setHUG hug hsc_env
msg' = (\messager -> \recomp -> messager hsc_env kn recomp (LinkNode deps uid)) <$> env_messager
- linkresult <- liftIO $ withAbstractSem compile_sem $ do
- link (ghcLink dflags)
- hsc_env'
- True -- We already decided to link
- msg'
- (hsc_HPT hsc_env')
+ linkresult <- lift $ MaybeT $ withAbstractSem compile_sem $ withLoggerHsc k make_env $ \lcl_hsc_env -> do
+ let hsc_env' = setHUG hug lcl_hsc_env
+ wrapAction diag_wrapper hsc_env' $ do
+ link (ghcLink dflags)
+ hsc_env'
+ True -- We already decided to link
+ msg'
+ (hsc_HPT hsc_env')
case linkresult of
Failed -> fail "Link Failed"
Succeeded -> return ()
=====================================
compiler/GHC/Driver/Pipeline.hs
=====================================
@@ -22,7 +22,7 @@ module GHC.Driver.Pipeline (
compileForeign, compileEmptyStub,
-- * Linking
- link, linkingNeeded, checkLinkInfo,
+ link, checkLinkInfo,
-- * PipeEnv
PipeEnv(..), mkPipeEnv, phaseOutputFilenameNew,
@@ -424,22 +424,13 @@ link' hsc_env batch_attempt_linking mHscMessager hpt
return Succeeded
else do
- -- TODO: This is very awkward.
-
- -- 1. Ban using --make mode to create -bytecodelib, since then you would not need in-memory linkables
- -- 2. Make Linkable and ByteCodeObject more similar, so that you can translate between them.
- -- * Either store .o files in ByteCodeObject <-- MP thinks this way
- -- * or Store ForeignStubs/ForeignSrcs in Linkable
- -- 3. Store ByteCodeObject in Linkable directly
- let hackyMPtodo l = [ cbc | cbc <- linkableByteCodeObjects l ]
-
let linkObjectLinkable action =
- checkLinkablesUpToDate hsc_env mHscMessager home_mods pkg_deps staticLink homeMod_object $ \linkables ->
+ checkLinkablesUpToDate hsc_env mHscMessager home_mods pkg_deps staticLink (checkNativeLibraryLinkingNeeded staticLink) homeMod_object $ \linkables ->
let obj_files = concatMap linkableObjs linkables
in action obj_files
linkBytecodeLinkable action =
- checkLinkablesUpToDate hsc_env mHscMessager home_mods pkg_deps staticLink homeMod_bytecode $ \linkables ->
- let bytecode = concatMap hackyMPtodo linkables
+ checkLinkablesUpToDate hsc_env mHscMessager home_mods pkg_deps staticLink checkBytecodeLibraryLinkingNeeded homeMod_bytecode $ \linkables ->
+ let bytecode = concatMap linkableByteCodeObjects linkables
in action bytecode
-- Don't showPass in Batch mode; doLink will do that for us.
@@ -465,38 +456,31 @@ link' hsc_env batch_attempt_linking mHscMessager hpt
-- | Check that the relevant linkables are up-to-date and then apply the given action
-- to them.
-checkLinkablesUpToDate :: Foldable t => HscEnv
- -> t (RecompileRequired -> IO b)
+checkLinkablesUpToDate :: HscEnv
+ -> Maybe (RecompileRequired -> IO b)
-> [HomeModInfo]
-> [UnitId]
-> Bool
+ -> (Logger -> DynFlags -> UnitEnv -> [Linkable] -> [UnitId] -> IO RecompileRequired)
-> (HomeModLinkable -> Maybe Linkable)
-> ([Linkable] -> IO ()) -> IO ()
-checkLinkablesUpToDate hsc_env mHscMessager home_mods pkg_deps staticLink linkable_selector action = do
+checkLinkablesUpToDate hsc_env mHscMessager home_mods pkg_deps staticLink linkingNeeded linkable_selector action = do
let dflags = hsc_dflags hsc_env
logger = hsc_logger hsc_env
unit_env = hsc_unit_env hsc_env
- let -- The .o files for the home modules
- -- obj_files = concat (mapMaybe (fmap linkableObjs . homeMod_object) linkables)
-
- -- The .gbc files for the home modules
- -- bytecode = concat (mapMaybe (fmap hackyMPtodo . homeMod_bytecode) linkables)
-
-
-
- platform = targetPlatform dflags
+ let platform = targetPlatform dflags
arch_os = platformArchOS platform
exe_file = exeFileName arch_os staticLink (outputFile_ dflags)
-- 1. Check that all modules have a linkable
let linkables = checkAllModulesHaveLinkable linkable_selector home_mods
case linkables of
- -- MP: Use a proper error when not all modules have a linkable
- Left missing -> pprPanic "checkLinkablesUpToDate: todo, need proper error" (ppr missing)
+ Left missing -> throwOneError $ fmap GhcDriverMessage $
+ mkPlainErrorMsgEnvelope noSrcSpan $ DriverMissingLinkableForModule missing
Right linkables -> do
-- 2. Check that the linkables are up to date
- linking_needed <- linkingNeeded logger dflags unit_env staticLink linkables pkg_deps
+ linking_needed <- linkingNeeded logger dflags unit_env linkables pkg_deps
forM_ mHscMessager $ \hscMessage -> hscMessage linking_needed
if not (gopt Opt_ForceRecomp dflags) && (linking_needed == UpToDate)
then debugTraceMsg logger 2 (text exe_file <+> text "is up to date, linking not required.")
@@ -535,8 +519,25 @@ linkJSBinary logger tmpfs fc dflags unit_env obj_files pkg_deps = do
let cfg = initStgToJSConfig dflags
jsLinkBinary fc lc_cfg cfg logger tmpfs dflags unit_env obj_files pkg_deps
-linkingNeeded :: Logger -> DynFlags -> UnitEnv -> Bool -> [Linkable] -> [UnitId] -> IO RecompileRequired
-linkingNeeded logger dflags unit_env staticLink linkables pkg_deps = do
+-- | Bytecode libraries are simpler to check for linking needed since they do not
+-- depend on any other libraries.
+checkBytecodeLibraryLinkingNeeded :: Logger -> DynFlags -> UnitEnv -> [Linkable] -> [UnitId] -> IO RecompileRequired
+checkBytecodeLibraryLinkingNeeded _logger dflags unit_env linkables _pkg_deps = do
+ let platform = ue_platform unit_env
+ arch_os = platformArchOS platform
+ exe_file = exeFileName arch_os False (outputFile_ dflags)
+
+ e_bytecode_lib_time <- modificationTimeIfExists exe_file
+ case e_bytecode_lib_time of
+ Nothing -> return $ NeedsRecompile MustCompile
+ Just t -> do
+ let bytecode_times = map linkableTime linkables
+ if any (t <) bytecode_times
+ then return $ needsRecompileBecause ObjectsChanged
+ else return UpToDate
+
+checkNativeLibraryLinkingNeeded :: Bool -> Logger -> DynFlags -> UnitEnv -> [Linkable] -> [UnitId] -> IO RecompileRequired
+checkNativeLibraryLinkingNeeded staticLink logger dflags unit_env linkables pkg_deps = do
-- if the modification time on the executable is later than the
-- modification times on all of the objects and libraries, then omit
-- linking (unless the -fforce-recomp flag was given).
@@ -544,10 +545,10 @@ linkingNeeded logger dflags unit_env staticLink linkables pkg_deps = do
unit_state = ue_homeUnitState unit_env
arch_os = platformArchOS platform
exe_file = exeFileName arch_os staticLink (outputFile_ dflags)
- e_exe_time <- tryIO $ getModificationUTCTime exe_file
+ e_exe_time <- modificationTimeIfExists exe_file
case e_exe_time of
- Left _ -> return $ NeedsRecompile MustCompile
- Right t -> do
+ Nothing -> return $ NeedsRecompile MustCompile
+ Just t -> do
-- first check object files and extra_ld_inputs
let extra_ld_inputs = [ f | FileOption _ f <- ldInputs dflags ]
(errs,extra_times) <- partitionWithM (tryIO . getModificationUTCTime) extra_ld_inputs
=====================================
compiler/GHC/Linker/ByteCode.hs
=====================================
@@ -15,7 +15,6 @@ linkBytecodeLib hsc_env gbcs = do
-- The .gbc files from the command line
let bytecodeObjects = [f | FileOption _ f <- ldInputs dflags]
- -- INSERT_YOUR_CODE
let logger = hsc_logger hsc_env
let allFiles = (map text bytecodeObjects) ++ [ angleBrackets (text "in-memory" <+> ppr (bco_module bco)) | bco <- gbcs ]
debugTraceMsg logger 2 $
=====================================
compiler/GHC/Types/Error/Codes.hs
=====================================
@@ -405,6 +405,7 @@ type family GhcDiagnosticCode c = n | n -> c where
GhcDiagnosticCode "DriverModuleGraphCycle" = 92213
GhcDiagnosticCode "DriverInstantiationNodeInDependencyGeneration" = 74284
GhcDiagnosticCode "DriverNoConfiguredLLVMToolchain" = 66599
+ GhcDiagnosticCode "DriverMissingLinkableForModule" = 47338
-- Constraint solver diagnostic codes
GhcDiagnosticCode "BadTelescope" = 97739
=====================================
docs/users_guide/phases.rst
=====================================
@@ -1048,6 +1048,20 @@ for example).
when linking against this package.
See :ref:`shared object name mangling <building-packages>` for details.
+.. ghc-flag:: -bytecodelib
+ :shortdesc: Generate a bytecode library
+ :type: dynamic
+ :category: linking
+
+ Generate a bytecode library. A bytecode library is a collection of bytecode
+ artifacts.
+
+ This unit can be used to package bytecode together for a library.
+
+
+
+
+
.. ghc-flag:: -dynload
:shortdesc: Selects one of a number of modes for finding shared libraries at runtime.
:type: dynamic
=====================================
testsuite/tests/driver/bytecode-object/Makefile
=====================================
@@ -134,7 +134,7 @@ bytecode_object20:
# Test that -bytecodelib without -fbyte-code results in an error
bytecode_object21:
- "$(TEST_HC)" $(TEST_HC_OPTS) --make -bytecodelib -o pkg.bytecode BytecodeTest.hs
+ ! "$(TEST_HC)" $(TEST_HC_OPTS) --make -bytecodelib -o pkg.bytecode BytecodeTest.hs
# Test that you can link together .gbc files with -c and -bytecodelib
bytecode_object22:
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9d26339f51f016174c834e9bb3a3fe…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9d26339f51f016174c834e9bb3a3fe…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/fendor/t23703] 2 commits: Refactor distinct constructor tables map construction
by Hannes Siebenhandl (@fendor) 07 Oct '25
by Hannes Siebenhandl (@fendor) 07 Oct '25
07 Oct '25
Hannes Siebenhandl pushed to branch wip/fendor/t23703 at Glasgow Haskell Compiler / GHC
Commits:
f83232cf by Finley McIlwaine at 2025-10-07T10:07:11+02:00
Refactor distinct constructor tables map construction
Adds `GHC.Types.Unique.FM.alterUFM_L`, `GHC.Types.Unique.DFM.alterUDFM_L`
`GHC.Data.Word64Map.alterLookupWithKey` to support fusion of distinct
constructor data insertion and lookup during the construction of the data con
map in `GHC.Stg.Debug.numberDataCon`.
- - - - -
b3e2f670 by Finley McIlwaine at 2025-10-07T10:08:44+02:00
Allow per constructor refinement of distinct-constructor-tables
Introduce `-fno-distinct-constructor-tables`. A distinct constructor table
configuration is built from the combination of flags given, in order. For
example, to only generate distinct constructor tables for a few specific
constructors and no others, just pass
`-fdistinct-constructor-tables-only=C1,...,CN`.
This flag can be supplied multiple times to extend the set of
constructors to generate a distinct info table for.
You can disable generation of distinct constructor tables for all
configurations by passing `-fno-distinct-constructor-tables`.
The various configurations of these flags is included in the `DynFlags`
fingerprints, which should result in the expected recompilation logic.
Adds a test that checks for distinct tables for various given or omitted
constructors.
Updates CountDepsAst and CountDepsParser tests to account for new dependencies.
Fixes #23703
- - - - -
33 changed files:
- compiler/GHC/Data/Word64Map/Internal.hs
- compiler/GHC/Data/Word64Map/Lazy.hs
- compiler/GHC/Driver/Config/Stg/Debug.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Flags.hs
- compiler/GHC/Iface/Recomp/Flags.hs
- compiler/GHC/Stg/Debug.hs
- + compiler/GHC/Stg/Debug/Types.hs
- compiler/GHC/Types/Unique/DFM.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/ghc.cabal.in
- docs/users_guide/debug-info.rst
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- + testsuite/tests/rts/ipe/distinct-tables/Main.hs
- + testsuite/tests/rts/ipe/distinct-tables/Makefile
- + testsuite/tests/rts/ipe/distinct-tables/X.hs
- + testsuite/tests/rts/ipe/distinct-tables/all.T
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables01.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables02.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables03.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables04.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables05.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables06.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables07.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables08.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables09.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables10.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables11.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables12.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables13.stdout
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f776c0919161ab9b3522913881b467…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f776c0919161ab9b3522913881b467…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/andreask/occ_anal_tuning] 5 commits: testsuite: Use ghci_ways to set ways in PackedDataCon/UnboxedTuples/UnliftedDataTypeInterp tests
by Andreas Klebinger (@AndreasK) 07 Oct '25
by Andreas Klebinger (@AndreasK) 07 Oct '25
07 Oct '25
Andreas Klebinger pushed to branch wip/andreask/occ_anal_tuning 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.
- - - - -
41bdb16f by Andreas Klebinger at 2025-10-06T18:04:34-04:00
Add a perf test for #26425
- - - - -
1da0c700 by Andreas Klebinger at 2025-10-06T18:05:14-04:00
Testsuite: Silence warnings about Wx-partial in concprog001
- - - - -
ec22d744 by Andreas Klebinger at 2025-10-07T08:03:44+00:00
Try using a strict env for OccAnal
- - - - -
26 changed files:
- compiler/GHC.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Data/Word64Map/Internal.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
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Var/Env.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/Core/Opt/OccurAnal.hs
=====================================
@@ -10,6 +10,10 @@
-- bad for performance, so I increased the limit to allow it to unbox
-- consistently.
+-- {-# OPTIONS_GHC -ddump-simpl -ddump-stg -dumpdir dumps -ddump-to-file #-}
+-- {-# OPTIONS_GHC -fdistinct-constructor-tables -finfo-table-map #-}
+-- {-# OPTIONS_GHC -ticky -ticky-allocd -ticky-LNE #-}
+
{-
(c) The GRASP/AQUA Project, Glasgow University, 1992-1998
@@ -984,7 +988,7 @@ occAnalBind !env lvl ire (NonRec bndr rhs) thing_inside combine
= -- Analyse the RHS and /then/ the body
let -- Analyse the rhs first, generating rhs_uds
!(rhs_uds_s, bndr', rhs') = occAnalNonRecRhs env lvl ire mb_join bndr rhs
- rhs_uds = foldr1 orUDs rhs_uds_s -- NB: orUDs. See (W4) of
+ rhs_uds = foldl1' orUDs rhs_uds_s -- NB: orUDs. See (W4) of
-- Note [Occurrence analysis for join points]
-- Now analyse the body, adding the join point
@@ -3650,8 +3654,10 @@ data WithTailUsageDetails a = WTUD !TailUsageDetails !a
-------------------
-- UsageDetails API
-andUDs, orUDs
- :: UsageDetails -> UsageDetails -> UsageDetails
+-- {-# NOINLINE andUDs #-}
+-- {-# NOINLINE orUDs #-}
+andUDs:: UsageDetails -> UsageDetails -> UsageDetails
+orUDs :: UsageDetails -> UsageDetails -> UsageDetails
andUDs = combineUsageDetailsWith andLocalOcc
orUDs = combineUsageDetailsWith orLocalOcc
@@ -3760,16 +3766,17 @@ restrictFreeVars bndrs fvs = restrictUniqSetToUFM bndrs fvs
combineUsageDetailsWith :: (LocalOcc -> LocalOcc -> LocalOcc)
-> UsageDetails -> UsageDetails -> UsageDetails
{-# INLINE combineUsageDetailsWith #-}
+{-# SCC combineUsageDetailsWith #-}
combineUsageDetailsWith plus_occ_info
uds1@(UD { ud_env = env1, ud_z_many = z_many1, ud_z_in_lam = z_in_lam1, ud_z_tail = z_tail1 })
uds2@(UD { ud_env = env2, ud_z_many = z_many2, ud_z_in_lam = z_in_lam2, ud_z_tail = z_tail2 })
| isEmptyVarEnv env1 = uds2
| isEmptyVarEnv env2 = uds1
| otherwise
- = UD { ud_env = plusVarEnv_C plus_occ_info env1 env2
- , ud_z_many = plusVarEnv z_many1 z_many2
- , ud_z_in_lam = plusVarEnv z_in_lam1 z_in_lam2
- , ud_z_tail = plusVarEnv z_tail1 z_tail2 }
+ = UD { ud_env = {-# SCC ud_env #-} strictPlusVarEnv_C plus_occ_info env1 env2
+ , ud_z_many = {-# SCC ud_z_many #-} strictPlusVarEnv z_many1 z_many2
+ , ud_z_in_lam = {-# SCC ud_z_in_lam #-} strictPlusVarEnv z_in_lam1 z_in_lam2
+ , ud_z_tail = {-# SCC ud_z_tail #-} strictPlusVarEnv z_tail1 z_tail2 }
lookupLetOccInfo :: UsageDetails -> Id -> OccInfo
-- Don't use locally-generated occ_info for exported (visible-elsewhere)
=====================================
compiler/GHC/Data/Word64Map/Internal.hs
=====================================
@@ -3,6 +3,7 @@
{-# OPTIONS_HADDOCK not-home #-}
{-# OPTIONS_GHC -fno-warn-incomplete-uni-patterns #-}
+{-# OPTIONS_GHC -ddump-simpl -ddump-stg-final -ddump-to-file -dumpdir dumps #-}
-----------------------------------------------------------------------------
=====================================
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)
=====================================
compiler/GHC/Types/Unique/FM.hs
=====================================
@@ -51,7 +51,9 @@ module GHC.Types.Unique.FM (
delListFromUFM,
delListFromUFM_Directly,
plusUFM,
+ strictPlusUFM,
plusUFM_C,
+ strictPlusUFM_C,
plusUFM_CD,
plusUFM_CD2,
mergeUFM,
@@ -251,16 +253,24 @@ delListFromUFM_Directly = foldl' delFromUFM_Directly
delFromUFM_Directly :: UniqFM key elt -> Unique -> UniqFM key elt
delFromUFM_Directly (UFM m) u = UFM (M.delete (getKey u) m)
--- Bindings in right argument shadow those in the left
+-- | Bindings in right argument shadow those in the left.
+--
+-- Unlike containers this union is right-biased for historic reasons.
plusUFM :: UniqFM key elt -> UniqFM key elt -> UniqFM key elt
--- M.union is left-biased, plusUFM should be right-biased.
plusUFM (UFM x) (UFM y) = UFM (M.union y x)
-- Note (M.union y x), with arguments flipped
-- M.union is left-biased, plusUFM should be right-biased.
+-- | Right biased
+strictPlusUFM :: UniqFM key elt -> UniqFM key elt -> UniqFM key elt
+strictPlusUFM (UFM x) (UFM y) = UFM (MS.union y x)
+
plusUFM_C :: (elt -> elt -> elt) -> UniqFM key elt -> UniqFM key elt -> UniqFM key elt
plusUFM_C f (UFM x) (UFM y) = UFM (M.unionWith f x y)
+strictPlusUFM_C :: (elt -> elt -> elt) -> UniqFM key elt -> UniqFM key elt -> UniqFM key elt
+strictPlusUFM_C f (UFM x) (UFM y) = UFM (MS.unionWith f x y)
+
-- | `plusUFM_CD f m1 d1 m2 d2` merges the maps using `f` as the
-- combinding function and `d1` resp. `d2` as the default value if
-- there is no entry in `m1` reps. `m2`. The domain is the union of
=====================================
compiler/GHC/Types/Var/Env.hs
=====================================
@@ -12,7 +12,8 @@ module GHC.Types.Var.Env (
elemVarEnv, disjointVarEnv, anyVarEnv,
extendVarEnv, extendVarEnv_C, extendVarEnv_Acc,
extendVarEnvList,
- plusVarEnv, plusVarEnv_C, plusVarEnv_CD, plusMaybeVarEnv_C,
+ strictPlusVarEnv, plusVarEnv, plusVarEnv_C, strictPlusVarEnv_C,
+ plusVarEnv_CD, plusMaybeVarEnv_C,
plusVarEnvList, alterVarEnv,
delVarEnvList, delVarEnv,
minusVarEnv,
@@ -511,6 +512,7 @@ extendVarEnv :: VarEnv a -> Var -> a -> VarEnv a
extendVarEnv_C :: (a->a->a) -> VarEnv a -> Var -> a -> VarEnv a
extendVarEnv_Acc :: (a->b->b) -> (a->b) -> VarEnv b -> Var -> a -> VarEnv b
plusVarEnv :: VarEnv a -> VarEnv a -> VarEnv a
+strictPlusVarEnv :: VarEnv a -> VarEnv a -> VarEnv a
plusVarEnvList :: [VarEnv a] -> VarEnv a
extendVarEnvList :: VarEnv a -> [(Var, a)] -> VarEnv a
varEnvDomain :: VarEnv elt -> UnVarSet
@@ -522,6 +524,7 @@ delVarEnvList :: Foldable f => VarEnv a -> f Var -> VarEnv a
delVarEnv :: VarEnv a -> Var -> VarEnv a
minusVarEnv :: VarEnv a -> VarEnv b -> VarEnv a
plusVarEnv_C :: (a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv a
+strictPlusVarEnv_C :: (a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv a
plusVarEnv_CD :: (a -> a -> a) -> VarEnv a -> a -> VarEnv a -> a -> VarEnv a
plusMaybeVarEnv_C :: (a -> a -> Maybe a) -> VarEnv a -> VarEnv a -> VarEnv a
mapVarEnv :: (a -> b) -> VarEnv a -> VarEnv b
@@ -548,6 +551,7 @@ extendVarEnv_C = addToUFM_C
extendVarEnv_Acc = addToUFM_Acc
extendVarEnvList = addListToUFM
plusVarEnv_C = plusUFM_C
+strictPlusVarEnv_C = strictPlusUFM_C
plusVarEnv_CD = plusUFM_CD
plusMaybeVarEnv_C = plusMaybeUFM_C
delVarEnvList = delListFromUFM
@@ -556,6 +560,7 @@ delVarEnvList = delListFromUFM
delVarEnv = delFromUFM
minusVarEnv = minusUFM
plusVarEnv = plusUFM
+strictPlusVarEnv = strictPlusUFM
plusVarEnvList = plusUFMList
-- lookupVarEnv is very hot (in part due to being called by substTyVar),
-- if it's not inlined than the mere allocation of the Just constructor causes
=====================================
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/6db54184feb8064e90a3f64934cd16…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6db54184feb8064e90a3f64934cd16…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/andreask/bomb_out] 46 commits: Allow disabling builtin rules (#20298)
by Andreas Klebinger (@AndreasK) 07 Oct '25
by Andreas Klebinger (@AndreasK) 07 Oct '25
07 Oct '25
Andreas Klebinger pushed to branch wip/andreask/bomb_out at Glasgow Haskell Compiler / GHC
Commits:
5ae89054 by Sylvain Henry at 2025-09-24T17:07:00-04:00
Allow disabling builtin rules (#20298)
Add a way to disable built-in rules programmatically and with a debug flag.
I also took the opportunity to add a debug flag to disable bignum rules,
which was only possible programmatically (e.g. in a plugin).
- - - - -
135242ca by Rodrigo Mesquita at 2025-09-24T17:07:44-04:00
Don't use build CFLAGS and friends as target settings
In the GHC in tree configure, `CFLAGS`, `CXXFLAGS`, and similar tool
configuration flags apply to the BUILD phase of the compiler, i.e. to
the tools run to compile GHC itself.
Notably, they should /not/ be carried over to the Target settings, i.e.
these flags should /not/ apply to the tool which GHC invokes at runtime.
Fixes #25637
- - - - -
b418408b by Irene Knapp at 2025-09-25T09:47:54-04:00
Document etymology of "bind" as the name for `>>=`
It took me twenty years of contemplation to realize why it's called that.
I therefore feel that it may not be obvious to beginners.
- - - - -
e9c5e46f by Brandon Chinn at 2025-09-25T09:48:36-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.
- - - - -
8bf5b309 by Cheng Shao at 2025-09-25T09:49:18-04:00
wasm: remove the --no-turbo-fast-api-calls hack from dynamic linker shebang
This patch removes the `--no-turbo-fast-api-calls` hack from the dyld
script shebang; it was used to workaround v8 fast call coredumps in
nodejs and no longer needed, and comes with a performance penalty,
hence the removal.
- - - - -
c1cab0c3 by Sylvain Henry at 2025-09-26T10:36:30-04:00
Revert "Add necessary flag for js linking"
This reverts commit 84f68e2231b2eddb2e1dc4e90af394ef0f2e803f.
This commit didn't have the expected effect. See discussion in #26290.
Instead we export HEAP8 and HEAPU8 from rts/js/mem.js
- - - - -
0a434a80 by Sylvain Henry at 2025-09-26T10:36:30-04:00
JS: export HEAPU8 (#26290)
This is now required by newer Emscripten versions.
- - - - -
b10296a9 by Andreas Klebinger at 2025-09-26T10:37:11-04:00
sizeExpr: Improve Tick handling.
When determining if we scrutinize a function argument we
now properly look through ticks. Fixes #26444.
- - - - -
d9e2a9a7 by mniip at 2025-09-26T16:00:50-04:00
rts: Refactor parsing of -h flags
We have a nontrivial amount of heap profiling flags available in the
non-profiled runtime, so it makes sense to reuse the parsing code
between the profiled and the non-profiled runtime, only restricting
which flags are allowed.
- - - - -
089e45aa by mniip at 2025-09-26T16:00:50-04:00
rts: Fix parsing of -h options with braces
When the "filter by" -h options were introduced in
bc210f7d267e8351ccb66972f4b3a650eb9338bb, the braces were mandatory.
Then in 3c22fb21fb18e27ce8d941069a6915fce584a526, the braces were made
optional. Then in d1ce35d2271ac8b79cb5e37677b1a989749e611c the brace
syntax stopped working, and no one seems to have noticed.
- - - - -
423f1472 by mniip at 2025-09-26T16:00:50-04:00
rts: add -hT<type> and -hi<table id> heap filtering options (#26361)
They are available in non-profiled builds.
Along the way fixed a bug where combining -he<era> and -hr<retainer>
would ignore whether the retainer matches or not.
- - - - -
4cda4785 by mniip at 2025-09-26T16:00:50-04:00
docs: Document -hT<type> and -hi<addr>
- - - - -
982ad30f by mniip at 2025-09-26T16:00:50-04:00
rts: Refactor dumping the heap census
Always do the printing of the total size right next to where the bucket
label is printed. This prevents accidentally printing a label without
the corresponding amount.
Fixed a bug where exactly this happened for -hi profile and the 0x0
(uncategorized) info table.
There is now also much more symmetry between fprintf(hp_file,...) and
the corresponding traceHeapProfSampleString.
- - - - -
8cbe006a by Cheng Shao at 2025-09-26T16:01:34-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>
- - - - -
0ddd0fdc by soulomoon at 2025-09-28T19:24:10-04:00
Remove hptAllInstances usage during upsweep
Previously, during the upsweep phase when
checking safe imports, we were loading the module
interface with runTcInteractive, which in turn calls
hptAllInstances. This accesses non-below modules
from the home package table.
Change the implementation of checkSafeImports
to use initTcWithGbl and loadSysInterface to load the
module interface, since we already have TcGblEnv at hand.
This eliminates the unnecessary use of runTcInteractive
and hptAllInstances during the upsweep phase.
- - - - -
e05c496c by Ben Gamari at 2025-09-28T19:24:59-04:00
base: Update changelog to reflect timing of IOPort# removal
This change will make 9.14 afterall.
- - - - -
bdc9d130 by Cheng Shao at 2025-09-28T19:25:45-04:00
rts: fix wasm JSFFI initialization constructor code
This commit fixes wasm JSFFI initialization constructor code so that
the constructor is self-contained and avoids invoking a fake
__main_argc_argv function. The previous approach of reusing
__main_void logic in wasi-libc saves a tiny bit of code, at the
expense of link-time trouble whenever GHC links a wasm module without
-no-hs-main, in which case the driver-generated main function would
clash with the definition here, resulting in a linker error. It's
simply better to avoid messing with the main function, and it would
additionally allow linking wasm32-wasi command modules that does make
use of synchronous JSFFI.
- - - - -
5d59fc8f by Cheng Shao at 2025-09-28T19:26:27-04:00
rts: provide stub implementations of ExecPage functions for wasm
This patch provides stub implementations of ExecPage functions for
wasm. They are never actually invoked at runtime for any non-TNTC
platform, yet they can cause link-time errors of missing symbols when
the GHCi.InfoTable module gets linked into the final wasm module (e.g.
a GHC API program).
- - - - -
a4d664c7 by Cheng Shao at 2025-09-29T17:29:22+02:00
compiler/ghci: replace the LoadDLL message with LoadDLLs
As a part of #25407, this commit changes the LoadDLL message to
LoadDLLs, which takes a list of DLL paths to load and returns the list
of remote pointer handles. The wasm dyld is refactored to take
advantage of LoadDLLs and harvest background parallelism. On other
platforms, LoadDLLs is based on a fallback codepath that does
sequential loading.
The driver is not actually emitting singular LoadDLLs message with
multiple DLLs yet, this is left in subsequent commits.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
c7fc4bae by Cheng Shao at 2025-09-29T17:29:22+02:00
driver: separate downsweep/upsweep phase in loadPackages'
This commit refactors GHC.Linker.Loader.loadPackages' to be separated
into downsweep/upsweep phases:
- The downsweep phase performs dependency analysis and generates a
list of topologically sorted packages to load
- The upsweep phase sequentially loads these packages by calling
loadPackage
This is a necessary refactoring to make it possible to make loading of
DLLs concurrent.
- - - - -
ab180104 by Cheng Shao at 2025-09-29T17:57:19+02:00
driver: emit single LoadDLLs message to load multiple DLLs
This commit refactors the driver so that it emits a single LoadDLLs
message to load multiple DLLs in GHC.Linker.Loader.loadPackages'.
Closes #25407.
-------------------------
Metric Increase:
MultiLayerModulesTH_OneShot
TcPlugin_RewritePerf
-------------------------
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
9c304ec0 by Sean D. Gillespie at 2025-09-29T19:57:07-04:00
Fix SIZED_BIN_OP_TY_INT casts in RTS interpreter
Correct `SIZED_BIN_OP_TY_INT` cast to integer. Previously, it cast
its second operand as its parameter `ty`. This does not currently
cause any issues, since we are only using it for bit shifts.
Fixes #26287
- - - - -
a1de535f by Luite Stegeman at 2025-09-30T18:40:28-04:00
rts: Fix lost wakeups in threadPaused for threads blocked on black holes
The lazy blackholing code in threadPaused could overwrite closures
that were already eagerly blackholed, and as such wouldn't have a
marked update frame. If the black hole was overwritten by its
original owner, this would lead to an undetected collision, and
the contents of any existing blocking queue being lost.
This adds a check for eagerly blackholed closures and avoids
overwriting their contents.
Fixes #26324
- - - - -
b7e21e49 by Luite Stegeman at 2025-09-30T18:40:28-04:00
rts: push the correct update frame in stg_AP_STACK
The frame contains an eager black hole (__stg_EAGER_BLACKHOLE_info) so
we should push an stg_bh_upd_frame_info instead of an stg_upd_frame_info.
- - - - -
02a7c18a by Cheng Shao at 2025-09-30T18:41:27-04:00
ghci: fix lookupSymbolInDLL behavior on wasm
This patch fixes lookupSymbolInDLL behavior on wasm to return Nothing
instead of throwing. On wasm, we only have lookupSymbol, and the
driver would attempt to call lookupSymbolInDLL first before falling
back to lookupSymbol, so lookupSymbolInDLL needs to return Nothing
gracefully for the fallback behavior to work.
- - - - -
aa0ca5e3 by Cheng Shao at 2025-09-30T18:41:27-04:00
hadrian/compiler: enable internal-interpreter for ghc library in wasm stage1
This commit enables the internal-interpreter flag for ghc library in
wasm stage1, as well as other minor adjustments to make it actually
possible to launch a ghc api session that makes use of the internal
interpreter. Closes #26431 #25400.
- - - - -
69503668 by Cheng Shao at 2025-09-30T18:41:27-04:00
testsuite: add T26431 test case
This commit adds T26431 to testsuite/tests/ghci-wasm which goes
through the complete bytecode compilation/linking/running pipeline in
wasm, so to witness that the ghc shared library in wasm have full
support for internal-interpreter.
- - - - -
e9445c01 by Matthew Pickering at 2025-09-30T18:42:23-04:00
driver: Load bytecode static pointer entries during linking
Previously the entries were loaded too eagerly, during upsweep, but we
should delay loading them until we know that the relevant bytecode
object is demanded.
Towards #25230
- - - - -
b8307eab by Cheng Shao at 2025-09-30T18:43:14-04:00
autoconf/ghc-toolchain: remove obsolete C99 check
This patch removes obsolete c99 check from autoconf/ghc-toolchain. For
all toolchain & platform combination we support, gnu11 or above is
already supported without any -std flag required, and our RTS already
required C11 quite a few years ago, so the C99 check is completely
pointless.
- - - - -
9c293544 by Simon Peyton Jones at 2025-10-01T09:36:10+01:00
Fix buglet in GHC.Core.Unify.uVarOrFam
We were failing to match two totally-equal types!
This led to #26457.
- - - - -
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
- - - - -
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.
- - - - -
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.
- - - - -
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.
- - - - -
c9ec4d43 by Simon Hengel at 2025-10-02T18:42:20-04:00
Update copyright in documentation
- - - - -
da9633a9 by Matthew Pickering at 2025-10-02T18:43:04-04:00
loader: Unify loadDecls and loadModuleLinkables functions
These two functions nearly did the same thing. I have refactored them so
that `loadDecls` now calls `loadModuleLinkables`.
Fixes #26459
- - - - -
5db98d80 by Simon Hengel at 2025-10-02T18:43:53-04:00
Fix typo
- - - - -
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.
- - - - -
41bdb16f by Andreas Klebinger at 2025-10-06T18:04:34-04:00
Add a perf test for #26425
- - - - -
1da0c700 by Andreas Klebinger at 2025-10-06T18:05:14-04:00
Testsuite: Silence warnings about Wx-partial in concprog001
- - - - -
74ddf3ff by Andreas Klebinger at 2025-10-07T08:03:40+00:00
exprSize: Accumulate size as we go to allow early bomb out.
When dealing with branches in the AST we now accumulate
expr size across branches, rather than computing both
branches before adding them up.
This way we can abort early when it's clear an expression
is too large to be useful.
This fixes an issue I observed in #26425 where we sometimes
spent a significant amount of time computing unfolding sizes
in deeply nested but branching rhss.
Speedup is on the order of ~1%-4% depending on the program we
are compiling.
- - - - -
6affa095 by Andreas Klebinger at 2025-10-07T08:03:40+00:00
ExprSize: Encode presence of discount in type argument
- - - - -
7f13f924 by Andreas Klebinger at 2025-10-07T08:03:40+00:00
Skip TooBig check in size_up
- - - - -
55a84e20 by Andreas Klebinger at 2025-10-07T08:03:40+00:00
Make accumulator raw size
- - - - -
153895a3 by Andreas Klebinger at 2025-10-07T08:03:40+00:00
Some cleanup
- - - - -
109 changed files:
- compiler/GHC.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Core/Opt/ConstantFold.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Rules/Config.hs
- compiler/GHC/Core/Unfold.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Driver/Backend.hs
- compiler/GHC/Driver/Backend/Internal.hs
- compiler/GHC/Driver/Config/Core/Rules.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Plugins.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Tidy/StaticPtrTable.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/Lexer/String.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/cbits/keepCAFsForGHCi.c
- compiler/ghc.cabal.in
- configure.ac
- distrib/configure.ac.in
- docs/users_guide/conf.py
- docs/users_guide/debugging.rst
- docs/users_guide/extending_ghc.rst
- docs/users_guide/profiling.rst
- ghc/Main.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Settings/Packages.hs
- libraries/base/changelog.md
- libraries/ghc-internal/src/GHC/Internal/Base.hs
- libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ObjLink.hs
- libraries/ghci/GHCi/Run.hs
- m4/fp_cmm_cpp_cmd_with_args.m4
- − m4/fp_set_cflags_c99.m4
- m4/fp_setup_windows_toolchain.m4
- m4/fptools_set_c_ld_flags.m4
- m4/ghc_toolchain.m4
- rts/Apply.cmm
- + rts/BuiltinClosures.c
- + rts/BuiltinClosures.h
- rts/ExecPage.c
- rts/Interpreter.c
- rts/ProfHeap.c
- rts/RetainerSet.c
- rts/RtsFlags.c
- rts/RtsStartup.c
- rts/StgMiscClosures.cmm
- rts/ThreadPaused.c
- rts/include/rts/Constants.h
- rts/include/rts/Flags.h
- rts/include/stg/MiscClosures.h
- rts/js/mem.js
- rts/rts.cabal
- rts/wasm/JSFFI.c
- testsuite/driver/testglobals.py
- testsuite/driver/testlib.py
- + testsuite/tests/codeGen/should_compile/T20298a.hs
- + testsuite/tests/codeGen/should_compile/T20298a.stderr
- + testsuite/tests/codeGen/should_compile/T20298b.hs
- + testsuite/tests/codeGen/should_compile/T20298b.stderr
- + testsuite/tests/codeGen/should_compile/T20298c.hs
- + testsuite/tests/codeGen/should_compile/T20298c.stderr
- testsuite/tests/codeGen/should_compile/all.T
- testsuite/tests/concurrent/prog001/all.T
- + testsuite/tests/cross/should_run/T26449.hs
- + testsuite/tests/cross/should_run/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-wasm/T26431.stdout
- testsuite/tests/ghci-wasm/all.T
- 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/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- + testsuite/tests/parser/should_run/T26415.hs
- + testsuite/tests/parser/should_run/T26415.stdout
- testsuite/tests/parser/should_run/all.T
- + testsuite/tests/perf/compiler/T26425.hs
- testsuite/tests/perf/compiler/all.T
- − 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/linker/T2615.hs
- − 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/typecheck/should_compile/T26457.hs
- testsuite/tests/typecheck/should_compile/all.T
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cpp.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.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/6e725431b202ee291e55c0dd959d6c…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6e725431b202ee291e55c0dd959d6c…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/fendor/t23703] Allow per constructor refinement of distinct-constructor-tables
by Hannes Siebenhandl (@fendor) 07 Oct '25
by Hannes Siebenhandl (@fendor) 07 Oct '25
07 Oct '25
Hannes Siebenhandl pushed to branch wip/fendor/t23703 at Glasgow Haskell Compiler / GHC
Commits:
f776c091 by Finley McIlwaine at 2025-10-07T09:50:00+02:00
Allow per constructor refinement of distinct-constructor-tables
Introduce `-fno-distinct-constructor-tables`. A distinct constructor table
configuration is built from the combination of flags given, in order. For
example, to only generate distinct constructor tables for a few specific
constructors and no others, just pass
`-fdistinct-constructor-tables-only=C1,...,CN`.
This flag can be supplied multiple times to extend the set of
constructors to generate a distinct info table for.
You can disable generation of distinct constructor tables for all
configurations by passing `-fno-distinct-constructor-tables`.
The various configurations of these flags is included in the `DynFlags`
fingerprints, which should result in the expected recompilation logic.
Adds a test that checks for distinct tables for various given or omitted
constructors.
Updates CountDepsAst and CountDepsParser tests to account for new dependencies.
Fixes #23703
- - - - -
29 changed files:
- compiler/GHC/Driver/Config/Stg/Debug.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Flags.hs
- compiler/GHC/Iface/Recomp/Flags.hs
- compiler/GHC/Stg/Debug.hs
- + compiler/GHC/Stg/Debug/Types.hs
- compiler/ghc.cabal.in
- docs/users_guide/debug-info.rst
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- + testsuite/tests/rts/ipe/distinct-tables/Main.hs
- + testsuite/tests/rts/ipe/distinct-tables/Makefile
- + testsuite/tests/rts/ipe/distinct-tables/X.hs
- + testsuite/tests/rts/ipe/distinct-tables/all.T
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables01.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables02.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables03.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables04.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables05.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables06.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables07.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables08.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables09.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables10.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables11.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables12.stdout
- + testsuite/tests/rts/ipe/distinct-tables/distinct_tables13.stdout
Changes:
=====================================
compiler/GHC/Driver/Config/Stg/Debug.hs
=====================================
@@ -10,5 +10,5 @@ import GHC.Driver.DynFlags
initStgDebugOpts :: DynFlags -> StgDebugOpts
initStgDebugOpts dflags = StgDebugOpts
{ stgDebug_infoTableMap = gopt Opt_InfoTableMap dflags
- , stgDebug_distinctConstructorTables = gopt Opt_DistinctConstructorTables dflags
+ , stgDebug_distinctConstructorTables = distinctConstructorTables dflags
}
=====================================
compiler/GHC/Driver/DynFlags.hs
=====================================
@@ -117,6 +117,7 @@ import GHC.Types.SrcLoc
import GHC.Unit.Module
import GHC.Unit.Module.Warnings
import GHC.Utils.CliOption
+import GHC.Stg.Debug.Types (StgDebugDctConfig(..))
import GHC.SysTools.Terminal ( stderrSupportsAnsiColors )
import GHC.UniqueSubdir (uniqueSubdir)
import GHC.Utils.Outputable
@@ -134,6 +135,7 @@ import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Except (ExceptT)
import Control.Monad.Trans.Reader (ReaderT)
import Control.Monad.Trans.Writer (WriterT)
+import qualified Data.Set as Set
import Data.Word
import System.IO
import System.IO.Error (catchIOError)
@@ -142,7 +144,6 @@ import System.FilePath (normalise, (</>))
import System.Directory
import GHC.Foreign (withCString, peekCString)
-import qualified Data.Set as Set
import GHC.Types.Unique.Set
import qualified GHC.LanguageExtensions as LangExt
@@ -479,7 +480,11 @@ data DynFlags = DynFlags {
-- 'Int' because it can be used to test uniques in decreasing order.
-- | Temporary: CFG Edge weights for fast iterations
- cfgWeights :: Weights
+ cfgWeights :: Weights,
+
+ -- | Configuration specifying which constructor names we should create
+ -- distinct info tables for
+ distinctConstructorTables :: StgDebugDctConfig
}
class HasDynFlags m where
@@ -742,7 +747,9 @@ defaultDynFlags mySettings =
reverseErrors = False,
maxErrors = Nothing,
- cfgWeights = defaultWeights
+ cfgWeights = defaultWeights,
+
+ distinctConstructorTables = None
}
type FatalMessager = String -> IO ()
=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -595,7 +595,6 @@ data GeneralFlag
| Opt_NoBuiltinRules
| Opt_NoBignumRules
- | Opt_DistinctConstructorTables
| Opt_InfoTableMap
| Opt_InfoTableMapWithFallback
| Opt_InfoTableMapWithStack
@@ -986,7 +985,6 @@ codeGenFlags = EnumSet.fromList
, Opt_DoTagInferenceChecks
-- Flags that affect debugging information
- , Opt_DistinctConstructorTables
, Opt_InfoTableMap
, Opt_InfoTableMapWithStack
, Opt_InfoTableMapWithFallback
=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -277,6 +277,7 @@ import GHC.CmmToAsm.CFG.Weight
import GHC.Core.Opt.CallerCC
import GHC.Parser (parseIdentifier)
import GHC.Parser.Lexer (mkParserOpts, initParserState, P(..), ParseResult(..))
+import GHC.Stg.Debug.Types
import GHC.SysTools.BaseDir ( expandToolDir, expandTopDir )
@@ -1916,6 +1917,13 @@ dynamic_flags_deps = [
-- Caller-CC
, make_ord_flag defGhcFlag "fprof-callers"
(HasArg setCallerCcFilters)
+ , make_ord_flag defGhcFlag "fdistinct-constructor-tables"
+ (noArg enableDistinctConstructorTables)
+ , make_ord_flag defGhcFlag "fno-distinct-constructor-tables"
+ (noArg disableDistinctConstructorTables)
+ , make_ord_flag defGhcFlag "fdistinct-constructor-tables-only"
+ (Prefix onlyDistinctConstructorTables)
+
------ Compiler flags -----------------------------------------------
, make_ord_flag defGhcFlag "fasm" (NoArg (setObjBackend ncgBackend))
@@ -2617,7 +2625,6 @@ fFlagsDeps = [
flagSpec "cmm-thread-sanitizer" Opt_CmmThreadSanitizer,
flagSpec "split-sections" Opt_SplitSections,
flagSpec "break-points" Opt_InsertBreakpoints,
- flagSpec "distinct-constructor-tables" Opt_DistinctConstructorTables,
flagSpec "info-table-map" Opt_InfoTableMap,
flagSpec "info-table-map-with-stack" Opt_InfoTableMapWithStack,
flagSpec "info-table-map-with-fallback" Opt_InfoTableMapWithFallback
@@ -3215,6 +3222,41 @@ setCallerCcFilters arg =
Right filt -> upd $ \d -> d { callerCcFilters = filt : callerCcFilters d }
Left err -> addErr err
+enableDistinctConstructorTables :: DynFlags -> DynFlags
+enableDistinctConstructorTables d =
+ d { distinctConstructorTables = All
+ }
+
+disableDistinctConstructorTables :: DynFlags -> DynFlags
+disableDistinctConstructorTables d =
+ d { distinctConstructorTables = None
+ }
+
+onlyDistinctConstructorTables :: String -> DynP ()
+onlyDistinctConstructorTables arg = do
+ let cs = parseDistinctConstructorTablesArg arg
+ upd $ \d ->
+ d { distinctConstructorTables =
+ (distinctConstructorTables d) `dctConfigOnly` cs
+ }
+
+-- | Parse a string of comma-separated constructor names into a 'Set' of
+-- 'String's with one entry per constructor.
+parseDistinctConstructorTablesArg :: String -> Set.Set String
+parseDistinctConstructorTablesArg =
+ -- Ensure we insert the last constructor name built by the fold, if not
+ -- empty
+ uncurry insertNonEmpty
+ . foldr go ("", Set.empty)
+ where
+ go :: Char -> (String, Set.Set String) -> (String, Set.Set String)
+ go ',' (cur, acc) = ("", Set.insert cur acc)
+ go c (cur, acc) = (c : cur, acc)
+
+ insertNonEmpty :: String -> Set.Set String -> Set.Set String
+ insertNonEmpty "" = id
+ insertNonEmpty cs = Set.insert cs
+
setMainIs :: String -> DynP ()
setMainIs arg = parse parse_main_f arg
where
=====================================
compiler/GHC/Iface/Flags.hs
=====================================
@@ -6,12 +6,15 @@ module GHC.Iface.Flags (
, IfaceExtension(..)
, IfaceLanguage(..)
, IfaceCppOptions(..)
+ , IfaceCodeGen(..)
+ , IfaceDistinctConstructorConfig(..)
, pprIfaceDynFlags
, missingExtraFlagInfo
) where
import GHC.Prelude
+import qualified Data.Set as Set
import GHC.Utils.Outputable
import Control.DeepSeq
import GHC.Utils.Fingerprint
@@ -22,6 +25,7 @@ import GHC.Types.SafeHaskell
import GHC.Core.Opt.CallerCC.Types
import qualified GHC.LanguageExtensions as LangExt
+import GHC.Stg.Debug.Types
-- The part of DynFlags which recompilation information needs
data IfaceDynFlags = IfaceDynFlags
@@ -35,7 +39,7 @@ data IfaceDynFlags = IfaceDynFlags
, ifacePaths :: [String]
, ifaceProf :: Maybe IfaceProfAuto
, ifaceTicky :: [IfaceGeneralFlag]
- , ifaceCodeGen :: [IfaceGeneralFlag]
+ , ifaceCodeGen :: IfaceCodeGen
, ifaceFatIface :: Bool
, ifaceDebugLevel :: Int
, ifaceCallerCCFilters :: [CallerCcFilter]
@@ -58,7 +62,7 @@ pprIfaceDynFlags (IfaceDynFlags a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14)
, text "ticky:"
, nest 2 $ vcat (map ppr a10)
, text "codegen:"
- , nest 2 $ vcat (map ppr a11)
+ , nest 2 $ ppr a11
, text "fat-iface:" <+> ppr a12
, text "debug-level:" <+> ppr a13
, text "caller-cc-filters:" <+> ppr a14
@@ -191,4 +195,60 @@ instance Outputable IfaceCppOptions where
, text "signature:"
, nest 2 $ parens (ppr fp) <+> ppr (map (text @SDoc) wos)
- ]
\ No newline at end of file
+ ]
+
+data IfaceCodeGen = IfaceCodeGen
+ { ifaceCodeGenFlags :: [IfaceGeneralFlag]
+ , ifaceCodeGenDistinctConstructorTables :: IfaceDistinctConstructorConfig
+ }
+
+instance NFData IfaceCodeGen where
+ rnf (IfaceCodeGen flags distinctCnstrTables) =
+ rnf flags `seq` rnf distinctCnstrTables
+
+instance Binary IfaceCodeGen where
+ put_ bh (IfaceCodeGen flags distinctCnstrTables) = do
+ put_ bh flags
+ put_ bh distinctCnstrTables
+
+ get bh =
+ IfaceCodeGen <$> get bh <*> get bh
+
+instance Outputable IfaceCodeGen where
+ ppr (IfaceCodeGen flags distinctCnstrTables) =
+ vcat
+ [ text "flags:"
+ , nest 2 $ ppr flags
+ , text "distinct constructor tables:"
+ , nest 2 $ ppr distinctCnstrTables
+ ]
+
+newtype IfaceDistinctConstructorConfig = IfaceDistinctConstructorConfig StgDebugDctConfig
+
+instance NFData IfaceDistinctConstructorConfig where
+ rnf (IfaceDistinctConstructorConfig cnf) = case cnf of
+ All -> ()
+ (Only v) -> rnf v
+ None -> ()
+
+instance Outputable IfaceDistinctConstructorConfig where
+ ppr (IfaceDistinctConstructorConfig cnf) = case cnf of
+ All -> text "all"
+ (Only v) -> text "only" <+> brackets (hcat $ fmap text $ Set.toList v)
+ None -> text "none"
+
+instance Binary IfaceDistinctConstructorConfig where
+ put_ bh (IfaceDistinctConstructorConfig cnf) = case cnf of
+ All -> putByte bh 0
+ (Only cs) -> do
+ putByte bh 1
+ put_ bh cs
+ None -> putByte bh 2
+
+ get bh = do
+ h <- getByte bh
+ IfaceDistinctConstructorConfig <$>
+ case h of
+ 0 -> pure All
+ 1 -> Only <$> get bh
+ _ -> pure None
=====================================
compiler/GHC/Iface/Recomp/Flags.hs
=====================================
@@ -91,12 +91,30 @@ fingerprintDynFlags hsc_env this_mod nameio =
mapMaybe (\f -> (if f `gopt` dflags then Just (IfaceGeneralFlag f) else Nothing)) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk, Opt_Ticky_Tag]
-- Other flags which affect code generation
- codegen = mapMaybe (\f -> (if f `gopt` dflags then Just (IfaceGeneralFlag f) else Nothing)) (EnumSet.toList codeGenFlags)
+ codegen = IfaceCodeGen
+ { ifaceCodeGenFlags = mapMaybe (\f -> (if f `gopt` dflags then Just (IfaceGeneralFlag f) else Nothing)) (EnumSet.toList codeGenFlags)
+ , ifaceCodeGenDistinctConstructorTables = IfaceDistinctConstructorConfig distinctConstructorTables
+ }
-- Did we include core for all bindings?
fat_iface = gopt Opt_WriteIfSimplifiedCore dflags
- f = IfaceDynFlags mainis safeHs lang exts cpp js cmm paths prof ticky codegen fat_iface debugLevel callerCcFilters
+ f = IfaceDynFlags
+ { ifaceMainIs = mainis
+ , ifaceSafeMode = safeHs
+ , ifaceLang = lang
+ , ifaceExts = exts
+ , ifaceCppOptions = cpp
+ , ifaceJsOptions = js
+ , ifaceCmmOptions = cmm
+ , ifacePaths = paths
+ , ifaceProf = prof
+ , ifaceTicky = ticky
+ , ifaceCodeGen = codegen
+ , ifaceFatIface = fat_iface
+ , ifaceDebugLevel = debugLevel
+ , ifaceCallerCCFilters = callerCcFilters
+ }
in (computeFingerprint nameio f, f)
=====================================
compiler/GHC/Stg/Debug.hs
=====================================
@@ -1,9 +1,12 @@
-{-# LANGUAGE TupleSections #-}
+{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE TupleSections #-}
-- This module contains functions which implement
-- the -finfo-table-map and -fdistinct-constructor-tables flags
module GHC.Stg.Debug
( StgDebugOpts(..)
+ , StgDebugDctConfig(..)
+ , dctConfigOnly
, collectDebugInformation
) where
@@ -17,11 +20,13 @@ import GHC.Types.Tickish
import GHC.Core.DataCon
import GHC.Types.IPE
import GHC.Unit.Module
-import GHC.Types.Name ( getName, getOccName, occNameFS, nameSrcSpan)
+import GHC.Types.Name ( getName, getOccName, occNameFS, nameSrcSpan, occName, occNameString)
import GHC.Data.FastString
+import GHC.Stg.Debug.Types
import Control.Monad (when)
import Control.Monad.Trans.Reader
+import qualified Data.Set as Set
import GHC.Utils.Monad.State.Strict
import Control.Monad.Trans.Class
import GHC.Types.SrcLoc
@@ -29,13 +34,6 @@ import Control.Applicative
import qualified Data.List.NonEmpty as NE
import Data.List.NonEmpty (NonEmpty(..))
-data SpanWithLabel = SpanWithLabel RealSrcSpan LexicalFastString
-
-data StgDebugOpts = StgDebugOpts
- { stgDebug_infoTableMap :: !Bool
- , stgDebug_distinctConstructorTables :: !Bool
- }
-
data R = R { rOpts :: StgDebugOpts, rModLocation :: ModLocation, rSpan :: Maybe SpanWithLabel }
type M a = ReaderT R (State InfoTableProvMap) a
@@ -164,10 +162,11 @@ numberDataCon dc _ | isUnboxedTupleDataCon dc = return NoNumber
numberDataCon dc _ | isUnboxedSumDataCon dc = return NoNumber
numberDataCon dc ts = do
opts <- asks rOpts
- if stgDebug_distinctConstructorTables opts then do
- -- -fdistinct-constructor-tables is enabled. Add an entry to the data
- -- constructor map for this occurrence of the data constructor with a unique
- -- number and a src span
+ if shouldMakeDistinctTable opts dc then do
+ -- -fdistinct-constructor-tables is enabled and we do want to make distinct
+ -- tables for this constructor. Add an entry to the data constructor map for
+ -- this occurrence of the data constructor with a unique number and a src
+ -- span
env <- lift get
mcc <- asks rSpan
let
@@ -192,7 +191,8 @@ numberDataCon dc ts = do
Nothing -> NoNumber
Just (_, res) -> Numbered (fst (NE.head res))
else do
- -- -fdistinct-constructor-tables is not enabled
+ -- -fdistinct-constructor-tables is not enabled, or we do not want to make
+ -- distinct tables for this specific constructor
return NoNumber
selectTick :: [StgTickish] -> Maybe (RealSrcSpan, LexicalFastString)
@@ -202,6 +202,19 @@ selectTick = foldl' go Nothing
go _ (SourceNote rss d) = Just (rss, d)
go acc _ = acc
+-- | Descide whether a distinct info table should be made for a usage of a data
+-- constructor. We only want to do this if -fdistinct-constructor-tables was
+-- given and this constructor name was given, or no constructor names were
+-- given.
+shouldMakeDistinctTable :: StgDebugOpts -> DataCon -> Bool
+shouldMakeDistinctTable StgDebugOpts{..} dc =
+ case stgDebug_distinctConstructorTables of
+ All -> True
+ Only these -> Set.member dcStr these
+ None -> False
+ where
+ dcStr = occNameString . occName $ dataConName dc
+
{-
Note [Mapping Info Tables to Source Positions]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
=====================================
compiler/GHC/Stg/Debug/Types.hs
=====================================
@@ -0,0 +1,53 @@
+module GHC.Stg.Debug.Types where
+
+import GHC.Prelude
+
+import GHC.Data.FastString
+import GHC.Types.SrcLoc
+
+import Data.Set (Set)
+import qualified Data.Set as Set
+
+data SpanWithLabel = SpanWithLabel RealSrcSpan LexicalFastString
+
+data StgDebugOpts = StgDebugOpts
+ { stgDebug_infoTableMap :: !Bool
+ , stgDebug_distinctConstructorTables :: !StgDebugDctConfig
+ }
+
+-- | Configuration describing which constructors should be given distinct info
+-- tables for each usage.
+data StgDebugDctConfig =
+ -- | Create distinct constructor tables for each usage of any data
+ -- constructor.
+ --
+ -- This is the behavior if just @-fdistinct-constructor-tables@ is supplied.
+ All
+
+ -- | Create distinct constructor tables for each usage of only these data
+ -- constructors.
+ --
+ -- This is the behavior if @-fdistinct-constructor-tables-only=C1,...,CN@ is
+ -- supplied.
+ | Only !(Set String)
+
+ -- | Do not create distinct constructor tables for any data constructor.
+ --
+ -- This is the behavior if @-fno-distinct-constructor-tables@ is given.
+ | None
+
+-- | Given a distinct constructor tables configuration and a set of constructor
+-- names that we want to generate distinct info tables for, create a new
+-- configuration which includes those constructors.
+--
+-- If the given set is empty, that means the user has entered
+-- @-fdistinct-constructor-tables@ with no constructor names specified, and
+-- therefore we consider that an 'All' configuration.
+dctConfigOnly :: StgDebugDctConfig -> Set String -> StgDebugDctConfig
+dctConfigOnly cfg cs
+ | Set.null cs = All
+ | otherwise =
+ case cfg of
+ All -> Only cs
+ Only cs' -> Only $ Set.union cs' cs
+ None -> Only cs
=====================================
compiler/ghc.cabal.in
=====================================
@@ -739,6 +739,7 @@ Library
GHC.Stg.EnforceEpt.Rewrite
GHC.Stg.EnforceEpt.TagSig
GHC.Stg.EnforceEpt.Types
+ GHC.Stg.Debug.Types
GHC.Stg.FVs
GHC.Stg.Lift
GHC.Stg.Lift.Analysis
=====================================
docs/users_guide/debug-info.rst
=====================================
@@ -368,7 +368,8 @@ to a source location. This lookup table is generated by using the ``-finfo-table
an info table to an approximate source position of where that
info table statically originated from. If you
also want more precise information about constructor info tables then you
- should also use :ghc-flag:`-fdistinct-constructor-tables`.
+ should also use :ghc-flag:`-fdistinct-constructor-tables
+ <-fdistinct-constructor-tables>`.
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
@@ -467,6 +468,38 @@ to a source location. This lookup table is generated by using the ``-finfo-table
each info table will correspond to the usage of a data constructor rather
than the data constructor itself.
+.. ghc-flag:: -fno-distinct-constructor-tables
+ :shortdesc: Avoid generating a fresh info table for each usage of a data
+ constructor.
+ :type: dynamic
+ :category: debugging
+
+ :since: 9.16
+
+ Use this flag to don't generate distinct info for any usages of any data
+ constructors.
+
+.. ghc-flag:: -fdistinct-constructor-tables-only=⟨cs⟩
+ :shortdesc: Generate a fresh info table for each usage
+ of a data constructor.
+ :type: dynamic
+ :category: debugging
+
+ :since: 9.16
+
+ The entries in the info table map resulting from
+ :ghc-flag:`-fdistinct-constructor-tables` flag may significantly
+ increase the size of executables. However, generating distinct info tables
+ for *every* usage of *every* data constructor often results in more
+ information than necessary. Instead, we would like to generate these
+ distinct tables for some specific constructors. To do this, the names of the
+ constructors we are interested in may be supplied to this flag in a
+ comma-separated list. If no constructor names are supplied (i.e. just
+ ``-fdistinct-constructor-tables`` is given) then fresh info tables will be
+ generated for every usage of every constructor.
+
+ For example, to only generate distinct info tables for the ``Just`` and
+ ``Right`` constructors, use ``-fdistinct-constructor-tables=Just,Right``.
Querying the Info Table Map
---------------------------
=====================================
testsuite/tests/count-deps/CountDepsAst.stdout
=====================================
@@ -123,6 +123,7 @@ GHC.Runtime.Heap.Layout
GHC.Settings
GHC.Settings.Config
GHC.Settings.Constants
+GHC.Stg.Debug.Types
GHC.Stg.EnforceEpt.TagSig
GHC.StgToCmm.Types
GHC.SysTools.Terminal
=====================================
testsuite/tests/count-deps/CountDepsParser.stdout
=====================================
@@ -142,6 +142,7 @@ GHC.Runtime.Heap.Layout
GHC.Settings
GHC.Settings.Config
GHC.Settings.Constants
+GHC.Stg.Debug.Types
GHC.Stg.EnforceEpt.TagSig
GHC.StgToCmm.Types
GHC.SysTools.Terminal
=====================================
testsuite/tests/rts/ipe/distinct-tables/Main.hs
=====================================
@@ -0,0 +1,37 @@
+module Main where
+
+import GHC.InfoProv
+import qualified X
+
+main = do
+ printIp =<< whereFrom cafA1
+ printIp =<< whereFrom cafA2
+ printIp =<< whereFrom cafB1
+ printIp =<< whereFrom cafB2
+ printIp =<< whereFrom cafC1
+ printIp =<< whereFrom cafC2
+ printIp =<< whereFrom (ACon ())
+ printIp =<< whereFrom cafXA
+ printIp =<< whereFrom X.cafXA1
+ printIp =<< whereFrom X.cafXA2
+ printIp =<< whereFrom (X.ACon ())
+ printIp =<< whereFrom (BCon cafA1)
+ printIp =<< whereFrom (CCon (cafA1, BCon (ACon ())))
+ where
+ -- Get rid of the src file path since it makes test output difficult to diff
+ -- on Windows
+ printIp = print . stripIpSrc
+ stripIpSrc (Just ip) = ip { ipSrcFile = "" }
+
+data A = ACon ()
+data B = BCon A
+data C = CCon (A, B)
+
+cafA1 = ACon ()
+cafA2 = ACon ()
+cafB1 = BCon cafA1
+cafB2 = BCon cafA2
+cafC1 = CCon (cafA1, cafB1)
+cafC2 = CCon (cafA2, cafB2)
+
+cafXA = X.ACon ()
=====================================
testsuite/tests/rts/ipe/distinct-tables/Makefile
=====================================
@@ -0,0 +1,66 @@
+TOP=../../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+# This test runs ghc with various combinations of
+# -f{no-}distinct-constructor-tables for different constructors and checks that
+# whereFrom finds (or fails to find) their provenance appropriately.
+
+distinct_tables01:
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables-only=ACon Main.hs
+ ./Main
+
+distinct_tables02:
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables-only=BCon Main.hs
+ ./Main
+
+distinct_tables03:
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables-only=CCon Main.hs
+ ./Main
+
+distinct_tables04:
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables-only=ACon,BCon Main.hs
+ ./Main
+
+distinct_tables05:
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables-only=ACon -fdistinct-constructor-tables-only=BCon -fdistinct-constructor-tables-only=CCon Main.hs
+ ./Main
+
+distinct_tables06:
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables-only=ACon -fno-distinct-constructor-tables Main.hs
+ ./Main
+
+distinct_tables07:
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables -fdistinct-constructor-tables-only=ACon -fno-distinct-constructor-tables Main.hs
+ ./Main
+
+distinct_tables08:
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 -finfo-table-map -fno-distinct-constructor-tables Main.hs
+ ./Main
+
+distinct_tables09:
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 -finfo-table-map -fno-distinct-constructor-tables -fdistinct-constructor-tables-only=ACon Main.hs
+ ./Main
+
+distinct_tables10:
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables Main.hs
+ ./Main
+
+# Recompilation tests
+distinct_tables11:
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables Main.hs
+ ./Main
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables -fdistinct-constructor-tables-only=ACon Main.hs
+ ./Main
+
+distinct_tables12:
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 -finfo-table-map -fno-distinct-constructor-tables Main.hs
+ ./Main
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables Main.hs
+ ./Main
+
+distinct_tables13:
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables Main.hs
+ ./Main
+ "$(TEST_HC)" $(TEST_HC_OPTS) -v0 -finfo-table-map -fdistinct-constructor-tables -fdistinct-constructor-tables-only=ACon Main.hs
+ ./Main
=====================================
testsuite/tests/rts/ipe/distinct-tables/X.hs
=====================================
@@ -0,0 +1,7 @@
+module X where
+
+-- A type with the same constructor name as 'Main.ACon'
+data X = ACon ()
+
+cafXA1 = ACon ()
+cafXA2 = ACon ()
=====================================
testsuite/tests/rts/ipe/distinct-tables/all.T
=====================================
@@ -0,0 +1,13 @@
+test('distinct_tables01', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
+test('distinct_tables02', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
+test('distinct_tables03', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
+test('distinct_tables04', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
+test('distinct_tables05', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
+test('distinct_tables06', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
+test('distinct_tables07', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
+test('distinct_tables08', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
+test('distinct_tables09', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
+test('distinct_tables10', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
+test('distinct_tables11', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
+test('distinct_tables12', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
+test('distinct_tables13', [extra_files(['Main.hs', 'X.hs',])], makefile_test, [])
=====================================
testsuite/tests/rts/ipe/distinct-tables/distinct_tables01.stdout
=====================================
@@ -0,0 +1,13 @@
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"}
+InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"}
+InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"}
+InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"}
+InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"}
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
=====================================
testsuite/tests/rts/ipe/distinct-tables/distinct_tables02.stdout
=====================================
@@ -0,0 +1,13 @@
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "32:1-18"}
+InfoProv {ipName = "BCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "33:1-18"}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "18:17-38"}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
=====================================
testsuite/tests/rts/ipe/distinct-tables/distinct_tables03.stdout
=====================================
@@ -0,0 +1,13 @@
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "34:1-27"}
+InfoProv {ipName = "CCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "35:1-27"}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_Main_3_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "19:34-38"}
=====================================
testsuite/tests/rts/ipe/distinct-tables/distinct_tables04.stdout
=====================================
@@ -0,0 +1,13 @@
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"}
+InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"}
+InfoProv {ipName = "BCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "32:1-18"}
+InfoProv {ipName = "BCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "33:1-18"}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"}
+InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"}
+InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"}
+InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"}
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"}
+InfoProv {ipName = "BCon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "18:17-38"}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
=====================================
testsuite/tests/rts/ipe/distinct-tables/distinct_tables05.stdout
=====================================
@@ -0,0 +1,13 @@
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"}
+InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"}
+InfoProv {ipName = "BCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "32:1-18"}
+InfoProv {ipName = "BCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "33:1-18"}
+InfoProv {ipName = "CCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "34:1-27"}
+InfoProv {ipName = "CCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "35:1-27"}
+InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"}
+InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"}
+InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"}
+InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"}
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"}
+InfoProv {ipName = "BCon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "18:17-38"}
+InfoProv {ipName = "CCon_Main_3_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "19:34-38"}
=====================================
testsuite/tests/rts/ipe/distinct-tables/distinct_tables06.stdout
=====================================
@@ -0,0 +1,13 @@
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
=====================================
testsuite/tests/rts/ipe/distinct-tables/distinct_tables07.stdout
=====================================
@@ -0,0 +1,13 @@
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
=====================================
testsuite/tests/rts/ipe/distinct-tables/distinct_tables08.stdout
=====================================
@@ -0,0 +1,13 @@
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
=====================================
testsuite/tests/rts/ipe/distinct-tables/distinct_tables09.stdout
=====================================
@@ -0,0 +1,13 @@
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"}
+InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"}
+InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"}
+InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"}
+InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"}
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
=====================================
testsuite/tests/rts/ipe/distinct-tables/distinct_tables10.stdout
=====================================
@@ -0,0 +1,13 @@
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"}
+InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"}
+InfoProv {ipName = "BCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "32:1-18"}
+InfoProv {ipName = "BCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "33:1-18"}
+InfoProv {ipName = "CCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "34:1-27"}
+InfoProv {ipName = "CCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "35:1-27"}
+InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"}
+InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"}
+InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"}
+InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"}
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"}
+InfoProv {ipName = "BCon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "18:17-38"}
+InfoProv {ipName = "CCon_Main_3_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "19:34-38"}
=====================================
testsuite/tests/rts/ipe/distinct-tables/distinct_tables11.stdout
=====================================
@@ -0,0 +1,26 @@
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"}
+InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"}
+InfoProv {ipName = "BCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "32:1-18"}
+InfoProv {ipName = "BCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "33:1-18"}
+InfoProv {ipName = "CCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "34:1-27"}
+InfoProv {ipName = "CCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "35:1-27"}
+InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"}
+InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"}
+InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"}
+InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"}
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"}
+InfoProv {ipName = "BCon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "18:17-38"}
+InfoProv {ipName = "CCon_Main_3_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "19:34-38"}
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"}
+InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"}
+InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"}
+InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"}
+InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"}
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
=====================================
testsuite/tests/rts/ipe/distinct-tables/distinct_tables12.stdout
=====================================
@@ -0,0 +1,26 @@
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"}
+InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"}
+InfoProv {ipName = "BCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "32:1-18"}
+InfoProv {ipName = "BCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "33:1-18"}
+InfoProv {ipName = "CCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "34:1-27"}
+InfoProv {ipName = "CCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "35:1-27"}
+InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"}
+InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"}
+InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"}
+InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"}
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"}
+InfoProv {ipName = "BCon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "18:17-38"}
+InfoProv {ipName = "CCon_Main_3_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "19:34-38"}
=====================================
testsuite/tests/rts/ipe/distinct-tables/distinct_tables13.stdout
=====================================
@@ -0,0 +1,26 @@
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"}
+InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"}
+InfoProv {ipName = "BCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "32:1-18"}
+InfoProv {ipName = "BCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "cafB2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "33:1-18"}
+InfoProv {ipName = "CCon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "34:1-27"}
+InfoProv {ipName = "CCon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "cafC2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "35:1-27"}
+InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"}
+InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"}
+InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"}
+InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"}
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"}
+InfoProv {ipName = "BCon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "B", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "18:17-38"}
+InfoProv {ipName = "CCon_Main_3_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "C", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "19:34-38"}
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA1", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "30:1-15"}
+InfoProv {ipName = "ACon_Main_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "cafA2", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "31:1-15"}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "ACon_Main_4_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "A", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "13:17-35"}
+InfoProv {ipName = "ACon_Main_0_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "37:1-17"}
+InfoProv {ipName = "ACon_X_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA1", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "6:1-16"}
+InfoProv {ipName = "ACon_X_2_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "cafXA2", ipUnitId = "main", ipMod = "X", ipSrcFile = "", ipSrcSpan = "7:1-16"}
+InfoProv {ipName = "ACon_Main_1_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "X", ipLabel = "main", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = "17:17-37"}
+InfoProv {ipName = "BCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
+InfoProv {ipName = "CCon_con_info", ipDesc = CONSTR_1_0, ipTyDesc = "", ipLabel = "", ipUnitId = "main", ipMod = "Main", ipSrcFile = "", ipSrcSpan = ""}
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f776c0919161ab9b3522913881b467f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f776c0919161ab9b3522913881b467f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc] Pushed new branch wip/fix/toolTarget-ghc-heap
by Hannes Siebenhandl (@fendor) 07 Oct '25
by Hannes Siebenhandl (@fendor) 07 Oct '25
07 Oct '25
Hannes Siebenhandl pushed new branch wip/fix/toolTarget-ghc-heap at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix/toolTarget-ghc-heap
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc] Pushed new branch wip/fendor/t23703-backup
by Hannes Siebenhandl (@fendor) 07 Oct '25
by Hannes Siebenhandl (@fendor) 07 Oct '25
07 Oct '25
Hannes Siebenhandl pushed new branch wip/fendor/t23703-backup at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fendor/t23703-backup
You're receiving this email because of your account on gitlab.haskell.org.
1
0