[Git][ghc/ghc][master] Remove unnecessary irrefutable patterns from Bifunctor instances for tuples
by Marge Bot (@marge-bot) 02 Sep '25
by Marge Bot (@marge-bot) 02 Sep '25
02 Sep '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
ca5b0283 by Sergey Vinokurov at 2025-09-01T23:02:23-04:00
Remove unnecessary irrefutable patterns from Bifunctor instances for tuples
Implementation of https://github.com/haskell/core-libraries-committee/issues/339
Metric Decrease:
mhu-perf
- - - - -
2 changed files:
- libraries/base/changelog.md
- libraries/base/src/Data/Bifunctor.hs
Changes:
=====================================
libraries/base/changelog.md
=====================================
@@ -7,6 +7,7 @@
* Modify the implementation of `Data.List.sortOn` to use `(>)` instead of `compare`. ([CLC proposal #332](https://github.com/haskell/core-libraries-committee/issues/332))
* `GHC.Exts.IOPort#` and its related operations have been removed ([CLC #213](https://github.com/haskell/core-libraries-committee/issues/213))
* Fix bug where `naturalAndNot` was incorrectly truncating results ([CLC proposal #350](github.com/haskell/core-libraries-committee/issues/350))
+ * Remove extra laziness from `Data.Bifunctor.Bifunctor` instances for all tuples to have the same laziness as their `Data.Functor.Functor` counterparts (i.e. they became more strict than before) ([CLC proposal #339](https://github.com/haskell/core-libraries-committee/issues/339))
## 4.22.0.0 *TBA*
* Shipped with GHC 9.14.1
=====================================
libraries/base/src/Data/Bifunctor.hs
=====================================
@@ -133,39 +133,39 @@ class (forall a. Functor (p a)) => Bifunctor p where
second = bimap id
--- | Class laws for tuples hold only up to laziness. Both
--- 'first' 'id' and 'second' 'id' are lazier than 'id' (and 'fmap' 'id'):
+-- | Tuple instances have the same laziness as for 'Functor'. Both
+-- 'first' 'id' and 'second' 'id' have the same laziness as 'id' (and 'fmap' 'id'):
--
--- >>> first id (undefined :: (Int, Word)) `seq` ()
--- ()
--- >>> second id (undefined :: (Int, Word)) `seq` ()
--- ()
+-- >>> first id (errorWithoutStackTrace "error!" :: (Int, Word)) `seq` ()
+-- *** Exception: error!
+-- >>> second id (errorWithoutStackTrace "error!" :: (Int, Word)) `seq` ()
+-- *** Exception: error!
-- >>> id (errorWithoutStackTrace "error!" :: (Int, Word)) `seq` ()
-- *** Exception: error!
--
-- @since 4.8.0.0
instance Bifunctor (,) where
- bimap f g ~(a, b) = (f a, g b)
+ bimap f g (a, b) = (f a, g b)
-- | @since 4.8.0.0
instance Bifunctor ((,,) x1) where
- bimap f g ~(x1, a, b) = (x1, f a, g b)
+ bimap f g (x1, a, b) = (x1, f a, g b)
-- | @since 4.8.0.0
instance Bifunctor ((,,,) x1 x2) where
- bimap f g ~(x1, x2, a, b) = (x1, x2, f a, g b)
+ bimap f g (x1, x2, a, b) = (x1, x2, f a, g b)
-- | @since 4.8.0.0
instance Bifunctor ((,,,,) x1 x2 x3) where
- bimap f g ~(x1, x2, x3, a, b) = (x1, x2, x3, f a, g b)
+ bimap f g (x1, x2, x3, a, b) = (x1, x2, x3, f a, g b)
-- | @since 4.8.0.0
instance Bifunctor ((,,,,,) x1 x2 x3 x4) where
- bimap f g ~(x1, x2, x3, x4, a, b) = (x1, x2, x3, x4, f a, g b)
+ bimap f g (x1, x2, x3, x4, a, b) = (x1, x2, x3, x4, f a, g b)
-- | @since 4.8.0.0
instance Bifunctor ((,,,,,,) x1 x2 x3 x4 x5) where
- bimap f g ~(x1, x2, x3, x4, x5, a, b) = (x1, x2, x3, x4, x5, f a, g b)
+ bimap f g (x1, x2, x3, x4, x5, a, b) = (x1, x2, x3, x4, x5, f a, g b)
-- | @since 4.8.0.0
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ca5b02838abf8ad9d7a262396eb3df7…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ca5b02838abf8ad9d7a262396eb3df7…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] RTS: rely less on Hadrian for flag setting (#25843)
by Marge Bot (@marge-bot) 02 Sep '25
by Marge Bot (@marge-bot) 02 Sep '25
02 Sep '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
a1567efd by Sylvain Henry at 2025-09-01T23:01:35-04:00
RTS: rely less on Hadrian for flag setting (#25843)
Hadrian used to pass -Dfoo command-line flags directly to build the rts.
We can replace most of these flags with CPP based on cabal flags.
It makes building boot libraries with cabal-install simpler (cf #25843).
- - - - -
4 changed files:
- hadrian/src/Settings/Packages.hs
- rts/RtsMessages.c
- rts/RtsUtils.c
- rts/Trace.c
Changes:
=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -287,15 +287,6 @@ ghcInternalArgs = package ghcInternal ? do
-- | RTS-specific command line arguments.
rtsPackageArgs :: Args
rtsPackageArgs = package rts ? do
- projectVersion <- getSetting ProjectVersion
- buildPlatform <- queryBuild targetPlatformTriple
- buildArch <- queryBuild queryArch
- buildOs <- queryBuild queryOS
- buildVendor <- queryBuild queryVendor
- targetPlatform <- queryTarget targetPlatformTriple
- targetArch <- queryTarget queryArch
- targetOs <- queryTarget queryOS
- targetVendor <- queryTarget queryVendor
ghcUnreg <- queryTarget tgtUnregisterised
ghcEnableTNC <- queryTarget tgtTablesNextToCode
rtsWays <- getRtsWays
@@ -363,25 +354,11 @@ rtsPackageArgs = package rts ? do
, inputs ["**/RtsMessages.c", "**/Trace.c"] ?
pure
- ["-DProjectVersion=" ++ show projectVersion
- , "-DRtsWay=\"rts_" ++ show way ++ "\""
+ [ "-DRtsWay=\"rts_" ++ show way ++ "\""
]
, input "**/RtsUtils.c" ? pure
- [ "-DProjectVersion=" ++ show projectVersion
- -- the RTS' host is the compiler's target (the target should be
- -- per stage ideally...)
- , "-DHostPlatform=" ++ show targetPlatform
- , "-DHostArch=" ++ show targetArch
- , "-DHostOS=" ++ show targetOs
- , "-DHostVendor=" ++ show targetVendor
- , "-DBuildPlatform=" ++ show buildPlatform
- , "-DBuildArch=" ++ show buildArch
- , "-DBuildOS=" ++ show buildOs
- , "-DBuildVendor=" ++ show buildVendor
- , "-DGhcUnregisterised=" ++ show (yesNo ghcUnreg)
- , "-DTablesNextToCode=" ++ show (yesNo ghcEnableTNC)
- , "-DRtsWay=\"rts_" ++ show way ++ "\""
+ [ "-DRtsWay=\"rts_" ++ show way ++ "\""
]
-- We're after pure performance here. So make sure fast math and
=====================================
rts/RtsMessages.c
=====================================
@@ -9,6 +9,7 @@
#include "rts/PosixSource.h"
#include "Rts.h"
#include "RtsUtils.h"
+#include "ghcversion.h"
#include "eventlog/EventLog.h"
@@ -177,7 +178,7 @@ rtsFatalInternalErrorFn(const char *s, va_list ap)
libdwFree(session);
#endif
fprintf(stderr, "\n");
- fprintf(stderr, " (GHC version %s for %s)\n", ProjectVersion, xstr(HostPlatform_TYPE));
+ fprintf(stderr, " (GHC version %s for %s)\n", __GLASGOW_HASKELL_FULL_VERSION__, xstr(HostPlatform_TYPE));
fprintf(stderr, " Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug\n");
fflush(stderr);
}
=====================================
rts/RtsUtils.c
=====================================
@@ -9,6 +9,8 @@
#include "rts/PosixSource.h"
#include "Rts.h"
#include "RtsAPI.h"
+#include "ghcplatform.h"
+#include "ghcversion.h"
#include "RtsUtils.h"
#include "Ticky.h"
@@ -369,20 +371,28 @@ void printRtsInfo(const RtsConfig rts_config) {
/* The first entry is just a hack to make it easy to get the
* commas right */
printf(" [(\"GHC RTS\", \"YES\")\n");
- mkRtsInfoPair("GHC version", ProjectVersion);
+ mkRtsInfoPair("GHC version", __GLASGOW_HASKELL_FULL_VERSION__);
mkRtsInfoPair("RTS way", RtsWay);
- mkRtsInfoPair("Host platform", HostPlatform);
- mkRtsInfoPair("Host architecture", HostArch);
- mkRtsInfoPair("Host OS", HostOS);
- mkRtsInfoPair("Host vendor", HostVendor);
+ mkRtsInfoPair("Host platform", HOST_ARCH "-" HOST_VENDOR "-" HOST_OS);
+ mkRtsInfoPair("Host architecture", HOST_ARCH);
+ mkRtsInfoPair("Host OS", HOST_OS);
+ mkRtsInfoPair("Host vendor", HOST_VENDOR);
mkRtsInfoPair("Word size", TOSTRING(WORD_SIZE_IN_BITS));
// TODO(@Ericson2314) This is a joint property of the RTS and generated
// code. The compiler will soon be multi-target so it doesn't make sense to
// say the target is <ABI adj>, unless we are talking about the host
// platform of the compiler / ABI used by a compiler plugin. This is *not*
// that, so I think a rename is in order to avoid confusion.
- mkRtsInfoPair("Compiler unregisterised", GhcUnregisterised);
- mkRtsInfoPair("Tables next to code", TablesNextToCode);
+#if defined(UnregisterisedCompiler)
+ mkRtsInfoPair("Compiler unregisterised", "YES");
+#else
+ mkRtsInfoPair("Compiler unregisterised", "NO");
+#endif
+#if defined(TABLES_NEXT_TO_CODE)
+ mkRtsInfoPair("Tables next to code", "YES");
+#else
+ mkRtsInfoPair("Tables next to code", "NO");
+#endif
mkRtsInfoPair("Flag -with-rtsopts", /* See #15261 */
rts_config.rts_opts != NULL ? rts_config.rts_opts : "");
selectIOManager(); /* resolve the io-manager, accounting for flags */
=====================================
rts/Trace.c
=====================================
@@ -8,6 +8,7 @@
// external headers
#include "Rts.h"
+#include "ghcversion.h"
// internal headers
#include "Trace.h"
@@ -503,7 +504,7 @@ void traceOSProcessInfo_(void) {
#endif
{
char buf[256];
- snprintf(buf, sizeof(buf), "GHC-%s %s", ProjectVersion, RtsWay);
+ snprintf(buf, sizeof(buf), "GHC-%s %s", __GLASGOW_HASKELL_FULL_VERSION__, RtsWay);
postCapsetStrEvent(EVENT_RTS_IDENTIFIER,
CAPSET_OSPROCESS_DEFAULT,
buf);
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a1567efd3d3e6d5f8cf257366d441fc…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a1567efd3d3e6d5f8cf257366d441fc…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Simon Peyton Jones pushed to branch wip/T26315 at Glasgow Haskell Compiler / GHC
Commits:
04f3db59 by Simon Peyton Jones at 2025-09-02T01:01:25+01:00
Wibbles
- - - - -
5 changed files:
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/Utils/Monad.hs
Changes:
=====================================
compiler/GHC/Tc/Gen/Sig.hs
=====================================
@@ -39,7 +39,7 @@ import GHC.Tc.Gen.HsType
import GHC.Tc.Solver( reportUnsolvedEqualities, pushLevelAndSolveEqualitiesX
, emitResidualConstraints )
import GHC.Tc.Solver.Solve( solveWanteds )
-import GHC.Tc.Solver.Monad( runTcS, setTcSMode, TcSMode(..), runTcSWithEvBinds )
+import GHC.Tc.Solver.Monad( runTcS, setTcSMode, TcSMode(..), vanillaTcSMode, runTcSWithEvBinds )
import GHC.Tc.Validity ( checkValidType )
import GHC.Tc.Utils.Monad
=====================================
compiler/GHC/Tc/Solver/Dict.hs
=====================================
@@ -1146,12 +1146,12 @@ matchLocalInst :: TcPredType -> CtLoc -> TcS ClsInstResult
-- Look up the predicate in Given quantified constraints,
-- which are effectively just local instance declarations.
matchLocalInst body_pred loc
- = odo { -- Look in the inert set for a matching Given quantified constraint
+ = do { -- Look in the inert set for a matching Given quantified constraint
inerts@(IS { inert_cans = ics }) <- getInertSet
; case match_local_inst inerts (inert_qcis ics) of
- { ([], []) -> do { traceTcS "No local instance for" (ppr body_pred)
- ; return NoInstance }
- ; (matches, unifs) ->
+ { ([], []) -> do { traceTcS "No local instance for" (ppr body_pred)
+ ; return NoInstance }
+ ; (matches, unifs) ->
do { -- Find the best match
-- See Note [Use only the best matching quantified constraint]
=====================================
compiler/GHC/Tc/Solver/Monad.hs
=====================================
@@ -909,19 +909,19 @@ data TcSMode
-- ^ Do not select an OVERLAPPABLE instance
, tcsmFullySolveQCIs :: Bool
-- ^ Fully solve all constraints, without using local Givens
- deriving (Eq)
+ }
vanillaTcSMode :: TcSMode
-vanillaTcSMode = TcSMode { tcs_pm_check = False
+vanillaTcSMode = TcSMode { tcsmPmCheck = False
, tcsmEarlyAbort = False
, tcsmSkipOverlappable = False
, tcsmFullySolveQCIs = False }
instance Outputable TcSMode where
- ppr (TcSMode { tcs_pm_check = pm, tcsmEarlyAbort = ea
+ ppr (TcSMode { tcsmPmCheck = pm, tcsmEarlyAbort = ea
, tcsmSkipOverlappable = so, tcsmFullySolveQCIs = fs })
= text "TcSMode" <> (braces $
- text "pm=" <> ppr pmc <> comma <>
+ text "pm=" <> ppr pm <> comma <>
text "ea=" <> ppr ea <> comma <>
text "so=" <> ppr so <> comma <>
text "fs=" <> ppr fs)
@@ -1111,9 +1111,9 @@ runTcS tcs
runTcSEarlyAbort :: TcS a -> TcM a
runTcSEarlyAbort tcs
= do { ev_binds_var <- TcM.newTcEvBinds
- ; runTcSWithEvBinds' TcSEarlyAbort ev_binds_var tcs }
+ ; runTcSWithEvBinds' mode ev_binds_var tcs }
where
- mode = vanillaTcSMode { tcsmEarlyAbort = True ]
+ mode = vanillaTcSMode { tcsmEarlyAbort = True }
-- | This can deal only with equality constraints.
runTcSEqualities :: TcS a -> TcM a
@@ -1124,9 +1124,9 @@ runTcSEqualities thing_inside
-- | A variant of 'runTcS' that takes and returns an 'InertSet' for
-- later resumption of the 'TcS' session.
runTcSInerts :: InertSet -> TcS a -> TcM (a, InertSet)
-runTcSInerts inerts tcs = do
+runTcSInerts inerts tcs
= do { ev_binds_var <- TcM.newTcEvBinds
- ; runTcSWithEvBinds' (vanillaTcMode { tcsmPmCheck = True })
+ ; runTcSWithEvBinds' (vanillaTcSMode { tcsmPmCheck = True })
ev_binds_var $
do { setInertSet inerts
; a <- tcs
@@ -1136,7 +1136,7 @@ runTcSInerts inerts tcs = do
runTcSWithEvBinds :: EvBindsVar
-> TcS a
-> TcM a
-runTcSWithEvBinds = runTcSWithEvBinds' TcSVanilla
+runTcSWithEvBinds = runTcSWithEvBinds' vanillaTcSMode
runTcSWithEvBinds' :: TcSMode
-> EvBindsVar
@@ -1917,7 +1917,7 @@ matchGlobalInst :: DynFlags -> Class -> [Type] -> CtLoc -> TcS TcM.ClsInstResult
matchGlobalInst dflags cls tys loc
= do { mode <- getTcSMode
; let skip_overlappable = tcsmSkipOverlappable mode
- ; wrapTcS $ TcM.matchGlobalInst dflags short_cut cls tys (Just loc) }
+ ; wrapTcS $ TcM.matchGlobalInst dflags skip_overlappable cls tys (Just loc) }
tcInstSkolTyVarsX :: SkolemInfo -> Subst -> [TyVar] -> TcS (Subst, [TcTyVar])
tcInstSkolTyVarsX skol_info subst tvs = wrapTcS $ TcM.tcInstSkolTyVarsX skol_info subst tvs
=====================================
compiler/GHC/Tc/Solver/Solve.hs
=====================================
@@ -362,6 +362,12 @@ solveImplication imp@(Implic { ic_tclvl = tclvl
; traceTcS "solveImplication 2"
(ppr given_insols $$ ppr residual_wanted)
+
+ ; evbinds <- TcS.getTcEvBindsMap ev_binds_var
+ ; traceTcS "solveImplication 3" $ vcat
+ [ text "ev_binds_var" <+> ppr ev_binds_var
+ , text "implication evbinds =" <+> ppr (evBindMapBinds evbinds) ]
+
; let final_wanted = residual_wanted `addInsols` given_insols
-- Don't lose track of the insoluble givens,
-- which signal unreachable code; put them in ic_wanted
@@ -1504,7 +1510,7 @@ solveWantedQCI :: TcSMode
-> TcS (Maybe (Either Ct Implication))
-- Try to solve a quantified constraint.
-- In TcSChortCut mode, insist on solving it fully or not at all
--- Returns
+-- Returns
-- No-op on all Cts other than CQuantCan
-- See Note [Solving a Wanted forall-constraint]
solveWantedQCI mode ct@(CQuantCan (QCI { qci_ev = ev, qci_tvs = tvs
@@ -1548,22 +1554,23 @@ solveWantedQCI mode ct@(CQuantCan (QCI { qci_ev = ev, qci_tvs = tvs
; imp' <- solveImplication imp
- ; let do_update_evidence = setWantedEvTerm dest EvCanonical $
- EvFun { et_tvs = skol_tvs, et_given = given_ev_vars
- , et_binds = TcEvBinds ev_binds_var
- , et_body = wantedCtEvEvId wanted_ev }
-
- ; if | isSolvedStatus (ic_status imp')
- -> -- Fully solved, we are all done!
- do { do_update_evidence; return Nothing }
-
- | tcsmFullySolveQCIs mode
- -> -- No-op if we must fully solve quantified constraints
+ ; if | tcsmFullySolveQCIs mode
+ , not (isSolvedStatus (ic_status imp'))
+ -> -- Not fully solved, but mode says that we must fully
+ -- solve quantified constraints; so abandon the attempt
return (Just (Left ct))
| otherwise
- -> -- Otherwise return partly-solved implication
- do { do_update_evidence; return (Just (Right imp')) }
+ -> -- Record evidence and return residual implication
+ -- NB: even if it is fully solved we must return it, because it is
+ -- carrying a record of which evidence variables are used
+ -- See Note [Free vars of EvFun] in GHC.Tc.Types.Evidence
+ do { setWantedEvTerm dest EvCanonical $
+ EvFun { et_tvs = skol_tvs, et_given = given_ev_vars
+ , et_binds = TcEvBinds ev_binds_var
+ , et_body = wantedCtEvEvId wanted_ev }
+
+ ; return (Just (Right imp')) }
}
| otherwise -- A Given QCInst
=====================================
compiler/GHC/Tc/Utils/Monad.hs
=====================================
@@ -1840,10 +1840,14 @@ updTcEvBinds old_var new_var
addTcEvBind :: EvBindsVar -> EvBind -> TcM ()
-- Add a binding to the TcEvBinds by side effect
addTcEvBind (EvBindsVar { ebv_binds = ev_ref, ebv_uniq = u }) ev_bind
- = do { traceTc "addTcEvBind" $ ppr u $$
- ppr ev_bind
- ; bnds <- readTcRef ev_ref
- ; writeTcRef ev_ref (extendEvBinds bnds ev_bind) }
+ = do { bnds <- readTcRef ev_ref
+ ; let bnds' = extendEvBinds bnds ev_bind
+ ; traceTc "addTcEvBind" $
+ vcat [ text "EvBindsVar:" <+> ppr u
+ , text "ev_bind:" <+> ppr ev_bind
+ , text "bnds:" <+> ppr bnds
+ , text "bnds':" <+> ppr bnds' ]
+ ; writeTcRef ev_ref bnds' }
addTcEvBind (CoEvBindsVar { ebv_uniq = u }) ev_bind
= pprPanic "addTcEvBind CoEvBindsVar" (ppr ev_bind $$ ppr u)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/04f3db59ab95729799944157c11da7b…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/04f3db59ab95729799944157c11da7b…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T26315] 44 commits: testsuite: Fix T20006b
by Simon Peyton Jones (@simonpj) 01 Sep '25
by Simon Peyton Jones (@simonpj) 01 Sep '25
01 Sep '25
Simon Peyton Jones pushed to branch wip/T26315 at Glasgow Haskell Compiler / GHC
Commits:
54be78ef by Ben Gamari at 2025-08-19T16:28:05-04:00
testsuite: Fix T20006b
This test is supposed to fail for non-threaded ways yet it
was previously marked as only failing in `normal`.
Fix this.
- - - - -
f4bac607 by Simon Peyton Jones at 2025-08-19T16:28:47-04:00
Take yet more care with reporting redundant constraints
This small patch fixes #25992, which relates to reporting redundant
constraints on default-method declarations.
See (TRC5) in Note [Tracking redundant constraints]
- - - - -
ab130fec by fendor at 2025-08-19T16:29:29-04:00
Bump dependencies of hadrian-bootstrap-gen to use GHC 9.6.7
- - - - -
6d02ac6f by fendor at 2025-08-19T16:29:29-04:00
Bump required GHC version for test-bootstrap jobs to 9.10.1
Include test-bootstrap job for GHC 9.12.2.
Update hadrian bootstrap plans use GHC 9.10 and 9.12
Remove older GHC bootstrap configurations.
We require at least GHC 9.10.1 to build GHC.
Adds plans for:
* 9.10.1
* 9.10.2
* 9.12.1
* 9.12.2
- - - - -
9e857171 by Brandon Chinn at 2025-08-20T11:47:46-04:00
Don't warn unused-imports with used generated imports
Fixes #21730
* The old notion of "implicit" import has been renamed to "generated". See Note [Generated imports] in GHC.Hs.ImpExp.
* ImportMap now keeps track of generated and user-written imports separately. This avoids the fake SrcSpan we used to give the implicit Prelude import, and the hack that went with it.
* -ddump-minimal-imports now considers generated imports (but still only
warns on + prints user-written imports)
* bestImport considers generated imports to take priority over user-written imports.
- - - - -
9fb3bad4 by Ben Gamari at 2025-08-20T11:48:31-04:00
mailmap: Use ben(a)well-typed.com more liberally
Nearly all of this work was done while working for Well-Typed.
- - - - -
774fec37 by Ben Gamari at 2025-08-20T11:49:15-04:00
Add primop to annotate the call stack with arbitrary data
We introduce a new primop `annotateStack#` which allows us to push
arbitrary data onto the call-stack.
This allows us to extract the data later when decoding the stack, for
example when an exception is thrown, showing more information to the
user without having to annotate the full call-stack with `HasCallStack`
constraints.
A new stack frame value is introduced `AnnFrame`, which consists of
nothing but a generic payload.
The primop has a small wrapper API that allows users to annotate their
call-stack in programs.
There is a pure API and an IO-based one. The former is a little bit
dubious, as it affects the evaluation of a program, so use with care.
The latter is "safe", as it doesn't change the evaluation of the
program.
The stack annotation mechanism is similarly implemented to the
`ExceptionAnnotation` and `Exception`, there is a typeclass to indicate
something can be pushed onto the call-stack and all values are wrapped
in the existential `SomeStackAnnotation`, which recover the type of the
annotation payload.
There is currently no builtin way to show the stack annotations when
`Backtraces` are displayed (i.e., when showing stack traces to the user),
which we will address in a follow-up MR.
-------------------------
Metric Increase:
ghc_experimental_so
-------------------------
We increase the size of the package, so this is not unreasonable.
Co-Authored-By: fendor <fendor(a)posteo.de>
Co-Authored-By: Ben Gamari <bgamari.foss(a)gmail.com>
- - - - -
fdfa3892 by Ben Gamari at 2025-08-20T11:49:57-04:00
testsuite: Add regression test for #24606
- - - - -
39b2e382 by Cheng Shao at 2025-08-20T11:50:40-04:00
compiler: only use `Name` instead of `Id` in `SptEntry`
As a part of #26298, this patch refactors `SptEntry` to only carry a
`Name` instead of `Id`: we do not care about extra information like
caffyness or type at all in any static pointer related codegen logic.
This is necessary to make `SptEntry` serializable, as a part of the
grand plan of serializable bytecode.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
276f8ea8 by Vekhir -- at 2025-08-20T11:51:35-04:00
Bump Cabal dependency
- - - - -
0b9c7437 by Zubin Duggal at 2025-08-20T11:52:18-04:00
ci: Teach ci.sh to fetch FreeBSD artifacts from ghcup unofficial bindists and bootstrap compiler on FreeBSD to 9.10.1
Also refactor fetch_ghc logic in ci.sh, renaming the GHC_VERSION enviorment configuration variable to FETCH_GHC_VERSION,
making it clear that it is intended for use on platforms like Windows and FreeBSD where we don't want to use the GHC
excecutable from the platform environment and instead need to download and install GHC-$FETCH_GHC_VERSION from a release
bindist.
Fixes #26296
- - - - -
b2914797 by Cheng Shao at 2025-08-20T11:53:00-04:00
driver: use UniqSet for hiddenModules in DynFlags/FinderOpts
This patch replaces Set ModuleName with UniqSet ModuleName in
DynFlags.hiddenModules and FinderOpts.finder_hiddenModules for
improved efficiency.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
0335d899 by Cheng Shao at 2025-08-20T11:53:00-04:00
driver: use UniqMap ModuleName in the finder
This patch replaces Map ModuleName with UniqMap ModuleName in the
finder for improved efficiency.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
91f4faaa by Cheng Shao at 2025-08-20T11:53:43-04:00
configure: check python3 version and require minimal 3.7
Since !9515, the testsuite driver requires python3 version to be at
least 3.7, though this has never been checked by configure logic. This
patch implements the version check. Fixes #23234.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
df4ee9b4 by Cheng Shao at 2025-08-20T11:54:25-04:00
compiler: use zero cost coerce in GHC.CmmToAsm.CFG.loopInfo
This patch refactors GHC.CmmToAsm.CFG.loopInfo to use zero cost coerce
and thus addresses the TODO. For coerce to work, constructors of
Label/LabelMap/LabelSet from GHC.Cmm.Dataflow.Label are exposed,
though I believe it's a worthy tradeoff to avoid unnecessary runtime
cost without using unsafeCoerce, since the latter could be a landmine
for future refactoring.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
ccda188d by Simon Peyton Jones at 2025-08-20T11:55:07-04:00
Start with empty inerts in shortcut solving
When short-cut solving we were starting with an inert set that had
unsolved Wanteds. This caused an infinite loop (#26314), because a
typechecker plugin kept being given that unsolved Wanted.
It's better just to start with an empty inert set
- - - - -
c8882ed7 by Ben Gamari at 2025-08-20T11:55:49-04:00
configure: Bump minimal bootstrap GHC version to 9.8
- - - - -
f0a19d74 by fendor at 2025-08-20T19:55:00-04:00
Remove deprecated functions from the ghci package
- - - - -
ebeb991b by fendor at 2025-08-20T19:55:00-04:00
base: Remove unstable heap representation details from GHC.Exts
- - - - -
e368e247 by Rodrigo Mesquita at 2025-08-20T19:55:42-04:00
bytecode: Use 32bits for breakpoint index
Fixes #26325
- - - - -
42724462 by Simon Hengel at 2025-08-21T17:52:11-04:00
Serialize wired-in names as external names when creating HIE files
Note that the domain of de-serialized names stays the same.
Specifically, for known-key names, before `lookupKnownKeyName` was used,
while now this is handled by `lookupOrigNameCache` which captures the
same range provided that the OrigNameCache has been initialized with
`knownKeyNames` (which is the case by default).
(fixes #26238)
- - - - -
6a43f8ec by Cheng Shao at 2025-08-21T17:52:52-04:00
compiler: fix closure C type in SPT init code
This patch fixes the closure C type in SPT init code to StgClosure,
instead of the previously incorrect StgPtr. Having an incorrect C type
makes SPT init code not compatible with other foreign stub generation
logic, which may also emit their own extern declarations for the same
closure symbols and thus will clash with the incorrect prototypes in
SPT init code.
- - - - -
5b5d9d47 by Ben Gamari at 2025-08-25T14:29:35-04:00
Revert "STM: don't create a transaction in the rhs of catchRetry# (#26028)"
This reverts commit 0a5836891ca29836a24c306d2a364c2e4b5377fd
- - - - -
10f06163 by Cheng Shao at 2025-08-25T14:30:16-04:00
wasm: ensure setKeepCAFs() is called in ghci
This patch is a critical bugfix for #26106, see comment and linked
issue for details.
- - - - -
bedc1004 by Cheng Shao at 2025-08-26T09:31:18-04:00
compiler: use zero cost coerce in hoopl setElems/mapToList
This patch is a follow-up of !14680 and changes setElems/mapToList in
GHC/Cmm/Dataflow/Label to use coerce instead of mapping mkHooplLabel
over the keys.
- - - - -
13250d97 by Ryan Scott at 2025-08-26T09:31:59-04:00
Reject infix promoted data constructors without DataKinds
In the rename, make sure to apply the same `DataKinds` checks for both
`HsTyVar` (for prefix promoted data constructors) and `HsOpTy` (for infix
promoted data constructors) alike.
Fixes #26318.
- - - - -
37655c46 by Teo Camarasu at 2025-08-26T15:24:51-04:00
tests: disable T22859 under LLVM
This test was failing under the LLVM backend since the allocations
differ from the NCG.
Resolves #26282
- - - - -
2cbba9d6 by Teo Camarasu at 2025-08-26T15:25:33-04:00
base-exports: update version numbers
As the version of the compiler has been bumped, a lot of the embedded
version numbers will need to be updated if we ever run this test with
`--test-accept` so let's just update them now, and keep future diffs
clean.
- - - - -
f9f2ffcf by Alexandre Esteves at 2025-08-27T07:19:14-04:00
Import new name for 'utimbuf' on windows to fix #26337
Fixes an `-Wincompatible-pointer-types` instance that turns into an error on
recent toolchains and surfaced as such on nixpkgs when doing linux->ucrt cross.
This long-standing warning has been present at least since 9.4:
```
C:\GitLabRunner\builds\0\1709189\tmp\ghc16652_0\ghc_4.c:26:115: error:
warning: incompatible pointer types passing 'struct utimbuf *' to parameter of type 'struct _utimbuf *' [-Wincompatible-pointer-types]
|
26 | HsInt32 ghczuwrapperZC9ZCbaseZCSystemziPosixziInternalsZCzuutime(char* a1, struct utimbuf* a2) {return _utime(a1, a2);}
| ^
HsInt32 ghczuwrapperZC9ZCbaseZCSystemziPosixziInternalsZCzuutime(char* a1, struct utimbuf* a2) {return _utime(a1, a2);}
^~
C:\GitLabRunner\builds\0\1709189\_build\stage0\lib\..\..\mingw\x86_64-w64-mingw32\include\sys\utime.h:109:72: error:
note: passing argument to parameter '_Utimbuf' here
|
109 | __CRT_INLINE int __cdecl _utime(const char *_Filename,struct _utimbuf *_Utimbuf) {
| ^
__CRT_INLINE int __cdecl _utime(const char *_Filename,struct _utimbuf *_Utimbuf) {
```
- - - - -
ae89f000 by Hassan Al-Awwadi at 2025-08-27T07:19:56-04:00
Adds the fucnction addDependentDirectory to Q, resolving issue #26148.
This function adds a new directory to the list of things a module depends upon. That means that when the contents of the directory change, the recompilation checker will notice this and the module will be recompiled. Documentation has also been added for addDependentFunction and addDependentDirectory in the user guide.
- - - - -
00478944 by Simon Peyton Jones at 2025-08-27T16:48:30+01:00
Comments only
- - - - -
a7884589 by Simon Peyton Jones at 2025-08-28T11:08:23+01:00
Type-family occurs check in unification
The occurs check in `GHC.Core.Unify.uVarOrFam` was inadequate in dealing
with type families.
Better now. See Note [The occurs check in the Core unifier].
As I did this I realised that the whole apartness thing is trickier than I
thought: see the new Note [Shortcomings of the apartness test]
- - - - -
8adfc222 by sheaf at 2025-08-28T19:47:17-04:00
Fix orientation in HsWrapper composition (<.>)
This commit fixes the order in which WpCast HsWrappers are composed,
fixing a bug introduced in commit 56b32c5a2d5d7cad89a12f4d74dc940e086069d1.
Fixes #26350
- - - - -
eb2ab1e2 by Oleg Grenrus at 2025-08-29T11:00:53-04:00
Generalise thNameToGhcName by adding HasHscEnv
There were multiple single monad-specific `getHscEnv` across codebase.
HasHscEnv is modelled on HasDynFlags.
My first idea was to simply add thNameToGhcNameHsc and
thNameToGhcNameTc, but those would been exactly the same
as thNameToGhcName already.
Also add an usage example to thNameToGhcName and mention that it's
recommended way of looking up names in GHC plugins
- - - - -
2d575a7f by fendor at 2025-08-29T11:01:36-04:00
configure: Bump minimal bootstrap GHC version to 9.10
- - - - -
716274a5 by Simon Peyton Jones at 2025-08-29T17:27:12-04:00
Fix deep subsumption again
This commit fixed #26255:
commit 56b32c5a2d5d7cad89a12f4d74dc940e086069d1
Author: sheaf <sam.derbyshire(a)gmail.com>
Date: Mon Aug 11 15:50:47 2025 +0200
Improve deep subsumption
This commit improves the DeepSubsumption sub-typing implementation
in GHC.Tc.Utils.Unify.tc_sub_type_deep by being less eager to fall back
to unification.
But alas it still wasn't quite right for view patterns: #26331
This MR does a generalisation to fix it. A bit of a sledgehammer to crack
a nut, but nice.
* Add a field `ir_inst :: InferInstFlag` to `InferResult`, where
```
data InferInstFlag = IIF_Sigma | IIF_ShallowRho | IIF_DeepRho
```
* The flag says exactly how much `fillInferResult` should instantiate
before filling the hole.
* We can also use this to replace the previous very ad-hoc `tcInferSigma`
that was used to implement GHCi's `:type` command.
- - - - -
27206c5e by sheaf at 2025-08-29T17:28:14-04:00
Back-compat for TH SpecialiseP data-con of Pragma
This commit improves the backwards-compatibility story for the
SpecialiseP constructor of the Template Haskell 'Pragma' datatype.
Instead of keeping the constructor but deprecating it, this commit makes
it into a bundled pattern synonym of the Pragma datatype. We no longer
deprecate it; it's useful for handling old-form specialise pragmas.
- - - - -
26dbcf61 by fendor at 2025-08-30T05:10:08-04:00
Move stack decoding logic from ghc-heap to ghc-internal
The stack decoding logic in `ghc-heap` is more sophisticated than the one
currently employed in `CloneStack`. We want to use the stack decoding
implementation from `ghc-heap` in `base`.
We cannot simply depend on `ghc-heap` in `base` due do bootstrapping
issues.
Thus, we move the code that is necessary to implement stack decoding to
`ghc-internal`. This is the right location, as we don't want to add a
new API to `base`.
Moving the stack decoding logic and re-exposing it in ghc-heap is
insufficient, though, as we have a dependency cycle between.
* ghc-heap depends on stage1:ghc-internal
* stage0:ghc depends on stage0:ghc-heap
To fix this, we remove ghc-heap from the set of `stage0` dependencies.
This is not entirely straight-forward, as a couple of boot dependencies,
such as `ghci` depend on `ghc-heap`.
Luckily, the boot compiler of GHC is now >=9.10, so we can migrate `ghci`
to use `ghc-internal` instead of `ghc-heap`, which already exports the
relevant modules.
However, we cannot 100% remove ghc's dependency on `ghc-heap`, since
when we compile `stage0:ghc`, `stage1:ghc-internal` is not yet
available.
Thus, when we compile with the boot-compiler, we still depend on an
older version of `ghc-heap`, and only use the modules from `ghc-internal`,
if the `ghc-internal` version is recent enough.
-------------------------
Metric Increase:
T24602_perf_size
T25046_perf_size_gzip
T25046_perf_size_unicode
T25046_perf_size_unicode_gzip
size_hello_artifact
size_hello_artifact_gzip
size_hello_unicode
size_hello_unicode_gzip
-------------------------
These metric increases are unfortunate, they are most likely caused by
the larger (literally in terms of lines of code) stack decoder implementation
that are now linked into hello-word binaries.
On linux, it is almost a 10% increase, which is considerable.
- - - - -
bd80bb70 by fendor at 2025-08-30T05:10:08-04:00
Implement `decode` in terms of `decodeStackWithIpe`
Uses the more efficient stack decoder implementation.
- - - - -
24441165 by fendor at 2025-08-30T05:10:08-04:00
Remove stg_decodeStackzh
- - - - -
fb9cc882 by Simon Peyton Jones at 2025-08-30T05:10:51-04:00
Fix a long standing bug in the coercion optimiser
We were mis-optimising ForAllCo, leading to #26345
Part of the poblem was the tricky tower of abstractions leading to
the dreadful
GHC.Core.TyCo.Subst.substForAllCoTyVarBndrUsing
This function was serving two masters: regular substitution, but also
coercion optimsation. So tricky was it that it did so wrong.
In this MR I locate all the fancy footwork for coercion optimisation
in GHC.Core.Coercion.Opt, where it belongs. That leaves substitution
free to be much simpler.
- - - - -
88997f1b by Simon Peyton Jones at 2025-09-01T10:48:03+01:00
Refactor to solve forall-constraints via an implication again
WIP to fix #26315
- - - - -
3ca95c3f by Simon Peyton Jones at 2025-09-01T10:48:03+01:00
wibble
- - - - -
72d975c5 by Simon Peyton Jones at 2025-09-01T17:46:19+01:00
Improvements
..needs documentation
- - - - -
282 changed files:
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .mailmap
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm/Dataflow/Label.hs
- compiler/GHC/CmmToAsm/CFG.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/Opt/Monad.hs
- compiler/GHC/Core/TyCo/Compare.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Config/Finder.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Env/Types.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Usage.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Ext/Binary.hs
- compiler/GHC/Iface/Ext/Types.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Recomp/Types.hs
- compiler/GHC/Iface/Tidy/StaticPtrTable.hs
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Plugins.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Runtime/Heap/Inspect.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/StgToJS/StaticPtr.hs
- compiler/GHC/Tc/Deriv/Utils.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Expr.hs-boot
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Zonk/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Name/Cache.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/SptEntry.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Deps.hs
- compiler/ghc.cabal.in
- configure.ac
- docs/users_guide/9.16.1-notes.rst
- docs/users_guide/separate_compilation.rst
- ghc/GHCi/UI.hs
- hadrian/bootstrap/generate_bootstrap_plans
- hadrian/bootstrap/hadrian-bootstrap-gen.cabal
- hadrian/bootstrap/plan-9_10_1.json
- hadrian/bootstrap/plan-9_6_5.json → hadrian/bootstrap/plan-9_10_2.json
- hadrian/bootstrap/plan-9_6_6.json → hadrian/bootstrap/plan-9_12_1.json
- hadrian/bootstrap/plan-9_6_4.json → hadrian/bootstrap/plan-9_12_2.json
- − hadrian/bootstrap/plan-9_6_1.json
- − hadrian/bootstrap/plan-9_6_2.json
- − hadrian/bootstrap/plan-9_6_3.json
- − hadrian/bootstrap/plan-9_8_1.json
- − hadrian/bootstrap/plan-9_8_2.json
- hadrian/bootstrap/plan-bootstrap-9_10_1.json
- hadrian/bootstrap/plan-bootstrap-9_6_5.json → hadrian/bootstrap/plan-bootstrap-9_10_2.json
- hadrian/bootstrap/plan-bootstrap-9_6_6.json → hadrian/bootstrap/plan-bootstrap-9_12_1.json
- hadrian/bootstrap/plan-bootstrap-9_8_1.json → hadrian/bootstrap/plan-bootstrap-9_12_2.json
- − hadrian/bootstrap/plan-bootstrap-9_6_1.json
- − hadrian/bootstrap/plan-bootstrap-9_6_2.json
- − hadrian/bootstrap/plan-bootstrap-9_6_3.json
- − hadrian/bootstrap/plan-bootstrap-9_6_4.json
- − hadrian/bootstrap/plan-bootstrap-9_8_2.json
- hadrian/bootstrap/src/Main.hs
- hadrian/hadrian.cabal
- hadrian/src/Rules/ToolArgs.hs
- hadrian/src/Settings/Default.hs
- libraries/base/changelog.md
- libraries/base/src/GHC/Exts.hs
- libraries/base/src/GHC/Stack/CloneStack.hs
- libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
- libraries/ghc-experimental/ghc-experimental.cabal.in
- + libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs
- libraries/ghc-heap/GHC/Exts/Heap/ClosureTypes.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- + libraries/ghc-heap/GHC/Exts/Heap/Constants.hs
- + libraries/ghc-heap/GHC/Exts/Heap/InfoTable.hs
- + libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hs
- + libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hs
- libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs
- libraries/ghc-heap/GHC/Exts/Stack.hs
- + libraries/ghc-heap/GHC/Exts/Stack/Constants.hs
- libraries/ghc-heap/GHC/Exts/Stack/Decode.hs
- libraries/ghc-heap/ghc-heap.cabal.in
- libraries/ghc-heap/cbits/HeapPrim.cmm → libraries/ghc-internal/cbits/HeapPrim.cmm
- libraries/ghc-heap/cbits/Stack.cmm → libraries/ghc-internal/cbits/Stack.cmm
- libraries/ghc-internal/cbits/StackCloningDecoding.cmm
- libraries/ghc-heap/cbits/Stack_c.c → libraries/ghc-internal/cbits/Stack_c.c
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/jsbits/base.js
- libraries/ghc-internal/src/GHC/Internal/ClosureTypes.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- + libraries/ghc-internal/src/GHC/Internal/Heap/Closures.hs
- libraries/ghc-heap/GHC/Exts/Heap/Constants.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/Constants.hsc
- libraries/ghc-heap/GHC/Exts/Heap/InfoTable.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/InfoTable.hsc
- libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/InfoTable/Types.hsc
- libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/InfoTableProf.hsc
- + libraries/ghc-internal/src/GHC/Internal/Heap/ProfInfo/Types.hs
- libraries/ghc-internal/src/GHC/Internal/Stack/CloneStack.hs
- libraries/ghc-heap/GHC/Exts/Stack/Constants.hsc → libraries/ghc-internal/src/GHC/Internal/Stack/Constants.hsc
- + libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
- libraries/ghc-internal/src/GHC/Internal/System/Posix/Internals.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
- + libraries/ghc-internal/tests/stack-annotation/Makefile
- + libraries/ghc-internal/tests/stack-annotation/TestUtils.hs
- + libraries/ghc-internal/tests/stack-annotation/all.T
- + libraries/ghc-internal/tests/stack-annotation/ann_frame001.hs
- + libraries/ghc-internal/tests/stack-annotation/ann_frame001.stdout
- + libraries/ghc-internal/tests/stack-annotation/ann_frame002.hs
- + libraries/ghc-internal/tests/stack-annotation/ann_frame002.stdout
- + libraries/ghc-internal/tests/stack-annotation/ann_frame003.hs
- + libraries/ghc-internal/tests/stack-annotation/ann_frame003.stdout
- + libraries/ghc-internal/tests/stack-annotation/ann_frame004.hs
- + libraries/ghc-internal/tests/stack-annotation/ann_frame004.stdout
- libraries/ghci/GHCi/CreateBCO.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/TH.hs
- libraries/ghci/ghci.cabal.in
- libraries/template-haskell/Language/Haskell/TH/Lib.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- libraries/template-haskell/changelog.md
- m4/find_python.m4
- rts/CloneStack.c
- rts/CloneStack.h
- rts/ClosureFlags.c
- rts/Disassembler.c
- rts/Interpreter.c
- rts/LdvProfile.c
- rts/PrimOps.cmm
- rts/Printer.c
- rts/RaiseAsync.c
- rts/RetainerProfile.c
- rts/RtsSymbols.c
- rts/STM.c
- rts/TraverseHeap.c
- rts/include/rts/storage/ClosureTypes.h
- rts/include/rts/storage/Closures.h
- rts/include/stg/MiscClosures.h
- rts/js/profiling.js
- rts/sm/Compact.c
- rts/sm/Evac.c
- rts/sm/NonMovingMark.c
- rts/sm/Sanity.c
- rts/sm/Scav.c
- testsuite/.gitignore
- testsuite/tests/backpack/should_fail/bkpfail11.stderr
- testsuite/tests/backpack/should_fail/bkpfail43.stderr
- testsuite/tests/gadt/T12468.stderr
- testsuite/tests/ghc-e/should_fail/T24172.stderr
- testsuite/tests/ghci/scripts/T8353.stderr
- testsuite/tests/ghci/scripts/ghci038.stdout
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- testsuite/tests/interface-stability/ghc-prim-exports.stdout
- testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- − testsuite/tests/lib/stm/T26028.hs
- − testsuite/tests/lib/stm/T26028.stdout
- − testsuite/tests/lib/stm/all.T
- − testsuite/tests/module/T21752.stderr
- testsuite/tests/module/mod150.stderr
- testsuite/tests/module/mod151.stderr
- testsuite/tests/module/mod152.stderr
- testsuite/tests/module/mod153.stderr
- testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T19082.stderr
- + testsuite/tests/patsyn/should_compile/T26331.hs
- + testsuite/tests/patsyn/should_compile/T26331a.hs
- testsuite/tests/patsyn/should_compile/all.T
- testsuite/tests/perf/compiler/hard_hole_fits.stderr
- testsuite/tests/plugins/Makefile
- + testsuite/tests/plugins/T21730-plugin/Makefile
- + testsuite/tests/plugins/T21730-plugin/Setup.hs
- + testsuite/tests/plugins/T21730-plugin/T21730-plugin.cabal
- + testsuite/tests/plugins/T21730-plugin/T21730_Plugin.hs
- + testsuite/tests/plugins/T21730.hs
- testsuite/tests/plugins/all.T
- testsuite/tests/quotes/LiftErrMsg.stderr
- testsuite/tests/quotes/LiftErrMsgDefer.stderr
- testsuite/tests/quotes/LiftErrMsgTyped.stderr
- testsuite/tests/rename/should_compile/T22513d.stderr
- testsuite/tests/rename/should_compile/T22513e.stderr
- testsuite/tests/rename/should_compile/T22513f.stderr
- testsuite/tests/rename/should_compile/T22513g.stderr
- testsuite/tests/rename/should_compile/T22513h.stderr
- testsuite/tests/rename/should_compile/T22513i.stderr
- testsuite/tests/rename/should_compile/rn039.ghc.stderr
- testsuite/tests/rename/should_fail/T15487.stderr
- testsuite/tests/rename/should_fail/T18740a.stderr
- testsuite/tests/rename/should_fail/rnfail044.stderr
- testsuite/tests/rts/all.T
- testsuite/tests/rts/flags/all.T
- testsuite/tests/safeHaskell/flags/SafeFlags17.stderr
- testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs
- + testsuite/tests/simplCore/should_compile/T24606.hs
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/th/Makefile
- testsuite/tests/th/T10267.stderr
- testsuite/tests/th/T14627.stderr
- testsuite/tests/th/T15321.stderr
- + testsuite/tests/th/TH_Depends_Dir.hs
- + testsuite/tests/th/TH_Depends_Dir.stdout
- + testsuite/tests/th/TH_Depends_Dir_External.hs
- testsuite/tests/th/all.T
- testsuite/tests/typecheck/should_compile/T13050.stderr
- testsuite/tests/typecheck/should_compile/T14273.stderr
- testsuite/tests/typecheck/should_compile/T14434.hs
- testsuite/tests/typecheck/should_compile/T14590.stderr
- testsuite/tests/typecheck/should_compile/T25180.stderr
- + testsuite/tests/typecheck/should_compile/T25992a.hs
- + testsuite/tests/typecheck/should_compile/T26345.hs
- + testsuite/tests/typecheck/should_compile/T26346.hs
- + testsuite/tests/typecheck/should_compile/T26350.hs
- + testsuite/tests/typecheck/should_compile/T26358.hs
- testsuite/tests/typecheck/should_compile/T9497a.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/subsumption_sort_hole_fits.stderr
- testsuite/tests/typecheck/should_fail/T14884.stderr
- testsuite/tests/typecheck/should_fail/T21130.stderr
- testsuite/tests/typecheck/should_fail/T23739b.stderr
- testsuite/tests/typecheck/should_fail/T23739c.stderr
- + testsuite/tests/typecheck/should_fail/T26318.hs
- + testsuite/tests/typecheck/should_fail/T26318.stderr
- testsuite/tests/typecheck/should_fail/T9497d.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail037.stderr
- testsuite/tests/typecheck/should_run/T9497a-run.stderr
- testsuite/tests/typecheck/should_run/T9497b-run.stderr
- testsuite/tests/typecheck/should_run/T9497c-run.stderr
- testsuite/tests/vdq-rta/should_fail/T23738_fail_pun.stderr
- utils/deriveConstants/Main.hs
- utils/haddock/haddock-api/src/Haddock/InterfaceFile.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/ad2a64fadd99988249df0e20a61cdb…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ad2a64fadd99988249df0e20a61cdb…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Driver: substitute virtual Prim module in --make mode too
by Marge Bot (@marge-bot) 01 Sep '25
by Marge Bot (@marge-bot) 01 Sep '25
01 Sep '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
6c78de2d by Sylvain Henry at 2025-09-01T08:46:19-04:00
Driver: substitute virtual Prim module in --make mode too
When we build ghc-internal with --make (e.g. with cabal-install), we
need to be careful to substitute the virtual interface file for
GHC.Internal.Prim:
- after code generation (we generate code for an empty module, so we get
an empty interface)
- when we try to reload its .hi file
- - - - -
26e0db16 by fendor at 2025-09-01T08:47:01-04:00
Expose Stack Annotation frames in IPE backtraces by default
When decoding the Haskell-native call stack and displaying the IPE information
for the stack frames, we print the `StackAnnotation` of the `AnnFrame` by default.
This means, when an exception is thrown, any intermediate stack annotations will
be displayed in the `IPE Backtrace`.
Example backtrace:
```
Exception: ghc-internal:GHC.Internal.Exception.ErrorCall:
Oh no!
IPE backtrace:
annotateCallStackIO, called at app/Main.hs:48:10 in backtrace-0.1.0.0-inplace-server:Main
annotateCallStackIO, called at app/Main.hs:46:13 in backtrace-0.1.0.0-inplace-server:Main
Main.handler (app/Main.hs:(46,1)-(49,30))
Main.liftIO (src/Servant/Server/Internal/Handler.hs:30:36-42)
Servant.Server.Internal.Delayed.runHandler' (src/Servant/Server/Internal/Handler.hs:27:31-41)
Control.Monad.Trans.Resource.runResourceT (./Control/Monad/Trans/Resource.hs:(192,14)-(197,18))
Network.Wai.Handler.Warp.HTTP1.processRequest (./Network/Wai/Handler/Warp/HTTP1.hs:195:20-22)
Network.Wai.Handler.Warp.HTTP1.processRequest (./Network/Wai/Handler/Warp/HTTP1.hs:(195,5)-(203,31))
Network.Wai.Handler.Warp.HTTP1.http1server.loop (./Network/Wai/Handler/Warp/HTTP1.hs:(141,9)-(157,42))
HasCallStack backtrace:
error, called at app/Main.hs:48:32 in backtrace-0.1.0.0-inplace-server:Main
```
The first two entries have been added by `annotateCallStackIO`, defined in `annotateCallStackIO`.
- - - - -
81eddfb9 by Sylvain Henry at 2025-09-01T09:20:16-04:00
RTS: rely less on Hadrian for flag setting (#25843)
Hadrian used to pass -Dfoo command-line flags directly to build the rts.
We can replace most of these flags with CPP based on cabal flags.
It makes building boot libraries with cabal-install simpler (cf #25843).
- - - - -
eebaa1ee by Sergey Vinokurov at 2025-09-01T09:20:25-04:00
Remove unnecessary irrefutable patterns from Bifunctor instances for tuples
Implementation of https://github.com/haskell/core-libraries-committee/issues/339
Metric Decrease:
mhu-perf
- - - - -
295be6d4 by sheaf at 2025-09-01T09:20:39-04:00
Only use active rules when simplifying rule RHSs
When we are simplifying the RHS of a rule, we make sure to only apply
rewrites from rules that are active throughout the original rule's
range of active phases.
For example, if a rule is always active, we only fire rules that are
themselves always active when simplifying the RHS. Ditto for inline
activations.
This is achieved by setting the simplifier phase to a range of phases,
using the new SimplPhaseRange constructor. Then:
1. When simplifying the RHS of a rule, or of a stable unfolding,
we set the simplifier phase to a range of phases, computed from
the activation of the RULE/unfolding activation, using the
function 'phaseFromActivation'.
The details are explained in Note [What is active in the RHS of a RULE?]
in GHC.Core.Opt.Simplify.Utils.
2. The activation check for other rules and inlinings is then:
does the activation of the other rule/inlining cover the whole
phase range set in sm_phase? This continues to use the 'isActive'
function, which now accounts for phase ranges.
On the way, this commit also moves the exact-print SourceText annotation
from the Activation datatype to the ActivationAnn type. This keeps the
main Activation datatype free of any extra cruft.
Fixes #26323
- - - - -
54 changed files:
- compiler/GHC/Core/Opt/Pipeline/Types.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Inline.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Driver/Config/Core/Lint.hs
- compiler/GHC/Driver/Config/Core/Opt/Simplify.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Parser.y
- compiler/GHC/Tc/Deriv/Generics.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Utils/Binary.hs
- hadrian/src/Settings/Packages.hs
- hie.yaml
- libraries/base/changelog.md
- libraries/base/src/Data/Bifunctor.hs
- libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- + libraries/ghc-internal/src/GHC/Internal/Stack/Annotation.hs
- libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
- libraries/ghc-internal/tests/stack-annotation/ann_frame002.stdout
- libraries/ghc-internal/tests/stack-annotation/ann_frame004.stdout
- rts/RtsMessages.c
- rts/RtsUtils.c
- rts/Trace.c
- + testsuite/tests/driver/make-prim/GHC/Internal/Prim.hs
- + testsuite/tests/driver/make-prim/Makefile
- + testsuite/tests/driver/make-prim/Test.hs
- + testsuite/tests/driver/make-prim/Test2.hs
- + testsuite/tests/driver/make-prim/all.T
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- testsuite/tests/perf/compiler/T4007.stdout
- testsuite/tests/simplCore/should_compile/T15056.stderr
- testsuite/tests/simplCore/should_compile/T15445.stderr
- + testsuite/tests/simplCore/should_compile/T26323b.hs
- testsuite/tests/simplCore/should_compile/all.T
- + testsuite/tests/simplCore/should_run/T26323.hs
- + testsuite/tests/simplCore/should_run/T26323.stdout
- testsuite/tests/simplCore/should_run/all.T
- utils/check-exact/ExactPrint.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4c6c5795ae99b5119426574e7a2afe…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4c6c5795ae99b5119426574e7a2afe…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] Expose Stack Annotation frames in IPE backtraces by default
by Marge Bot (@marge-bot) 01 Sep '25
by Marge Bot (@marge-bot) 01 Sep '25
01 Sep '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
26e0db16 by fendor at 2025-09-01T08:47:01-04:00
Expose Stack Annotation frames in IPE backtraces by default
When decoding the Haskell-native call stack and displaying the IPE information
for the stack frames, we print the `StackAnnotation` of the `AnnFrame` by default.
This means, when an exception is thrown, any intermediate stack annotations will
be displayed in the `IPE Backtrace`.
Example backtrace:
```
Exception: ghc-internal:GHC.Internal.Exception.ErrorCall:
Oh no!
IPE backtrace:
annotateCallStackIO, called at app/Main.hs:48:10 in backtrace-0.1.0.0-inplace-server:Main
annotateCallStackIO, called at app/Main.hs:46:13 in backtrace-0.1.0.0-inplace-server:Main
Main.handler (app/Main.hs:(46,1)-(49,30))
Main.liftIO (src/Servant/Server/Internal/Handler.hs:30:36-42)
Servant.Server.Internal.Delayed.runHandler' (src/Servant/Server/Internal/Handler.hs:27:31-41)
Control.Monad.Trans.Resource.runResourceT (./Control/Monad/Trans/Resource.hs:(192,14)-(197,18))
Network.Wai.Handler.Warp.HTTP1.processRequest (./Network/Wai/Handler/Warp/HTTP1.hs:195:20-22)
Network.Wai.Handler.Warp.HTTP1.processRequest (./Network/Wai/Handler/Warp/HTTP1.hs:(195,5)-(203,31))
Network.Wai.Handler.Warp.HTTP1.http1server.loop (./Network/Wai/Handler/Warp/HTTP1.hs:(141,9)-(157,42))
HasCallStack backtrace:
error, called at app/Main.hs:48:32 in backtrace-0.1.0.0-inplace-server:Main
```
The first two entries have been added by `annotateCallStackIO`, defined in `annotateCallStackIO`.
- - - - -
9 changed files:
- libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- + libraries/ghc-internal/src/GHC/Internal/Stack/Annotation.hs
- libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
- libraries/ghc-internal/tests/stack-annotation/ann_frame002.stdout
- libraries/ghc-internal/tests/stack-annotation/ann_frame004.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
Changes:
=====================================
libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs
=====================================
@@ -58,6 +58,7 @@ import Data.Typeable
import GHC.Exts
import GHC.IO
import GHC.Internal.Stack
+import GHC.Internal.Stack.Annotation
-- Note [User-defined stack annotations for better stack traces]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -127,31 +128,10 @@ import GHC.Internal.Stack
-- This means, right now, if you want to reliably capture stack frame annotations,
-- in both pure and impure code, prefer 'throw' and 'throwIO' variants over 'error'.
--- ----------------------------------------------------------------------------
--- StackAnnotation
--- ----------------------------------------------------------------------------
-
--- | 'StackAnnotation's are types which can be pushed onto the call stack
--- as the payload of 'AnnFrame' stack frames.
---
-class StackAnnotation a where
- displayStackAnnotation :: a -> String
-
-- ----------------------------------------------------------------------------
-- Annotations
-- ----------------------------------------------------------------------------
--- |
--- The @SomeStackAnnotation@ type is the root of the stack annotation type hierarchy.
--- When the call stack is annotated with a value of type @a@, behind the scenes it is
--- encapsulated in a @SomeStackAnnotation@.
---
-data SomeStackAnnotation where
- SomeStackAnnotation :: forall a. (Typeable a, StackAnnotation a) => a -> SomeStackAnnotation
-
-instance StackAnnotation SomeStackAnnotation where
- displayStackAnnotation (SomeStackAnnotation a) = displayStackAnnotation a
-
data StringAnnotation where
StringAnnotation :: String -> StringAnnotation
@@ -175,7 +155,7 @@ instance Show CallStackAnnotation where
instance StackAnnotation CallStackAnnotation where
displayStackAnnotation (CallStackAnnotation cs) = case getCallStack cs of
[] -> "<unknown source location>"
- ((_,srcLoc):_) -> prettySrcLoc srcLoc
+ ((fnName,srcLoc):_) -> fnName ++ ", called at " ++ prettySrcLoc srcLoc
-- ----------------------------------------------------------------------------
-- Annotate the CallStack with custom data
=====================================
libraries/ghc-internal/ghc-internal.cabal.in
=====================================
@@ -295,6 +295,7 @@ Library
GHC.Internal.Stable
GHC.Internal.StableName
GHC.Internal.Stack
+ GHC.Internal.Stack.Annotation
GHC.Internal.Stack.CCS
GHC.Internal.Stack.CloneStack
GHC.Internal.Stack.Constants
=====================================
libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
=====================================
@@ -11,7 +11,7 @@ import GHC.Internal.IORef
import GHC.Internal.IO.Unsafe (unsafePerformIO)
import GHC.Internal.Exception.Context
import GHC.Internal.Ptr
-import GHC.Internal.Data.Maybe (fromMaybe)
+import GHC.Internal.Data.Maybe (fromMaybe, mapMaybe)
import GHC.Internal.Stack.Types as GHC.Stack (CallStack, HasCallStack)
import qualified GHC.Internal.Stack as HCS
import qualified GHC.Internal.ExecutionStack.Internal as ExecStack
@@ -144,7 +144,7 @@ displayBacktraces bts = concat
displayExec = unlines . map (indent 2 . flip ExecStack.showLocation "") . fromMaybe [] . ExecStack.stackFrames
-- The unsafePerformIO here is safe as 'StackSnapshot' makes sure neither the stack frames nor
-- references closures can be garbage collected.
- displayIpe = unlines . map (indent 2 . CloneStack.prettyStackEntry) . unsafePerformIO . CloneStack.decode
+ displayIpe = unlines . mapMaybe (fmap (indent 2) . CloneStack.prettyStackFrameWithIpe) . unsafePerformIO . CloneStack.decodeStackWithIpe
displayHsc = unlines . map (indent 2 . prettyCallSite) . HCS.getCallStack
where prettyCallSite (f, loc) = f ++ ", called at " ++ HCS.prettySrcLoc loc
=====================================
libraries/ghc-internal/src/GHC/Internal/Stack/Annotation.hs
=====================================
@@ -0,0 +1,31 @@
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+module GHC.Internal.Stack.Annotation where
+
+import GHC.Internal.Base
+import GHC.Internal.Data.Typeable
+
+-- ----------------------------------------------------------------------------
+-- StackAnnotation
+-- ----------------------------------------------------------------------------
+
+-- | 'StackAnnotation's are types which can be pushed onto the call stack
+-- as the payload of 'AnnFrame' stack frames.
+--
+class StackAnnotation a where
+ displayStackAnnotation :: a -> String
+
+-- ----------------------------------------------------------------------------
+-- Annotations
+-- ----------------------------------------------------------------------------
+
+-- |
+-- The @SomeStackAnnotation@ type is the root of the stack annotation type hierarchy.
+-- When the call stack is annotated with a value of type @a@, behind the scenes it is
+-- encapsulated in a @SomeStackAnnotation@.
+--
+data SomeStackAnnotation where
+ SomeStackAnnotation :: forall a. (Typeable a, StackAnnotation a) => a -> SomeStackAnnotation
+
+instance StackAnnotation SomeStackAnnotation where
+ displayStackAnnotation (SomeStackAnnotation a) = displayStackAnnotation a
=====================================
libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
=====================================
@@ -4,6 +4,7 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GHCForeignImportPrim #-}
{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
@@ -23,6 +24,7 @@ module GHC.Internal.Stack.Decode (
StackEntry(..),
-- * Pretty printing
prettyStackEntry,
+ prettyStackFrameWithIpe,
)
where
@@ -39,6 +41,7 @@ import GHC.Internal.Data.Tuple
import GHC.Internal.Foreign.Ptr
import GHC.Internal.Foreign.Storable
import GHC.Internal.Exts
+import GHC.Internal.Unsafe.Coerce
import GHC.Internal.ClosureTypes
import GHC.Internal.Heap.Closures
@@ -52,6 +55,7 @@ import GHC.Internal.Heap.Closures
)
import GHC.Internal.Heap.Constants (wORD_SIZE_IN_BITS)
import GHC.Internal.Heap.InfoTable
+import GHC.Internal.Stack.Annotation
import GHC.Internal.Stack.Constants
import GHC.Internal.Stack.CloneStack
import GHC.Internal.InfoProv.Types (InfoProv (..), ipLoc, lookupIPE)
@@ -560,6 +564,16 @@ decodeStackWithFrameUnpack unpackFrame (StackSnapshot stack#) = do
-- Pretty printing functions for stack entries, stack frames and provenance info
-- ----------------------------------------------------------------------------
+prettyStackFrameWithIpe :: (StackFrame, Maybe InfoProv) -> Maybe String
+prettyStackFrameWithIpe (frame, mipe) =
+ case frame of
+ AnnFrame {annotation = Box someStackAnno } ->
+ case unsafeCoerce someStackAnno of
+ SomeStackAnnotation ann ->
+ Just $ displayStackAnnotation ann
+ _ ->
+ (prettyStackEntry . toStackEntry) <$> mipe
+
prettyStackEntry :: StackEntry -> String
prettyStackEntry (StackEntry {moduleName=mod_nm, functionName=fun_nm, srcLoc=loc}) =
mod_nm ++ "." ++ fun_nm ++ " (" ++ loc ++ ")"
=====================================
libraries/ghc-internal/tests/stack-annotation/ann_frame002.stdout
=====================================
@@ -1,11 +1,11 @@
Start some work
10946
Stack annotations:
-- ann_frame002.hs:18:7 in main:Main
-- ann_frame002.hs:12:11 in main:Main
+- annotateCallStackIO, called at ann_frame002.hs:18:7 in main:Main
+- annotateCallStackIO, called at ann_frame002.hs:12:11 in main:Main
Finish some work
Some more work in bar
17711
Stack annotations:
- bar
-- ann_frame002.hs:23:7 in main:Main
+- annotateCallStackIO, called at ann_frame002.hs:23:7 in main:Main
=====================================
libraries/ghc-internal/tests/stack-annotation/ann_frame004.stdout
=====================================
@@ -1,17 +1,17 @@
Stack annotations:
-- ann_frame004.hs:21:17 in main:Main
-- ann_frame004.hs:21:17 in main:Main
-- ann_frame004.hs:21:17 in main:Main
-- ann_frame004.hs:21:17 in main:Main
-- ann_frame004.hs:21:17 in main:Main
-- ann_frame004.hs:21:17 in main:Main
-- ann_frame004.hs:21:17 in main:Main
-- ann_frame004.hs:21:17 in main:Main
-- ann_frame004.hs:21:17 in main:Main
-- ann_frame004.hs:21:17 in main:Main
-- ann_frame004.hs:21:17 in main:Main
-- ann_frame004.hs:21:17 in main:Main
-- ann_frame004.hs:21:17 in main:Main
-- ann_frame004.hs:13:10 in main:Main
+- annotateCallStack, called at ann_frame004.hs:21:17 in main:Main
+- annotateCallStack, called at ann_frame004.hs:21:17 in main:Main
+- annotateCallStack, called at ann_frame004.hs:21:17 in main:Main
+- annotateCallStack, called at ann_frame004.hs:21:17 in main:Main
+- annotateCallStack, called at ann_frame004.hs:21:17 in main:Main
+- annotateCallStack, called at ann_frame004.hs:21:17 in main:Main
+- annotateCallStack, called at ann_frame004.hs:21:17 in main:Main
+- annotateCallStack, called at ann_frame004.hs:21:17 in main:Main
+- annotateCallStack, called at ann_frame004.hs:21:17 in main:Main
+- annotateCallStack, called at ann_frame004.hs:21:17 in main:Main
+- annotateCallStack, called at ann_frame004.hs:21:17 in main:Main
+- annotateCallStack, called at ann_frame004.hs:21:17 in main:Main
+- annotateCallStack, called at ann_frame004.hs:21:17 in main:Main
+- annotateCallStack, called at ann_frame004.hs:13:10 in main:Main
- bar
-- ann_frame004.hs:12:7 in main:Main
+- annotateCallStackIO, called at ann_frame004.hs:12:7 in main:Main
=====================================
testsuite/tests/interface-stability/ghc-experimental-exports.stdout
=====================================
@@ -10949,10 +10949,6 @@ module System.Mem.Experimental where
-- Instances:
-instance GHC.Stack.Annotation.Experimental.StackAnnotation GHC.Stack.Annotation.Experimental.CallStackAnnotation -- Defined in ‘GHC.Stack.Annotation.Experimental’
-instance GHC.Stack.Annotation.Experimental.StackAnnotation GHC.Stack.Annotation.Experimental.ShowAnnotation -- Defined in ‘GHC.Stack.Annotation.Experimental’
-instance GHC.Stack.Annotation.Experimental.StackAnnotation GHC.Stack.Annotation.Experimental.SomeStackAnnotation -- Defined in ‘GHC.Stack.Annotation.Experimental’
-instance GHC.Stack.Annotation.Experimental.StackAnnotation GHC.Stack.Annotation.Experimental.StringAnnotation -- Defined in ‘GHC.Stack.Annotation.Experimental’
instance GHC.Internal.Base.Alternative GHC.Internal.Types.IO -- Defined in ‘GHC.Internal.Base’
instance GHC.Internal.Base.Alternative [] -- Defined in ‘GHC.Internal.Base’
instance GHC.Internal.Base.Alternative GHC.Internal.Maybe.Maybe -- Defined in ‘GHC.Internal.Base’
@@ -11151,3 +11147,7 @@ instance GHC.Internal.Show.Show GHC.Internal.IO.SubSystem.IoSubSystem -- Defined
instance GHC.Internal.Show.Show GHC.Stack.Annotation.Experimental.CallStackAnnotation -- Defined in ‘GHC.Stack.Annotation.Experimental’
instance GHC.Internal.Show.Show GHC.Internal.Stats.GCDetails -- Defined in ‘GHC.Internal.Stats’
instance GHC.Internal.Show.Show GHC.Internal.Stats.RTSStats -- Defined in ‘GHC.Internal.Stats’
+instance GHC.Internal.Stack.Annotation.StackAnnotation GHC.Stack.Annotation.Experimental.CallStackAnnotation -- Defined in ‘GHC.Stack.Annotation.Experimental’
+instance GHC.Internal.Stack.Annotation.StackAnnotation GHC.Stack.Annotation.Experimental.ShowAnnotation -- Defined in ‘GHC.Stack.Annotation.Experimental’
+instance GHC.Internal.Stack.Annotation.StackAnnotation GHC.Stack.Annotation.Experimental.StringAnnotation -- Defined in ‘GHC.Stack.Annotation.Experimental’
+instance GHC.Internal.Stack.Annotation.StackAnnotation GHC.Internal.Stack.Annotation.SomeStackAnnotation -- Defined in ‘GHC.Internal.Stack.Annotation’
=====================================
testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
=====================================
@@ -10952,10 +10952,6 @@ module System.Mem.Experimental where
-- Instances:
-instance GHC.Stack.Annotation.Experimental.StackAnnotation GHC.Stack.Annotation.Experimental.CallStackAnnotation -- Defined in ‘GHC.Stack.Annotation.Experimental’
-instance GHC.Stack.Annotation.Experimental.StackAnnotation GHC.Stack.Annotation.Experimental.ShowAnnotation -- Defined in ‘GHC.Stack.Annotation.Experimental’
-instance GHC.Stack.Annotation.Experimental.StackAnnotation GHC.Stack.Annotation.Experimental.SomeStackAnnotation -- Defined in ‘GHC.Stack.Annotation.Experimental’
-instance GHC.Stack.Annotation.Experimental.StackAnnotation GHC.Stack.Annotation.Experimental.StringAnnotation -- Defined in ‘GHC.Stack.Annotation.Experimental’
instance GHC.Internal.Base.Alternative GHC.Internal.Types.IO -- Defined in ‘GHC.Internal.Base’
instance GHC.Internal.Base.Alternative [] -- Defined in ‘GHC.Internal.Base’
instance GHC.Internal.Base.Alternative GHC.Internal.Maybe.Maybe -- Defined in ‘GHC.Internal.Base’
@@ -11154,3 +11150,7 @@ instance GHC.Internal.Show.Show GHC.Internal.IO.SubSystem.IoSubSystem -- Defined
instance GHC.Internal.Show.Show GHC.Stack.Annotation.Experimental.CallStackAnnotation -- Defined in ‘GHC.Stack.Annotation.Experimental’
instance GHC.Internal.Show.Show GHC.Internal.Stats.GCDetails -- Defined in ‘GHC.Internal.Stats’
instance GHC.Internal.Show.Show GHC.Internal.Stats.RTSStats -- Defined in ‘GHC.Internal.Stats’
+instance GHC.Internal.Stack.Annotation.StackAnnotation GHC.Stack.Annotation.Experimental.CallStackAnnotation -- Defined in ‘GHC.Stack.Annotation.Experimental’
+instance GHC.Internal.Stack.Annotation.StackAnnotation GHC.Stack.Annotation.Experimental.ShowAnnotation -- Defined in ‘GHC.Stack.Annotation.Experimental’
+instance GHC.Internal.Stack.Annotation.StackAnnotation GHC.Stack.Annotation.Experimental.StringAnnotation -- Defined in ‘GHC.Stack.Annotation.Experimental’
+instance GHC.Internal.Stack.Annotation.StackAnnotation GHC.Internal.Stack.Annotation.SomeStackAnnotation -- Defined in ‘GHC.Internal.Stack.Annotation’
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/26e0db16365059f0fdfe63b773852df…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/26e0db16365059f0fdfe63b773852df…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] Driver: substitute virtual Prim module in --make mode too
by Marge Bot (@marge-bot) 01 Sep '25
by Marge Bot (@marge-bot) 01 Sep '25
01 Sep '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
6c78de2d by Sylvain Henry at 2025-09-01T08:46:19-04:00
Driver: substitute virtual Prim module in --make mode too
When we build ghc-internal with --make (e.g. with cabal-install), we
need to be careful to substitute the virtual interface file for
GHC.Internal.Prim:
- after code generation (we generate code for an empty module, so we get
an empty interface)
- when we try to reload its .hi file
- - - - -
11 changed files:
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Recomp.hs
- + testsuite/tests/driver/make-prim/GHC/Internal/Prim.hs
- + testsuite/tests/driver/make-prim/Makefile
- + testsuite/tests/driver/make-prim/Test.hs
- + testsuite/tests/driver/make-prim/Test2.hs
- + testsuite/tests/driver/make-prim/all.T
Changes:
=====================================
compiler/GHC/Driver/Downsweep.hs
=====================================
@@ -519,7 +519,7 @@ loopFixedModule key loc done = do
-- part of the compiler.
lookupIfaceByModuleHsc hsc_env (mnkToModule key) >>= \case
Just iface -> return (M.Succeeded iface)
- Nothing -> readIface (hsc_logger hsc_env) (hsc_dflags hsc_env) (hsc_NC hsc_env) (mnkToModule key) (ml_hi_file loc)
+ Nothing -> readIface (hsc_hooks hsc_env) (hsc_logger hsc_env) (hsc_dflags hsc_env) (hsc_NC hsc_env) (mnkToModule key) (ml_hi_file loc)
case read_result of
M.Succeeded iface -> do
-- Computer information about this node
=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -1296,7 +1296,7 @@ hscDesugarAndSimplify summary (FrontendTypecheck tc_result) tc_warnings mb_old_h
-- when compiling gHC_PRIM without generating code (e.g. with
-- Haddock), we still want the virtual interface in the cache
if ms_mod summary == gHC_PRIM
- then return $ HscUpdate (getGhcPrimIface hsc_env)
+ then return $ HscUpdate (getGhcPrimIface (hsc_hooks hsc_env))
else return $ HscUpdate iface
@@ -1311,7 +1311,7 @@ hscDesugarAndSimplify summary (FrontendTypecheck tc_result) tc_warnings mb_old_h
-- when compiling gHC_PRIM without generating code (e.g. with
-- Haddock), we still want the virtual interface in the cache
if ms_mod summary == gHC_PRIM
- then return $ HscUpdate (getGhcPrimIface hsc_env)
+ then return $ HscUpdate (getGhcPrimIface (hsc_hooks hsc_env))
else return $ HscUpdate iface
{-
=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -1618,7 +1618,7 @@ executeCompileNode k n !old_hmi hug mrehydrate_mods mni = do
executeCompileNodeFixed hsc_env MakeEnv{diag_wrapper, env_messager} mod loc =
wrapAction diag_wrapper hsc_env $ do
forM_ env_messager $ \hscMessage -> hscMessage hsc_env (k, n) UpToDate (ModuleNode [] (ModuleNodeFixed mod loc))
- read_result <- readIface (hsc_logger hsc_env) (hsc_dflags hsc_env) (hsc_NC hsc_env) (mnkToModule mod) (ml_hi_file loc)
+ read_result <- readIface (hsc_hooks hsc_env) (hsc_logger hsc_env) (hsc_dflags hsc_env) (hsc_NC hsc_env) (mnkToModule mod) (ml_hi_file loc)
case read_result of
M.Failed interface_err ->
let mn = mnkModuleName mod
=====================================
compiler/GHC/Driver/Pipeline.hs
=====================================
@@ -44,6 +44,7 @@ module GHC.Driver.Pipeline (
import GHC.Prelude
+import GHC.Builtin.Names
import GHC.Platform
@@ -91,6 +92,7 @@ import GHC.Data.StringBuffer ( hPutStringBuffer )
import GHC.Data.Maybe ( expectJust )
import GHC.Iface.Make ( mkFullIface )
+import GHC.Iface.Load ( getGhcPrimIface )
import GHC.Runtime.Loader ( initializePlugins )
@@ -819,7 +821,13 @@ hscGenBackendPipeline pipe_env hsc_env mod_sum result = do
let !linkable = Linkable part_time (ms_mod mod_sum) (NE.singleton (DotO final_object ModuleObject))
-- Add the object linkable to the potential bytecode linkable which was generated in HscBackend.
return (mlinkable { homeMod_object = Just linkable })
- return (miface, final_linkable)
+
+ -- when building ghc-internal with --make (e.g. with cabal-install), we want
+ -- the virtual interface for gHC_PRIM in the cache, not the empty one.
+ let miface_final
+ | ms_mod mod_sum == gHC_PRIM = getGhcPrimIface (hsc_hooks hsc_env)
+ | otherwise = miface
+ return (miface_final, final_linkable)
asPipeline :: P m => Bool -> PipeEnv -> HscEnv -> Maybe ModLocation -> FilePath -> m (Maybe ObjFile)
asPipeline use_cpp pipe_env hsc_env location input_fn =
=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -895,6 +895,7 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do
mhome_unit = hsc_home_unit_maybe hsc_env
dflags = hsc_dflags hsc_env
logger = hsc_logger hsc_env
+ hooks = hsc_hooks hsc_env
trace_if logger (sep [hsep [text "Reading",
@@ -905,59 +906,51 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do
ppr mod <> semi],
nest 4 (text "reason:" <+> doc_str)])
- -- Check for GHC.Prim, and return its static interface
- -- See Note [GHC.Prim] in primops.txt.pp.
- -- TODO: make this check a function
- if mod `installedModuleEq` gHC_PRIM
- then do
- let iface = getGhcPrimIface hsc_env
- return (Succeeded (iface, panic "GHC.Prim ModLocation (findAndReadIface)"))
- else do
- -- Look for the file
- mb_found <- liftIO (findExactModule hsc_env mod hi_boot_file)
- case mb_found of
- InstalledFound loc -> do
- -- See Note [Home module load error]
- if HUG.memberHugUnitId (moduleUnit mod) (hsc_HUG hsc_env)
- && not (isOneShot (ghcMode dflags))
- then return (Failed (HomeModError mod loc))
- else do
- r <- read_file logger name_cache unit_state dflags wanted_mod (ml_hi_file loc)
- case r of
- Failed err
- -> return (Failed $ BadIfaceFile err)
- Succeeded (iface,_fp)
- -> do
- r2 <- load_dynamic_too_maybe logger name_cache unit_state
- (setDynamicNow dflags) wanted_mod
- iface loc
- case r2 of
- Failed sdoc -> return (Failed sdoc)
- Succeeded {} -> return $ Succeeded (iface, loc)
- err -> do
- trace_if logger (text "...not found")
- return $ Failed $ cannotFindInterface
- unit_state
- mhome_unit
- profile
- (moduleName mod)
- err
+ -- Look for the file
+ mb_found <- liftIO (findExactModule hsc_env mod hi_boot_file)
+ case mb_found of
+ InstalledFound loc -> do
+ -- See Note [Home module load error]
+ if HUG.memberHugUnitId (moduleUnit mod) (hsc_HUG hsc_env)
+ && not (isOneShot (ghcMode dflags))
+ then return (Failed (HomeModError mod loc))
+ else do
+ r <- read_file hooks logger name_cache unit_state dflags wanted_mod (ml_hi_file loc)
+ case r of
+ Failed err
+ -> return (Failed $ BadIfaceFile err)
+ Succeeded (iface,_fp)
+ -> do
+ r2 <- load_dynamic_too_maybe hooks logger name_cache unit_state
+ (setDynamicNow dflags) wanted_mod
+ iface loc
+ case r2 of
+ Failed sdoc -> return (Failed sdoc)
+ Succeeded {} -> return $ Succeeded (iface, loc)
+ err -> do
+ trace_if logger (text "...not found")
+ return $ Failed $ cannotFindInterface
+ unit_state
+ mhome_unit
+ profile
+ (moduleName mod)
+ err
-- | Check if we need to try the dynamic interface for -dynamic-too
-load_dynamic_too_maybe :: Logger -> NameCache -> UnitState -> DynFlags
+load_dynamic_too_maybe :: Hooks -> Logger -> NameCache -> UnitState -> DynFlags
-> Module -> ModIface -> ModLocation
-> IO (MaybeErr MissingInterfaceError ())
-load_dynamic_too_maybe logger name_cache unit_state dflags wanted_mod iface loc
+load_dynamic_too_maybe hooks logger name_cache unit_state dflags wanted_mod iface loc
-- Indefinite interfaces are ALWAYS non-dynamic.
| not (moduleIsDefinite (mi_module iface)) = return (Succeeded ())
- | gopt Opt_BuildDynamicToo dflags = load_dynamic_too logger name_cache unit_state dflags wanted_mod iface loc
+ | gopt Opt_BuildDynamicToo dflags = load_dynamic_too hooks logger name_cache unit_state dflags wanted_mod iface loc
| otherwise = return (Succeeded ())
-load_dynamic_too :: Logger -> NameCache -> UnitState -> DynFlags
+load_dynamic_too :: Hooks -> Logger -> NameCache -> UnitState -> DynFlags
-> Module -> ModIface -> ModLocation
-> IO (MaybeErr MissingInterfaceError ())
-load_dynamic_too logger name_cache unit_state dflags wanted_mod iface loc = do
- read_file logger name_cache unit_state dflags wanted_mod (ml_dyn_hi_file loc) >>= \case
+load_dynamic_too hooks logger name_cache unit_state dflags wanted_mod iface loc = do
+ read_file hooks logger name_cache unit_state dflags wanted_mod (ml_dyn_hi_file loc) >>= \case
Succeeded (dynIface, _)
| mi_mod_hash iface == mi_mod_hash dynIface
-> return (Succeeded ())
@@ -971,10 +964,10 @@ load_dynamic_too logger name_cache unit_state dflags wanted_mod iface loc = do
-read_file :: Logger -> NameCache -> UnitState -> DynFlags
+read_file :: Hooks -> Logger -> NameCache -> UnitState -> DynFlags
-> Module -> FilePath
-> IO (MaybeErr ReadInterfaceError (ModIface, FilePath))
-read_file logger name_cache unit_state dflags wanted_mod file_path = do
+read_file hooks logger name_cache unit_state dflags wanted_mod file_path = do
-- Figure out what is recorded in mi_module. If this is
-- a fully definite interface, it'll match exactly, but
@@ -985,7 +978,7 @@ read_file logger name_cache unit_state dflags wanted_mod file_path = do
(_, Just indef_mod) ->
instModuleToModule unit_state
(uninstantiateInstantiatedModule indef_mod)
- read_result <- readIface logger dflags name_cache wanted_mod' file_path
+ read_result <- readIface hooks logger dflags name_cache wanted_mod' file_path
case read_result of
Failed err -> return (Failed err)
Succeeded iface -> return (Succeeded (iface, file_path))
@@ -1012,13 +1005,14 @@ flagsToIfCompression dflags
-- Failed err <=> file not found, or unreadable, or illegible
-- Succeeded iface <=> successfully found and parsed
readIface
- :: Logger
+ :: Hooks
+ -> Logger
-> DynFlags
-> NameCache
-> Module
-> FilePath
-> IO (MaybeErr ReadInterfaceError ModIface)
-readIface logger dflags name_cache wanted_mod file_path = do
+readIface hooks logger dflags name_cache wanted_mod file_path = do
trace_if logger (text "readIFace" <+> text file_path)
let profile = targetProfile dflags
res <- tryMost $ readBinIface profile name_cache CheckHiWay QuietBinIFace file_path
@@ -1028,9 +1022,14 @@ readIface logger dflags name_cache wanted_mod file_path = do
-- critical for correctness of recompilation checking
-- (it lets us tell when -this-unit-id has changed.)
| wanted_mod == actual_mod
- -> return (Succeeded iface)
+ -> return (Succeeded final_iface)
| otherwise -> return (Failed err)
where
+ final_iface
+ -- Check for GHC.Prim, and return its static interface
+ -- See Note [GHC.Prim] in primops.txt.pp.
+ | wanted_mod == gHC_PRIM = getGhcPrimIface hooks
+ | otherwise = iface
actual_mod = mi_module iface
err = HiModuleNameMismatchWarn file_path wanted_mod actual_mod
@@ -1245,8 +1244,8 @@ instance Outputable WhereFrom where
-- This is a helper function that takes into account the hook allowing ghc-prim
-- interface to be extended via the ghc-api. Afaik it was introduced for GHCJS
-- so that it can add its own primitive types.
-getGhcPrimIface :: HscEnv -> ModIface
-getGhcPrimIface hsc_env =
- case ghcPrimIfaceHook (hsc_hooks hsc_env) of
+getGhcPrimIface :: Hooks -> ModIface
+getGhcPrimIface hooks =
+ case ghcPrimIfaceHook hooks of
Nothing -> ghcPrimIface
Just h -> h
=====================================
compiler/GHC/Iface/Recomp.hs
=====================================
@@ -306,7 +306,7 @@ check_old_iface hsc_env mod_summary maybe_iface
loadIface read_dflags iface_path = do
let ncu = hsc_NC hsc_env
- read_result <- readIface logger read_dflags ncu (ms_mod mod_summary) iface_path
+ read_result <- readIface (hsc_hooks hsc_env) logger read_dflags ncu (ms_mod mod_summary) iface_path
case read_result of
Failed err -> do
let msg = readInterfaceErrorDiagnostic err
=====================================
testsuite/tests/driver/make-prim/GHC/Internal/Prim.hs
=====================================
@@ -0,0 +1,5 @@
+{-# LANGUAGE NoImplicitPrelude #-}
+
+module GHC.Internal.Prim where
+
+
=====================================
testsuite/tests/driver/make-prim/Makefile
=====================================
@@ -0,0 +1,11 @@
+TOP=../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+make-prim:
+ # build once to test the substitution of the virtual interface in --make
+ # mode with codegen
+ "$(TEST_HC)" $(TEST_HC_OPTS) --make Test.hs -this-unit-id ghc-internal -hide-all-packages -dno-typeable-binds -v0
+ # build a different module (Test2) in --make mode to test the reloading
+ # of the GHC.Internal.Prim interface
+ "$(TEST_HC)" $(TEST_HC_OPTS) --make Test2.hs -this-unit-id ghc-internal -hide-all-packages -dno-typeable-binds -v0
=====================================
testsuite/tests/driver/make-prim/Test.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+
+module Test where
+
+import GHC.Internal.Prim
+
+foo :: Int# -> Int#
+foo = notI#
=====================================
testsuite/tests/driver/make-prim/Test2.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+
+module Test2 where
+
+import GHC.Internal.Prim
+
+foo :: Int# -> Int#
+foo = notI#
=====================================
testsuite/tests/driver/make-prim/all.T
=====================================
@@ -0,0 +1 @@
+test('make-prim', [extra_files(['Test.hs','Test2.hs', 'GHC', 'GHC/Internal', 'GHC/Internal/Prim.hs'])], makefile_test, ['make-prim'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6c78de2d6506bbbd9952ef884bdb60d…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6c78de2d6506bbbd9952ef884bdb60d…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T26217] 47 commits: configure: Allow use of LLVM 20
by Teo Camarasu (@teo) 01 Sep '25
by Teo Camarasu (@teo) 01 Sep '25
01 Sep '25
Teo Camarasu pushed to branch wip/T26217 at Glasgow Haskell Compiler / GHC
Commits:
ca03226d by Ben Gamari at 2025-08-18T13:43:20+00:00
configure: Allow use of LLVM 20
- - - - -
783cd7d6 by Cheng Shao at 2025-08-18T20:13:14-04:00
compiler: use `UniqMap` instead of `Map` for `BCEnv` in bytecode compiler
The bytecode compiler maintains a `BCEnv` which was previously `Map Id
StackDepth`. Given `Id` is `Uniquable`, we might as well use `UniqMap`
here as a more efficient data structure, hence this patch.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
58e46da9 by fendor at 2025-08-18T20:13:56-04:00
rts: Strip lower three bits when hashing Word instead of lower eight bits
- - - - -
45dbfa23 by Cheng Shao at 2025-08-18T20:14:37-04:00
libffi: update to 3.5.2
Bumps libffi submodule.
- - - - -
54be78ef by Ben Gamari at 2025-08-19T16:28:05-04:00
testsuite: Fix T20006b
This test is supposed to fail for non-threaded ways yet it
was previously marked as only failing in `normal`.
Fix this.
- - - - -
f4bac607 by Simon Peyton Jones at 2025-08-19T16:28:47-04:00
Take yet more care with reporting redundant constraints
This small patch fixes #25992, which relates to reporting redundant
constraints on default-method declarations.
See (TRC5) in Note [Tracking redundant constraints]
- - - - -
ab130fec by fendor at 2025-08-19T16:29:29-04:00
Bump dependencies of hadrian-bootstrap-gen to use GHC 9.6.7
- - - - -
6d02ac6f by fendor at 2025-08-19T16:29:29-04:00
Bump required GHC version for test-bootstrap jobs to 9.10.1
Include test-bootstrap job for GHC 9.12.2.
Update hadrian bootstrap plans use GHC 9.10 and 9.12
Remove older GHC bootstrap configurations.
We require at least GHC 9.10.1 to build GHC.
Adds plans for:
* 9.10.1
* 9.10.2
* 9.12.1
* 9.12.2
- - - - -
9e857171 by Brandon Chinn at 2025-08-20T11:47:46-04:00
Don't warn unused-imports with used generated imports
Fixes #21730
* The old notion of "implicit" import has been renamed to "generated". See Note [Generated imports] in GHC.Hs.ImpExp.
* ImportMap now keeps track of generated and user-written imports separately. This avoids the fake SrcSpan we used to give the implicit Prelude import, and the hack that went with it.
* -ddump-minimal-imports now considers generated imports (but still only
warns on + prints user-written imports)
* bestImport considers generated imports to take priority over user-written imports.
- - - - -
9fb3bad4 by Ben Gamari at 2025-08-20T11:48:31-04:00
mailmap: Use ben(a)well-typed.com more liberally
Nearly all of this work was done while working for Well-Typed.
- - - - -
774fec37 by Ben Gamari at 2025-08-20T11:49:15-04:00
Add primop to annotate the call stack with arbitrary data
We introduce a new primop `annotateStack#` which allows us to push
arbitrary data onto the call-stack.
This allows us to extract the data later when decoding the stack, for
example when an exception is thrown, showing more information to the
user without having to annotate the full call-stack with `HasCallStack`
constraints.
A new stack frame value is introduced `AnnFrame`, which consists of
nothing but a generic payload.
The primop has a small wrapper API that allows users to annotate their
call-stack in programs.
There is a pure API and an IO-based one. The former is a little bit
dubious, as it affects the evaluation of a program, so use with care.
The latter is "safe", as it doesn't change the evaluation of the
program.
The stack annotation mechanism is similarly implemented to the
`ExceptionAnnotation` and `Exception`, there is a typeclass to indicate
something can be pushed onto the call-stack and all values are wrapped
in the existential `SomeStackAnnotation`, which recover the type of the
annotation payload.
There is currently no builtin way to show the stack annotations when
`Backtraces` are displayed (i.e., when showing stack traces to the user),
which we will address in a follow-up MR.
-------------------------
Metric Increase:
ghc_experimental_so
-------------------------
We increase the size of the package, so this is not unreasonable.
Co-Authored-By: fendor <fendor(a)posteo.de>
Co-Authored-By: Ben Gamari <bgamari.foss(a)gmail.com>
- - - - -
fdfa3892 by Ben Gamari at 2025-08-20T11:49:57-04:00
testsuite: Add regression test for #24606
- - - - -
39b2e382 by Cheng Shao at 2025-08-20T11:50:40-04:00
compiler: only use `Name` instead of `Id` in `SptEntry`
As a part of #26298, this patch refactors `SptEntry` to only carry a
`Name` instead of `Id`: we do not care about extra information like
caffyness or type at all in any static pointer related codegen logic.
This is necessary to make `SptEntry` serializable, as a part of the
grand plan of serializable bytecode.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
276f8ea8 by Vekhir -- at 2025-08-20T11:51:35-04:00
Bump Cabal dependency
- - - - -
0b9c7437 by Zubin Duggal at 2025-08-20T11:52:18-04:00
ci: Teach ci.sh to fetch FreeBSD artifacts from ghcup unofficial bindists and bootstrap compiler on FreeBSD to 9.10.1
Also refactor fetch_ghc logic in ci.sh, renaming the GHC_VERSION enviorment configuration variable to FETCH_GHC_VERSION,
making it clear that it is intended for use on platforms like Windows and FreeBSD where we don't want to use the GHC
excecutable from the platform environment and instead need to download and install GHC-$FETCH_GHC_VERSION from a release
bindist.
Fixes #26296
- - - - -
b2914797 by Cheng Shao at 2025-08-20T11:53:00-04:00
driver: use UniqSet for hiddenModules in DynFlags/FinderOpts
This patch replaces Set ModuleName with UniqSet ModuleName in
DynFlags.hiddenModules and FinderOpts.finder_hiddenModules for
improved efficiency.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
0335d899 by Cheng Shao at 2025-08-20T11:53:00-04:00
driver: use UniqMap ModuleName in the finder
This patch replaces Map ModuleName with UniqMap ModuleName in the
finder for improved efficiency.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
91f4faaa by Cheng Shao at 2025-08-20T11:53:43-04:00
configure: check python3 version and require minimal 3.7
Since !9515, the testsuite driver requires python3 version to be at
least 3.7, though this has never been checked by configure logic. This
patch implements the version check. Fixes #23234.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
df4ee9b4 by Cheng Shao at 2025-08-20T11:54:25-04:00
compiler: use zero cost coerce in GHC.CmmToAsm.CFG.loopInfo
This patch refactors GHC.CmmToAsm.CFG.loopInfo to use zero cost coerce
and thus addresses the TODO. For coerce to work, constructors of
Label/LabelMap/LabelSet from GHC.Cmm.Dataflow.Label are exposed,
though I believe it's a worthy tradeoff to avoid unnecessary runtime
cost without using unsafeCoerce, since the latter could be a landmine
for future refactoring.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
ccda188d by Simon Peyton Jones at 2025-08-20T11:55:07-04:00
Start with empty inerts in shortcut solving
When short-cut solving we were starting with an inert set that had
unsolved Wanteds. This caused an infinite loop (#26314), because a
typechecker plugin kept being given that unsolved Wanted.
It's better just to start with an empty inert set
- - - - -
c8882ed7 by Ben Gamari at 2025-08-20T11:55:49-04:00
configure: Bump minimal bootstrap GHC version to 9.8
- - - - -
f0a19d74 by fendor at 2025-08-20T19:55:00-04:00
Remove deprecated functions from the ghci package
- - - - -
ebeb991b by fendor at 2025-08-20T19:55:00-04:00
base: Remove unstable heap representation details from GHC.Exts
- - - - -
e368e247 by Rodrigo Mesquita at 2025-08-20T19:55:42-04:00
bytecode: Use 32bits for breakpoint index
Fixes #26325
- - - - -
42724462 by Simon Hengel at 2025-08-21T17:52:11-04:00
Serialize wired-in names as external names when creating HIE files
Note that the domain of de-serialized names stays the same.
Specifically, for known-key names, before `lookupKnownKeyName` was used,
while now this is handled by `lookupOrigNameCache` which captures the
same range provided that the OrigNameCache has been initialized with
`knownKeyNames` (which is the case by default).
(fixes #26238)
- - - - -
6a43f8ec by Cheng Shao at 2025-08-21T17:52:52-04:00
compiler: fix closure C type in SPT init code
This patch fixes the closure C type in SPT init code to StgClosure,
instead of the previously incorrect StgPtr. Having an incorrect C type
makes SPT init code not compatible with other foreign stub generation
logic, which may also emit their own extern declarations for the same
closure symbols and thus will clash with the incorrect prototypes in
SPT init code.
- - - - -
5b5d9d47 by Ben Gamari at 2025-08-25T14:29:35-04:00
Revert "STM: don't create a transaction in the rhs of catchRetry# (#26028)"
This reverts commit 0a5836891ca29836a24c306d2a364c2e4b5377fd
- - - - -
10f06163 by Cheng Shao at 2025-08-25T14:30:16-04:00
wasm: ensure setKeepCAFs() is called in ghci
This patch is a critical bugfix for #26106, see comment and linked
issue for details.
- - - - -
bedc1004 by Cheng Shao at 2025-08-26T09:31:18-04:00
compiler: use zero cost coerce in hoopl setElems/mapToList
This patch is a follow-up of !14680 and changes setElems/mapToList in
GHC/Cmm/Dataflow/Label to use coerce instead of mapping mkHooplLabel
over the keys.
- - - - -
13250d97 by Ryan Scott at 2025-08-26T09:31:59-04:00
Reject infix promoted data constructors without DataKinds
In the rename, make sure to apply the same `DataKinds` checks for both
`HsTyVar` (for prefix promoted data constructors) and `HsOpTy` (for infix
promoted data constructors) alike.
Fixes #26318.
- - - - -
37655c46 by Teo Camarasu at 2025-08-26T15:24:51-04:00
tests: disable T22859 under LLVM
This test was failing under the LLVM backend since the allocations
differ from the NCG.
Resolves #26282
- - - - -
2cbba9d6 by Teo Camarasu at 2025-08-26T15:25:33-04:00
base-exports: update version numbers
As the version of the compiler has been bumped, a lot of the embedded
version numbers will need to be updated if we ever run this test with
`--test-accept` so let's just update them now, and keep future diffs
clean.
- - - - -
f9f2ffcf by Alexandre Esteves at 2025-08-27T07:19:14-04:00
Import new name for 'utimbuf' on windows to fix #26337
Fixes an `-Wincompatible-pointer-types` instance that turns into an error on
recent toolchains and surfaced as such on nixpkgs when doing linux->ucrt cross.
This long-standing warning has been present at least since 9.4:
```
C:\GitLabRunner\builds\0\1709189\tmp\ghc16652_0\ghc_4.c:26:115: error:
warning: incompatible pointer types passing 'struct utimbuf *' to parameter of type 'struct _utimbuf *' [-Wincompatible-pointer-types]
|
26 | HsInt32 ghczuwrapperZC9ZCbaseZCSystemziPosixziInternalsZCzuutime(char* a1, struct utimbuf* a2) {return _utime(a1, a2);}
| ^
HsInt32 ghczuwrapperZC9ZCbaseZCSystemziPosixziInternalsZCzuutime(char* a1, struct utimbuf* a2) {return _utime(a1, a2);}
^~
C:\GitLabRunner\builds\0\1709189\_build\stage0\lib\..\..\mingw\x86_64-w64-mingw32\include\sys\utime.h:109:72: error:
note: passing argument to parameter '_Utimbuf' here
|
109 | __CRT_INLINE int __cdecl _utime(const char *_Filename,struct _utimbuf *_Utimbuf) {
| ^
__CRT_INLINE int __cdecl _utime(const char *_Filename,struct _utimbuf *_Utimbuf) {
```
- - - - -
ae89f000 by Hassan Al-Awwadi at 2025-08-27T07:19:56-04:00
Adds the fucnction addDependentDirectory to Q, resolving issue #26148.
This function adds a new directory to the list of things a module depends upon. That means that when the contents of the directory change, the recompilation checker will notice this and the module will be recompiled. Documentation has also been added for addDependentFunction and addDependentDirectory in the user guide.
- - - - -
00478944 by Simon Peyton Jones at 2025-08-27T16:48:30+01:00
Comments only
- - - - -
a7884589 by Simon Peyton Jones at 2025-08-28T11:08:23+01:00
Type-family occurs check in unification
The occurs check in `GHC.Core.Unify.uVarOrFam` was inadequate in dealing
with type families.
Better now. See Note [The occurs check in the Core unifier].
As I did this I realised that the whole apartness thing is trickier than I
thought: see the new Note [Shortcomings of the apartness test]
- - - - -
8adfc222 by sheaf at 2025-08-28T19:47:17-04:00
Fix orientation in HsWrapper composition (<.>)
This commit fixes the order in which WpCast HsWrappers are composed,
fixing a bug introduced in commit 56b32c5a2d5d7cad89a12f4d74dc940e086069d1.
Fixes #26350
- - - - -
eb2ab1e2 by Oleg Grenrus at 2025-08-29T11:00:53-04:00
Generalise thNameToGhcName by adding HasHscEnv
There were multiple single monad-specific `getHscEnv` across codebase.
HasHscEnv is modelled on HasDynFlags.
My first idea was to simply add thNameToGhcNameHsc and
thNameToGhcNameTc, but those would been exactly the same
as thNameToGhcName already.
Also add an usage example to thNameToGhcName and mention that it's
recommended way of looking up names in GHC plugins
- - - - -
2d575a7f by fendor at 2025-08-29T11:01:36-04:00
configure: Bump minimal bootstrap GHC version to 9.10
- - - - -
716274a5 by Simon Peyton Jones at 2025-08-29T17:27:12-04:00
Fix deep subsumption again
This commit fixed #26255:
commit 56b32c5a2d5d7cad89a12f4d74dc940e086069d1
Author: sheaf <sam.derbyshire(a)gmail.com>
Date: Mon Aug 11 15:50:47 2025 +0200
Improve deep subsumption
This commit improves the DeepSubsumption sub-typing implementation
in GHC.Tc.Utils.Unify.tc_sub_type_deep by being less eager to fall back
to unification.
But alas it still wasn't quite right for view patterns: #26331
This MR does a generalisation to fix it. A bit of a sledgehammer to crack
a nut, but nice.
* Add a field `ir_inst :: InferInstFlag` to `InferResult`, where
```
data InferInstFlag = IIF_Sigma | IIF_ShallowRho | IIF_DeepRho
```
* The flag says exactly how much `fillInferResult` should instantiate
before filling the hole.
* We can also use this to replace the previous very ad-hoc `tcInferSigma`
that was used to implement GHCi's `:type` command.
- - - - -
27206c5e by sheaf at 2025-08-29T17:28:14-04:00
Back-compat for TH SpecialiseP data-con of Pragma
This commit improves the backwards-compatibility story for the
SpecialiseP constructor of the Template Haskell 'Pragma' datatype.
Instead of keeping the constructor but deprecating it, this commit makes
it into a bundled pattern synonym of the Pragma datatype. We no longer
deprecate it; it's useful for handling old-form specialise pragmas.
- - - - -
26dbcf61 by fendor at 2025-08-30T05:10:08-04:00
Move stack decoding logic from ghc-heap to ghc-internal
The stack decoding logic in `ghc-heap` is more sophisticated than the one
currently employed in `CloneStack`. We want to use the stack decoding
implementation from `ghc-heap` in `base`.
We cannot simply depend on `ghc-heap` in `base` due do bootstrapping
issues.
Thus, we move the code that is necessary to implement stack decoding to
`ghc-internal`. This is the right location, as we don't want to add a
new API to `base`.
Moving the stack decoding logic and re-exposing it in ghc-heap is
insufficient, though, as we have a dependency cycle between.
* ghc-heap depends on stage1:ghc-internal
* stage0:ghc depends on stage0:ghc-heap
To fix this, we remove ghc-heap from the set of `stage0` dependencies.
This is not entirely straight-forward, as a couple of boot dependencies,
such as `ghci` depend on `ghc-heap`.
Luckily, the boot compiler of GHC is now >=9.10, so we can migrate `ghci`
to use `ghc-internal` instead of `ghc-heap`, which already exports the
relevant modules.
However, we cannot 100% remove ghc's dependency on `ghc-heap`, since
when we compile `stage0:ghc`, `stage1:ghc-internal` is not yet
available.
Thus, when we compile with the boot-compiler, we still depend on an
older version of `ghc-heap`, and only use the modules from `ghc-internal`,
if the `ghc-internal` version is recent enough.
-------------------------
Metric Increase:
T24602_perf_size
T25046_perf_size_gzip
T25046_perf_size_unicode
T25046_perf_size_unicode_gzip
size_hello_artifact
size_hello_artifact_gzip
size_hello_unicode
size_hello_unicode_gzip
-------------------------
These metric increases are unfortunate, they are most likely caused by
the larger (literally in terms of lines of code) stack decoder implementation
that are now linked into hello-word binaries.
On linux, it is almost a 10% increase, which is considerable.
- - - - -
bd80bb70 by fendor at 2025-08-30T05:10:08-04:00
Implement `decode` in terms of `decodeStackWithIpe`
Uses the more efficient stack decoder implementation.
- - - - -
24441165 by fendor at 2025-08-30T05:10:08-04:00
Remove stg_decodeStackzh
- - - - -
fb9cc882 by Simon Peyton Jones at 2025-08-30T05:10:51-04:00
Fix a long standing bug in the coercion optimiser
We were mis-optimising ForAllCo, leading to #26345
Part of the poblem was the tricky tower of abstractions leading to
the dreadful
GHC.Core.TyCo.Subst.substForAllCoTyVarBndrUsing
This function was serving two masters: regular substitution, but also
coercion optimsation. So tricky was it that it did so wrong.
In this MR I locate all the fancy footwork for coercion optimisation
in GHC.Core.Coercion.Opt, where it belongs. That leaves substitution
free to be much simpler.
- - - - -
6601832b by Teo Camarasu at 2025-09-01T13:38:58+01:00
ghc-internal: invert dependency of GHC.Internal.TH.Syntax on Data.Data
This means that Data.Data no longer blocks building TH.Syntax, which
allows greater parallelism in our builds.
We move the Data.Data.Data instances to Data.Data. Quasi depends on
Data.Data for one of its methods, so,
we split the Quasi/Q, etc definition out of GHC.Internal.TH.Syntax
into its own module. This has the added benefit of splitting up this
quite large module.
Previously TH.Syntax was a bottleneck when compiling ghc-internal. Now
it is less of a bottle-neck and is also slightly quicker to
compile (since it no longer contains these instances) at the cost of
making Data.Data slightly more expensive to compile.
TH.Lift which depends on TH.Syntax can also compile quicker and no
longer blocks ghc-internal finishing to compile.
Resolves #26217
-------------------------
Metric Decrease:
MultiLayerModulesTH_OneShot
T13253
T21839c
T24471
Metric Increase:
T12227
-------------------------
- - - - -
93e3ac68 by Teo Camarasu at 2025-09-01T13:38:59+01:00
compiler: delete unused names in Builtins.Names.TH
returnQ and bindQ are no longer used in the compiler.
There was also a very old comment that referred to them that I have modernized
- - - - -
296 changed files:
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .mailmap
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm/Dataflow/Label.hs
- compiler/GHC/CmmToAsm/CFG.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/Opt/Monad.hs
- compiler/GHC/Core/TyCo/Compare.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Config/Finder.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Env/Types.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Usage.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Ext/Binary.hs
- compiler/GHC/Iface/Ext/Types.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Recomp/Types.hs
- compiler/GHC/Iface/Tidy/StaticPtrTable.hs
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Plugins.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Runtime/Heap/Inspect.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/StgToJS/StaticPtr.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Expr.hs-boot
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Gen/Splice.hs-boot
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Types/TH.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Name/Cache.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/SptEntry.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Deps.hs
- compiler/ghc.cabal.in
- configure.ac
- docs/users_guide/9.16.1-notes.rst
- docs/users_guide/separate_compilation.rst
- ghc/GHCi/UI.hs
- hadrian/bootstrap/generate_bootstrap_plans
- hadrian/bootstrap/hadrian-bootstrap-gen.cabal
- hadrian/bootstrap/plan-9_10_1.json
- hadrian/bootstrap/plan-9_6_5.json → hadrian/bootstrap/plan-9_10_2.json
- hadrian/bootstrap/plan-9_6_6.json → hadrian/bootstrap/plan-9_12_1.json
- hadrian/bootstrap/plan-9_6_4.json → hadrian/bootstrap/plan-9_12_2.json
- − hadrian/bootstrap/plan-9_6_1.json
- − hadrian/bootstrap/plan-9_6_2.json
- − hadrian/bootstrap/plan-9_6_3.json
- − hadrian/bootstrap/plan-9_8_1.json
- − hadrian/bootstrap/plan-9_8_2.json
- hadrian/bootstrap/plan-bootstrap-9_10_1.json
- hadrian/bootstrap/plan-bootstrap-9_6_5.json → hadrian/bootstrap/plan-bootstrap-9_10_2.json
- hadrian/bootstrap/plan-bootstrap-9_6_6.json → hadrian/bootstrap/plan-bootstrap-9_12_1.json
- hadrian/bootstrap/plan-bootstrap-9_8_1.json → hadrian/bootstrap/plan-bootstrap-9_12_2.json
- − hadrian/bootstrap/plan-bootstrap-9_6_1.json
- − hadrian/bootstrap/plan-bootstrap-9_6_2.json
- − hadrian/bootstrap/plan-bootstrap-9_6_3.json
- − hadrian/bootstrap/plan-bootstrap-9_6_4.json
- − hadrian/bootstrap/plan-bootstrap-9_8_2.json
- hadrian/bootstrap/src/Main.hs
- hadrian/hadrian.cabal
- hadrian/src/Rules/ToolArgs.hs
- hadrian/src/Settings/Default.hs
- libffi-tarballs
- libraries/base/changelog.md
- libraries/base/src/Data/Array/Byte.hs
- libraries/base/src/Data/Fixed.hs
- libraries/base/src/GHC/Exts.hs
- libraries/base/src/GHC/Stack/CloneStack.hs
- + libraries/ghc-boot-th/GHC/Boot/TH/Monad.hs
- libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
- libraries/ghc-boot-th/ghc-boot-th.cabal.in
- libraries/ghc-experimental/ghc-experimental.cabal.in
- + libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs
- libraries/ghc-heap/GHC/Exts/Heap/ClosureTypes.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- + libraries/ghc-heap/GHC/Exts/Heap/Constants.hs
- + libraries/ghc-heap/GHC/Exts/Heap/InfoTable.hs
- + libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hs
- + libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hs
- libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs
- libraries/ghc-heap/GHC/Exts/Stack.hs
- + libraries/ghc-heap/GHC/Exts/Stack/Constants.hs
- libraries/ghc-heap/GHC/Exts/Stack/Decode.hs
- libraries/ghc-heap/ghc-heap.cabal.in
- libraries/ghc-heap/cbits/HeapPrim.cmm → libraries/ghc-internal/cbits/HeapPrim.cmm
- libraries/ghc-heap/cbits/Stack.cmm → libraries/ghc-internal/cbits/Stack.cmm
- libraries/ghc-internal/cbits/StackCloningDecoding.cmm
- libraries/ghc-heap/cbits/Stack_c.c → libraries/ghc-internal/cbits/Stack_c.c
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/jsbits/base.js
- libraries/ghc-internal/src/GHC/Internal/ClosureTypes.hs
- libraries/ghc-internal/src/GHC/Internal/Data/Data.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- + libraries/ghc-internal/src/GHC/Internal/Heap/Closures.hs
- libraries/ghc-heap/GHC/Exts/Heap/Constants.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/Constants.hsc
- libraries/ghc-heap/GHC/Exts/Heap/InfoTable.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/InfoTable.hsc
- libraries/ghc-heap/GHC/Exts/Heap/InfoTable/Types.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/InfoTable/Types.hsc
- libraries/ghc-heap/GHC/Exts/Heap/InfoTableProf.hsc → libraries/ghc-internal/src/GHC/Internal/Heap/InfoTableProf.hsc
- + libraries/ghc-internal/src/GHC/Internal/Heap/ProfInfo/Types.hs
- libraries/ghc-internal/src/GHC/Internal/Stack/CloneStack.hs
- libraries/ghc-heap/GHC/Exts/Stack/Constants.hsc → libraries/ghc-internal/src/GHC/Internal/Stack/Constants.hsc
- + libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
- libraries/ghc-internal/src/GHC/Internal/System/Posix/Internals.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
- + libraries/ghc-internal/src/GHC/Internal/TH/Monad.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Quote.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
- + libraries/ghc-internal/tests/stack-annotation/Makefile
- + libraries/ghc-internal/tests/stack-annotation/TestUtils.hs
- + libraries/ghc-internal/tests/stack-annotation/all.T
- + libraries/ghc-internal/tests/stack-annotation/ann_frame001.hs
- + libraries/ghc-internal/tests/stack-annotation/ann_frame001.stdout
- + libraries/ghc-internal/tests/stack-annotation/ann_frame002.hs
- + libraries/ghc-internal/tests/stack-annotation/ann_frame002.stdout
- + libraries/ghc-internal/tests/stack-annotation/ann_frame003.hs
- + libraries/ghc-internal/tests/stack-annotation/ann_frame003.stdout
- + libraries/ghc-internal/tests/stack-annotation/ann_frame004.hs
- + libraries/ghc-internal/tests/stack-annotation/ann_frame004.stdout
- libraries/ghci/GHCi/CreateBCO.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/TH.hs
- libraries/ghci/ghci.cabal.in
- libraries/template-haskell/Language/Haskell/TH/Lib.hs
- libraries/template-haskell/Language/Haskell/TH/Quote.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- libraries/template-haskell/changelog.md
- m4/find_python.m4
- rts/CloneStack.c
- rts/CloneStack.h
- rts/ClosureFlags.c
- rts/Disassembler.c
- rts/Hash.c
- rts/Interpreter.c
- rts/LdvProfile.c
- rts/PrimOps.cmm
- rts/Printer.c
- rts/RaiseAsync.c
- rts/RetainerProfile.c
- rts/RtsSymbols.c
- rts/STM.c
- rts/TraverseHeap.c
- rts/include/rts/storage/ClosureTypes.h
- rts/include/rts/storage/Closures.h
- rts/include/stg/MiscClosures.h
- rts/js/profiling.js
- rts/sm/Compact.c
- rts/sm/Evac.c
- rts/sm/NonMovingMark.c
- rts/sm/Sanity.c
- rts/sm/Scav.c
- testsuite/.gitignore
- testsuite/tests/deriving/should_compile/T14682.stderr
- testsuite/tests/deriving/should_compile/drv-empty-data.stderr
- testsuite/tests/gadt/T12468.stderr
- testsuite/tests/ghc-e/should_fail/T24172.stderr
- testsuite/tests/ghci/scripts/T8353.stderr
- testsuite/tests/ghci/scripts/ghci038.stdout
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- testsuite/tests/interface-stability/ghc-prim-exports.stdout
- testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- − testsuite/tests/lib/stm/T26028.hs
- − testsuite/tests/lib/stm/T26028.stdout
- − testsuite/tests/lib/stm/all.T
- − testsuite/tests/module/T21752.stderr
- testsuite/tests/module/mod150.stderr
- testsuite/tests/module/mod151.stderr
- testsuite/tests/module/mod152.stderr
- testsuite/tests/module/mod153.stderr
- testsuite/tests/overloadedrecflds/should_fail/T18999_NoDisambiguateRecordFields.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T19082.stderr
- + testsuite/tests/patsyn/should_compile/T26331.hs
- + testsuite/tests/patsyn/should_compile/T26331a.hs
- testsuite/tests/patsyn/should_compile/all.T
- testsuite/tests/perf/compiler/hard_hole_fits.stderr
- testsuite/tests/plugins/Makefile
- + testsuite/tests/plugins/T21730-plugin/Makefile
- + testsuite/tests/plugins/T21730-plugin/Setup.hs
- + testsuite/tests/plugins/T21730-plugin/T21730-plugin.cabal
- + testsuite/tests/plugins/T21730-plugin/T21730_Plugin.hs
- + testsuite/tests/plugins/T21730.hs
- testsuite/tests/plugins/all.T
- testsuite/tests/plugins/plugins10.stdout
- testsuite/tests/quotes/LiftErrMsg.stderr
- testsuite/tests/quotes/LiftErrMsgDefer.stderr
- testsuite/tests/quotes/LiftErrMsgTyped.stderr
- testsuite/tests/rename/should_compile/T22513d.stderr
- testsuite/tests/rename/should_compile/T22513e.stderr
- testsuite/tests/rename/should_compile/T22513f.stderr
- testsuite/tests/rename/should_compile/T22513g.stderr
- testsuite/tests/rename/should_compile/T22513h.stderr
- testsuite/tests/rename/should_compile/T22513i.stderr
- testsuite/tests/rename/should_compile/rn039.ghc.stderr
- testsuite/tests/rename/should_fail/T15487.stderr
- testsuite/tests/rename/should_fail/T18740a.stderr
- testsuite/tests/rename/should_fail/rnfail044.stderr
- testsuite/tests/rts/all.T
- testsuite/tests/rts/flags/all.T
- testsuite/tests/safeHaskell/flags/SafeFlags17.stderr
- + testsuite/tests/simplCore/should_compile/T24606.hs
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/splice-imports/SI29.stderr
- testsuite/tests/th/Makefile
- testsuite/tests/th/T10267.stderr
- testsuite/tests/th/T11452.stderr
- testsuite/tests/th/T14627.stderr
- testsuite/tests/th/T15321.stderr
- testsuite/tests/th/T7276.stderr
- + testsuite/tests/th/TH_Depends_Dir.hs
- + testsuite/tests/th/TH_Depends_Dir.stdout
- + testsuite/tests/th/TH_Depends_Dir_External.hs
- testsuite/tests/th/TH_NestedSplicesFail3.stderr
- testsuite/tests/th/TH_NestedSplicesFail4.stderr
- testsuite/tests/th/all.T
- testsuite/tests/typecheck/should_compile/T13050.stderr
- testsuite/tests/typecheck/should_compile/T14273.stderr
- testsuite/tests/typecheck/should_compile/T14590.stderr
- testsuite/tests/typecheck/should_compile/T25180.stderr
- + testsuite/tests/typecheck/should_compile/T25992a.hs
- + testsuite/tests/typecheck/should_compile/T26345.hs
- + testsuite/tests/typecheck/should_compile/T26346.hs
- + testsuite/tests/typecheck/should_compile/T26350.hs
- + testsuite/tests/typecheck/should_compile/T26358.hs
- testsuite/tests/typecheck/should_compile/T9497a.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/subsumption_sort_hole_fits.stderr
- testsuite/tests/typecheck/should_fail/T14884.stderr
- testsuite/tests/typecheck/should_fail/T21130.stderr
- testsuite/tests/typecheck/should_fail/T23739b.stderr
- testsuite/tests/typecheck/should_fail/T23739c.stderr
- + testsuite/tests/typecheck/should_fail/T26318.hs
- + testsuite/tests/typecheck/should_fail/T26318.stderr
- testsuite/tests/typecheck/should_fail/T9497d.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail037.stderr
- testsuite/tests/typecheck/should_run/T9497a-run.stderr
- testsuite/tests/typecheck/should_run/T9497b-run.stderr
- testsuite/tests/typecheck/should_run/T9497c-run.stderr
- testsuite/tests/vdq-rta/should_fail/T23738_fail_pun.stderr
- utils/deriveConstants/Main.hs
- utils/haddock/haddock-api/src/Haddock/InterfaceFile.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/c450440389ad97e89e4088bf0d8441…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c450440389ad97e89e4088bf0d8441…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/fendor/t23812] 3 commits: Refactor distinct constructor tables map construction
by Hannes Siebenhandl (@fendor) 01 Sep '25
by Hannes Siebenhandl (@fendor) 01 Sep '25
01 Sep '25
Hannes Siebenhandl pushed to branch wip/fendor/t23812 at Glasgow Haskell Compiler / GHC
Commits:
62f51fad by Finley McIlwaine at 2025-09-01T10:56:54+02:00
Refactor distinct constructor tables map construction
Adds `GHC.Types.Unique.Map.alterUniqMap_L`, `GHC.Types.Unique.FM.alterUFM_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`.
- - - - -
561a1835 by Finley McIlwaine at 2025-09-01T10:57:59+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 create distinct constructor tables for all constructors except for a
specific few named `C1`,..., `CN`, pass `-fdistinct-contructor-tables` followed
by `fno-distinct-constructor-tables=C1,...,CN`. To only generate distinct
constuctor tables for a few specific constructors and no others, just pass
`-fdistinct-constructor-tables=C1,...,CN`.
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
- - - - -
59f3f686 by Finley McIlwaine at 2025-09-01T10:58:56+02:00
Add -f{no-}distinct-constructor-tables-per-module
With -fdistinct-constructor-tables-per-module, only one info table will be
created for all equivalent constructors used in the same module. Just like
`-f{no-}distinct-constructor-tables`, these flags can also be given a
comma-separated list of constructor names to specify exactly which constructors
this behavior should apply to.
This commit alters the distinct-tables test to also test the behavior of these
flags.
Fixes #23812
- - - - -
41 changed files:
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/CoreToStg.hs
- compiler/GHC/Data/Word64Map/Internal.hs
- compiler/GHC/Data/Word64Map/Lazy.hs
- compiler/GHC/Driver/Config/Stg/Debug.hs
- compiler/GHC/Driver/Config/StgToCmm.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/GenerateCgIPEStub.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/Stg/Syntax.hs
- compiler/GHC/StgToCmm.hs
- compiler/GHC/StgToCmm/Config.hs
- compiler/GHC/StgToCmm/DataCon.hs
- compiler/GHC/StgToCmm/Layout.hs
- compiler/GHC/StgToCmm/Ticky.hs
- compiler/GHC/StgToCmm/Utils.hs
- compiler/GHC/Types/IPE.hs
- compiler/GHC/Types/Unique/DFM.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Unique/Map.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
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5b8f2fff4837073fa91caa12a7e4ed…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5b8f2fff4837073fa91caa12a7e4ed…
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) 01 Sep '25
by Hannes Siebenhandl (@fendor) 01 Sep '25
01 Sep '25
Hannes Siebenhandl pushed to branch wip/fendor/t23703 at Glasgow Haskell Compiler / GHC
Commits:
62f51fad by Finley McIlwaine at 2025-09-01T10:56:54+02:00
Refactor distinct constructor tables map construction
Adds `GHC.Types.Unique.Map.alterUniqMap_L`, `GHC.Types.Unique.FM.alterUFM_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`.
- - - - -
561a1835 by Finley McIlwaine at 2025-09-01T10:57:59+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 create distinct constructor tables for all constructors except for a
specific few named `C1`,..., `CN`, pass `-fdistinct-contructor-tables` followed
by `fno-distinct-constructor-tables=C1,...,CN`. To only generate distinct
constuctor tables for a few specific constructors and no others, just pass
`-fdistinct-constructor-tables=C1,...,CN`.
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/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/Types/Unique/Map.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
Changes:
=====================================
compiler/GHC/Data/Word64Map/Internal.hs
=====================================
@@ -100,6 +100,7 @@ module GHC.Data.Word64Map.Internal (
, updateWithKey
, updateLookupWithKey
, alter
+ , alterLookupWithKey
, alterF
-- * Combine
@@ -986,6 +987,39 @@ alter f k Nil = case f Nothing of
Just x -> Tip k x
Nothing -> Nil
+-- | \(O(\min(n,W))\). The expression (@'alterLookupWithKey' f k map@) alters
+-- the value @x@ at @k@, or absence thereof, and returns the result of the
+-- alteration. 'alterLookupWithKey' can be used to insert, delete, or update a
+-- value in a 'Word64Map'.
+--
+-- Note that the behavior of this function differs from 'updateLookupWithKey',
+-- and instead matches the behavior of 'Data.Map.updateLookupWithKey'.
+alterLookupWithKey :: (Maybe a -> Maybe a) -> Key -> Word64Map a -> (Maybe a, Word64Map a)
+alterLookupWithKey f !k t@(Bin p m l r)
+ | nomatch k p m =
+ case f Nothing of
+ Nothing -> (Nothing, t)
+ Just x -> (Just x, link k (Tip k x) p t)
+ | zero k m =
+ let !(res, l') = alterLookupWithKey f k l
+ in (res, binCheckLeft p m l' r)
+ | otherwise =
+ let !(res, r') = alterLookupWithKey f k r
+ in (res, binCheckRight p m l r')
+alterLookupWithKey f k t@(Tip ky y)
+ | k==ky =
+ case f (Just y) of
+ Just x -> (Just x, Tip ky x)
+ Nothing -> (Nothing, Nil)
+ | otherwise =
+ case f Nothing of
+ Just x -> (Just x, link k (Tip k x) ky t)
+ Nothing -> (Nothing, Tip ky y)
+alterLookupWithKey f k Nil =
+ case f Nothing of
+ Just x -> (Just x, Tip k x)
+ Nothing -> (Nothing, Nil)
+
-- | \(O(\min(n,W))\). The expression (@'alterF' f k map@) alters the value @x@ at
-- @k@, or absence thereof. 'alterF' can be used to inspect, insert, delete,
-- or update a value in an 'Word64Map'. In short : @'lookup' k <$> 'alterF' f k m = f
=====================================
compiler/GHC/Data/Word64Map/Lazy.hs
=====================================
@@ -93,6 +93,7 @@ module GHC.Data.Word64Map.Lazy (
, updateWithKey
, updateLookupWithKey
, alter
+ , alterLookupWithKey
, alterF
-- * Query
=====================================
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
@@ -477,7 +478,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
@@ -739,7 +744,9 @@ defaultDynFlags mySettings =
reverseErrors = False,
maxErrors = Nothing,
- cfgWeights = defaultWeights
+ cfgWeights = defaultWeights,
+
+ distinctConstructorTables = None
}
type FatalMessager = String -> IO ()
=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -593,7 +593,6 @@ data GeneralFlag
| Opt_FastLlvm -- hidden flag
| Opt_NoTypeableBinds
- | Opt_DistinctConstructorTables
| Opt_InfoTableMap
| Opt_InfoTableMapWithFallback
| Opt_InfoTableMapWithStack
@@ -982,7 +981,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 )
@@ -1908,6 +1909,10 @@ dynamic_flags_deps = [
-- Caller-CC
, make_ord_flag defGhcFlag "fprof-callers"
(HasArg setCallerCcFilters)
+ , make_ord_flag defGhcFlag "fdistinct-constructor-tables"
+ (OptPrefix setDistinctConstructorTables)
+ , make_ord_flag defGhcFlag "fno-distinct-constructor-tables"
+ (OptPrefix unSetDistinctConstructorTables)
------ Compiler flags -----------------------------------------------
, make_ord_flag defGhcFlag "fasm" (NoArg (setObjBackend ncgBackend))
@@ -2609,7 +2614,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
@@ -3207,6 +3211,39 @@ setCallerCcFilters arg =
Right filt -> upd $ \d -> d { callerCcFilters = filt : callerCcFilters d }
Left err -> addErr err
+setDistinctConstructorTables :: String -> DynP ()
+setDistinctConstructorTables arg = do
+ let cs = parseDistinctConstructorTablesArg arg
+ upd $ \d ->
+ d { distinctConstructorTables =
+ (distinctConstructorTables d) `dctConfigPlus` cs
+ }
+
+unSetDistinctConstructorTables :: String -> DynP ()
+unSetDistinctConstructorTables arg = do
+ let cs = parseDistinctConstructorTablesArg arg
+ upd $ \d ->
+ d { distinctConstructorTables =
+ (distinctConstructorTables d) `dctConfigMinus` 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,66 @@ 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
+ (AllExcept 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)
+ (AllExcept v) -> text "all except" <+> 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
+ (AllExcept cs) -> do
+ putByte bh 2
+ put_ bh cs
+ None -> putByte bh 3
+
+ get bh = do
+ h <- getByte bh
+ IfaceDistinctConstructorConfig <$>
+ case h of
+ 0 -> pure All
+ 1 -> Only <$> get bh
+ 2 -> AllExcept <$> 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,13 @@
-{-# 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(..)
+ , dctConfigPlus
+ , dctConfigMinus
, collectDebugInformation
) where
@@ -17,11 +21,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 +35,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
@@ -155,6 +154,8 @@ recordStgIdPosition id best_span ss = do
let mbspan = (\(SpanWithLabel rss d) -> (rss, d)) <$> (best_span <|> cc <|> ss)
lift $ modify (\env -> env { provClosure = addToUDFM (provClosure env) (idName id) (idName id, (idType id, mbspan)) })
+-- | If @-fdistinct-constructor-tables@ is enabled, each occurrence of a data
+-- constructor will be given its own info table
numberDataCon :: DataCon -> [StgTickish] -> M ConstructorNumber
-- Unboxed tuples and sums do not allocate so they
-- have no info tables.
@@ -162,22 +163,59 @@ numberDataCon dc _ | isUnboxedTupleDataCon dc = return NoNumber
numberDataCon dc _ | isUnboxedSumDataCon dc = return NoNumber
numberDataCon dc ts = do
opts <- asks rOpts
- if not (stgDebug_distinctConstructorTables opts) then return NoNumber else do
+ 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 !mbest_span = (\(SpanWithLabel rss l) -> (rss, l)) <$> (selectTick ts <|> mcc)
- let !dcMap' = alterUDFM (maybe (Just (dc, (0, mbest_span) :| [] ))
- (\(_dc, xs@((k, _):|_)) -> Just $! (dc, (k + 1, mbest_span) `NE.cons` xs))) (provDC env) dc
+ let
+ -- Guess a src span for this occurrence using source note ticks and the
+ -- current span in the environment
+ !mbest_span = selectTick ts <|> (\(SpanWithLabel rss l) -> (rss, l)) <$> mcc
+
+ -- Add the occurrence to the data constructor map of the InfoTableProvMap,
+ -- noting the unique number assigned for this occurence
+ (!r, !dcMap') =
+ alterUDFM_L
+ ( maybe
+ (Just (dc, (0, mbest_span) :| [] ))
+ ( \(_dc, xs@((k, _):|_)) ->
+ Just $! (dc, (k + 1, mbest_span) `NE.cons` xs)
+ )
+ )
+ (provDC env)
+ dc
lift $ put (env { provDC = dcMap' })
- let r = lookupUDFM dcMap' dc
return $ case r of
Nothing -> NoNumber
Just (_, res) -> Numbered (fst (NE.head res))
+ else do
+ -- -fdistinct-constructor-tables is not enabled, or we do not want to make
+ -- distinct tables for this specific constructor
+ return NoNumber
-selectTick :: [StgTickish] -> Maybe SpanWithLabel
-selectTick [] = Nothing
-selectTick (SourceNote rss d : ts ) = selectTick ts <|> Just (SpanWithLabel rss d)
-selectTick (_:ts) = selectTick ts
+selectTick :: [StgTickish] -> Maybe (RealSrcSpan, LexicalFastString)
+selectTick = foldl' go Nothing
+ where
+ go :: Maybe (RealSrcSpan, LexicalFastString) -> StgTickish -> Maybe (RealSrcSpan, LexicalFastString)
+ 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
+ AllExcept these -> Set.notMember 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,80 @@
+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=C1,...,CN@ is
+ -- supplied.
+ | Only !(Set String)
+
+ -- | Create distinct constructor tables for each usage of any data
+ -- constructor except these ones.
+ --
+ -- This is the behavior if @-fdistinct-constructor-tables@ and
+ -- @-fno-distinct-constructor-tables=C1,...,CN@ is given.
+ | AllExcept !(Set String)
+
+ -- | Do not create distinct constructor tables for any data constructor.
+ --
+ -- This is the behavior if no @-fdistinct-constructor-tables@ is given (or
+ -- @-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.
+dctConfigPlus :: StgDebugDctConfig -> Set String -> StgDebugDctConfig
+dctConfigPlus cfg cs
+ | Set.null cs = All
+ | otherwise =
+ case cfg of
+ All -> All
+ Only cs' -> Only $ Set.union cs' cs
+ AllExcept cs' -> AllExcept $ Set.difference cs' cs
+ None -> Only cs
+
+-- | Given a distinct constructor tables configuration and a set of constructor
+-- names that we /do not/ want to generate distinct info tables for, create a
+-- new configuration which excludes those constructors.
+--
+-- If the given set is empty, that means the user has entered
+-- @-fno-distinct-constructor-tables@ with no constructor names specified, and
+-- therefore we consider that a 'None' configuration.
+dctConfigMinus :: StgDebugDctConfig -> Set String -> StgDebugDctConfig
+dctConfigMinus cfg cs
+ | Set.null cs = None
+ | otherwise =
+ case cfg of
+ All -> AllExcept cs
+ Only cs' -> Only $ Set.difference cs' cs
+ AllExcept cs' -> AllExcept $ Set.union cs' cs
+ None -> None
+
=====================================
compiler/GHC/Types/Unique/DFM.hs
=====================================
@@ -39,6 +39,7 @@ module GHC.Types.Unique.DFM (
adjustUDFM,
adjustUDFM_Directly,
alterUDFM,
+ alterUDFM_L,
mapUDFM,
mapMaybeUDFM,
mapMUDFM,
@@ -436,16 +437,18 @@ adjustUDFM f (UDFM m i) k = UDFM (M.adjust (fmap f) (getKey $ getUnique k) m) i
adjustUDFM_Directly :: (elt -> elt) -> UniqDFM key elt -> Unique -> UniqDFM key elt
adjustUDFM_Directly f (UDFM m i) k = UDFM (M.adjust (fmap f) (getKey k) m) i
--- | The expression (alterUDFM f k map) alters value x at k, or absence
--- thereof. alterUDFM can be used to insert, delete, or update a value in
+-- | The expression (@'alterUDFM' f map k@) alters value x at k, or absence
+-- thereof. 'alterUDFM' can be used to insert, delete, or update a value in
-- UniqDFM. Use addToUDFM, delFromUDFM or adjustUDFM when possible, they are
-- more efficient.
+--
+-- 'alterUDFM' is non-strict in @k@.
alterUDFM
:: Uniquable key
- => (Maybe elt -> Maybe elt) -- How to adjust
- -> UniqDFM key elt -- old
- -> key -- new
- -> UniqDFM key elt -- result
+ => (Maybe elt -> Maybe elt) -- ^ How to adjust the element
+ -> UniqDFM key elt -- ^ Old 'UniqDFM'
+ -> key -- ^ @key@ of the element to adjust
+ -> UniqDFM key elt -- ^ New element at @key@ and modified 'UniqDFM'
alterUDFM f (UDFM m i) k =
UDFM (M.alter alterf (getKey $ getUnique k) m) (i + 1)
where
@@ -454,6 +457,35 @@ alterUDFM f (UDFM m i) k =
inject Nothing = Nothing
inject (Just v) = Just $ TaggedVal v i
+-- | The expression (@'alterUDFM_L' f map k@) alters value @x@ at @k@, or absence
+-- thereof and returns the new element at @k@ if there is any.
+-- 'alterUDFM_L' can be used to insert, delete, or update a value in
+-- UniqDFM. Use addToUDFM, delFromUDFM or adjustUDFM when possible, they are
+-- more efficient.
+--
+-- Note, 'alterUDFM_L' is strict in @k@.
+alterUDFM_L
+ :: forall key elt . Uniquable key
+ => (Maybe elt -> Maybe elt) -- ^ How to adjust the element
+ -> UniqDFM key elt -- ^ Old 'UniqDFM'
+ -> key -- ^ @key@ of the element to adjust
+ -> (Maybe elt, UniqDFM key elt) -- ^ New element at @key@ and modified 'UniqDFM'
+alterUDFM_L f (UDFM m i) k =
+ let
+ -- Force the key Word64 as the thunk is almost never worth it.
+ !key = getKey $ getUnique k
+ (mElt, udfm) = M.alterF (dupe . alterf) key m
+ in
+ (mElt, UDFM udfm (i + 1))
+ where
+ dupe :: Maybe (TaggedVal elt) -> (Maybe elt, Maybe (TaggedVal elt))
+ dupe mt = (fmap taggedFst mt, mt)
+ alterf :: Maybe (TaggedVal elt) -> (Maybe (TaggedVal elt))
+ alterf Nothing = inject $ f Nothing
+ alterf (Just (TaggedVal v _)) = inject $ f (Just v)
+ inject Nothing = Nothing
+ inject (Just v) = Just $ TaggedVal v i
+
-- | Map a function over every value in a UniqDFM
mapUDFM :: (elt1 -> elt2) -> UniqDFM key elt1 -> UniqDFM key elt2
mapUDFM f (UDFM m i) = UDFM (MS.map (fmap f) m) i
=====================================
compiler/GHC/Types/Unique/FM.hs
=====================================
@@ -44,7 +44,7 @@ module GHC.Types.Unique.FM (
addListToUFM,addListToUFM_C,
addToUFM_Directly,
addListToUFM_Directly,
- adjustUFM, alterUFM, alterUFM_Directly,
+ adjustUFM, alterUFM, alterUFM_L, alterUFM_Directly,
adjustUFM_Directly,
delFromUFM,
delFromUFM_Directly,
@@ -215,6 +215,16 @@ alterUFM
-> UniqFM key elt -- ^ result
alterUFM f (UFM m) k = UFM (M.alter f (getKey $ getUnique k) m)
+alterUFM_L
+ :: Uniquable key
+ => (Maybe elt -> Maybe elt) -- ^ How to adjust
+ -> UniqFM key elt -- ^ old
+ -> key -- ^ new
+ -> (Maybe elt, UniqFM key elt) -- ^ result
+alterUFM_L f (UFM m) k =
+ let (r, m') = (M.alterLookupWithKey f (getKey $ getUnique k) m)
+ in (r, UFM m')
+
alterUFM_Directly
:: (Maybe elt -> Maybe elt) -- ^ How to adjust
-> UniqFM key elt -- ^ old
=====================================
compiler/GHC/Types/Unique/Map.hs
=====================================
@@ -22,6 +22,7 @@ module GHC.Types.Unique.Map (
addToUniqMap_Acc,
addToUniqMap_L,
alterUniqMap,
+ alterUniqMap_L,
addListToUniqMap_C,
adjustUniqMap,
delFromUniqMap,
@@ -160,6 +161,15 @@ alterUniqMap :: Uniquable k
alterUniqMap f (UniqMap m) k = UniqMap $
alterUFM (fmap (k,) . f . fmap snd) m k
+alterUniqMap_L :: Uniquable k
+ => (Maybe a -> Maybe a)
+ -> UniqMap k a
+ -> k
+ -> (Maybe a, UniqMap k a)
+alterUniqMap_L f (UniqMap m) k =
+ let (r, m') = alterUFM_L (fmap (k,) . f . fmap snd) m k
+ in (snd <$> r, UniqMap m')
+
addListToUniqMap_C
:: Uniquable k
=> (a -> a -> a)
=====================================
compiler/ghc.cabal.in
=====================================
@@ -737,6 +737,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=⟨cs⟩>`.
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
@@ -453,7 +454,7 @@ to a source location. This lookup table is generated by using the ``-finfo-table
from the info table map and decrease the size of executables with info table
profiling information.
-.. ghc-flag:: -fdistinct-constructor-tables
+.. ghc-flag:: -fdistinct-constructor-tables=⟨cs⟩
:shortdesc: Generate a fresh info table for each usage
of a data constructor.
:type: dynamic
@@ -467,6 +468,41 @@ 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.
+ :since: 9.16
+
+ The entries in the info table map resulting from this 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``.
+
+.. ghc-flag:: -fno-distinct-constructor-tables=⟨cs⟩
+ :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 refine the set of data constructors for which distinct info
+ tables are generated (as specified by
+ :ghc-flag:`-fdistinct-constructor-tables
+ <-fdistinct-constructor-tables=⟨cs⟩>`).
+ If no constructor names are given
+ (i.e. just ``-fno-distinct-constructor-tables`` is given) then no distinct
+ info tables will be generated for any usages of any data constructors.
+
+ For example, to generate distinct constructor tables for all data
+ constructors except those named ``MyConstr``, pass both
+ ``-fdistinct-constructor-tables`` and
+ ``-fno-distinct-constructor-tables=MyConstr``.
Querying the Info Table Map
---------------------------
=====================================
testsuite/tests/count-deps/CountDepsAst.stdout
=====================================
@@ -132,6 +132,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
=====================================
@@ -151,6 +151,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,31 @@
+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=ACon Main.hs && ./Main
+
+distinct_tables02:
+ @$$TEST_HC $$TEST_HC_OPTS -v0 -finfo-table-map -fdistinct-constructor-tables=BCon Main.hs && ./Main
+
+distinct_tables03:
+ @$$TEST_HC $$TEST_HC_OPTS -v0 -finfo-table-map -fdistinct-constructor-tables=CCon Main.hs && ./Main
+
+distinct_tables04:
+ @$$TEST_HC $$TEST_HC_OPTS -v0 -finfo-table-map -fdistinct-constructor-tables=ACon,BCon Main.hs && ./Main
+
+distinct_tables05:
+ @$$TEST_HC $$TEST_HC_OPTS -v0 -finfo-table-map -fdistinct-constructor-tables -fno-distinct-constructor-tables=ACon Main.hs && ./Main
+
+distinct_tables06:
+ @$$TEST_HC $$TEST_HC_OPTS -v0 -finfo-table-map -fdistinct-constructor-tables -fno-distinct-constructor-tables=BCon Main.hs && ./Main
+
+distinct_tables07:
+ @$$TEST_HC $$TEST_HC_OPTS -v0 -finfo-table-map -fdistinct-constructor-tables -fno-distinct-constructor-tables=CCon Main.hs && ./Main
+
+distinct_tables08:
+ @$$TEST_HC $$TEST_HC_OPTS -v0 -finfo-table-map -fdistinct-constructor-tables -fno-distinct-constructor-tables=BCon,CCon 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,8 @@
+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, [])
=====================================
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_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_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_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_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_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_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_tables07.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_tables08.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 = ""}
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bbc3179500756a427cdafb2feecde4…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bbc3179500756a427cdafb2feecde4…
You're receiving this email because of your account on gitlab.haskell.org.
1
0