
[Git][ghc/ghc][wip/fendor/ann-frame] Add primop to annotate the call stack with arbitrary data
by Hannes Siebenhandl (@fendor) 14 Aug '25
by Hannes Siebenhandl (@fendor) 14 Aug '25
14 Aug '25
Hannes Siebenhandl pushed to branch wip/fendor/ann-frame at Glasgow Haskell Compiler / GHC
Commits:
2ac65a1c by Ben Gamari at 2025-08-14T13:22:00+02: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>
- - - - -
47 changed files:
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.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/Stack.hs
- libraries/ghc-heap/GHC/Exts/Stack/Constants.hsc
- libraries/ghc-heap/GHC/Exts/Stack/Decode.hs
- + libraries/ghc-heap/tests/stack-annotation/Makefile
- + libraries/ghc-heap/tests/stack-annotation/TestUtils.hs
- + libraries/ghc-heap/tests/stack-annotation/all.T
- + libraries/ghc-heap/tests/stack-annotation/ann_frame001.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame001.stdout
- + libraries/ghc-heap/tests/stack-annotation/ann_frame002.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame002.stdout
- + libraries/ghc-heap/tests/stack-annotation/ann_frame003.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame003.stdout
- + libraries/ghc-heap/tests/stack-annotation/ann_frame004.hs
- + libraries/ghc-heap/tests/stack-annotation/ann_frame004.stdout
- libraries/ghc-internal/src/GHC/Internal/ClosureTypes.hs
- rts/ClosureFlags.c
- rts/LdvProfile.c
- rts/PrimOps.cmm
- rts/Printer.c
- rts/RetainerProfile.c
- rts/RtsSymbols.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/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
- utils/deriveConstants/Main.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2ac65a1c900f9f35a42c78d11bea56e…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2ac65a1c900f9f35a42c78d11bea56e…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Simon Peyton Jones pushed to branch wip/T23162-spj at Glasgow Haskell Compiler / GHC
Commits:
58d6142b by Simon Peyton Jones at 2025-08-14T12:15:10+01:00
More wibbles
In particular, solve fundeps with Givens only
- - - - -
5 changed files:
- compiler/GHC/Runtime/Heap/Inspect.hs
- compiler/GHC/Tc/Solver/FunDeps.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Utils/Outputable.hs
Changes:
=====================================
compiler/GHC/Runtime/Heap/Inspect.hs
=====================================
@@ -253,7 +253,7 @@ pprTermM y p t = pprDeeper `liftM` ppr_termM y p t
ppr_termM y p Term{dc=Left dc_tag, subTerms=tt} = do
tt_docs <- mapM (y app_prec) tt
return $ cparen (not (null tt) && p >= app_prec)
- (text dc_tag <+> pprDeeperList fsep tt_docs)
+ (text dc_tag <+> pprDeeper (fsep tt_docs))
ppr_termM y p Term{dc=Right dc, subTerms=tt}
{- | dataConIsInfix dc, (t1:t2:tt') <- tt --TODO fixity
@@ -270,7 +270,7 @@ ppr_termM y p Term{dc=Right dc, subTerms=tt}
show_tm tt_docs
| null tt_docs = ppr dc
| otherwise = cparen (p >= app_prec) $
- sep [ppr dc, nest 2 (pprDeeperList fsep tt_docs)]
+ sep [ppr dc, nest 2 (pprDeeper (fsep tt_docs))]
ppr_termM y p t@NewtypeWrap{} = pprNewtypeWrap y p t
ppr_termM y p RefWrap{wrapped_term=t} = do
=====================================
compiler/GHC/Tc/Solver/FunDeps.hs
=====================================
@@ -929,6 +929,11 @@ solving.
solveFunDeps :: CtEvidence -- The work item
-> [FunDepEqn (CtLoc, RewriterSet)]
-> TcS Bool
+-- Solve a bunch of type-equality equations, generated by functional dependencies
+-- By "solve" we mean: (only) do unifications. We do not generate evidence, and
+-- other than unifications there should be no effects whatsoever
+--
+-- Return True if some unifications happened
-- See Note [FunDep and implicit parameter reactions]
solveFunDeps work_ev fd_eqns
| null fd_eqns
=====================================
compiler/GHC/Tc/Solver/InertSet.hs
=====================================
@@ -16,7 +16,7 @@ module GHC.Tc.Solver.InertSet (
-- * The inert set
InertSet(..),
InertCans(..),
- emptyInertSet, emptyInertCans,
+ emptyInertSet, emptyInertCans, resetInertCans,
noGivenNewtypeReprEqs, updGivenEqs,
prohibitedSuperClassSolve,
@@ -76,7 +76,7 @@ import GHC.Utils.Panic
import GHC.Data.Bag
import Control.Monad ( forM_ )
-import Data.List.NonEmpty ( NonEmpty(..), (<|) )
+import qualified Data.List.NonEmpty as NE
import Data.Function ( on )
{-
@@ -305,7 +305,7 @@ instance Outputable WorkList where
* *
********************************************************************* -}
-type CycleBreakerVarStack = NonEmpty (Bag (TcTyVar, TcType))
+type CycleBreakerVarStack = NE.NonEmpty (Bag (TcTyVar, TcType))
-- ^ a stack of (CycleBreakerTv, original family applications) lists
-- first element in the stack corresponds to current implication;
-- later elements correspond to outer implications
@@ -323,6 +323,7 @@ data InertSet
, inert_givens :: InertCans
-- A subset of inert_cans, containing only Givens
-- Used to initialise inert_cans when recursing inside implications
+ -- See `resetInertCans`
, inert_cycle_breakers :: CycleBreakerVarStack
@@ -378,13 +379,21 @@ emptyInertSet :: TcLevel -> InertSet
emptyInertSet given_eq_lvl
= IS { inert_cans = empty_cans
, inert_givens = empty_cans
- , inert_cycle_breakers = emptyBag :| []
+ , inert_cycle_breakers = emptyBag NE.:| []
, inert_famapp_cache = emptyFunEqs
, inert_solved_dicts = emptyDictMap
, inert_safehask = emptyDictMap }
where
empty_cans = emptyInertCans given_eq_lvl
+
+resetInertCans :: InertSet -> InertSet
+-- Reset the `inert_cans` to the saved `inert_givens :: InertCans`
+-- In effect, this just purges all Wanteds from the InertSet
+resetInertCans inerts@(IS { inert_givens = saved_givens })
+ = inerts { inert_cans = saved_givens }
+
+
{- Note [Solved dictionaries]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
When we apply a top-level instance declaration, we add the "solved"
@@ -1913,8 +1922,9 @@ prohibitedSuperClassSolve given_loc wanted_loc
-- | Push a fresh environment onto the cycle-breaker var stack. Useful
-- when entering a nested implication.
-pushCycleBreakerVarStack :: CycleBreakerVarStack -> CycleBreakerVarStack
-pushCycleBreakerVarStack = (emptyBag <|)
+pushCycleBreakerVarStack :: InertSet -> InertSet
+pushCycleBreakerVarStack inerts@(IS { inert_cycle_breakers = cbs })
+ = inerts { inert_cycle_breakers = emptyBag NE.<| cbs }
-- | Add a new cycle-breaker binding to the top environment on the stack.
addCycleBreakerBindings :: Bag (TcTyVar, Type) -- ^ (cbv,expansion) pairs
@@ -1923,14 +1933,14 @@ addCycleBreakerBindings prs ics
= assertPpr (all (isCycleBreakerTyVar . fst) prs) (ppr prs) $
ics { inert_cycle_breakers = add_to (inert_cycle_breakers ics) }
where
- add_to (top_env :| rest_envs) = (prs `unionBags` top_env) :| rest_envs
+ add_to (top_env NE.:| rest_envs) = (prs `unionBags` top_env) NE.:| rest_envs
-- | Perform a monadic operation on all pairs in the top environment
-- in the stack.
forAllCycleBreakerBindings_ :: Monad m
=> CycleBreakerVarStack
-> (TcTyVar -> TcType -> m ()) -> m ()
-forAllCycleBreakerBindings_ (top_env :| _rest_envs) action
+forAllCycleBreakerBindings_ (top_env NE.:| _rest_envs) action
= forM_ top_env (uncurry action)
{-# INLINABLE forAllCycleBreakerBindings_ #-} -- to allow SPECIALISE later
=====================================
compiler/GHC/Tc/Solver/Monad.hs
=====================================
@@ -1177,14 +1177,13 @@ nestImplicTcS ev_binds_var inner_tclvl (TcS thing_inside)
= TcS $ \ env@(TcSEnv { tcs_inerts = old_inert_var }) ->
do { inerts <- TcM.readTcRef old_inert_var
- -- Initialise the inert_cans from the inert_givens of the parent
- -- so that the child is not polluted with the parent's inert Wanteds
+ -- resetInertcans: initialise the inert_cans from the inert_givens of the
+ -- parent so that the child is not polluted with the parent's inert Wanteds
-- See Note [trySolveImplication] in GHC.Tc.Solver.Solve
-- All other InertSet fields are inherited
- ; let nest_inert = inerts { inert_cycle_breakers = pushCycleBreakerVarStack
- (inert_cycle_breakers inerts)
- , inert_cans = (inert_givens inerts)
- { inert_given_eqs = False } }
+ ; let nest_inert = pushCycleBreakerVarStack $
+ resetInertCans $
+ inerts
; new_inert_var <- TcM.newTcRef nest_inert
; new_wl_var <- TcM.newTcRef emptyWorkList
; let nest_env = env { tcs_ev_binds = ev_binds_var
@@ -1203,6 +1202,26 @@ nestImplicTcS ev_binds_var inner_tclvl (TcS thing_inside)
#endif
; return res }
+nestFunDepsTcS :: TcS a -> TcS (Bool, a)
+nestFunDepsTcS (TcS thing_inside)
+ = reportUnifications $
+ TcS $ \ env@(TcSEnv { tcs_inerts = inerts_var }) ->
+ TcM.pushTcLevelM_ $
+ -- pushTcLevelTcM: increase the level so that unification variables
+ -- allocated by the fundep-creation itself don't count as useful unifications
+ do { inerts <- TcM.readTcRef inerts_var
+ ; let nest_inerts = resetInertCans inerts
+ -- resetInertCasns: like nestImplicTcS
+ ; new_inert_var <- TcM.newTcRef nest_inerts
+ ; new_wl_var <- TcM.newTcRef emptyWorkList
+ ; let nest_env = env { tcs_inerts = new_inert_var
+ , tcs_worklist = new_wl_var }
+
+ ; TcM.traceTc "nestFunDepsTcS {" empty
+ ; res <- thing_inside nest_env
+ ; TcM.traceTc "nestFunDepsTcS }" empty
+ ; return res }
+
nestTcS :: TcS a -> TcS a
-- Use the current untouchables, augmenting the current
-- evidence bindings, and solved dictionaries
@@ -1262,24 +1281,6 @@ tryTcS (TcS thing_inside)
; return True } }
-nestFunDepsTcS :: TcS a -> TcS (Bool, a)
-nestFunDepsTcS (TcS thing_inside)
- = reportUnifications $
- TcS $ \ env@(TcSEnv { tcs_inerts = inerts_var }) ->
- TcM.pushTcLevelM_ $
- -- pushTcLevelTcM: increase the level so that unification variables
- -- allocated by the fundep-creation itself don't count as useful unifications
- do { inerts <- TcM.readTcRef inerts_var
- ; new_inert_var <- TcM.newTcRef inerts
- ; new_wl_var <- TcM.newTcRef emptyWorkList
- ; let nest_env = env { tcs_inerts = new_inert_var
- , tcs_worklist = new_wl_var }
-
- ; TcM.traceTc "nestFunDepsTcS {" empty
- ; res <- thing_inside nest_env
- ; TcM.traceTc "nestFunDepsTcS }" empty
- ; return res }
-
updateInertsWith :: InertSet -> InertSet -> InertSet
-- Update the current inert set with bits from a nested solve,
-- that finished with a new inert set
=====================================
compiler/GHC/Utils/Outputable.hs
=====================================
@@ -528,8 +528,10 @@ pprDeeperList f ds
| null ds = f []
| otherwise = SDoc work
where
- work ctx@SDC{ sdocStyle=PprUser {} }
+ work ctx@SDC{ sdocStyle=PprUser _ (PartWay {}) _ }
= let -- Only do this depth-limitation in User style
+ -- when PartWay is on. Why not for DefaultDepth?
+ -- I have no idea; seems like a bug to me.
go _ [] = []
go i (d:ds) | i >= default_depth = [text "...."]
| otherwise = d : go (i+1) ds
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/58d6142b4d86d4b6e157acdbf3cc685…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/58d6142b4d86d4b6e157acdbf3cc685…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/andreask/linker_fix] 29 commits: refactor: Modify Data.List.sortOn to use (>) instead of compare. (#26184)
by Andreas Klebinger (@AndreasK) 14 Aug '25
by Andreas Klebinger (@AndreasK) 14 Aug '25
14 Aug '25
Andreas Klebinger pushed to branch wip/andreask/linker_fix at Glasgow Haskell Compiler / GHC
Commits:
1f9e4f54 by Stephen Morgan at 2025-08-03T15:14:08+10:00
refactor: Modify Data.List.sortOn to use (>) instead of compare. (#26184)
This lets a more efficient (>) operation be used if one exists.
This is technically a breaking change for malformed Ord instances, where
x > y is not equivalent to compare x y == GT.
Discussed by the CLC in issue #332: https://github.com/haskell/core-libraries-committee/issues/332
- - - - -
4f6bc9cf by fendor at 2025-08-04T17:50:06-04:00
Revert "base: Expose Backtraces constructor and fields"
This reverts commit 17db44c5b32fff82ea988fa4f1a233d1a27bdf57.
- - - - -
bcdec657 by Zubin Duggal at 2025-08-05T10:37:29+05:30
compiler: Export a version of `newNameCache` that is not prone to footguns.
`newNameCache` must be initialized with both a non-"reserved" unique tag, as well
as a list of known key names. Failing to do so results in hard to debug unique conflicts.
It is difficult for API users to tell which unique tags are safe to use. So instead of leaving
this up to the user to decide, we now export a version of `newNameCache` which uses a guaranteed
non-reserved unique tag. In fact, this is now the way the unique tag is initialized for all invocations
of the compiler.
The original version of `newNameCache` is now exported as `newNameCache'` for advanced users.
We also deprecate `initNameCache` as it is also prone to footguns and is completely subsumed in
functionality by `newNameCache` and `newNameCache'`.
Fixes #26135 and #26055
- - - - -
57d3b4a8 by Andrew Lelechenko at 2025-08-05T18:36:31-04:00
hadrian: bump Stackage snapshot to LTS 24.2 / GHC 9.10.2
In line with #25693 we should use GHC 9.10 as a boot compiler,
while Hadrian stack.yaml was stuck on GHC 9.6.
- - - - -
c2a78cea by Peng Fan at 2025-08-05T18:37:27-04:00
NCG/LA64: implement atomic write with finer-grained DBAR hints
Signed-off-by: Peng Fan <fanpeng(a)loongson.cn>
- - - - -
95231c8e by Teo Camarasu at 2025-08-06T08:35:58-04:00
CODEOWNERS: add CLC as codeowner of base
We also remove hvr, since I think he is no longer active
- - - - -
77df0ded by Andrew Lelechenko at 2025-08-06T08:36:39-04:00
Bump submodule text to 2.1.3
- - - - -
8af260d0 by Nikolaos Chatzikonstantinou at 2025-08-06T08:37:23-04:00
docs: fix internal import in getopt examples
This external-facing doc example shouldn't mention GHC internals when
using 'fromMaybe'.
- - - - -
69cc16ca by Marc Scholten at 2025-08-06T15:51:28-04:00
README: Add note on ghc.nix
- - - - -
93a2f450 by Daniel Díaz at 2025-08-06T15:52:14-04:00
Link to the "Strict Bindings" docs from the linear types docs
Strict Bidings are relevant for the kinds of multiplicity annotations
linear lets support.
- - - - -
246b7853 by Matthew Pickering at 2025-08-07T06:58:30-04:00
level imports: Check the level of exported identifiers
The level imports specification states that exported identifiers have to
be at level 0. This patch adds the requird level checks that all
explicitly mentioned identifiers occur at level 0.
For implicit export specifications (T(..) and module B), only level 0
identifiers are selected for re-export.
ghc-proposal: https://github.com/ghc-proposals/ghc-proposals/pull/705
Fixes #26090
- - - - -
358bc4fc by fendor at 2025-08-07T06:59:12-04:00
Bump GHC on darwin CI to 9.10.1
- - - - -
1903ae35 by Matthew Pickering at 2025-08-07T12:21:10+01:00
ipe: Place strings and metadata into specific .ipe section
By placing the .ipe metadata into a specific section it can be stripped
from the final binary if desired.
```
objcopy --remove-section .ipe <binary>
upx <binary>
```
Towards #21766
- - - - -
c80dd91c by Matthew Pickering at 2025-08-07T12:22:42+01:00
ipe: Place magic word at the start of entries in the .ipe section
The magic word "IPE\nIPE\n" is placed at the start of .ipe sections,
then if the section is stripped, we can check whether the section starts
with the magic word or not to determine whether there is metadata
present or not.
Towards #21766
- - - - -
cab42666 by Matthew Pickering at 2025-08-07T12:22:42+01:00
ipe: Use stable IDs for IPE entries
IPEs have historically been indexed and reported by their address.
This makes it impossible to compare profiles between runs, since the
addresses may change (due to ASLR) and also makes it tricky to separate
out the IPE map from the binary.
This small patch adds a stable identifier for each IPE entry.
The stable identifier is a single 64 bit word. The high-bits are a
per-module identifier and the low bits identify which entry in each
module.
1. When a node is added into the IPE buffer it is assigned a unique
identifier from an incrementing global counter.
2. Each entry already has an index by it's position in the
`IpeBufferListNode`.
The two are combined together by the `IPE_ENTRY_KEY` macro.
Info table profiling uses the stable identifier rather than the address
of the info table.
The benefits of this change are:
* Profiles from different runs can be easily compared
* The metadata can be extracted from the binary (via the eventlog for
example) and then stripped from the executable.
Fixes #21766
- - - - -
2860a9a5 by Simon Peyton Jones at 2025-08-07T20:29:18-04:00
In TcSShortCut, typechecker plugins should get empty Givens
Solving in TcShortCut mode means /ignoring the Givens/. So we
should not pass them to typechecker plugins!
Fixes #26258.
This is a fixup to the earlier MR:
commit 1bd12371feacc52394a0e660ef9349f9e8ee1c06
Author: Simon Peyton Jones <simon.peytonjones(a)gmail.com>
Date: Mon Jul 21 10:04:49 2025 +0100
Improve treatment of SPECIALISE pragmas -- again!
- - - - -
2157db2d by sterni at 2025-08-08T15:32:39-04:00
hadrian: enable terminfo if --with-curses-* flags are given
The GHC make build system used to support WITH_TERMINFO in ghc.mk which
allowed controlling whether to build GHC with terminfo or not. hadrian
has replaced this with a system where this is effectively controlled by
the cross-compiling setting (the default WITH_TERMINFO value was bassed
on CrossCompiling, iirc).
This behavior is undesireable in some cases and there is not really a
good way to work around it. Especially for downstream packagers,
modifying this via UserSettings is not really feasible since such a
source file has to be kept in sync with Settings/Default.hs manually
since it can't import Settings.Default or any predefined Flavour
definitions.
To avoid having to add a new setting to cfg/system.config and/or a new
configure flag (though I'm happy to implement both if required), I've
chosen to take --with-curses-* being set explicitly as an indication
that the user wants to have terminfo enabled. This would work for
Nixpkgs which sets these flags [1] as well as haskell.nix [2] (which
goes to some extreme measures [3] [4] to force terminfo in all scenarios).
In general, I'm an advocate for making the GHC build be the same for
native and cross insofar it is possible since it makes packaging GHC and
Haskell related things while still supporting cross much less
compilicated. A more minimal GHC with reduced dependencies should
probably be a specific flavor, not the default.
Partially addresses #26288 by forcing terminfo to be built if the user
explicitly passes configure flags related to it. However, it isn't built
by default when cross-compiling yet nor is there an explicit way to
control the package being built.
[1]: https://github.com/NixOS/nixpkgs/blob/3a7266fcefcb9ce353df49ba3f292d0644376…
[2]: https://github.com/input-output-hk/haskell.nix/blob/6eaafcdf04bab7be745d1aa…
[3]: https://github.com/input-output-hk/haskell.nix/blob/6eaafcdf04bab7be745d1aa…
[4]: https://github.com/input-output-hk/haskell.nix/blob/6eaafcdf04bab7be745d1aa…
- - - - -
b3c31488 by David Feuer at 2025-08-08T15:33:21-04:00
Add default QuasiQuoters
Add `defaultQuasiQuoter` and `namedDefaultQuasiQuoter` to make it easier
to write `QuasiQuoters` that give helpful error messages when they're
used in inappropriate contexts.
Closes #24434.
- - - - -
03555ed8 by Sylvain Henry at 2025-08-10T22:20:57-04:00
Handle non-fractional CmmFloats in Cmm's CBE (#26229)
Since f8d9d016305be355f518c141f6c6d4826f2de9a2, toRational for Float and
Double converts float's infinity and NaN into Rational's infinity and
NaN (respectively 1%0 and 0%0).
Cmm CommonBlockEliminator hashing function needs to take these values
into account as they can appear as literals now. See added testcase.
- - - - -
6c956af3 by J. Ryan Stinnett at 2025-08-10T22:21:42-04:00
Fix extensions list in `DoAndIfThenElse` docs
- - - - -
6dc420b1 by J. Ryan Stinnett at 2025-08-10T22:21:42-04:00
Document status of `RelaxedPolyRec` extension
This adds a brief extension page explaining the status of the
`RelaxedPolyRec` extension. The behaviour of this mode is already
explained elsewhere, so this page is mainly for completeness so that
various lists of extensions have somewhere to point to for this flag.
Fixes #18630
- - - - -
18036d52 by Simon Peyton Jones at 2025-08-11T11:31:20-04:00
Take more care in zonkEqTypes on AppTy/AppTy
This patch fixes #26256.
See Note [zonkEqTypes and the PKTI] in GHC.Tc.Solver.Equality
- - - - -
c8d76a29 by Zubin Duggal at 2025-08-11T11:32:02-04:00
ci: upgrade bootstrap compiler on windows to 9.10.1
- - - - -
34fc50c1 by Ben Gamari at 2025-08-11T13:36:25-04:00
Kill IOPort#
This type is unnecessary, having been superceded by `MVar` and a rework
of WinIO's blocking logic.
See #20947.
See https://github.com/haskell/core-libraries-committee/issues/213.
- - - - -
56b32c5a by sheaf at 2025-08-12T10:00:19-04:00
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.
For example, we now are properly able to prove the subtyping relationship
((∀ a. a->a) -> Int) -> Bool <= β[tau] Bool
for an unfilled metavariable β. In this case (with an AppTy on the right),
we used to fall back to unification. No longer: now, given that the LHS
is a FunTy and that the RHS is a deep rho type (does not need any instantiation),
we try to make the RHS into a FunTy, viz.
β := (->) γ
We can then continue using covariance & contravariance of the function
arrow, which allows us to prove the subtyping relationship, instead of
trying to unify which would cause us to error out with:
Couldn't match expected type ‘β’ with actual type ‘(->) ((∀ a. a -> a) -> Int)
See Note [FunTy vs non-FunTy case in tc_sub_type_deep] in GHC.Tc.Utils.Unify.
The other main improvement in this patch concerns type inference.
The main subsumption logic happens (before & after this patch) in
GHC.Tc.Gen.App.checkResultTy. However, before this patch, all of the
DeepSubsumption logic only kicked in in 'check' mode, not in 'infer' mode.
This patch adds deep instantiation in the 'infer' mode of checkResultTy
when we are doing deep subsumption, which allows us to accept programs
such as:
f :: Int -> (forall a. a->a)
g :: Int -> Bool -> Bool
test1 b =
case b of
True -> f
False -> g
test2 b =
case b of
True -> g
False -> f
See Note [Deeply instantiate in checkResultTy when inferring].
Finally, we add representation-polymorphism checks to ensure that the
lambda abstractions we introduce when doing subsumption obey the
representation polymorphism invariants of Note [Representation polymorphism invariants]
in GHC.Core. See Note [FunTy vs FunTy case in tc_sub_type_deep].
This is accompanied by a courtesy change to `(<.>) :: HsWrapper -> HsWrapper -> HsWrapper`,
adding the equation:
WpCast c1 <.> WpCast c2 = WpCast (c1 `mkTransCo` c2)
This is useful because mkWpFun does not introduce an eta-expansion when
both of the argument & result wrappers are casts; so this change allows
us to avoid introducing lambda abstractions when casts suffice.
Fixes #26225
- - - - -
d175aff8 by Sylvain Henry at 2025-08-12T10:01:31-04:00
Add regression test for #18619
- - - - -
a3983a26 by Sylvain Henry at 2025-08-12T10:02:20-04:00
RTS: remove some TSAN annotations (#20464)
Use RELAXED_LOAD_ALWAYS macro instead.
- - - - -
0434af81 by Ben Gamari at 2025-08-12T10:03:02-04:00
Bump time submodule to 1.15
Also required bumps of Cabal, directory, and hpc.
- - - - -
b6cf4866 by Andreas Klebinger at 2025-08-14T12:34:30+02:00
rts: LoadArchive/LoadObj - refactor object verification.
Fixes #26231.
We now consistently call `verifyAndInitOc` to check for valid object code.
Allowing us to replace the somewhat adhoc magic number checking in
loadArchive with the platform specific verification logic.
On windows this adds loadArchive support for
AArch64/32bit COFF bigobj files.
- - - - -
151 changed files:
- .gitlab/darwin/toolchain.nix
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- CODEOWNERS
- README.md
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/PrimOps/Ids.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/CommonBlockElim.hs
- compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- compiler/GHC/CmmToAsm/PPC/Ppr.hs
- compiler/GHC/CmmToAsm/Ppr.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/StgToCmm/InfoTableProv.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/Name/Cache.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/ghc.cabal.in
- docs/users_guide/conf.py
- docs/users_guide/debug-info.rst
- docs/users_guide/expected-undocumented-flags.txt
- docs/users_guide/exts/doandifthenelse.rst
- docs/users_guide/exts/linear_types.rst
- + docs/users_guide/exts/relaxed_poly_rec.rst
- docs/users_guide/exts/strict.rst
- docs/users_guide/exts/types.rst
- ghc/ghc-bin.cabal.in
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Packages.hs
- hadrian/stack.yaml
- hadrian/stack.yaml.lock
- libraries/Cabal
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- libraries/base/src/Control/Exception/Backtrace.hs
- libraries/base/src/Data/List/NonEmpty.hs
- libraries/base/src/GHC/Exts.hs
- − libraries/base/src/GHC/IOPort.hs
- libraries/base/src/System/Console/GetOpt.hs
- libraries/directory
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs
- libraries/ghc-internal/src/GHC/Internal/Event/Windows.hsc
- libraries/ghc-internal/src/GHC/Internal/Event/Windows/Thread.hs
- libraries/ghc-internal/src/GHC/Internal/Exts.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Buffer.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc
- − libraries/ghc-internal/src/GHC/Internal/IOPort.hs
- libraries/ghc-internal/src/GHC/Internal/Prim/PtrEq.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Quote.hs
- libraries/ghc-prim/changelog.md
- libraries/hpc
- libraries/template-haskell/Language/Haskell/TH/Quote.hs
- libraries/template-haskell/changelog.md
- libraries/text
- libraries/time
- libraries/unix
- rts/IPE.c
- rts/Linker.c
- rts/LinkerInternals.h
- rts/Prelude.h
- rts/PrimOps.cmm
- rts/ProfHeap.c
- rts/RtsSymbols.c
- rts/eventlog/EventLog.c
- rts/external-symbols.list.in
- rts/include/rts/IPE.h
- rts/include/stg/MiscClosures.h
- rts/include/stg/SMP.h
- rts/linker/LoadArchive.c
- rts/linker/MachO.c
- rts/linker/MachO.h
- rts/linker/PEi386.c
- rts/posix/ticker/Pthread.c
- rts/posix/ticker/TimerFd.c
- rts/win32/AsyncWinIO.c
- rts/win32/libHSghc-internal.def
- testsuite/tests/corelint/LintEtaExpand.stderr
- testsuite/tests/hiefile/should_run/TestUtils.hs
- testsuite/tests/indexed-types/should_fail/T5439.stderr
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- testsuite/tests/interface-stability/ghc-prim-exports.stdout
- testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- + testsuite/tests/numeric/should_compile/T26229.hs
- testsuite/tests/numeric/should_compile/all.T
- + testsuite/tests/numeric/should_run/T18619.hs
- + testsuite/tests/numeric/should_run/T18619.stderr
- testsuite/tests/numeric/should_run/all.T
- testsuite/tests/partial-sigs/should_compile/T10403.stderr
- + testsuite/tests/partial-sigs/should_compile/T26256.hs
- + testsuite/tests/partial-sigs/should_compile/T26256.stderr
- testsuite/tests/partial-sigs/should_compile/all.T
- testsuite/tests/partial-sigs/should_fail/T10615.stderr
- testsuite/tests/primops/should_run/UnliftedIOPort.hs
- testsuite/tests/primops/should_run/all.T
- + testsuite/tests/rep-poly/NoEtaRequired.hs
- testsuite/tests/rep-poly/T21906.stderr
- testsuite/tests/rep-poly/all.T
- testsuite/tests/rts/ipe/ipeMap.c
- testsuite/tests/rts/ipe/ipe_lib.c
- + testsuite/tests/splice-imports/DodgyLevelExport.hs
- + testsuite/tests/splice-imports/DodgyLevelExport.stderr
- + testsuite/tests/splice-imports/DodgyLevelExportA.hs
- + testsuite/tests/splice-imports/LevelImportExports.hs
- + testsuite/tests/splice-imports/LevelImportExports.stdout
- + testsuite/tests/splice-imports/LevelImportExportsA.hs
- testsuite/tests/splice-imports/Makefile
- + testsuite/tests/splice-imports/ModuleExport.hs
- + testsuite/tests/splice-imports/ModuleExport.stderr
- + testsuite/tests/splice-imports/ModuleExportA.hs
- + testsuite/tests/splice-imports/ModuleExportB.hs
- + testsuite/tests/splice-imports/T26090.hs
- + testsuite/tests/splice-imports/T26090.stderr
- + testsuite/tests/splice-imports/T26090A.hs
- testsuite/tests/splice-imports/all.T
- + testsuite/tests/typecheck/should_compile/T26225.hs
- + testsuite/tests/typecheck/should_compile/T26225b.hs
- + testsuite/tests/typecheck/should_compile/T26256a.hs
- testsuite/tests/typecheck/should_compile/all.T
- − testsuite/tests/typecheck/should_fail/T12563.stderr
- testsuite/tests/typecheck/should_fail/T14618.stderr
- testsuite/tests/typecheck/should_fail/T6022.stderr
- testsuite/tests/typecheck/should_fail/T8883.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail140.stderr
- utils/genprimopcode/Main.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/92bb42beca1722e7f42560552f8760…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/92bb42beca1722e7f42560552f8760…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/ubxsumtag] Use slots smaller than word as tag for smaller unboxed sums
by Luite Stegeman (@luite) 14 Aug '25
by Luite Stegeman (@luite) 14 Aug '25
14 Aug '25
Luite Stegeman pushed to branch wip/ubxsumtag at Glasgow Haskell Compiler / GHC
Commits:
5c2d26bb by Luite Stegeman at 2025-08-14T12:14:08+02:00
Use slots smaller than word as tag for smaller unboxed sums
This packs unboxed sums more efficiently by allowing
Word8, Word16 and Word32 for the tag field if the number of
constructors is small enough
- - - - -
10 changed files:
- compiler/GHC/Cmm/Utils.hs
- compiler/GHC/Stg/Unarise.hs
- compiler/GHC/Types/RepType.hs
- testsuite/tests/codeGen/should_compile/T25166.stdout → testsuite/tests/codeGen/should_compile/T25166.stdout-ws-32
- + testsuite/tests/codeGen/should_compile/T25166.stdout-ws-64
- + testsuite/tests/unboxedsums/UbxSumUnpackedSize.hs
- + testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout
- + testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout-ws-32
- testsuite/tests/unboxedsums/all.T
- testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs
Changes:
=====================================
compiler/GHC/Cmm/Utils.hs
=====================================
@@ -115,6 +115,9 @@ slotCmmType platform = \case
PtrUnliftedSlot -> gcWord platform
PtrLiftedSlot -> gcWord platform
WordSlot -> bWord platform
+ Word8Slot -> b8
+ Word16Slot -> b16
+ Word32Slot -> b32
Word64Slot -> b64
FloatSlot -> f32
DoubleSlot -> f64
=====================================
compiler/GHC/Stg/Unarise.hs
=====================================
@@ -404,7 +404,6 @@ import GHC.Stg.Syntax
import GHC.Stg.Utils
import GHC.Stg.Make
import GHC.Core.Type
-import GHC.Builtin.Types.Prim (intPrimTy)
import GHC.Builtin.Types
import GHC.Types.Unique.Supply
import GHC.Types.Unique
@@ -681,15 +680,15 @@ elimCase rho args bndr (MultiValAlt _) [GenStgAlt{ alt_con = _
elimCase rho args@(tag_arg : real_args) bndr (MultiValAlt _) alts
| isUnboxedSumBndr bndr
- = do tag_bndr <- mkId (mkFastString "tag") tagTy
+ = do tag_bndr <- mkId (mkFastString "tag") (tagTyArg tag_arg)
-- this won't be used but we need a binder anyway
let rho1 = extendRho rho bndr (MultiVal args)
scrut' = case tag_arg of
StgVarArg v -> StgApp v []
StgLitArg l -> StgLit l
-
- alts' <- unariseSumAlts rho1 real_args alts
- return (StgCase scrut' tag_bndr tagAltTy alts')
+ alt_ty = (tagAltTyArg tag_arg)
+ alts' <- unariseSumAlts rho1 alt_ty real_args alts
+ return (StgCase scrut' tag_bndr alt_ty alts')
elimCase _ args bndr alt_ty alts
= pprPanic "elimCase - unhandled case"
@@ -732,8 +731,9 @@ unariseAlts rho (MultiValAlt _) bndr [GenStgAlt{ alt_con = DEFAULT
unariseAlts rho (MultiValAlt _) bndr alts
| isUnboxedSumBndr bndr
= do (rho_sum_bndrs, scrt_bndrs@(tag_bndr : real_bndrs)) <- unariseConArgBinder rho bndr
- alts' <- unariseSumAlts rho_sum_bndrs (map StgVarArg real_bndrs) alts
- let inner_case = StgCase (StgApp tag_bndr []) tag_bndr tagAltTy alts'
+ let alt_ty = tagAltTy tag_bndr
+ alts' <- unariseSumAlts rho_sum_bndrs alt_ty (map StgVarArg real_bndrs) alts
+ let inner_case = StgCase (StgApp tag_bndr []) tag_bndr alt_ty alts'
return [GenStgAlt{ alt_con = DataAlt (tupleDataCon Unboxed (length scrt_bndrs))
, alt_bndrs = scrt_bndrs
, alt_rhs = inner_case
@@ -753,21 +753,23 @@ unariseAlt rho alt@GenStgAlt{alt_con=_,alt_bndrs=xs,alt_rhs=e}
-- | Make alternatives that match on the tag of a sum
-- (i.e. generate LitAlts for the tag)
unariseSumAlts :: UnariseEnv
+ -> AltType
-> [StgArg] -- sum components _excluding_ the tag bit.
-> [StgAlt] -- original alternative with sum LHS
-> UniqSM [StgAlt]
-unariseSumAlts env args alts
- = do alts' <- mapM (unariseSumAlt env args) alts
+unariseSumAlts env tag_slot args alts
+ = do alts' <- mapM (unariseSumAlt env tag_slot args) alts
return (mkDefaultLitAlt alts')
unariseSumAlt :: UnariseEnv
+ -> AltType
-> [StgArg] -- sum components _excluding_ the tag bit.
-> StgAlt -- original alternative with sum LHS
-> UniqSM StgAlt
-unariseSumAlt rho _ GenStgAlt{alt_con=DEFAULT,alt_bndrs=_,alt_rhs=e}
+unariseSumAlt rho _ _ GenStgAlt{alt_con=DEFAULT,alt_bndrs=_,alt_rhs=e}
= GenStgAlt DEFAULT mempty <$> unariseExpr rho e
-unariseSumAlt rho args alt@GenStgAlt{ alt_con = DataAlt sumCon
+unariseSumAlt rho tag_slot args alt@GenStgAlt{ alt_con = DataAlt sumCon
, alt_bndrs = bs
, alt_rhs = e
}
@@ -776,10 +778,19 @@ unariseSumAlt rho args alt@GenStgAlt{ alt_con = DataAlt sumCon
[b] -> mapSumIdBinders b args e rho
-- Sums must have one binder
_ -> pprPanic "unariseSumAlt2" (ppr args $$ pprPanicAlt alt)
- let lit_case = LitAlt (LitNumber LitNumInt (fromIntegral (dataConTag sumCon)))
+ let num_ty =
+ case tag_slot of
+ PrimAlt Int8Rep -> LitNumInt8
+ PrimAlt Word8Rep -> LitNumWord8
+ PrimAlt Int16Rep -> LitNumInt16
+ PrimAlt Word16Rep -> LitNumWord16
+ PrimAlt Int32Rep -> LitNumInt32
+ PrimAlt Word32Rep -> LitNumWord32
+ _ -> LitNumInt
+ lit_case = LitAlt (LitNumber num_ty (fromIntegral (dataConTag sumCon)))
GenStgAlt lit_case mempty <$> unariseExpr rho' e'
-unariseSumAlt _ scrt alt
+unariseSumAlt _ _ scrt alt
= pprPanic "unariseSumAlt3" (ppr scrt $$ pprPanicAlt alt)
--------------------------------------------------------------------------------
@@ -865,12 +876,6 @@ mapSumIdBinders alt_bndr args rhs rho0
typed_id_args = map StgVarArg typed_ids
- -- pprTrace "mapSumIdBinders"
- -- (text "fld_reps" <+> ppr fld_reps $$
- -- text "id_args" <+> ppr id_arg_exprs $$
- -- text "rhs" <+> ppr rhs $$
- -- text "rhs_with_casts" <+> ppr rhs_with_casts
- -- ) $
if isMultiValBndr alt_bndr
then return (extendRho rho0 alt_bndr (MultiVal typed_id_args), rhs_with_casts rhs)
else assert (typed_id_args `lengthIs` 1) $
@@ -921,13 +926,19 @@ mkUbxSum
)
mkUbxSum dc ty_args args0 us
= let
- _ :| sum_slots = ubxSumRepType ty_args
+ tag_slot :| sum_slots = ubxSumRepType ty_args
-- drop tag slot
field_slots = (mapMaybe (repSlotTy . stgArgRep) args0)
tag = dataConTag dc
layout' = layoutUbxSum sum_slots field_slots
- tag_arg = StgLitArg (LitNumber LitNumInt (fromIntegral tag))
+ tag_arg =
+ case tag_slot of
+ Word8Slot -> StgLitArg (LitNumber LitNumWord8 (fromIntegral tag))
+ Word16Slot -> StgLitArg (LitNumber LitNumWord16 (fromIntegral tag))
+ Word32Slot -> StgLitArg (LitNumber LitNumWord32 (fromIntegral tag))
+ WordSlot -> StgLitArg (LitNumber LitNumWord (fromIntegral tag))
+ _ -> pprPanic "mkUbxSum: unexpected tag slot: " (ppr tag_slot)
arg_idxs = IM.fromList (zipEqual layout' args0)
((_idx,_idx_map,_us,wrapper),slot_args)
@@ -990,6 +1001,9 @@ ubxSumRubbishArg :: SlotTy -> StgArg
ubxSumRubbishArg PtrLiftedSlot = StgVarArg aBSENT_SUM_FIELD_ERROR_ID
ubxSumRubbishArg PtrUnliftedSlot = StgVarArg aBSENT_SUM_FIELD_ERROR_ID
ubxSumRubbishArg WordSlot = StgLitArg (LitNumber LitNumWord 0)
+ubxSumRubbishArg Word8Slot = StgLitArg (LitNumber LitNumWord8 0)
+ubxSumRubbishArg Word16Slot = StgLitArg (LitNumber LitNumWord16 0)
+ubxSumRubbishArg Word32Slot = StgLitArg (LitNumber LitNumWord32 0)
ubxSumRubbishArg Word64Slot = StgLitArg (LitNumber LitNumWord64 0)
ubxSumRubbishArg FloatSlot = StgLitArg (LitFloat 0)
ubxSumRubbishArg DoubleSlot = StgLitArg (LitDouble 0)
@@ -1166,11 +1180,18 @@ isUnboxedTupleBndr = isUnboxedTupleType . idType
mkTuple :: [StgArg] -> StgExpr
mkTuple args = StgConApp (tupleDataCon Unboxed (length args)) NoNumber args []
-tagAltTy :: AltType
-tagAltTy = PrimAlt IntRep
+tagAltTyArg :: StgArg -> AltType
+tagAltTyArg a
+ | [pr] <- typePrimRep (stgArgType a) = PrimAlt pr
+ | otherwise = pprPanic "tagAltTyArg" (ppr a)
+
+tagAltTy :: Id -> AltType
+tagAltTy i
+ | [pr] <- typePrimRep (idType i) = PrimAlt pr
+ | otherwise = pprPanic "tagAltTy" (ppr $ idType i)
-tagTy :: Type
-tagTy = intPrimTy
+tagTyArg :: StgArg -> Type
+tagTyArg x = stgArgType x
voidArg :: StgArg
voidArg = StgVarArg voidPrimId
=====================================
compiler/GHC/Types/RepType.hs
=====================================
@@ -197,12 +197,12 @@ type SortedSlotTys = [SlotTy]
-- of the list we have the slot for the tag.
ubxSumRepType :: [[PrimRep]] -> NonEmpty SlotTy
ubxSumRepType constrs0
- -- These first two cases never classify an actual unboxed sum, which always
+ -- This first case never classifies an actual unboxed sum, which always
-- has at least two disjuncts. But it could happen if a user writes, e.g.,
-- forall (a :: TYPE (SumRep [IntRep])). ...
-- which could never be instantiated. We still don't want to panic.
| constrs0 `lengthLessThan` 2
- = WordSlot :| []
+ = Word8Slot :| []
| otherwise
= let
@@ -230,8 +230,17 @@ ubxSumRepType constrs0
rep :: [PrimRep] -> SortedSlotTys
rep ty = sort (map primRepSlot ty)
- sumRep = WordSlot :| combine_alts (map rep constrs0)
- -- WordSlot: for the tag of the sum
+ -- constructors start at 1, pick an appropriate slot size for the tag
+ tag_slot | length constrs0 < 256 = Word8Slot
+ | length constrs0 < 65536 = Word16Slot
+ -- we use 2147483647 instead of 4294967296 to avoid
+ -- overflow when building a 32 bit GHC. Please fix the
+ -- overflow if you encounter a type with more than 2147483646
+ -- constructors and need the tag to be 32 bits.
+ | length constrs0 < 2147483647 = Word32Slot
+ | otherwise = WordSlot
+
+ sumRep = tag_slot :| combine_alts (map rep constrs0)
in
sumRep
@@ -275,10 +284,17 @@ layoutUbxSum sum_slots0 arg_slots0 =
-- - Float slots: Shared between floating point types.
--
-- - Void slots: Shared between void types. Not used in sums.
---
--- TODO(michalt): We should probably introduce `SlotTy`s for 8-/16-/32-bit
--- values, so that we can pack things more tightly.
-data SlotTy = PtrLiftedSlot | PtrUnliftedSlot | WordSlot | Word64Slot | FloatSlot | DoubleSlot | VecSlot Int PrimElemRep
+
+data SlotTy = PtrLiftedSlot
+ | PtrUnliftedSlot
+ | Word8Slot
+ | Word16Slot
+ | Word32Slot
+ | WordSlot -- the order is important, later ones are bigger. this works for word sizes 32 and 64 bit (XXX fix this)
+ | Word64Slot
+ | FloatSlot
+ | DoubleSlot
+ | VecSlot Int PrimElemRep
deriving (Eq, Ord)
-- Constructor order is important! If slot A could fit into slot B
-- then slot A must occur first. E.g. FloatSlot before DoubleSlot
@@ -291,6 +307,9 @@ instance Outputable SlotTy where
ppr PtrUnliftedSlot = text "PtrUnliftedSlot"
ppr Word64Slot = text "Word64Slot"
ppr WordSlot = text "WordSlot"
+ ppr Word32Slot = text "Word32Slot"
+ ppr Word16Slot = text "Word16Slot"
+ ppr Word8Slot = text "Word8Slot"
ppr DoubleSlot = text "DoubleSlot"
ppr FloatSlot = text "FloatSlot"
ppr (VecSlot n e) = text "VecSlot" <+> ppr n <+> ppr e
@@ -307,14 +326,14 @@ primRepSlot (BoxedRep mlev) = case mlev of
Just Lifted -> PtrLiftedSlot
Just Unlifted -> PtrUnliftedSlot
primRepSlot IntRep = WordSlot
-primRepSlot Int8Rep = WordSlot
-primRepSlot Int16Rep = WordSlot
-primRepSlot Int32Rep = WordSlot
+primRepSlot Int8Rep = Word8Slot
+primRepSlot Int16Rep = Word16Slot
+primRepSlot Int32Rep = Word32Slot
primRepSlot Int64Rep = Word64Slot
primRepSlot WordRep = WordSlot
-primRepSlot Word8Rep = WordSlot
-primRepSlot Word16Rep = WordSlot
-primRepSlot Word32Rep = WordSlot
+primRepSlot Word8Rep = Word8Slot
+primRepSlot Word16Rep = Word16Slot
+primRepSlot Word32Rep = Word32Slot
primRepSlot Word64Rep = Word64Slot
primRepSlot AddrRep = WordSlot
primRepSlot FloatRep = FloatSlot
@@ -325,6 +344,9 @@ slotPrimRep :: SlotTy -> PrimRep
slotPrimRep PtrLiftedSlot = BoxedRep (Just Lifted)
slotPrimRep PtrUnliftedSlot = BoxedRep (Just Unlifted)
slotPrimRep Word64Slot = Word64Rep
+slotPrimRep Word32Slot = Word32Rep
+slotPrimRep Word16Slot = Word16Rep
+slotPrimRep Word8Slot = Word8Rep
slotPrimRep WordSlot = WordRep
slotPrimRep DoubleSlot = DoubleRep
slotPrimRep FloatSlot = FloatRep
@@ -349,11 +371,12 @@ fitsIn ty1 ty2
-- See Note [Casting slot arguments]
where
isWordSlot Word64Slot = True
+ isWordSlot Word32Slot = True
+ isWordSlot Word16Slot = True
+ isWordSlot Word8Slot = True
isWordSlot WordSlot = True
isWordSlot _ = False
-
-
{- **********************************************************************
* *
PrimRep
=====================================
testsuite/tests/codeGen/should_compile/T25166.stdout → testsuite/tests/codeGen/should_compile/T25166.stdout-ws-32
=====================================
@@ -2,5 +2,7 @@
Test.foo_closure:
const Test.D_con_info;
const GHC.Internal.Types.True_closure+2;
- const 2;
+ const 2 :: W8;
+ const 0 :: W16;
+ const 0 :: W8;
const 3;
=====================================
testsuite/tests/codeGen/should_compile/T25166.stdout-ws-64
=====================================
@@ -0,0 +1,9 @@
+[section ""data" . Test.foo_closure" {
+ Test.foo_closure:
+ const Test.D_con_info;
+ const GHC.Internal.Types.True_closure+2;
+ const 2 :: W8;
+ const 0 :: W32;
+ const 0 :: W16;
+ const 0 :: W8;
+ const 3;
=====================================
testsuite/tests/unboxedsums/UbxSumUnpackedSize.hs
=====================================
@@ -0,0 +1,250 @@
+module Main where
+
+import GHC.Exts.Heap.Closures
+import Control.Exception (evaluate)
+import Data.Word (Word32)
+
+-- this should get a Word8 tag
+data E1
+ = E1_1 | E1_2 | E1_3 | E1_4 | E1_5 | E1_6 | E1_7 | E1_8
+ | E1_9 | E1_10 | E1_11 | E1_12 | E1_13 | E1_14 | E1_15 | E1_16
+ | E1_17 | E1_18 | E1_19 | E1_20 | E1_21 | E1_22 | E1_23 | E1_24
+ | E1_25 | E1_26 | E1_27 | E1_28 | E1_29 | E1_30 | E1_31 | E1_32
+ | E1_33 | E1_34 | E1_35 | E1_36 | E1_37 | E1_38 | E1_39 | E1_40
+ | E1_41 | E1_42 | E1_43 | E1_44 | E1_45 | E1_46 | E1_47 | E1_48
+ | E1_49 | E1_50 | E1_51 | E1_52 | E1_53 | E1_54 | E1_55 | E1_56
+ | E1_57 | E1_58 | E1_59 | E1_60 | E1_61 | E1_62 | E1_63 | E1_64
+ | E1_65 | E1_66 | E1_67 | E1_68 | E1_69 | E1_70 | E1_71 | E1_72
+ | E1_73 | E1_74 | E1_75 | E1_76 | E1_77 | E1_78 | E1_79 | E1_80
+ | E1_81 | E1_82 | E1_83 | E1_84 | E1_85 | E1_86 | E1_87 | E1_88
+ | E1_89 | E1_90 | E1_91 | E1_92 | E1_93 | E1_94 | E1_95 | E1_96
+ | E1_97 | E1_98 | E1_99 | E1_100 | E1_101 | E1_102 | E1_103 | E1_104
+ | E1_105 | E1_106 | E1_107 | E1_108 | E1_109 | E1_110 | E1_111 | E1_112
+ | E1_113 | E1_114 | E1_115 | E1_116 | E1_117 | E1_118 | E1_119 | E1_120
+ | E1_121 | E1_122 | E1_123 | E1_124 | E1_125 | E1_126 | E1_127 | E1_128
+ | E1_129 | E1_130 | E1_131 | E1_132 | E1_133 | E1_134 | E1_135 | E1_136
+ | E1_137 | E1_138 | E1_139 | E1_140 | E1_141 | E1_142 | E1_143 | E1_144
+ | E1_145 | E1_146 | E1_147 | E1_148 | E1_149 | E1_150 | E1_151 | E1_152
+ | E1_153 | E1_154 | E1_155 | E1_156 | E1_157 | E1_158 | E1_159 | E1_160
+ | E1_161 | E1_162 | E1_163 | E1_164 | E1_165 | E1_166 | E1_167 | E1_168
+ | E1_169 | E1_170 | E1_171 | E1_172 | E1_173 | E1_174 | E1_175 | E1_176
+ | E1_177 | E1_178 | E1_179 | E1_180 | E1_181 | E1_182 | E1_183 | E1_184
+ | E1_185 | E1_186 | E1_187 | E1_188 | E1_189 | E1_190 | E1_191 | E1_192
+ | E1_193 | E1_194 | E1_195 | E1_196 | E1_197 | E1_198 | E1_199 | E1_200
+ | E1_201 | E1_202 | E1_203 | E1_204 | E1_205 | E1_206 | E1_207 | E1_208
+ | E1_209 | E1_210 | E1_211 | E1_212 | E1_213 | E1_214 | E1_215 | E1_216
+ | E1_217 | E1_218 | E1_219 | E1_220 | E1_221 | E1_222 | E1_223 | E1_224
+ | E1_225 | E1_226 | E1_227 | E1_228 | E1_229 | E1_230 | E1_231 | E1_232
+ | E1_233 | E1_234 | E1_235 | E1_236 | E1_237 | E1_238 | E1_239 | E1_240
+ | E1_241 | E1_242 | E1_243 | E1_244 | E1_245 | E1_246 | E1_247 | E1_248
+ | E1_249 | E1_250 | E1_251 | E1_252 | E1_253 | E1_254
+ deriving (Enum, Bounded, Show)
+
+-- this should get a Word8 tag
+data E2
+ = E2_1 | E2_2 | E2_3 | E2_4 | E2_5 | E2_6 | E2_7 | E2_8
+ | E2_9 | E2_10 | E2_11 | E2_12 | E2_13 | E2_14 | E2_15 | E2_16
+ | E2_17 | E2_18 | E2_19 | E2_20 | E2_21 | E2_22 | E2_23 | E2_24
+ | E2_25 | E2_26 | E2_27 | E2_28 | E2_29 | E2_30 | E2_31 | E2_32
+ | E2_33 | E2_34 | E2_35 | E2_36 | E2_37 | E2_38 | E2_39 | E2_40
+ | E2_41 | E2_42 | E2_43 | E2_44 | E2_45 | E2_46 | E2_47 | E2_48
+ | E2_49 | E2_50 | E2_51 | E2_52 | E2_53 | E2_54 | E2_55 | E2_56
+ | E2_57 | E2_58 | E2_59 | E2_60 | E2_61 | E2_62 | E2_63 | E2_64
+ | E2_65 | E2_66 | E2_67 | E2_68 | E2_69 | E2_70 | E2_71 | E2_72
+ | E2_73 | E2_74 | E2_75 | E2_76 | E2_77 | E2_78 | E2_79 | E2_80
+ | E2_81 | E2_82 | E2_83 | E2_84 | E2_85 | E2_86 | E2_87 | E2_88
+ | E2_89 | E2_90 | E2_91 | E2_92 | E2_93 | E2_94 | E2_95 | E2_96
+ | E2_97 | E2_98 | E2_99 | E2_100 | E2_101 | E2_102 | E2_103 | E2_104
+ | E2_105 | E2_106 | E2_107 | E2_108 | E2_109 | E2_110 | E2_111 | E2_112
+ | E2_113 | E2_114 | E2_115 | E2_116 | E2_117 | E2_118 | E2_119 | E2_120
+ | E2_121 | E2_122 | E2_123 | E2_124 | E2_125 | E2_126 | E2_127 | E2_128
+ | E2_129 | E2_130 | E2_131 | E2_132 | E2_133 | E2_134 | E2_135 | E2_136
+ | E2_137 | E2_138 | E2_139 | E2_140 | E2_141 | E2_142 | E2_143 | E2_144
+ | E2_145 | E2_146 | E2_147 | E2_148 | E2_149 | E2_150 | E2_151 | E2_152
+ | E2_153 | E2_154 | E2_155 | E2_156 | E2_157 | E2_158 | E2_159 | E2_160
+ | E2_161 | E2_162 | E2_163 | E2_164 | E2_165 | E2_166 | E2_167 | E2_168
+ | E2_169 | E2_170 | E2_171 | E2_172 | E2_173 | E2_174 | E2_175 | E2_176
+ | E2_177 | E2_178 | E2_179 | E2_180 | E2_181 | E2_182 | E2_183 | E2_184
+ | E2_185 | E2_186 | E2_187 | E2_188 | E2_189 | E2_190 | E2_191 | E2_192
+ | E2_193 | E2_194 | E2_195 | E2_196 | E2_197 | E2_198 | E2_199 | E2_200
+ | E2_201 | E2_202 | E2_203 | E2_204 | E2_205 | E2_206 | E2_207 | E2_208
+ | E2_209 | E2_210 | E2_211 | E2_212 | E2_213 | E2_214 | E2_215 | E2_216
+ | E2_217 | E2_218 | E2_219 | E2_220 | E2_221 | E2_222 | E2_223 | E2_224
+ | E2_225 | E2_226 | E2_227 | E2_228 | E2_229 | E2_230 | E2_231 | E2_232
+ | E2_233 | E2_234 | E2_235 | E2_236 | E2_237 | E2_238 | E2_239 | E2_240
+ | E2_241 | E2_242 | E2_243 | E2_244 | E2_245 | E2_246 | E2_247 | E2_248
+ | E2_249 | E2_250 | E2_251 | E2_252 | E2_253 | E2_254 | E2_255
+ deriving (Enum, Bounded, Show)
+
+-- this needs a Word16 tag
+data E3
+ = E3_1 | E3_2 | E3_3 | E3_4 | E3_5 | E3_6 | E3_7 | E3_8
+ | E3_9 | E3_10 | E3_11 | E3_12 | E3_13 | E3_14 | E3_15 | E3_16
+ | E3_17 | E3_18 | E3_19 | E3_20 | E3_21 | E3_22 | E3_23 | E3_24
+ | E3_25 | E3_26 | E3_27 | E3_28 | E3_29 | E3_30 | E3_31 | E3_32
+ | E3_33 | E3_34 | E3_35 | E3_36 | E3_37 | E3_38 | E3_39 | E3_40
+ | E3_41 | E3_42 | E3_43 | E3_44 | E3_45 | E3_46 | E3_47 | E3_48
+ | E3_49 | E3_50 | E3_51 | E3_52 | E3_53 | E3_54 | E3_55 | E3_56
+ | E3_57 | E3_58 | E3_59 | E3_60 | E3_61 | E3_62 | E3_63 | E3_64
+ | E3_65 | E3_66 | E3_67 | E3_68 | E3_69 | E3_70 | E3_71 | E3_72
+ | E3_73 | E3_74 | E3_75 | E3_76 | E3_77 | E3_78 | E3_79 | E3_80
+ | E3_81 | E3_82 | E3_83 | E3_84 | E3_85 | E3_86 | E3_87 | E3_88
+ | E3_89 | E3_90 | E3_91 | E3_92 | E3_93 | E3_94 | E3_95 | E3_96
+ | E3_97 | E3_98 | E3_99 | E3_100 | E3_101 | E3_102 | E3_103 | E3_104
+ | E3_105 | E3_106 | E3_107 | E3_108 | E3_109 | E3_110 | E3_111 | E3_112
+ | E3_113 | E3_114 | E3_115 | E3_116 | E3_117 | E3_118 | E3_119 | E3_120
+ | E3_121 | E3_122 | E3_123 | E3_124 | E3_125 | E3_126 | E3_127 | E3_128
+ | E3_129 | E3_130 | E3_131 | E3_132 | E3_133 | E3_134 | E3_135 | E3_136
+ | E3_137 | E3_138 | E3_139 | E3_140 | E3_141 | E3_142 | E3_143 | E3_144
+ | E3_145 | E3_146 | E3_147 | E3_148 | E3_149 | E3_150 | E3_151 | E3_152
+ | E3_153 | E3_154 | E3_155 | E3_156 | E3_157 | E3_158 | E3_159 | E3_160
+ | E3_161 | E3_162 | E3_163 | E3_164 | E3_165 | E3_166 | E3_167 | E3_168
+ | E3_169 | E3_170 | E3_171 | E3_172 | E3_173 | E3_174 | E3_175 | E3_176
+ | E3_177 | E3_178 | E3_179 | E3_180 | E3_181 | E3_182 | E3_183 | E3_184
+ | E3_185 | E3_186 | E3_187 | E3_188 | E3_189 | E3_190 | E3_191 | E3_192
+ | E3_193 | E3_194 | E3_195 | E3_196 | E3_197 | E3_198 | E3_199 | E3_200
+ | E3_201 | E3_202 | E3_203 | E3_204 | E3_205 | E3_206 | E3_207 | E3_208
+ | E3_209 | E3_210 | E3_211 | E3_212 | E3_213 | E3_214 | E3_215 | E3_216
+ | E3_217 | E3_218 | E3_219 | E3_220 | E3_221 | E3_222 | E3_223 | E3_224
+ | E3_225 | E3_226 | E3_227 | E3_228 | E3_229 | E3_230 | E3_231 | E3_232
+ | E3_233 | E3_234 | E3_235 | E3_236 | E3_237 | E3_238 | E3_239 | E3_240
+ | E3_241 | E3_242 | E3_243 | E3_244 | E3_245 | E3_246 | E3_247 | E3_248
+ | E3_249 | E3_250 | E3_251 | E3_252 | E3_253 | E3_254 | E3_255 | E3_256
+ deriving (Enum, Bounded, Show)
+
+data U_Bool = U_Bool {-# UNPACK #-} !Bool
+ {-# UNPACK #-} !Bool
+ {-# UNPACK #-} !Bool
+ {-# UNPACK #-} !Bool
+ {-# UNPACK #-} !Bool
+ {-# UNPACK #-} !Bool
+ {-# UNPACK #-} !Bool
+ {-# UNPACK #-} !Bool
+ deriving (Show)
+
+data U_E1 = U_E1 {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E1
+ deriving (Show)
+
+data U_E2 = U_E2 {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E2
+ deriving (Show)
+
+data U_E3 = U_E3 {-# UNPACK #-} !E3
+ {-# UNPACK #-} !E3
+ {-# UNPACK #-} !E3
+ {-# UNPACK #-} !E3
+ {-# UNPACK #-} !E3
+ {-# UNPACK #-} !E3
+ {-# UNPACK #-} !E3
+ {-# UNPACK #-} !E3
+ deriving (Show)
+
+data U_Mixed = U_Mixed {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E3
+ {-# UNPACK #-} !E3
+ {-# UNPACK #-} !Bool
+ {-# UNPACK #-} !Bool
+ deriving (Show)
+
+data U_Maybe = U_Maybe {-# UNPACK #-} !(Maybe Bool)
+ {-# UNPACK #-} !(Maybe Bool)
+ {-# UNPACK #-} !(Maybe Bool)
+ {-# UNPACK #-} !(Maybe Bool)
+ {-# UNPACK #-} !(Maybe Bool)
+ {-# UNPACK #-} !(Maybe Bool)
+ {-# UNPACK #-} !(Maybe Bool)
+ {-# UNPACK #-} !(Maybe Bool)
+ deriving (Show)
+
+
+data MaybeW32 = NothingW32
+ | JustW32 {-# UNPACK #-} !Word32
+ deriving (Show)
+
+data U_MaybeW32 = U_MaybeW32 {-# UNPACK #-} !MaybeW32
+ {-# UNPACK #-} !MaybeW32
+ {-# UNPACK #-} !MaybeW32
+ {-# UNPACK #-} !MaybeW32
+ {-# UNPACK #-} !MaybeW32
+ {-# UNPACK #-} !MaybeW32
+ {-# UNPACK #-} !MaybeW32
+ {-# UNPACK #-} !MaybeW32
+ deriving (Show)
+
+u_ba :: U_Bool
+u_ba = U_Bool minBound maxBound minBound maxBound
+ minBound maxBound minBound maxBound
+
+u_e1a :: U_E1
+u_e1a = U_E1 minBound maxBound minBound maxBound
+ minBound maxBound minBound maxBound
+
+u_e1b :: U_E1
+u_e1b = U_E1 maxBound minBound maxBound minBound
+ maxBound minBound maxBound minBound
+
+u_e1c :: U_E1
+u_e1c = U_E1 E1_1 E1_2 E1_3 E1_4
+ E1_5 E1_6 E1_7 E1_8
+
+u_e1d :: U_E1
+u_e1d = U_E1 E1_1 E1_16 E1_32 E1_64
+ E1_127 E1_128 E1_250 E1_254
+
+u_e2a :: U_E2
+u_e2a = U_E2 minBound maxBound minBound maxBound
+ minBound maxBound minBound maxBound
+
+u_e3a :: U_E3
+u_e3a = U_E3 minBound maxBound minBound maxBound
+ minBound maxBound minBound maxBound
+
+u_mixed :: U_Mixed
+u_mixed = U_Mixed maxBound minBound maxBound minBound
+ maxBound minBound maxBound minBound
+
+u_maybe :: U_Maybe
+u_maybe = U_Maybe Nothing (Just False) Nothing (Just True)
+ Nothing (Just False) Nothing (Just True)
+
+u_maybeW32 :: U_MaybeW32
+u_maybeW32 = U_MaybeW32 NothingW32 (JustW32 minBound)
+ NothingW32 (JustW32 maxBound)
+ NothingW32 (JustW32 minBound)
+ NothingW32 (JustW32 maxBound)
+
+test :: Show a => String -> a -> IO ()
+test name value = do
+ putStrLn $ "\n### " ++ name
+ value' <- evaluate value
+ print value'
+ putStrLn ("size: " ++ show (closureSize $ asBox value'))
+
+main :: IO ()
+main = do
+ test "u_ba" u_ba
+ test "u_e1a" u_e1a
+ test "u_e1b" u_e1b
+ test "u_e1c" u_e1c
+ test "u_e1d" u_e1d
+ test "u_e2a" u_e2a
+ test "u_e3a" u_e3a
+ test "u_mixed" u_mixed
+ test "u_maybe" u_maybe
+ test "u_maybeW32" u_maybeW32
=====================================
testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout
=====================================
@@ -0,0 +1,40 @@
+
+### u_ba
+U_Bool False True False True False True False True
+size: 2
+
+### u_e1a
+U_E1 E1_1 E1_254 E1_1 E1_254 E1_1 E1_254 E1_1 E1_254
+size: 2
+
+### u_e1b
+U_E1 E1_254 E1_1 E1_254 E1_1 E1_254 E1_1 E1_254 E1_1
+size: 2
+
+### u_e1c
+U_E1 E1_1 E1_2 E1_3 E1_4 E1_5 E1_6 E1_7 E1_8
+size: 2
+
+### u_e1d
+U_E1 E1_1 E1_16 E1_32 E1_64 E1_127 E1_128 E1_250 E1_254
+size: 2
+
+### u_e2a
+U_E2 E2_1 E2_255 E2_1 E2_255 E2_1 E2_255 E2_1 E2_255
+size: 2
+
+### u_e3a
+U_E3 E3_1 E3_256 E3_1 E3_256 E3_1 E3_256 E3_1 E3_256
+size: 3
+
+### u_mixed
+U_Mixed E1_254 E1_1 E2_255 E2_1 E3_256 E3_1 True False
+size: 3
+
+### u_maybe
+U_Maybe Nothing (Just False) Nothing (Just True) Nothing (Just False) Nothing (Just True)
+size: 10
+
+### u_maybeW32
+U_MaybeW32 NothingW32 (JustW32 0) NothingW32 (JustW32 4294967295) NothingW32 (JustW32 0) NothingW32 (JustW32 4294967295)
+size: 9
=====================================
testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout-ws-32
=====================================
@@ -0,0 +1,40 @@
+
+### u_ba
+U_Bool False True False True False True False True
+size: 3
+
+### u_e1a
+U_E1 E1_1 E1_254 E1_1 E1_254 E1_1 E1_254 E1_1 E1_254
+size: 3
+
+### u_e1b
+U_E1 E1_254 E1_1 E1_254 E1_1 E1_254 E1_1 E1_254 E1_1
+size: 3
+
+### u_e1c
+U_E1 E1_1 E1_2 E1_3 E1_4 E1_5 E1_6 E1_7 E1_8
+size: 3
+
+### u_e1d
+U_E1 E1_1 E1_16 E1_32 E1_64 E1_127 E1_128 E1_250 E1_254
+size: 3
+
+### u_e2a
+U_E2 E2_1 E2_255 E2_1 E2_255 E2_1 E2_255 E2_1 E2_255
+size: 3
+
+### u_e3a
+U_E3 E3_1 E3_256 E3_1 E3_256 E3_1 E3_256 E3_1 E3_256
+size: 5
+
+### u_mixed
+U_Mixed E1_254 E1_1 E2_255 E2_1 E3_256 E3_1 True False
+size: 4
+
+### u_maybe
+U_Maybe Nothing (Just False) Nothing (Just True) Nothing (Just False) Nothing (Just True)
+size: 11
+
+### u_maybeW32
+U_MaybeW32 NothingW32 (JustW32 0) NothingW32 (JustW32 4294967295) NothingW32 (JustW32 0) NothingW32 (JustW32 4294967295)
+size: 17
=====================================
testsuite/tests/unboxedsums/all.T
=====================================
@@ -62,3 +62,5 @@ test('ManyUbxSums',
['ManyUbxSums',
[('ManyUbxSums_Addr.hs','')]
, '-v0 -dstg-lint -dcmm-lint'])
+
+test('UbxSumUnpackedSize', normal, compile_and_run, [""])
=====================================
testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs
=====================================
@@ -63,33 +63,33 @@ layout_tests = sequence_
assert_layout "layout1"
[ ubxtup [ intTy, intPrimTy ]
, ubxtup [ intPrimTy, intTy ] ]
- [ WordSlot, PtrLiftedSlot, WordSlot ]
+ [ Word8Slot, PtrLiftedSlot, WordSlot ]
layout2 =
assert_layout "layout2"
[ ubxtup [ intTy ]
, intTy ]
- [ WordSlot, PtrLiftedSlot ]
+ [ Word8Slot, PtrLiftedSlot ]
layout3 =
assert_layout "layout3"
[ ubxtup [ intTy, intPrimTy, intTy, intPrimTy ]
, ubxtup [ intPrimTy, intTy, intPrimTy, intTy ] ]
- [ WordSlot, PtrLiftedSlot, PtrLiftedSlot, WordSlot, WordSlot ]
+ [ Word8Slot, PtrLiftedSlot, PtrLiftedSlot, WordSlot, WordSlot ]
layout4 =
assert_layout "layout4"
[ ubxtup [ floatPrimTy, floatPrimTy ]
, ubxtup [ intPrimTy, intPrimTy ] ]
- [ WordSlot, WordSlot, WordSlot, FloatSlot, FloatSlot ]
+ [ Word8Slot, WordSlot, WordSlot, FloatSlot, FloatSlot ]
layout5 =
assert_layout "layout5"
[ ubxtup [ intPrimTy, intPrimTy ]
, ubxtup [ floatPrimTy, floatPrimTy ] ]
- [ WordSlot, WordSlot, WordSlot, FloatSlot, FloatSlot ]
+ [ Word8Slot, WordSlot, WordSlot, FloatSlot, FloatSlot ]
enum_layout =
assert_layout "enum"
(replicate 10 (ubxtup []))
- [ WordSlot ]
+ [ Word8Slot ]
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5c2d26bbb8b67cbc4f29c5d29f4585e…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5c2d26bbb8b67cbc4f29c5d29f4585e…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 10 commits: Make injecting implicit bindings into its own pass
by Marge Bot (@marge-bot) 14 Aug '25
by Marge Bot (@marge-bot) 14 Aug '25
14 Aug '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
8967356c by Simon Peyton Jones at 2025-08-14T05:48:27-04:00
Make injecting implicit bindings into its own pass
Previously we were injecting "impliicit bindings" (data constructor
worker and wrappers etc)
- both at the end of CoreTidy,
- and at the start of CorePrep
This is unpleasant and confusing. This patch puts it it its own pass,
addImplicitBinds, which runs between the two.
The function `GHC.CoreToStg.AddImplicitBinds.addImplicitBinds` now takes /all/
TyCons, not just the ones for algebraic data types. That change ripples
through to
- corePrepPgm
- doCodeGen
- byteCodeGen
All take [TyCon] which includes all TyCons
- - - - -
1f6a0745 by Simon Peyton Jones at 2025-08-14T05:48:27-04:00
Implement unary classes
The big change is described exhaustively in
Note [Unary class magic] in GHC.Core.TyCon
Other changes
* We never unbox class dictionaries in worker/wrapper. This has been true for some
time now, but the logic is now centralised in functions in
GHC.Core.Opt.WorkWrap.Utils, namely `canUnboxTyCon`, and `canUnboxArg`
See Note [Do not unbox class dictionaries] in GHC.Core.Opt.WorkWrap.Utils.
* Refactored the `notWorthFloating` logic in GHc.Core.Opt.SetLevels.
I can't remember if I actually changed any behaviour here, but if so it's
only in a corner cases.
* Fixed a bug in `GHC.Core.TyCon.isEnumerationTyCon`, which was wrongly returning
True for (##).
* Remove redundant Role argument to `liftCoSubstWithEx`. It was always
Representational.
* I refactored evidence generation in the constraint solver:
* Made GHC.Tc.Types.Evidence contain better abstactions for evidence
generation.
* I deleted the file `GHC.Tc.Types.EvTerm` and merged its (small) contents
elsewhere. It wasn't paying its way.
* Made evidence for implicit parameters go via a proper abstraction.
* Fix inlineBoringOk; see (IB6) in Note [inlineBoringOk]
This fixes a slowdown in `countdownEffectfulDynLocal`
in the `effectful` library.
Smaller things
* Rename `isDataTyCon` to `isBoxedDataTyCon`.
* GHC.Core.Corecion.liftCoSubstWithEx was only called with Representational role,
so I baked that into the function and removed the argument.
* Get rid of `GHC.Core.TyCon.tyConSingleAlgDataCon_maybe` in favour of calling
`not isNewTyCon` at the call sites; more explicit.
* Refatored `GHC.Core.TyCon.isInjectiveTyCon`; but I don't think I changed its
behaviour
* Moved `decomposeIPPred` to GHC.Core.Predicate
Compile time performance changes:
geo. mean +0.1%
minimum -6.8%
maximum +14.4%
The +14% one is in T21839c, where it seems that a bit more inlining
is taking place. That seems acceptable; and the average change is small
Metric Decrease:
LargeRecord
T12227
T12707
T16577
T21839r
T5642
Metric Increase:
T15164
T21839c
T3294
T5321FD
T5321Fun
WWRec
- - - - -
a96fc664 by Simon Peyton Jones at 2025-08-14T05:48:27-04:00
Slight improvement to pre/postInlineUnconditionally
Avoids an extra simplifier iteration
- - - - -
03b54cff by Simon Peyton Jones at 2025-08-14T05:48:27-04:00
Fix a long-standing assertion error in normSplitTyConApp_maybe
- - - - -
6cf50c2b by Simon Peyton Jones at 2025-08-14T05:48:27-04:00
Add comment to coercion optimiser
- - - - -
2f91234b by fendor at 2025-08-14T05:48:29-04:00
Remove deprecated functions from the ghci package
- - - - -
4514b52f by fendor at 2025-08-14T05:48:29-04:00
base: Remove unstable heap representation details from GHC.Exts
- - - - -
00054e38 by Recursion Ninja at 2025-08-14T05:48:30-04:00
Resolving issues #20645 and #26109
Correctly sign extending and casting smaller bit width types for LLVM operations:
- bitReverse8#
- bitReverse16#
- bitReverse32#
- byteSwap16#
- byteSwap32#
- pdep8#
- pdep16#
- pext8#
- pext16#
- - - - -
dc4ee54a by Sylvain Henry at 2025-08-14T05:48:37-04:00
JS: export HEAP8 symbol (#26290)
Newer Emscripten requires this.
- - - - -
16a76fb3 by Cheng Shao at 2025-08-14T05:48:38-04:00
hadrian: enforce have_llvm=False for wasm32/js
This patch fixes hadrian to always pass have_llvm=False to the
testsuite driver for wasm32/js targets. These targets don't really
support the LLVM backend, and the optllvm test way doesn't work. We
used to special-case wasm32/js to avoid auto-adding optllvm way in
testsuite/config/ghc, but this is still problematic if someone writes
a new LLVM-related test and uses something like when(have_llvm(),
extra_ways(["optllvm"])). So better just enforce have_llvm=False for
these targets here.
- - - - -
118 changed files:
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unfold.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg.hs
- + compiler/GHC/CoreToStg/AddImplicitBinds.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/Call.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Instance/Family.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- − compiler/GHC/Tc/Types/EvTerm.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/RepType.hs
- compiler/GHC/Types/TyThing.hs
- compiler/ghc.cabal.in
- hadrian/src/Settings/Builders/RunTest.hs
- libraries/base/changelog.md
- libraries/base/src/GHC/Exts.hs
- libraries/ghc-internal/cbits/pdep.c
- libraries/ghc-internal/cbits/pext.c
- libraries/ghci/GHCi/CreateBCO.hs
- libraries/ghci/GHCi/TH.hs
- libraries/ghci/ghci.cabal.in
- rts/js/mem.js
- testsuite/config/ghc
- testsuite/driver/testlib.py
- testsuite/tests/core-to-stg/T24124.stderr
- testsuite/tests/deSugar/should_compile/T2431.stderr
- testsuite/tests/dmdanal/should_compile/T16029.stdout
- testsuite/tests/dmdanal/sigs/T21119.stderr
- testsuite/tests/dmdanal/sigs/T21888.stderr
- testsuite/tests/ghci.debugger/scripts/break011.stdout
- testsuite/tests/ghci.debugger/scripts/break024.stdout
- testsuite/tests/indexed-types/should_compile/T2238.hs
- + testsuite/tests/llvm/should_run/T20645.hs
- + testsuite/tests/llvm/should_run/T20645.stdout
- testsuite/tests/llvm/should_run/all.T
- − testsuite/tests/module/T21752.stderr
- testsuite/tests/numeric/should_compile/T15547.stderr
- testsuite/tests/numeric/should_compile/T23907.stderr
- testsuite/tests/numeric/should_run/foundation.hs
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/simplCore/should_compile/DataToTagFamilyScrut.stderr
- testsuite/tests/simplCore/should_compile/T15205.stderr
- testsuite/tests/simplCore/should_compile/T17366.stderr
- testsuite/tests/simplCore/should_compile/T17966.stderr
- testsuite/tests/simplCore/should_compile/T22309.stderr
- testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr
- testsuite/tests/simplCore/should_compile/T23307.stderr
- testsuite/tests/simplCore/should_compile/T23307a.stderr
- testsuite/tests/simplCore/should_compile/T25389.stderr
- testsuite/tests/simplCore/should_compile/T25713.stderr
- testsuite/tests/simplCore/should_compile/T7360.stderr
- testsuite/tests/simplStg/should_compile/T15226b.stderr
- testsuite/tests/tcplugins/CtIdPlugin.hs
- testsuite/tests/typecheck/should_compile/Makefile
- testsuite/tests/typecheck/should_compile/T12763.stderr
- testsuite/tests/typecheck/should_compile/T14774.stdout
- testsuite/tests/typecheck/should_compile/T18406b.stderr
- testsuite/tests/typecheck/should_compile/T18529.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/unboxedsums/unpack_sums_7.stdout
- testsuite/tests/wasm/should_run/control-flow/LoadCmmGroup.hs
- testsuite/tests/wasm/should_run/control-flow/RunWasm.hs
- utils/genprimopcode/Lexer.x
- utils/genprimopcode/Main.hs
- utils/genprimopcode/Parser.y
- utils/genprimopcode/ParserM.hs
- utils/genprimopcode/Syntax.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ae51e3702af6615e2552b62cf2de58…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ae51e3702af6615e2552b62cf2de58…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/ubxsumtag] 3 commits: Support larger unboxed sums
by Luite Stegeman (@luite) 14 Aug '25
by Luite Stegeman (@luite) 14 Aug '25
14 Aug '25
Luite Stegeman pushed to branch wip/ubxsumtag at Glasgow Haskell Compiler / GHC
Commits:
e4515501 by Luite Stegeman at 2025-08-14T11:19:55+02:00
Support larger unboxed sums
Change known constructor encoding for sums in interfaces to use
11 bits for both the arity and the alternative (up from 8 and 6,
respectively)
- - - - -
43efb285 by Luite Stegeman at 2025-08-14T11:21:43+02:00
Use slots smaller than word as tag for smaller unboxed sums
This packs unboxed sums more efficiently by allowing
Word8, Word16 and Word32 for the tag field if the number of
constructors is small enough
- - - - -
bdcc6de9 by Luite Stegeman at 2025-08-14T11:35:22+02:00
add test case
- - - - -
10 changed files:
- compiler/GHC/Builtin/Uniques.hs
- compiler/GHC/Cmm/Utils.hs
- compiler/GHC/Stg/Unarise.hs
- compiler/GHC/Types/RepType.hs
- testsuite/tests/codeGen/should_compile/T25166.stdout → testsuite/tests/codeGen/should_compile/T25166.stdout-ws-32
- + testsuite/tests/codeGen/should_compile/T25166.stdout-ws-64
- + testsuite/tests/unboxedsums/UbxSumUnpackedSize.hs
- + testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout
- + testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout-ws-32
- testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs
Changes:
=====================================
compiler/GHC/Builtin/Uniques.hs
=====================================
@@ -97,37 +97,37 @@ Note [Unique layout for unboxed sums]
Sum arities start from 2. The encoding is a bit funny: we break up the
integral part into bitfields for the arity, an alternative index (which is
-taken to be 0xfc in the case of the TyCon), and, in the case of a datacon, a
-tag (used to identify the sum's TypeRep binding).
+taken to be 0x1ffc in the case of the TyCon), and, in the case of a datacon,
+a tag (used to identify the sum's TypeRep binding).
This layout is chosen to remain compatible with the usual unique allocation
for wired-in data constructors described in GHC.Types.Unique
TyCon for sum of arity k:
- 00000000 kkkkkkkk 11111100
+ kkkkkkkk kkk11111 11111100
TypeRep of TyCon for sum of arity k:
- 00000000 kkkkkkkk 11111101
+ kkkkkkkk kkk11111 11111101
DataCon for sum of arity k and alternative n (zero-based):
- 00000000 kkkkkkkk nnnnnn00
+ kkkkkkkk kkknnnnn nnnnnn00
TypeRep for sum DataCon of arity k and alternative n (zero-based):
- 00000000 kkkkkkkk nnnnnn10
+ kkkkkkkk kkknnnnn nnnnnn10
-}
mkSumTyConUnique :: Arity -> Unique
mkSumTyConUnique arity =
- assertPpr (arity <= 0x3f) (ppr arity) $
- -- 0x3f since we only have 6 bits to encode the
+ assertPpr (arity <= 0x7ff) (ppr arity) $
+ -- 0x7ff since we only have 11 bits to encode the
-- alternative
- mkUniqueInt 'z' (arity `shiftL` 8 .|. 0xfc)
+ mkUniqueInt 'z' (arity `shiftL` 13 .|. 0x1ffc)
-- | Inverse of 'mkSumTyConUnique'
isSumTyConUnique :: Unique -> Maybe Arity
isSumTyConUnique u =
- case (tag, n .&. 0xfc) of
- ('z', 0xfc) -> Just (word64ToInt n `shiftR` 8)
+ case (tag, n .&. 0x1ffc) of
+ ('z', 0x1ffc) -> Just (word64ToInt n `shiftR` 13)
_ -> Nothing
where
(tag, n) = unpkUnique u
@@ -137,11 +137,11 @@ mkSumDataConUnique alt arity
| alt >= arity
= panic ("mkSumDataConUnique: " ++ show alt ++ " >= " ++ show arity)
| otherwise
- = mkUniqueInt 'z' (arity `shiftL` 8 + alt `shiftL` 2) {- skip the tycon -}
+ = mkUniqueInt 'z' (arity `shiftL` 13 + alt `shiftL` 2) {- skip the tycon -}
getUnboxedSumName :: Int -> Name
getUnboxedSumName n
- | n .&. 0xfc == 0xfc
+ | n .&. 0x1ffc == 0x1ffc
= case tag of
0x0 -> tyConName $ sumTyCon arity
0x1 -> getRep $ sumTyCon arity
@@ -155,8 +155,8 @@ getUnboxedSumName n
| otherwise
= pprPanic "getUnboxedSumName" (ppr n)
where
- arity = n `shiftR` 8
- alt = (n .&. 0xfc) `shiftR` 2
+ arity = n `shiftR` 13
+ alt = (n .&. 0x1ffc) `shiftR` 2
tag = 0x3 .&. n
getRep tycon =
fromMaybe (pprPanic "getUnboxedSumName(getRep)" (ppr tycon))
=====================================
compiler/GHC/Cmm/Utils.hs
=====================================
@@ -115,6 +115,9 @@ slotCmmType platform = \case
PtrUnliftedSlot -> gcWord platform
PtrLiftedSlot -> gcWord platform
WordSlot -> bWord platform
+ Word8Slot -> b8
+ Word16Slot -> b16
+ Word32Slot -> b32
Word64Slot -> b64
FloatSlot -> f32
DoubleSlot -> f64
=====================================
compiler/GHC/Stg/Unarise.hs
=====================================
@@ -404,7 +404,6 @@ import GHC.Stg.Syntax
import GHC.Stg.Utils
import GHC.Stg.Make
import GHC.Core.Type
-import GHC.Builtin.Types.Prim (intPrimTy)
import GHC.Builtin.Types
import GHC.Types.Unique.Supply
import GHC.Types.Unique
@@ -681,15 +680,15 @@ elimCase rho args bndr (MultiValAlt _) [GenStgAlt{ alt_con = _
elimCase rho args@(tag_arg : real_args) bndr (MultiValAlt _) alts
| isUnboxedSumBndr bndr
- = do tag_bndr <- mkId (mkFastString "tag") tagTy
+ = do tag_bndr <- mkId (mkFastString "tag") (tagTyArg tag_arg)
-- this won't be used but we need a binder anyway
let rho1 = extendRho rho bndr (MultiVal args)
scrut' = case tag_arg of
StgVarArg v -> StgApp v []
StgLitArg l -> StgLit l
-
- alts' <- unariseSumAlts rho1 real_args alts
- return (StgCase scrut' tag_bndr tagAltTy alts')
+ alt_ty = (tagAltTyArg tag_arg)
+ alts' <- unariseSumAlts rho1 alt_ty real_args alts
+ return (StgCase scrut' tag_bndr alt_ty alts')
elimCase _ args bndr alt_ty alts
= pprPanic "elimCase - unhandled case"
@@ -732,8 +731,9 @@ unariseAlts rho (MultiValAlt _) bndr [GenStgAlt{ alt_con = DEFAULT
unariseAlts rho (MultiValAlt _) bndr alts
| isUnboxedSumBndr bndr
= do (rho_sum_bndrs, scrt_bndrs@(tag_bndr : real_bndrs)) <- unariseConArgBinder rho bndr
- alts' <- unariseSumAlts rho_sum_bndrs (map StgVarArg real_bndrs) alts
- let inner_case = StgCase (StgApp tag_bndr []) tag_bndr tagAltTy alts'
+ let alt_ty = tagAltTy tag_bndr
+ alts' <- unariseSumAlts rho_sum_bndrs alt_ty (map StgVarArg real_bndrs) alts
+ let inner_case = StgCase (StgApp tag_bndr []) tag_bndr alt_ty alts'
return [GenStgAlt{ alt_con = DataAlt (tupleDataCon Unboxed (length scrt_bndrs))
, alt_bndrs = scrt_bndrs
, alt_rhs = inner_case
@@ -753,21 +753,23 @@ unariseAlt rho alt@GenStgAlt{alt_con=_,alt_bndrs=xs,alt_rhs=e}
-- | Make alternatives that match on the tag of a sum
-- (i.e. generate LitAlts for the tag)
unariseSumAlts :: UnariseEnv
+ -> AltType
-> [StgArg] -- sum components _excluding_ the tag bit.
-> [StgAlt] -- original alternative with sum LHS
-> UniqSM [StgAlt]
-unariseSumAlts env args alts
- = do alts' <- mapM (unariseSumAlt env args) alts
+unariseSumAlts env tag_slot args alts
+ = do alts' <- mapM (unariseSumAlt env tag_slot args) alts
return (mkDefaultLitAlt alts')
unariseSumAlt :: UnariseEnv
+ -> AltType
-> [StgArg] -- sum components _excluding_ the tag bit.
-> StgAlt -- original alternative with sum LHS
-> UniqSM StgAlt
-unariseSumAlt rho _ GenStgAlt{alt_con=DEFAULT,alt_bndrs=_,alt_rhs=e}
+unariseSumAlt rho _ _ GenStgAlt{alt_con=DEFAULT,alt_bndrs=_,alt_rhs=e}
= GenStgAlt DEFAULT mempty <$> unariseExpr rho e
-unariseSumAlt rho args alt@GenStgAlt{ alt_con = DataAlt sumCon
+unariseSumAlt rho tag_slot args alt@GenStgAlt{ alt_con = DataAlt sumCon
, alt_bndrs = bs
, alt_rhs = e
}
@@ -776,10 +778,19 @@ unariseSumAlt rho args alt@GenStgAlt{ alt_con = DataAlt sumCon
[b] -> mapSumIdBinders b args e rho
-- Sums must have one binder
_ -> pprPanic "unariseSumAlt2" (ppr args $$ pprPanicAlt alt)
- let lit_case = LitAlt (LitNumber LitNumInt (fromIntegral (dataConTag sumCon)))
+ let num_ty =
+ case tag_slot of
+ PrimAlt Int8Rep -> LitNumInt8
+ PrimAlt Word8Rep -> LitNumWord8
+ PrimAlt Int16Rep -> LitNumInt16
+ PrimAlt Word16Rep -> LitNumWord16
+ PrimAlt Int32Rep -> LitNumInt32
+ PrimAlt Word32Rep -> LitNumWord32
+ _ -> LitNumInt
+ lit_case = LitAlt (LitNumber num_ty (fromIntegral (dataConTag sumCon)))
GenStgAlt lit_case mempty <$> unariseExpr rho' e'
-unariseSumAlt _ scrt alt
+unariseSumAlt _ _ scrt alt
= pprPanic "unariseSumAlt3" (ppr scrt $$ pprPanicAlt alt)
--------------------------------------------------------------------------------
@@ -865,12 +876,6 @@ mapSumIdBinders alt_bndr args rhs rho0
typed_id_args = map StgVarArg typed_ids
- -- pprTrace "mapSumIdBinders"
- -- (text "fld_reps" <+> ppr fld_reps $$
- -- text "id_args" <+> ppr id_arg_exprs $$
- -- text "rhs" <+> ppr rhs $$
- -- text "rhs_with_casts" <+> ppr rhs_with_casts
- -- ) $
if isMultiValBndr alt_bndr
then return (extendRho rho0 alt_bndr (MultiVal typed_id_args), rhs_with_casts rhs)
else assert (typed_id_args `lengthIs` 1) $
@@ -921,13 +926,19 @@ mkUbxSum
)
mkUbxSum dc ty_args args0 us
= let
- _ :| sum_slots = ubxSumRepType ty_args
+ tag_slot :| sum_slots = ubxSumRepType ty_args
-- drop tag slot
field_slots = (mapMaybe (repSlotTy . stgArgRep) args0)
tag = dataConTag dc
layout' = layoutUbxSum sum_slots field_slots
- tag_arg = StgLitArg (LitNumber LitNumInt (fromIntegral tag))
+ tag_arg =
+ case tag_slot of
+ Word8Slot -> StgLitArg (LitNumber LitNumWord8 (fromIntegral tag))
+ Word16Slot -> StgLitArg (LitNumber LitNumWord16 (fromIntegral tag))
+ Word32Slot -> StgLitArg (LitNumber LitNumWord32 (fromIntegral tag))
+ WordSlot -> StgLitArg (LitNumber LitNumWord (fromIntegral tag))
+ _ -> pprPanic "mkUbxSum: unexpected tag slot: " (ppr tag_slot)
arg_idxs = IM.fromList (zipEqual layout' args0)
((_idx,_idx_map,_us,wrapper),slot_args)
@@ -990,6 +1001,9 @@ ubxSumRubbishArg :: SlotTy -> StgArg
ubxSumRubbishArg PtrLiftedSlot = StgVarArg aBSENT_SUM_FIELD_ERROR_ID
ubxSumRubbishArg PtrUnliftedSlot = StgVarArg aBSENT_SUM_FIELD_ERROR_ID
ubxSumRubbishArg WordSlot = StgLitArg (LitNumber LitNumWord 0)
+ubxSumRubbishArg Word8Slot = StgLitArg (LitNumber LitNumWord8 0)
+ubxSumRubbishArg Word16Slot = StgLitArg (LitNumber LitNumWord16 0)
+ubxSumRubbishArg Word32Slot = StgLitArg (LitNumber LitNumWord32 0)
ubxSumRubbishArg Word64Slot = StgLitArg (LitNumber LitNumWord64 0)
ubxSumRubbishArg FloatSlot = StgLitArg (LitFloat 0)
ubxSumRubbishArg DoubleSlot = StgLitArg (LitDouble 0)
@@ -1166,11 +1180,18 @@ isUnboxedTupleBndr = isUnboxedTupleType . idType
mkTuple :: [StgArg] -> StgExpr
mkTuple args = StgConApp (tupleDataCon Unboxed (length args)) NoNumber args []
-tagAltTy :: AltType
-tagAltTy = PrimAlt IntRep
+tagAltTyArg :: StgArg -> AltType
+tagAltTyArg a
+ | [pr] <- typePrimRep (stgArgType a) = PrimAlt pr
+ | otherwise = pprPanic "tagAltTyArg" (ppr a)
+
+tagAltTy :: Id -> AltType
+tagAltTy i
+ | [pr] <- typePrimRep (idType i) = PrimAlt pr
+ | otherwise = pprPanic "tagAltTy" (ppr $ idType i)
-tagTy :: Type
-tagTy = intPrimTy
+tagTyArg :: StgArg -> Type
+tagTyArg x = stgArgType x
voidArg :: StgArg
voidArg = StgVarArg voidPrimId
=====================================
compiler/GHC/Types/RepType.hs
=====================================
@@ -197,12 +197,12 @@ type SortedSlotTys = [SlotTy]
-- of the list we have the slot for the tag.
ubxSumRepType :: [[PrimRep]] -> NonEmpty SlotTy
ubxSumRepType constrs0
- -- These first two cases never classify an actual unboxed sum, which always
+ -- This first case never classifies an actual unboxed sum, which always
-- has at least two disjuncts. But it could happen if a user writes, e.g.,
-- forall (a :: TYPE (SumRep [IntRep])). ...
-- which could never be instantiated. We still don't want to panic.
| constrs0 `lengthLessThan` 2
- = WordSlot :| []
+ = Word8Slot :| []
| otherwise
= let
@@ -230,8 +230,14 @@ ubxSumRepType constrs0
rep :: [PrimRep] -> SortedSlotTys
rep ty = sort (map primRepSlot ty)
- sumRep = WordSlot :| combine_alts (map rep constrs0)
- -- WordSlot: for the tag of the sum
+ -- constructors start at 1 (XXX is this correct?)
+ tag_slot | length constrs0 < 256 = Word8Slot
+ | length constrs0 < 65536 = Word16Slot
+-- | length constrs0 < 4294967296 = Word32Slot
+ | length constrs0 < 2147483647 = Word32Slot -- XXX temporary for 32 bit platforms
+ | otherwise = WordSlot
+
+ sumRep = tag_slot :| combine_alts (map rep constrs0)
in
sumRep
@@ -275,10 +281,17 @@ layoutUbxSum sum_slots0 arg_slots0 =
-- - Float slots: Shared between floating point types.
--
-- - Void slots: Shared between void types. Not used in sums.
---
--- TODO(michalt): We should probably introduce `SlotTy`s for 8-/16-/32-bit
--- values, so that we can pack things more tightly.
-data SlotTy = PtrLiftedSlot | PtrUnliftedSlot | WordSlot | Word64Slot | FloatSlot | DoubleSlot | VecSlot Int PrimElemRep
+
+data SlotTy = PtrLiftedSlot
+ | PtrUnliftedSlot
+ | Word8Slot
+ | Word16Slot
+ | Word32Slot
+ | WordSlot -- the order is important, later ones are bigger. this works for word sizes 32 and 64 bit (XXX fix this)
+ | Word64Slot
+ | FloatSlot
+ | DoubleSlot
+ | VecSlot Int PrimElemRep
deriving (Eq, Ord)
-- Constructor order is important! If slot A could fit into slot B
-- then slot A must occur first. E.g. FloatSlot before DoubleSlot
@@ -291,6 +304,9 @@ instance Outputable SlotTy where
ppr PtrUnliftedSlot = text "PtrUnliftedSlot"
ppr Word64Slot = text "Word64Slot"
ppr WordSlot = text "WordSlot"
+ ppr Word32Slot = text "Word32Slot"
+ ppr Word16Slot = text "Word16Slot"
+ ppr Word8Slot = text "Word8Slot"
ppr DoubleSlot = text "DoubleSlot"
ppr FloatSlot = text "FloatSlot"
ppr (VecSlot n e) = text "VecSlot" <+> ppr n <+> ppr e
@@ -307,14 +323,14 @@ primRepSlot (BoxedRep mlev) = case mlev of
Just Lifted -> PtrLiftedSlot
Just Unlifted -> PtrUnliftedSlot
primRepSlot IntRep = WordSlot
-primRepSlot Int8Rep = WordSlot
-primRepSlot Int16Rep = WordSlot
-primRepSlot Int32Rep = WordSlot
+primRepSlot Int8Rep = Word8Slot
+primRepSlot Int16Rep = Word16Slot
+primRepSlot Int32Rep = Word32Slot
primRepSlot Int64Rep = Word64Slot
primRepSlot WordRep = WordSlot
-primRepSlot Word8Rep = WordSlot
-primRepSlot Word16Rep = WordSlot
-primRepSlot Word32Rep = WordSlot
+primRepSlot Word8Rep = Word8Slot
+primRepSlot Word16Rep = Word16Slot
+primRepSlot Word32Rep = Word32Slot
primRepSlot Word64Rep = Word64Slot
primRepSlot AddrRep = WordSlot
primRepSlot FloatRep = FloatSlot
@@ -325,6 +341,9 @@ slotPrimRep :: SlotTy -> PrimRep
slotPrimRep PtrLiftedSlot = BoxedRep (Just Lifted)
slotPrimRep PtrUnliftedSlot = BoxedRep (Just Unlifted)
slotPrimRep Word64Slot = Word64Rep
+slotPrimRep Word32Slot = Word32Rep
+slotPrimRep Word16Slot = Word16Rep
+slotPrimRep Word8Slot = Word8Rep
slotPrimRep WordSlot = WordRep
slotPrimRep DoubleSlot = DoubleRep
slotPrimRep FloatSlot = FloatRep
@@ -349,11 +368,12 @@ fitsIn ty1 ty2
-- See Note [Casting slot arguments]
where
isWordSlot Word64Slot = True
+ isWordSlot Word32Slot = True
+ isWordSlot Word16Slot = True
+ isWordSlot Word8Slot = True
isWordSlot WordSlot = True
isWordSlot _ = False
-
-
{- **********************************************************************
* *
PrimRep
=====================================
testsuite/tests/codeGen/should_compile/T25166.stdout → testsuite/tests/codeGen/should_compile/T25166.stdout-ws-32
=====================================
@@ -2,5 +2,7 @@
Test.foo_closure:
const Test.D_con_info;
const GHC.Internal.Types.True_closure+2;
- const 2;
+ const 2 :: W8;
+ const 0 :: W16;
+ const 0 :: W8;
const 3;
=====================================
testsuite/tests/codeGen/should_compile/T25166.stdout-ws-64
=====================================
@@ -0,0 +1,9 @@
+[section ""data" . Test.foo_closure" {
+ Test.foo_closure:
+ const Test.D_con_info;
+ const GHC.Internal.Types.True_closure+2;
+ const 2 :: W8;
+ const 0 :: W32;
+ const 0 :: W16;
+ const 0 :: W8;
+ const 3;
=====================================
testsuite/tests/unboxedsums/UbxSumUnpackedSize.hs
=====================================
@@ -0,0 +1,250 @@
+module Main where
+
+import GHC.Exts.Heap.Closures
+import Control.Exception (evaluate)
+import Data.Word (Word32)
+
+-- this should get a Word8 tag
+data E1
+ = E1_1 | E1_2 | E1_3 | E1_4 | E1_5 | E1_6 | E1_7 | E1_8
+ | E1_9 | E1_10 | E1_11 | E1_12 | E1_13 | E1_14 | E1_15 | E1_16
+ | E1_17 | E1_18 | E1_19 | E1_20 | E1_21 | E1_22 | E1_23 | E1_24
+ | E1_25 | E1_26 | E1_27 | E1_28 | E1_29 | E1_30 | E1_31 | E1_32
+ | E1_33 | E1_34 | E1_35 | E1_36 | E1_37 | E1_38 | E1_39 | E1_40
+ | E1_41 | E1_42 | E1_43 | E1_44 | E1_45 | E1_46 | E1_47 | E1_48
+ | E1_49 | E1_50 | E1_51 | E1_52 | E1_53 | E1_54 | E1_55 | E1_56
+ | E1_57 | E1_58 | E1_59 | E1_60 | E1_61 | E1_62 | E1_63 | E1_64
+ | E1_65 | E1_66 | E1_67 | E1_68 | E1_69 | E1_70 | E1_71 | E1_72
+ | E1_73 | E1_74 | E1_75 | E1_76 | E1_77 | E1_78 | E1_79 | E1_80
+ | E1_81 | E1_82 | E1_83 | E1_84 | E1_85 | E1_86 | E1_87 | E1_88
+ | E1_89 | E1_90 | E1_91 | E1_92 | E1_93 | E1_94 | E1_95 | E1_96
+ | E1_97 | E1_98 | E1_99 | E1_100 | E1_101 | E1_102 | E1_103 | E1_104
+ | E1_105 | E1_106 | E1_107 | E1_108 | E1_109 | E1_110 | E1_111 | E1_112
+ | E1_113 | E1_114 | E1_115 | E1_116 | E1_117 | E1_118 | E1_119 | E1_120
+ | E1_121 | E1_122 | E1_123 | E1_124 | E1_125 | E1_126 | E1_127 | E1_128
+ | E1_129 | E1_130 | E1_131 | E1_132 | E1_133 | E1_134 | E1_135 | E1_136
+ | E1_137 | E1_138 | E1_139 | E1_140 | E1_141 | E1_142 | E1_143 | E1_144
+ | E1_145 | E1_146 | E1_147 | E1_148 | E1_149 | E1_150 | E1_151 | E1_152
+ | E1_153 | E1_154 | E1_155 | E1_156 | E1_157 | E1_158 | E1_159 | E1_160
+ | E1_161 | E1_162 | E1_163 | E1_164 | E1_165 | E1_166 | E1_167 | E1_168
+ | E1_169 | E1_170 | E1_171 | E1_172 | E1_173 | E1_174 | E1_175 | E1_176
+ | E1_177 | E1_178 | E1_179 | E1_180 | E1_181 | E1_182 | E1_183 | E1_184
+ | E1_185 | E1_186 | E1_187 | E1_188 | E1_189 | E1_190 | E1_191 | E1_192
+ | E1_193 | E1_194 | E1_195 | E1_196 | E1_197 | E1_198 | E1_199 | E1_200
+ | E1_201 | E1_202 | E1_203 | E1_204 | E1_205 | E1_206 | E1_207 | E1_208
+ | E1_209 | E1_210 | E1_211 | E1_212 | E1_213 | E1_214 | E1_215 | E1_216
+ | E1_217 | E1_218 | E1_219 | E1_220 | E1_221 | E1_222 | E1_223 | E1_224
+ | E1_225 | E1_226 | E1_227 | E1_228 | E1_229 | E1_230 | E1_231 | E1_232
+ | E1_233 | E1_234 | E1_235 | E1_236 | E1_237 | E1_238 | E1_239 | E1_240
+ | E1_241 | E1_242 | E1_243 | E1_244 | E1_245 | E1_246 | E1_247 | E1_248
+ | E1_249 | E1_250 | E1_251 | E1_252 | E1_253 | E1_254
+ deriving (Enum, Bounded, Show)
+
+-- this should get a Word8 tag
+data E2
+ = E2_1 | E2_2 | E2_3 | E2_4 | E2_5 | E2_6 | E2_7 | E2_8
+ | E2_9 | E2_10 | E2_11 | E2_12 | E2_13 | E2_14 | E2_15 | E2_16
+ | E2_17 | E2_18 | E2_19 | E2_20 | E2_21 | E2_22 | E2_23 | E2_24
+ | E2_25 | E2_26 | E2_27 | E2_28 | E2_29 | E2_30 | E2_31 | E2_32
+ | E2_33 | E2_34 | E2_35 | E2_36 | E2_37 | E2_38 | E2_39 | E2_40
+ | E2_41 | E2_42 | E2_43 | E2_44 | E2_45 | E2_46 | E2_47 | E2_48
+ | E2_49 | E2_50 | E2_51 | E2_52 | E2_53 | E2_54 | E2_55 | E2_56
+ | E2_57 | E2_58 | E2_59 | E2_60 | E2_61 | E2_62 | E2_63 | E2_64
+ | E2_65 | E2_66 | E2_67 | E2_68 | E2_69 | E2_70 | E2_71 | E2_72
+ | E2_73 | E2_74 | E2_75 | E2_76 | E2_77 | E2_78 | E2_79 | E2_80
+ | E2_81 | E2_82 | E2_83 | E2_84 | E2_85 | E2_86 | E2_87 | E2_88
+ | E2_89 | E2_90 | E2_91 | E2_92 | E2_93 | E2_94 | E2_95 | E2_96
+ | E2_97 | E2_98 | E2_99 | E2_100 | E2_101 | E2_102 | E2_103 | E2_104
+ | E2_105 | E2_106 | E2_107 | E2_108 | E2_109 | E2_110 | E2_111 | E2_112
+ | E2_113 | E2_114 | E2_115 | E2_116 | E2_117 | E2_118 | E2_119 | E2_120
+ | E2_121 | E2_122 | E2_123 | E2_124 | E2_125 | E2_126 | E2_127 | E2_128
+ | E2_129 | E2_130 | E2_131 | E2_132 | E2_133 | E2_134 | E2_135 | E2_136
+ | E2_137 | E2_138 | E2_139 | E2_140 | E2_141 | E2_142 | E2_143 | E2_144
+ | E2_145 | E2_146 | E2_147 | E2_148 | E2_149 | E2_150 | E2_151 | E2_152
+ | E2_153 | E2_154 | E2_155 | E2_156 | E2_157 | E2_158 | E2_159 | E2_160
+ | E2_161 | E2_162 | E2_163 | E2_164 | E2_165 | E2_166 | E2_167 | E2_168
+ | E2_169 | E2_170 | E2_171 | E2_172 | E2_173 | E2_174 | E2_175 | E2_176
+ | E2_177 | E2_178 | E2_179 | E2_180 | E2_181 | E2_182 | E2_183 | E2_184
+ | E2_185 | E2_186 | E2_187 | E2_188 | E2_189 | E2_190 | E2_191 | E2_192
+ | E2_193 | E2_194 | E2_195 | E2_196 | E2_197 | E2_198 | E2_199 | E2_200
+ | E2_201 | E2_202 | E2_203 | E2_204 | E2_205 | E2_206 | E2_207 | E2_208
+ | E2_209 | E2_210 | E2_211 | E2_212 | E2_213 | E2_214 | E2_215 | E2_216
+ | E2_217 | E2_218 | E2_219 | E2_220 | E2_221 | E2_222 | E2_223 | E2_224
+ | E2_225 | E2_226 | E2_227 | E2_228 | E2_229 | E2_230 | E2_231 | E2_232
+ | E2_233 | E2_234 | E2_235 | E2_236 | E2_237 | E2_238 | E2_239 | E2_240
+ | E2_241 | E2_242 | E2_243 | E2_244 | E2_245 | E2_246 | E2_247 | E2_248
+ | E2_249 | E2_250 | E2_251 | E2_252 | E2_253 | E2_254 | E2_255
+ deriving (Enum, Bounded, Show)
+
+-- this needs a Word16 tag
+data E3
+ = E3_1 | E3_2 | E3_3 | E3_4 | E3_5 | E3_6 | E3_7 | E3_8
+ | E3_9 | E3_10 | E3_11 | E3_12 | E3_13 | E3_14 | E3_15 | E3_16
+ | E3_17 | E3_18 | E3_19 | E3_20 | E3_21 | E3_22 | E3_23 | E3_24
+ | E3_25 | E3_26 | E3_27 | E3_28 | E3_29 | E3_30 | E3_31 | E3_32
+ | E3_33 | E3_34 | E3_35 | E3_36 | E3_37 | E3_38 | E3_39 | E3_40
+ | E3_41 | E3_42 | E3_43 | E3_44 | E3_45 | E3_46 | E3_47 | E3_48
+ | E3_49 | E3_50 | E3_51 | E3_52 | E3_53 | E3_54 | E3_55 | E3_56
+ | E3_57 | E3_58 | E3_59 | E3_60 | E3_61 | E3_62 | E3_63 | E3_64
+ | E3_65 | E3_66 | E3_67 | E3_68 | E3_69 | E3_70 | E3_71 | E3_72
+ | E3_73 | E3_74 | E3_75 | E3_76 | E3_77 | E3_78 | E3_79 | E3_80
+ | E3_81 | E3_82 | E3_83 | E3_84 | E3_85 | E3_86 | E3_87 | E3_88
+ | E3_89 | E3_90 | E3_91 | E3_92 | E3_93 | E3_94 | E3_95 | E3_96
+ | E3_97 | E3_98 | E3_99 | E3_100 | E3_101 | E3_102 | E3_103 | E3_104
+ | E3_105 | E3_106 | E3_107 | E3_108 | E3_109 | E3_110 | E3_111 | E3_112
+ | E3_113 | E3_114 | E3_115 | E3_116 | E3_117 | E3_118 | E3_119 | E3_120
+ | E3_121 | E3_122 | E3_123 | E3_124 | E3_125 | E3_126 | E3_127 | E3_128
+ | E3_129 | E3_130 | E3_131 | E3_132 | E3_133 | E3_134 | E3_135 | E3_136
+ | E3_137 | E3_138 | E3_139 | E3_140 | E3_141 | E3_142 | E3_143 | E3_144
+ | E3_145 | E3_146 | E3_147 | E3_148 | E3_149 | E3_150 | E3_151 | E3_152
+ | E3_153 | E3_154 | E3_155 | E3_156 | E3_157 | E3_158 | E3_159 | E3_160
+ | E3_161 | E3_162 | E3_163 | E3_164 | E3_165 | E3_166 | E3_167 | E3_168
+ | E3_169 | E3_170 | E3_171 | E3_172 | E3_173 | E3_174 | E3_175 | E3_176
+ | E3_177 | E3_178 | E3_179 | E3_180 | E3_181 | E3_182 | E3_183 | E3_184
+ | E3_185 | E3_186 | E3_187 | E3_188 | E3_189 | E3_190 | E3_191 | E3_192
+ | E3_193 | E3_194 | E3_195 | E3_196 | E3_197 | E3_198 | E3_199 | E3_200
+ | E3_201 | E3_202 | E3_203 | E3_204 | E3_205 | E3_206 | E3_207 | E3_208
+ | E3_209 | E3_210 | E3_211 | E3_212 | E3_213 | E3_214 | E3_215 | E3_216
+ | E3_217 | E3_218 | E3_219 | E3_220 | E3_221 | E3_222 | E3_223 | E3_224
+ | E3_225 | E3_226 | E3_227 | E3_228 | E3_229 | E3_230 | E3_231 | E3_232
+ | E3_233 | E3_234 | E3_235 | E3_236 | E3_237 | E3_238 | E3_239 | E3_240
+ | E3_241 | E3_242 | E3_243 | E3_244 | E3_245 | E3_246 | E3_247 | E3_248
+ | E3_249 | E3_250 | E3_251 | E3_252 | E3_253 | E3_254 | E3_255 | E3_256
+ deriving (Enum, Bounded, Show)
+
+data U_Bool = U_Bool {-# UNPACK #-} !Bool
+ {-# UNPACK #-} !Bool
+ {-# UNPACK #-} !Bool
+ {-# UNPACK #-} !Bool
+ {-# UNPACK #-} !Bool
+ {-# UNPACK #-} !Bool
+ {-# UNPACK #-} !Bool
+ {-# UNPACK #-} !Bool
+ deriving (Show)
+
+data U_E1 = U_E1 {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E1
+ deriving (Show)
+
+data U_E2 = U_E2 {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E2
+ deriving (Show)
+
+data U_E3 = U_E3 {-# UNPACK #-} !E3
+ {-# UNPACK #-} !E3
+ {-# UNPACK #-} !E3
+ {-# UNPACK #-} !E3
+ {-# UNPACK #-} !E3
+ {-# UNPACK #-} !E3
+ {-# UNPACK #-} !E3
+ {-# UNPACK #-} !E3
+ deriving (Show)
+
+data U_Mixed = U_Mixed {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E1
+ {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E2
+ {-# UNPACK #-} !E3
+ {-# UNPACK #-} !E3
+ {-# UNPACK #-} !Bool
+ {-# UNPACK #-} !Bool
+ deriving (Show)
+
+data U_Maybe = U_Maybe {-# UNPACK #-} !(Maybe Bool)
+ {-# UNPACK #-} !(Maybe Bool)
+ {-# UNPACK #-} !(Maybe Bool)
+ {-# UNPACK #-} !(Maybe Bool)
+ {-# UNPACK #-} !(Maybe Bool)
+ {-# UNPACK #-} !(Maybe Bool)
+ {-# UNPACK #-} !(Maybe Bool)
+ {-# UNPACK #-} !(Maybe Bool)
+ deriving (Show)
+
+
+data MaybeW32 = NothingW32
+ | JustW32 {-# UNPACK #-} !Word32
+ deriving (Show)
+
+data U_MaybeW32 = U_MaybeW32 {-# UNPACK #-} !MaybeW32
+ {-# UNPACK #-} !MaybeW32
+ {-# UNPACK #-} !MaybeW32
+ {-# UNPACK #-} !MaybeW32
+ {-# UNPACK #-} !MaybeW32
+ {-# UNPACK #-} !MaybeW32
+ {-# UNPACK #-} !MaybeW32
+ {-# UNPACK #-} !MaybeW32
+ deriving (Show)
+
+u_ba :: U_Bool
+u_ba = U_Bool minBound maxBound minBound maxBound
+ minBound maxBound minBound maxBound
+
+u_e1a :: U_E1
+u_e1a = U_E1 minBound maxBound minBound maxBound
+ minBound maxBound minBound maxBound
+
+u_e1b :: U_E1
+u_e1b = U_E1 maxBound minBound maxBound minBound
+ maxBound minBound maxBound minBound
+
+u_e1c :: U_E1
+u_e1c = U_E1 E1_1 E1_2 E1_3 E1_4
+ E1_5 E1_6 E1_7 E1_8
+
+u_e1d :: U_E1
+u_e1d = U_E1 E1_1 E1_16 E1_32 E1_64
+ E1_127 E1_128 E1_250 E1_254
+
+u_e2a :: U_E2
+u_e2a = U_E2 minBound maxBound minBound maxBound
+ minBound maxBound minBound maxBound
+
+u_e3a :: U_E3
+u_e3a = U_E3 minBound maxBound minBound maxBound
+ minBound maxBound minBound maxBound
+
+u_mixed :: U_Mixed
+u_mixed = U_Mixed maxBound minBound maxBound minBound
+ maxBound minBound maxBound minBound
+
+u_maybe :: U_Maybe
+u_maybe = U_Maybe Nothing (Just False) Nothing (Just True)
+ Nothing (Just False) Nothing (Just True)
+
+u_maybeW32 :: U_MaybeW32
+u_maybeW32 = U_MaybeW32 NothingW32 (JustW32 minBound)
+ NothingW32 (JustW32 maxBound)
+ NothingW32 (JustW32 minBound)
+ NothingW32 (JustW32 maxBound)
+
+test :: Show a => String -> a -> IO ()
+test name value = do
+ putStrLn $ "\n### " ++ name
+ value' <- evaluate value
+ print value'
+ putStrLn ("size: " ++ show (closureSize $ asBox value'))
+
+main :: IO ()
+main = do
+ test "u_ba" u_ba
+ test "u_e1a" u_e1a
+ test "u_e1b" u_e1b
+ test "u_e1c" u_e1c
+ test "u_e1d" u_e1d
+ test "u_e2a" u_e2a
+ test "u_e3a" u_e3a
+ test "u_mixed" u_mixed
+ test "u_maybe" u_maybe
+ test "u_maybeW32" u_maybeW32
=====================================
testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout
=====================================
@@ -0,0 +1,40 @@
+
+### u_ba
+U_Bool False True False True False True False True
+size: 2
+
+### u_e1a
+U_E1 E1_1 E1_254 E1_1 E1_254 E1_1 E1_254 E1_1 E1_254
+size: 2
+
+### u_e1b
+U_E1 E1_254 E1_1 E1_254 E1_1 E1_254 E1_1 E1_254 E1_1
+size: 2
+
+### u_e1c
+U_E1 E1_1 E1_2 E1_3 E1_4 E1_5 E1_6 E1_7 E1_8
+size: 2
+
+### u_e1d
+U_E1 E1_1 E1_16 E1_32 E1_64 E1_127 E1_128 E1_250 E1_254
+size: 2
+
+### u_e2a
+U_E2 E2_1 E2_255 E2_1 E2_255 E2_1 E2_255 E2_1 E2_255
+size: 2
+
+### u_e3a
+U_E3 E3_1 E3_256 E3_1 E3_256 E3_1 E3_256 E3_1 E3_256
+size: 3
+
+### u_mixed
+U_Mixed E1_254 E1_1 E2_255 E2_1 E3_256 E3_1 True False
+size: 3
+
+### u_maybe
+U_Maybe Nothing (Just False) Nothing (Just True) Nothing (Just False) Nothing (Just True)
+size: 10
+
+### u_maybeW32
+U_MaybeW32 NothingW32 (JustW32 0) NothingW32 (JustW32 4294967295) NothingW32 (JustW32 0) NothingW32 (JustW32 4294967295)
+size: 9
=====================================
testsuite/tests/unboxedsums/UbxSumUnpackedSize.stdout-ws-32
=====================================
@@ -0,0 +1,40 @@
+
+### u_ba
+U_Bool False True False True False True False True
+size: 3
+
+### u_e1a
+U_E1 E1_1 E1_254 E1_1 E1_254 E1_1 E1_254 E1_1 E1_254
+size: 3
+
+### u_e1b
+U_E1 E1_254 E1_1 E1_254 E1_1 E1_254 E1_1 E1_254 E1_1
+size: 3
+
+### u_e1c
+U_E1 E1_1 E1_2 E1_3 E1_4 E1_5 E1_6 E1_7 E1_8
+size: 3
+
+### u_e1d
+U_E1 E1_1 E1_16 E1_32 E1_64 E1_127 E1_128 E1_250 E1_254
+size: 3
+
+### u_e2a
+U_E2 E2_1 E2_255 E2_1 E2_255 E2_1 E2_255 E2_1 E2_255
+size: 3
+
+### u_e3a
+U_E3 E3_1 E3_256 E3_1 E3_256 E3_1 E3_256 E3_1 E3_256
+size: 5
+
+### u_mixed
+U_Mixed E1_254 E1_1 E2_255 E2_1 E3_256 E3_1 True False
+size: 4
+
+### u_maybe
+U_Maybe Nothing (Just False) Nothing (Just True) Nothing (Just False) Nothing (Just True)
+size: 11
+
+### u_maybeW32
+U_MaybeW32 NothingW32 (JustW32 0) NothingW32 (JustW32 4294967295) NothingW32 (JustW32 0) NothingW32 (JustW32 4294967295)
+size: 17
=====================================
testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs
=====================================
@@ -63,33 +63,33 @@ layout_tests = sequence_
assert_layout "layout1"
[ ubxtup [ intTy, intPrimTy ]
, ubxtup [ intPrimTy, intTy ] ]
- [ WordSlot, PtrLiftedSlot, WordSlot ]
+ [ Word8Slot, PtrLiftedSlot, WordSlot ]
layout2 =
assert_layout "layout2"
[ ubxtup [ intTy ]
, intTy ]
- [ WordSlot, PtrLiftedSlot ]
+ [ Word8Slot, PtrLiftedSlot ]
layout3 =
assert_layout "layout3"
[ ubxtup [ intTy, intPrimTy, intTy, intPrimTy ]
, ubxtup [ intPrimTy, intTy, intPrimTy, intTy ] ]
- [ WordSlot, PtrLiftedSlot, PtrLiftedSlot, WordSlot, WordSlot ]
+ [ Word8Slot, PtrLiftedSlot, PtrLiftedSlot, WordSlot, WordSlot ]
layout4 =
assert_layout "layout4"
[ ubxtup [ floatPrimTy, floatPrimTy ]
, ubxtup [ intPrimTy, intPrimTy ] ]
- [ WordSlot, WordSlot, WordSlot, FloatSlot, FloatSlot ]
+ [ Word8Slot, WordSlot, WordSlot, FloatSlot, FloatSlot ]
layout5 =
assert_layout "layout5"
[ ubxtup [ intPrimTy, intPrimTy ]
, ubxtup [ floatPrimTy, floatPrimTy ] ]
- [ WordSlot, WordSlot, WordSlot, FloatSlot, FloatSlot ]
+ [ Word8Slot, WordSlot, WordSlot, FloatSlot, FloatSlot ]
enum_layout =
assert_layout "enum"
(replicate 10 (ubxtup []))
- [ WordSlot ]
+ [ Word8Slot ]
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/77d94fb362bf155f2589f5df2a063b…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/77d94fb362bf155f2589f5df2a063b…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/teo/move-out-bits-of-th-from-ghc-internal] 17 commits: Extend record-selector usage ticking to all binds using a record field
by Teo Camarasu (@teo) 14 Aug '25
by Teo Camarasu (@teo) 14 Aug '25
14 Aug '25
Teo Camarasu pushed to branch wip/teo/move-out-bits-of-th-from-ghc-internal at Glasgow Haskell Compiler / GHC
Commits:
62899117 by Florian Ragwitz at 2025-08-13T21:01:34-04:00
Extend record-selector usage ticking to all binds using a record field
This extends the previous handling of ticking for RecordWildCards and
NamedFieldPuns to all var bindings that involve record selectors.
Note that certain patterns such as `Foo{foo = 42}` will currently not tick the
`foo` selector, as ticking is triggered by `HsVar`s.
Closes #26191.
- - - - -
b37b3af7 by Florian Ragwitz at 2025-08-13T21:01:34-04:00
Add release notes for 9.16.1 and move description of latest HPC changes there.
- - - - -
a5e4b7d9 by Ben Gamari at 2025-08-13T21:02:18-04:00
rts: Clarify rationale for undefined atomic wrappers
Since c06e3f46d24ef69f3a3d794f5f604cb8c2a40cbc the RTS has declared
various atomic operation wrappers defined by ghc-internal as undefined.
While the rationale for this isn't clear from the commit message, I
believe that this is necessary due to the unregisterised backend.
Specifically, the code generator will reference these symbols when
compiling RTS Cmm sources.
- - - - -
50842f83 by Andreas Klebinger at 2025-08-13T21:03:01-04:00
Make unexpected LLVM versions a warning rather than an error.
Typically a newer LLVM version *will* work so erroring out if
a user uses a newer LLVM version is too aggressive.
Fixes #25915
- - - - -
c91e2650 by fendor at 2025-08-13T21:03:43-04:00
Store `StackTrace` and `StackSnapshot` in `Backtraces`
Instead of decoding the stack traces when collecting the `Backtraces`,
defer this decoding until actually showing the `Backtraces`.
This allows users to customise how `Backtraces` are displayed by
using a custom implementation of `displayExceptionWithInfo`, overwriting
the default implementation for `Backtraces` (`displayBacktraces`).
- - - - -
dee28cdd by fendor at 2025-08-13T21:03:43-04:00
Allow users to customise the collection of exception annotations
Add a global `CollectExceptionAnnotationMechanism` which determines how
`ExceptionAnnotation`s are collected upon throwing an `Exception`.
This API is exposed via `ghc-experimental`.
By overriding how we collect `Backtraces`, we can control how the
`Backtraces` are displayed to the user by newtyping `Backtraces` and
giving a different instance for `ExceptionAnnotation`.
A concrete use-case for this feature is allowing us to experiment with
alternative stack decoders, without having to modify `base`, which take
additional information from the stack frames.
This commit does not modify how `Backtraces` are currently
collected or displayed.
- - - - -
66024722 by fendor at 2025-08-13T21:03:43-04:00
Expose Backtraces internals from ghc-experimental
Additionally, expose the same API `base:Control.Exception.Backtrace`
to make it easier to use as a drop-in replacement.
- - - - -
a766286f by Reed Mullanix at 2025-08-13T21:04:36-04:00
ghc-internal: Fix naturalAndNot for NB/NS case
When the first argument to `naturalAndNot` is larger than a `Word` and the second is `Word`-sized, `naturalAndNot` will truncate the
result:
```
>>> naturalAndNot ((2 ^ 65) .|. (2 ^ 3)) (2 ^ 3)
0
```
In contrast, `naturalAndNot` does not truncate when both arguments are larger than a `Word`, so this appears to be a bug.
Luckily, the fix is pretty easy: we just need to call `bigNatAndNotWord#` instead of truncating.
Fixes #26230
- - - - -
3506fa7d by Simon Hengel at 2025-08-13T21:05:18-04:00
Report -pgms as a deprecated flag
(instead of reporting an unspecific warning)
Before:
on the commandline: warning:
Object splitting was removed in GHC 8.8
After:
on the commandline: warning: [GHC-53692] [-Wdeprecated-flags]
-pgms is deprecated: Object splitting was removed in GHC 8.8
- - - - -
51c701fe by Zubin Duggal at 2025-08-13T21:06:00-04:00
testsuite: Be more permissive when filtering out GNU_PROPERTY_TYPE linker warnings
The warning text is slightly different with ld.bfd.
Fixes #26249
- - - - -
dfe6f464 by Simon Hengel at 2025-08-13T21:06:43-04:00
Refactoring: Don't misuse `MCDiagnostic` for lint messages
`MCDiagnostic` is meant to be used for compiler diagnostics.
Any code that creates `MCDiagnostic` directly, without going through
`GHC.Driver.Errors.printMessage`, side steps `-fdiagnostics-as-json`
(see e.g. !14475, !14492 !14548).
To avoid this in the future I want to control more narrowly who creates
`MCDiagnostic` (see #24113).
Some parts of the compiler use `MCDiagnostic` purely for formatting
purposes, without creating any real compiler diagnostics. This change
introduces a helper function, `formatDiagnostic`, that can be used in
such cases instead of constructing `MCDiagnostic`.
- - - - -
a8b2fbae by Teo Camarasu at 2025-08-13T21:07:24-04:00
rts: ensure MessageBlackHole.link is always a valid closure
We turn a MessageBlackHole into an StgInd in wakeBlockingQueue().
Therefore it's important that the link field, which becomes the
indirection field, always points to a valid closure.
It's unclear whether it's currently possible for the previous behaviour
to lead to a crash, but it's good to be consistent about this invariant nonetheless.
Co-authored-by: Andreas Klebinger <klebinger.andreas(a)gmx.at>
- - - - -
4021181e by Teo Camarasu at 2025-08-13T21:07:24-04:00
rts: spin if we see a WHITEHOLE in messageBlackHole
When a BLACKHOLE gets cancelled in raiseAsync, we indirect to a THUNK.
GC can then shortcut this, replacing our BLACKHOLE with a fresh THUNK.
This THUNK is not guaranteed to have a valid indirectee field.
If at the same time, a message intended for the previous BLACKHOLE is
processed and concurrently we BLACKHOLE the THUNK, thus temporarily
turning it into a WHITEHOLE, we can get a segfault, since we look at the
undefined indirectee field of the THUNK
The fix is simple: spin if we see a WHITEHOLE, and it will soon be
replaced with a valid BLACKHOLE.
Resolves #26205
- - - - -
1107af89 by Oleg Grenrus at 2025-08-13T21:08:06-04:00
Allow defining HasField instances for naughty fields
Resolves #26295
... as HasField solver doesn't solve for fields with "naughty"
selectors, we could as well allow defining HasField instances for these
fields.
- - - - -
020e7587 by Sylvain Henry at 2025-08-13T21:09:00-04:00
Fix Data.List unqualified import warning
- - - - -
615dcdd5 by Teo Camarasu at 2025-08-14T09:21:53+00:00
template-haskell: move some identifiers from ghc-internal to template-haskell
These identifiers are not used internally by the compiler. Therefore we
have no reason for them to be in ghc-internal.
By moving them to template-haskell, we benefit from it being easier to
change them and we avoid having to build them in stage0.
Resolves #26048
- - - - -
a22d532f by Teo Camarasu at 2025-08-14T09:21:53+00:00
template-haskell: transfer $infix note to public module
This Haddock note should be in the public facing module
- - - - -
71 changed files:
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Stg/Lint.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/Types/Error.hs
- compiler/GHC/Utils/Error.hs
- − docs/users_guide/9.14.1-notes.rst
- + docs/users_guide/9.16.1-notes.rst
- docs/users_guide/release-notes.rst
- libraries/base/changelog.md
- libraries/ghc-bignum/changelog.md
- + libraries/ghc-experimental/src/GHC/Exception/Backtrace/Experimental.hs
- libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs
- libraries/ghc-internal/src/GHC/Internal/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs-boot
- 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/Syntax.hs
- + libraries/ghc-internal/tests/Makefile
- + libraries/ghc-internal/tests/all.T
- + libraries/ghc-internal/tests/backtraces/Makefile
- + libraries/ghc-internal/tests/backtraces/T14532a.hs
- + libraries/ghc-internal/tests/backtraces/T14532a.stdout
- + libraries/ghc-internal/tests/backtraces/T14532b.hs
- + libraries/ghc-internal/tests/backtraces/T14532b.stdout
- + libraries/ghc-internal/tests/backtraces/all.T
- 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/tests/all.T
- rts/Messages.c
- rts/StgMiscClosures.cmm
- rts/Updates.h
- rts/external-symbols.list.in
- rts/rts.cabal
- testsuite/driver/testlib.py
- testsuite/tests/arrows/should_compile/T21301.stderr
- testsuite/tests/deSugar/should_fail/DsStrictFail.stderr
- testsuite/tests/deSugar/should_run/T20024.stderr
- testsuite/tests/deSugar/should_run/dsrun005.stderr
- testsuite/tests/deSugar/should_run/dsrun007.stderr
- testsuite/tests/deSugar/should_run/dsrun008.stderr
- testsuite/tests/deriving/should_run/T9576.stderr
- testsuite/tests/ghci/scripts/Defer02.stderr
- testsuite/tests/ghci/scripts/T15325.stderr
- testsuite/tests/hpc/recsel/recsel.hs
- testsuite/tests/hpc/recsel/recsel.stdout
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- + testsuite/tests/numeric/should_run/T26230.hs
- + testsuite/tests/numeric/should_run/T26230.stdout
- testsuite/tests/numeric/should_run/all.T
- + testsuite/tests/overloadedrecflds/should_run/T26295.hs
- + testsuite/tests/overloadedrecflds/should_run/T26295.stdout
- testsuite/tests/overloadedrecflds/should_run/all.T
- testsuite/tests/patsyn/should_run/ghci.stderr
- testsuite/tests/quasiquotation/T4491/test.T
- testsuite/tests/quotes/LiftErrMsgDefer.stderr
- testsuite/tests/safeHaskell/safeLanguage/SafeLang15.stderr
- testsuite/tests/th/Makefile
- testsuite/tests/type-data/should_run/T22332a.stderr
- testsuite/tests/typecheck/should_run/T10284.stderr
- testsuite/tests/typecheck/should_run/T13838.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/unsatisfiable/T23816.stderr
- testsuite/tests/unsatisfiable/UnsatDefer.stderr
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4652e8b72d87f308333b4d8adf8f5d…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4652e8b72d87f308333b4d8adf8f5d…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: Make injecting implicit bindings into its own pass
by Marge Bot (@marge-bot) 14 Aug '25
by Marge Bot (@marge-bot) 14 Aug '25
14 Aug '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
eca24ea0 by Simon Peyton Jones at 2025-08-14T00:06:30-04:00
Make injecting implicit bindings into its own pass
Previously we were injecting "impliicit bindings" (data constructor
worker and wrappers etc)
- both at the end of CoreTidy,
- and at the start of CorePrep
This is unpleasant and confusing. This patch puts it it its own pass,
addImplicitBinds, which runs between the two.
The function `GHC.CoreToStg.AddImplicitBinds.addImplicitBinds` now takes /all/
TyCons, not just the ones for algebraic data types. That change ripples
through to
- corePrepPgm
- doCodeGen
- byteCodeGen
All take [TyCon] which includes all TyCons
- - - - -
e465c52f by Simon Peyton Jones at 2025-08-14T00:06:30-04:00
Implement unary classes
The big change is described exhaustively in
Note [Unary class magic] in GHC.Core.TyCon
Other changes
* We never unbox class dictionaries in worker/wrapper. This has been true for some
time now, but the logic is now centralised in functions in
GHC.Core.Opt.WorkWrap.Utils, namely `canUnboxTyCon`, and `canUnboxArg`
See Note [Do not unbox class dictionaries] in GHC.Core.Opt.WorkWrap.Utils.
* Refactored the `notWorthFloating` logic in GHc.Core.Opt.SetLevels.
I can't remember if I actually changed any behaviour here, but if so it's
only in a corner cases.
* Fixed a bug in `GHC.Core.TyCon.isEnumerationTyCon`, which was wrongly returning
True for (##).
* Remove redundant Role argument to `liftCoSubstWithEx`. It was always
Representational.
* I refactored evidence generation in the constraint solver:
* Made GHC.Tc.Types.Evidence contain better abstactions for evidence
generation.
* I deleted the file `GHC.Tc.Types.EvTerm` and merged its (small) contents
elsewhere. It wasn't paying its way.
* Made evidence for implicit parameters go via a proper abstraction.
* Fix inlineBoringOk; see (IB6) in Note [inlineBoringOk]
This fixes a slowdown in `countdownEffectfulDynLocal`
in the `effectful` library.
Smaller things
* Rename `isDataTyCon` to `isBoxedDataTyCon`.
* GHC.Core.Corecion.liftCoSubstWithEx was only called with Representational role,
so I baked that into the function and removed the argument.
* Get rid of `GHC.Core.TyCon.tyConSingleAlgDataCon_maybe` in favour of calling
`not isNewTyCon` at the call sites; more explicit.
* Refatored `GHC.Core.TyCon.isInjectiveTyCon`; but I don't think I changed its
behaviour
* Moved `decomposeIPPred` to GHC.Core.Predicate
Compile time performance changes:
geo. mean +0.1%
minimum -6.8%
maximum +14.4%
The +14% one is in T21839c, where it seems that a bit more inlining
is taking place. That seems acceptable; and the average change is small
Metric Decrease:
LargeRecord
T12227
T12707
T16577
T21839r
T5642
Metric Increase:
T15164
T21839c
T3294
T5321FD
T5321Fun
WWRec
- - - - -
790a101c by Simon Peyton Jones at 2025-08-14T00:06:30-04:00
Slight improvement to pre/postInlineUnconditionally
Avoids an extra simplifier iteration
- - - - -
b1e5526d by Simon Peyton Jones at 2025-08-14T00:06:30-04:00
Fix a long-standing assertion error in normSplitTyConApp_maybe
- - - - -
00b889ee by Simon Peyton Jones at 2025-08-14T00:06:30-04:00
Add comment to coercion optimiser
- - - - -
a3707288 by Recursion Ninja at 2025-08-14T00:06:31-04:00
Resolving issues #20645 and #26109
Correctly sign extending and casting smaller bit width types for LLVM operations:
- bitReverse8#
- bitReverse16#
- bitReverse32#
- byteSwap16#
- byteSwap32#
- pdep8#
- pdep16#
- pext8#
- pext16#
- - - - -
442d1cae by Sylvain Henry at 2025-08-14T00:06:51-04:00
JS: export HEAP8 symbol (#26290)
Newer Emscripten requires this.
- - - - -
ae51e370 by Cheng Shao at 2025-08-14T00:06:52-04:00
hadrian: enforce have_llvm=False for wasm32/js
This patch fixes hadrian to always pass have_llvm=False to the
testsuite driver for wasm32/js targets. These targets don't really
support the LLVM backend, and the optllvm test way doesn't work. We
used to special-case wasm32/js to avoid auto-adding optllvm way in
testsuite/config/ghc, but this is still problematic if someone writes
a new LLVM-related test and uses something like when(have_llvm(),
extra_ways(["optllvm"])). So better just enforce have_llvm=False for
these targets here.
- - - - -
112 changed files:
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unfold.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg.hs
- + compiler/GHC/CoreToStg/AddImplicitBinds.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/Call.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Instance/Family.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- − compiler/GHC/Tc/Types/EvTerm.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/RepType.hs
- compiler/GHC/Types/TyThing.hs
- compiler/ghc.cabal.in
- hadrian/src/Settings/Builders/RunTest.hs
- libraries/ghc-internal/cbits/pdep.c
- libraries/ghc-internal/cbits/pext.c
- rts/js/mem.js
- testsuite/config/ghc
- testsuite/driver/testlib.py
- testsuite/tests/core-to-stg/T24124.stderr
- testsuite/tests/deSugar/should_compile/T2431.stderr
- testsuite/tests/dmdanal/should_compile/T16029.stdout
- testsuite/tests/dmdanal/sigs/T21119.stderr
- testsuite/tests/dmdanal/sigs/T21888.stderr
- testsuite/tests/ghci.debugger/scripts/break011.stdout
- testsuite/tests/ghci.debugger/scripts/break024.stdout
- testsuite/tests/indexed-types/should_compile/T2238.hs
- + testsuite/tests/llvm/should_run/T20645.hs
- + testsuite/tests/llvm/should_run/T20645.stdout
- testsuite/tests/llvm/should_run/all.T
- testsuite/tests/numeric/should_compile/T15547.stderr
- testsuite/tests/numeric/should_compile/T23907.stderr
- testsuite/tests/numeric/should_run/foundation.hs
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/simplCore/should_compile/DataToTagFamilyScrut.stderr
- testsuite/tests/simplCore/should_compile/T15205.stderr
- testsuite/tests/simplCore/should_compile/T17366.stderr
- testsuite/tests/simplCore/should_compile/T17966.stderr
- testsuite/tests/simplCore/should_compile/T22309.stderr
- testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr
- testsuite/tests/simplCore/should_compile/T23307.stderr
- testsuite/tests/simplCore/should_compile/T23307a.stderr
- testsuite/tests/simplCore/should_compile/T25389.stderr
- testsuite/tests/simplCore/should_compile/T25713.stderr
- testsuite/tests/simplCore/should_compile/T7360.stderr
- testsuite/tests/simplStg/should_compile/T15226b.stderr
- testsuite/tests/tcplugins/CtIdPlugin.hs
- testsuite/tests/typecheck/should_compile/Makefile
- testsuite/tests/typecheck/should_compile/T12763.stderr
- testsuite/tests/typecheck/should_compile/T14774.stdout
- testsuite/tests/typecheck/should_compile/T18406b.stderr
- testsuite/tests/typecheck/should_compile/T18529.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/unboxedsums/unpack_sums_7.stdout
- testsuite/tests/wasm/should_run/control-flow/LoadCmmGroup.hs
- testsuite/tests/wasm/should_run/control-flow/RunWasm.hs
- utils/genprimopcode/Lexer.x
- utils/genprimopcode/Main.hs
- utils/genprimopcode/Parser.y
- utils/genprimopcode/ParserM.hs
- utils/genprimopcode/Syntax.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2d2a971afc33955ed7bcc88dc06b97…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2d2a971afc33955ed7bcc88dc06b97…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/symbolizer] 120 commits: compiler: Import AnnotationWrapper from ghc-internal
by Cheng Shao (@TerrorJack) 13 Aug '25
by Cheng Shao (@TerrorJack) 13 Aug '25
13 Aug '25
Cheng Shao pushed to branch wip/symbolizer at Glasgow Haskell Compiler / GHC
Commits:
67957854 by Ben Gamari at 2025-07-09T09:44:44-04:00
compiler: Import AnnotationWrapper from ghc-internal
Since `GHC.Desugar` exported from `base` has been deprecated.
- - - - -
813d99d6 by Ben Gamari at 2025-07-09T09:44:44-04:00
ghc-compact: Eliminate dependency on ghc-prim
- - - - -
0ec952a1 by Ben Gamari at 2025-07-09T09:44:44-04:00
ghc-heap: Eliminate dependency on ghc-prim
- - - - -
480074c3 by Ben Gamari at 2025-07-09T09:44:44-04:00
ghc-heap: Drop redundant import
- - - - -
03455829 by Ben Gamari at 2025-07-09T09:44:45-04:00
ghc-prim: Bump version to 0.13.1
There are no interface changes from 0.13.0 but the implementation now
lives in `ghc-internal`.
- - - - -
d315345a by Ben Gamari at 2025-07-09T09:44:45-04:00
template-haskell: Bump version number to 2.24.0.0
Bumps exceptions submodule.
- - - - -
004c800e by Ben Gamari at 2025-07-09T09:44:45-04:00
Bump GHC version number to 9.14
- - - - -
eb1a3816 by Ben Gamari at 2025-07-09T09:44:45-04:00
Bump parsec to 3.1.18.0
Bumps parsec submodule.
- - - - -
86f83296 by Ben Gamari at 2025-07-09T09:44:45-04:00
unix: Bump to 2.8.7.0
Bumps unix submodule.
- - - - -
89e13998 by Ben Gamari at 2025-07-09T09:44:45-04:00
binary: Bump to 0.8.9.3
Bumps binary submodule.
- - - - -
55fff191 by Ben Gamari at 2025-07-09T09:44:45-04:00
Win32: Bump to 2.14.2.0
Bumps Win32 submodule.
- - - - -
7dafa40c by Ben Gamari at 2025-07-09T09:44:45-04:00
base: Bump version to 4.22.0
Bumps various submodules.
- - - - -
ef03d8b8 by Rodrigo Mesquita at 2025-07-09T09:45:28-04:00
base: Export displayExceptionWithInfo
This function should be exposed from base following CLC#285
Approved change in CLC#344
Fixes #26058
- - - - -
01d3154e by Wen Kokke at 2025-07-10T17:06:36+01:00
Fix documentation for HEAP_PROF_SAMPLE_STRING
- - - - -
ac259c48 by Wen Kokke at 2025-07-10T17:06:38+01:00
Fix documentation for HEAP_PROF_SAMPLE_COST_CENTRE
- - - - -
2b4db9ba by Pi Delport at 2025-07-11T16:40:52-04:00
(Applicative docs typo: missing "one")
- - - - -
f707bab4 by Andreas Klebinger at 2025-07-12T14:56:16+01:00
Specialise: Improve specialisation by refactoring interestingDict
This MR addresses #26051, which concerns missed type-class specialisation.
The main payload of the MR is to completely refactor the key function
`interestingDict` in GHC.Core.Opt.Specialise
The main change is that we now also look at the structure of the
dictionary we consider specializing on, rather than only the type.
See the big `Note [Interesting dictionary arguments]`
- - - - -
ca7a9d42 by Simon Peyton Jones at 2025-07-12T14:56:16+01:00
Treat tuple dictionaries uniformly; don't unbox them
See `Note [Do not unbox class dictionaries]` in DmdAnal.hs,
sep (DNB1).
This MR reverses the plan in #23398, which suggested a special case to
unbox tuple dictionaries in worker/wrapper. But:
- This was the cause of a pile of complexity in the specialiser (#26158)
- Even with that complexity, specialision was still bad, very bad
See https://gitlab.haskell.org/ghc/ghc/-/issues/19747#note_626297
And it's entirely unnecessary! Specialision works fine without
unboxing tuple dictionaries.
- - - - -
be7296c9 by Andreas Klebinger at 2025-07-12T14:56:16+01:00
Remove complex special case from the type-class specialiser
There was a pretty tricky special case in Specialise which is no
longer necessary.
* Historical Note [Floating dictionaries out of cases]
* #26158
* #19747 https://gitlab.haskell.org/ghc/ghc/-/issues/19747#note_626297
This MR removes it. Hooray.
- - - - -
4acf3a86 by Ben Gamari at 2025-07-15T05:46:32-04:00
configure: bump version to 9.15
- - - - -
45efaf71 by Teo Camarasu at 2025-07-15T05:47:13-04:00
rts/nonmovingGC: remove n_free
We remove the nonmovingHeap.n_free variable.
We wanted this to track the length of nonmovingHeap.free.
But this isn't possible to do atomically.
When this isn't accurate we can get a segfault by going past the end of
the list.
Instead, we just count the length of the list when we grab it in
nonmovingPruneFreeSegment.
Resolves #26186
- - - - -
c635f164 by Ben Gamari at 2025-07-15T14:05:54-04:00
configure: Drop probing of ld.gold
As noted in #25716, `gold` has been dropped from binutils-2.44.
Fixes #25716.
Metric Increase:
size_hello_artifact_gzip
size_hello_unicode_gzip
ghc_prim_so
- - - - -
637bb538 by Ben Gamari at 2025-07-15T14:05:55-04:00
testsuite/recomp015: Ignore stderr
This is necessary since ld.bfd complains
that we don't have a .note.GNU-stack section,
potentially resulting in an executable stack.
- - - - -
d3cd4ec8 by Wen Kokke at 2025-07-15T14:06:39-04:00
Fix documentation for heap profile ID
- - - - -
73082769 by Ben Gamari at 2025-07-15T16:56:38-04:00
Bump win32-tarballs to v0.9
- - - - -
3b63b254 by Ben Gamari at 2025-07-15T16:56:39-04:00
rts/LoadArchive: Handle null terminated string tables
As of `llvm-ar` now emits filename tables terminated with null
characters instead of the usual POSIX `/\n` sequence.
Fixes #26150.
- - - - -
195f6527 by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: rename label so name doesn't conflict with param
- - - - -
63373b95 by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Handle API set symbol versioning conflicts
- - - - -
48e9aa3e by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Mark API set symbols as HIDDEN and correct symbol type
- - - - -
959e827a by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Implement WEAK EXTERNAL undef redirection by target symbol name
- - - - -
65f19293 by Ben Gamari at 2025-07-15T16:56:39-04:00
rts/LoadArchive: Handle string table entries terminated with /
llvm-ar appears to terminate string table entries with `/\n` [1]. This
matters in the case of thin archives, since the filename is used. In the
past this worked since `llvm-ar` would produce archives with "small"
filenames when possible. However, now it appears to always use the
string table.
[1] https://github.com/llvm/llvm-project/blob/bfb686bb5ba503e9386dc899e1ebbe248…
- - - - -
9cbb3ef5 by Ben Gamari at 2025-07-15T16:56:39-04:00
testsuite: Mark T12497 as fixed
Thanks to the LLVM toolchain update.
Closes #22694.
- - - - -
2854407e by Ben Gamari at 2025-07-15T16:56:39-04:00
testsuite: Accept new output of T11223_link_order_a_b_2_fail on Windows
The archive member number changed due to the fact that llvm-ar now uses a
string table.
- - - - -
28439593 by Ben Gamari at 2025-07-15T16:56:39-04:00
rts/linker/PEi386: Implement IMAGE_REL_AMD64_SECREL
This appears to now be used by libc++ as distributed by msys2.
- - - - -
2b053755 by Tamar Christina at 2025-07-15T16:56:39-04:00
rts: Cleanup merge resolution residue in lookupSymbolInDLL_PEi386 and make safe without dependent
- - - - -
e8acd2e7 by Wen Kokke at 2025-07-16T08:37:04-04:00
Remove the `profile_id` parameter from various RTS functions.
Various RTS functions took a `profile_id` parameter, intended to be used to
distinguish parallel heap profile breakdowns (e.g., `-hT` and `-hi`). However,
this feature was never implemented and the `profile_id` parameter was set to 0
throughout the RTS. This commit removes the parameter but leaves the hardcoded
profile ID in the functions that emit the encoded eventlog events as to not
change the protocol.
The affected functions are `traceHeapProfBegin`, `postHeapProfBegin`,
`traceHeapProfSampleString`, `postHeapProfSampleString`,
`traceHeapProfSampleCostCentre`, and `postHeapProfSampleCostCentre`.
- - - - -
76d392a2 by Wen Kokke at 2025-07-16T08:37:04-04:00
Make `traceHeapProfBegin` an init event.
- - - - -
bbaa44a7 by Peng Fan at 2025-07-16T16:50:42-04:00
NCG/LA64: Support finer-grained DBAR hints
For LA664 and newer uarchs, they have made finer granularity hints
available:
Bit4: ordering or completion (0: completion, 1: ordering)
Bit3: barrier for previous read (0: true, 1: false)
Bit2: barrier for previous write (0: true, 1: false)
Bit1: barrier for succeeding read (0: true, 1: false)
Bit0: barrier for succeeding write (0: true, 1: false)
And not affect the existing models because other hints are treated
as 'dbar 0' there.
- - - - -
7da86e16 by Andreas Klebinger at 2025-07-16T16:51:25-04:00
Disable -fprof-late-overloaded-calls for join points.
Currently GHC considers cost centres as destructive to
join contexts. Or in other words this is not considered valid:
join f x = ...
in
... -> scc<tick> jmp
This makes the functionality of `-fprof-late-overloaded-calls` not feasible
for join points in general. We used to try to work around this by putting the
ticks on the rhs of the join point rather than around the jump. However beyond
the loss of accuracy this was broken for recursive join points as we ended up
with something like:
rec-join f x = scc<tick> ... jmp f x
Which similarly is not valid as the tick once again destroys the tail call.
One might think we could limit ourselves to non-recursive tail calls and do
something clever like:
join f x = scc<tick> ...
in ... jmp f x
And sometimes this works! But sometimes the full rhs would look something like:
join g x = ....
join f x = scc<tick> ... -> jmp g x
Which, would again no longer be valid. I believe in the long run we can make
cost centre ticks non-destructive to join points. Or we could keep track of
where we are/are not allowed to insert a cost centre. But in the short term I will
simply disable the annotation of join calls under this flag.
- - - - -
7ee22fd5 by ARATA Mizuki at 2025-07-17T06:05:30-04:00
x86 NCG: Better lowering for shuffleFloatX4# and shuffleDoubleX2#
The new implementation
* make use of specialized instructions like (V)UNPCK{L,H}{PS,PD}, and
* do not require -mavx.
Close #26096
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
- - - - -
c6cd2da1 by Jappie Klooster at 2025-07-17T06:06:20-04:00
Update interact docs to explain about buffering
We need to tell the user to set to the
appropriate buffer format.
Otherwise, this function may get randomly stuck,
or just behave confusingly.
issue: https://gitlab.haskell.org/ghc/ghc/-/issues/26131
NB, I'm running this with cabal *NOT* ghci. ghci messes with buffering anyway.
```haskell
interaction :: String -> String
interaction "jappie" = "hi"
interaction "jakob" = "hello"
interaction x = "unkown input: " <> x
main :: IO ()
main = interact interaction
```
so in my input (prefixed by `>`) I get:
```
> jappie
unkown input: jappie
```
we confirmed later this was due to lack of \n matching.
Anyway movnig on to more unexpected stuff:
```haskell
main :: IO ()
main = do
interact (concatMap interaction . lines)
```
get's stuck forever.
actually `^D` (ctrl+d) unstucks it and runs all input as expected.
for example you can get:
```
> sdfkds
> fakdsf
unkown input: sdfkdsunkown input: fakdsf
```
This program works!
```haskell
interaction :: String -> String
interaction "jappie" = "hi \n"
interaction "jakob" = "hello \n"
interaction x = "unkown input: " <> x <> "\n"
main :: IO ()
main = do
interact (concatMap interaction . lines)
```
the reason is that linebuffering is set for both in and output by default.
so lines eats the input lines, and all the \n postfixes make sure the buffer
is put out.
- - - - -
9fa590a6 by Zubin Duggal at 2025-07-17T06:07:03-04:00
fetch_gitlab: Ensure we copy users_guide.pdf and Haddock.pdf to the release docs directory
Fixes #24093
- - - - -
cc650b4b by Andrew Lelechenko at 2025-07-17T12:30:24-04:00
Add Data.List.NonEmpty.mapMaybe
As per https://github.com/haskell/core-libraries-committee/issues/337
- - - - -
360fa82c by Duncan Coutts at 2025-07-17T12:31:14-04:00
base: Deprecate GHC.Weak.Finalize.runFinalizerBatch
https://github.com/haskell/core-libraries-committee/issues/342
- - - - -
f4e8466c by Alan Zimmerman at 2025-07-17T12:31:55-04:00
EPA: Update exact printing based on GHC 9.14 tests
As a result of migrating the GHC ghc-9.14 branch tests to
ghc-exactprint in
https://github.com/alanz/ghc-exactprint/tree/ghc-9.14, a couple of
discrepancies were picked up
- The opening paren for a DefaultDecl was printed in the wrong place
- The import declaration level specifiers were not printed.
This commit adds those fixes, and some tests for them.
The tests brought to light that the ImportDecl ppr instance had not
been updated for level specifiers, so it updates that too.
- - - - -
8b731e3c by Matthew Pickering at 2025-07-21T13:36:43-04:00
level imports: Fix infinite loop with cyclic module imports
I didn't anticipate that downsweep would run before we checked for
cyclic imports. Therefore we need to use the reachability function which
handles cyclic graphs.
Fixes #26087
- - - - -
d751a9f1 by Pierre Thierry at 2025-07-21T13:37:28-04:00
Fix documentation about deriving from generics
- - - - -
f8d9d016 by Andrew Lelechenko at 2025-07-22T21:13:28-04:00
Fix issues with toRational for types capable to represent infinite and not-a-number values
This commit fixes all of the following pitfalls:
> toRational (read "Infinity" :: Double)
179769313486231590772930519078902473361797697894230657273430081157732675805500963132708477322407536021120113879871393357658789768814416622492847430639474124377767893424865485276302219601246094119453082952085005768838150682342462881473913110540827237163350510684586298239947245938479716304835356329624224137216 % 1
> toRational (read "NaN" :: Double)
269653970229347386159395778618353710042696546841345985910145121736599013708251444699062715983611304031680170819807090036488184653221624933739271145959211186566651840137298227914453329401869141179179624428127508653257226023513694322210869665811240855745025766026879447359920868907719574457253034494436336205824 % 1
> realToFrac (read "NaN" :: Double) -- With -O0
Infinity
> realToFrac (read "NaN" :: Double) -- With -O1
NaN
> realToFrac (read "NaN" :: Double) :: CDouble
Infinity
> realToFrac (read "NaN" :: CDouble) :: Double
Infinity
Implements https://github.com/haskell/core-libraries-committee/issues/338
- - - - -
5dabc718 by Zubin Duggal at 2025-07-22T21:14:10-04:00
haddock: Don't warn about missing link destinations for derived names.
Fixes #26114
- - - - -
9c3a0937 by Matthew Pickering at 2025-07-22T21:14:52-04:00
template haskell: use a precise condition when implicitly lifting
Implicit lifting corrects a level error by replacing references to `x`
with `$(lift x)`, therefore you can use a level `n` binding at level `n
+ 1`, if it can be lifted.
Therefore, we now have a precise check that the use level is 1 more than
the bind level.
Before this bug was not observable as you only had 0 and 1 contexts but
it is easily evident when using explicit level imports.
Fixes #26088
- - - - -
5144b22f by Andreas Klebinger at 2025-07-22T21:15:34-04:00
Add since tag and more docs for do-clever-arg-eta-expansion
Fixes #26113
- - - - -
c865623b by Andreas Klebinger at 2025-07-22T21:15:34-04:00
Add since tag for -fexpose-overloaded-unfoldings
Fixes #26112
- - - - -
49a44ab7 by Simon Hengel at 2025-07-23T17:59:55+07:00
Refactor GHC.Driver.Errors.printMessages
- - - - -
84711c39 by Simon Hengel at 2025-07-23T18:27:34+07:00
Respect `-fdiagnostics-as-json` for error messages from pre-processors
(fixes #25480)
- - - - -
d046b5ab by Simon Hengel at 2025-07-24T06:12:05-04:00
Include the rendered message in -fdiagnostics-as-json output
This implements #26173.
- - - - -
d2b89603 by Ben Gamari at 2025-07-24T06:12:47-04:00
rts/Interpreter: Factor out ctoi tuple info tables into data
Instead of a massive case let's put this into data which we can reuse
elsewhere.
- - - - -
4bc78496 by Sebastian Graf at 2025-07-24T16:19:34-04:00
CprAnal: Detect recursive newtypes (#25944)
While `cprTransformDataConWork` handles recursive data con workers, it
did not detect the case when a newtype is responsible for the recursion.
This is now detected in the `Cast` case of `cprAnal`.
The same reproducer made it clear that `isRecDataCon` lacked congruent
handling for `AppTy` and `CastTy`, now fixed.
Furthermore, the new repro case T25944 triggered this bug via an
infinite loop in `cprFix`, caused by the infelicity in `isRecDataCon`.
While it should be much less likely to trigger such an infinite loop now
that `isRecDataCon` has been fixed, I made sure to abort the loop after
10 iterations and emitting a warning instead.
Fixes #25944.
- - - - -
0a583689 by Sylvain Henry at 2025-07-24T16:20:26-04:00
STM: don't create a transaction in the rhs of catchRetry# (#26028)
We don't need to create a transaction for the rhs of (catchRetry#)
because contrary to the lhs we don't need to abort it on retry. Moreover
it is particularly harmful if we have code such as (#26028):
let cN = readTVar vN >> retry
tree = c1 `orElse` (c2 `orElse` (c3 `orElse` ...))
atomically tree
Because it will stack transactions for the rhss and the read-sets of all
the transactions will be iteratively merged in O(n^2) after the
execution of the most nested retry.
- - - - -
a49eca26 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Renaming around predicate types
.. we were (as it turned out) abstracting over
type-class selectors in SPECIALISATION rules!
Wibble isEqPred
- - - - -
f80375dd by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Refactor of Specialise.hs
This patch just tidies up `specHeader` a bit, removing one
of its many results, and adding some comments.
No change in behaviour.
Also add a few more `HasDebugCallStack` contexts.
- - - - -
1bd12371 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Improve treatment of SPECIALISE pragmas -- again!
This MR does another major refactor of the way that SPECIALISE
pragmas work, to fix #26115, #26116, #26117.
* We now /always/ solve forall-constraints in an all-or-nothing way.
See Note [Solving a Wanted forall-constraint] in GHC.Tc.Solver.Solve
This means we might have unsolved quantified constraints, which need
to be reported. See `inert_insts` in `getUnsolvedInerts`.
* I refactored the short-cut solver for type classes to work by
recursively calling the solver rather than by having a little baby
solver that kept being not clever enough.
See Note [Shortcut solving] in GHC.Tc.Solver.Dict
* I totally rewrote the desugaring of SPECIALISE pragmas, again.
The new story is in Note [Desugaring new-form SPECIALISE pragmas]
in GHC.HsToCore.Binds
Both old-form and new-form SPECIALISE pragmas now route through the same
function `dsSpec_help`. The tricky function `decomposeRuleLhs` is now used only
for user-written RULES, not for SPECIALISE pragmas.
* I improved `solveOneFromTheOther` to account for rewriter sets. Previously
it would solve a non-rewritten dict from a rewritten one. For equalities
we were already dealing with this, in
Some incidental refactoring
* A small refactor: `ebv_tcvs` in `EvBindsBar` now has a list of coercions, rather
than a set of tyvars. We just delay taking the free vars.
* GHC.Core.FVs.exprFVs now returns /all/ free vars.
Use `exprLocalFVs` for Local vars.
Reason: I wanted another variant for /evidence/ variables.
* Ues `EvId` in preference to `EvVar`. (Evidence variables are always Ids.)
Rename `isEvVar` to `isEvId`.
* I moved `inert_safehask` out of `InertCans` and into `InertSet` where it
more properly belongs.
Compiler-perf changes:
* There was a palpable bug (#26117) which this MR fixes in
newWantedEvVar, which bypassed all the subtle overlapping-Given
and shortcutting logic. (See the new `newWantedEvVar`.) Fixing this
but leads to extra dictionary bindings; they are optimised away quickly
but they made CoOpt_Read allocate 3.6% more.
* Hpapily T15164 improves.
* The net compiler-allocation change is 0.0%
Metric Decrease:
T15164
Metric Increase:
CoOpt_Read
T12425
- - - - -
953fd8f1 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Solve forall-constraints immediately, or not at all
This MR refactors the constraint solver to solve forall-constraints immediately,
rather than emitting an implication constraint to be solved later.
The most immediate motivation was that when solving quantified constraints
in SPECIALISE pragmas, we really really don't want to leave behind half-
solved implications. Also it's in tune with the approach of the new
short-cut solver, which recursively invokes the solver.
It /also/ saves quite a bit of plumbing; e.g
- The `wl_implics` field of `WorkList` is gone,
- The types of `solveSimpleWanteds` and friends are simplified.
- An EvFun contains binding, rather than an EvBindsVar ref-cell that
will in the future contain bindings. That makes `evVarsOfTerm`
simpler. Much nicer.
It also improves error messages a bit.
All described in Note [Solving a Wanted forall-constraint] in
GHC.Tc.Solver.Solve.
One tiresome point: in the tricky case of `inferConstraintsCoerceBased`
we make a forall-constraint. This we /do/ want to partially solve, so
we can infer a suitable context. (I'd be quite happy to force the user to
write a context, bt I don't want to change behavior.) So we want to generate
an /implication/ constraint in `emitPredSpecConstraints` rather than a
/forall-constraint/ as we were doing before. Discussed in (WFA3) of
the above Note.
Incidental refactoring
* `GHC.Tc.Deriv.Infer.inferConstraints` was consulting the state monad for
the DerivEnv that the caller had just consulted. Nicer to pass it as an
argument I think, so I have done that. No change in behaviour.
- - - - -
6921ab42 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Remove duplicated code in Ast.hs for evTermFreeVars
This is just a tidy up.
- - - - -
1165f587 by Simon Peyton Jones at 2025-07-25T09:49:58+01:00
Small tc-tracing changes only
- - - - -
0776ffe0 by Simon Hengel at 2025-07-26T04:54:20-04:00
Respect `-fdiagnostics-as-json` for core diagnostics (see #24113)
- - - - -
cc1116e0 by Andrew Lelechenko at 2025-07-26T04:55:01-04:00
docs: add since pragma to Data.List.NonEmpty.mapMaybe
- - - - -
ee2dc248 by Simon Hengel at 2025-07-31T06:25:35-04:00
Update comments on `OptKind` to reflect the code reality
- - - - -
b029633a by Wen Kokke at 2025-07-31T06:26:21-04:00
rts: Disable --eventlog-flush-interval unless compiled with -threaded.
This commit fixes issue #26222:
Using --eventlog-flush-interval with the non-threaded RTS leads to eventlog corruption.
https://gitlab.haskell.org/ghc/ghc/-/issues/26222
This commit makes three changes when code is compiled against the non-threaded RTS:
1. It disables the --eventlog-flush-interval flag.
2. It disables the documentation for the --eventlog-flush-interval flag.
3. It disables the relevant state from RtsConfig and code from Timer.
4. It updates the entry for --eventlog-flush-interval in the users guide.
- - - - -
31159f1d by Wen Kokke at 2025-07-31T06:26:21-04:00
rts: Split T20006 into tests with and without -threaded
- - - - -
618687ef by Simon Hengel at 2025-07-31T06:27:03-04:00
docs/users_guide/win32-dlls.rst: Remove references to `readline`
- - - - -
083e40f1 by Rodrigo Mesquita at 2025-08-01T04:38:23-04:00
debugger: Uniquely identify breakpoints by internal id
Since b85b11994e0130ff2401dd4bbdf52330e0bcf776 (support inlining
breakpoints), a breakpoint has been identified at runtime by *two* pairs
of <module,index>.
- The first, aka a 'BreakpointId', uniquely identifies a breakpoint in
the source of a module by using the Tick index. A Tick index can index
into ModBreaks.modBreaks_xxx to fetch source-level information about
where that tick originated.
- When a user specifies e.g. a line breakpoint using :break, we'll reverse
engineer what a Tick index for that line
- We update the `BreakArray` of that module (got from the
LoaderState) at that tick index to `breakOn`.
- A BCO we can stop at is headed by a BRK_FUN instruction. This
instruction stores in an operand the `tick index` it is associated
to. We look it up in the associated `BreakArray` (also an operand)
and check wheter it was set to `breakOn`.
- The second, aka the `ibi_info_mod` + `ibi_info_ix` of the
`InternalBreakpointId`, uniquely index into the `imodBreaks_breakInfo`
-- the information we gathered during code generation about the
existing breakpoint *ocurrences*.
- Note that with optimisation there may be many occurrences of the
same source-tick-breakpoint across different modules. The
`ibi_info_ix` is unique per occurrence, but the `bi_tick_ix` may be
shared. See Note [Breakpoint identifiers] about this.
- Note that besides the tick ids, info ids are also stored in
`BRK_FUN` so the break handler can refer to the associated
`CgBreakInfo`.
In light of that, the driving changes come from the desire to have the
info_id uniquely identify the breakpoint at runtime, and the source tick
id being derived from it:
- An InternalBreakpointId should uniquely identify a breakpoint just
from the code-generation identifiers of `ibi_info_ix` and `ibi_info_mod`.
So we drop `ibi_tick_mod` and `ibi_tick_ix`.
- A BRK_FUN instruction need only record the "internal breakpoint id",
not the tick-level id.
So we drop the tick mod and tick index operands.
- A BreakArray should be indexed by InternalBreakpointId rather than
BreakpointId
That means we need to do some more work when setting a breakpoint.
Specifically, we need to figure out the internal ids (occurrences of a
breakpoint) from the source-level BreakpointId we want to set the
breakpoint at (recall :break refers to breaks at the source level).
Besides this change being an improvement to the handling of breakpoints
(it's clearer to have a single unique identifier than two competing
ones), it unlocks the possibility of generating "internal" breakpoints
during Cg (needed for #26042).
It should also be easier to introduce multi-threaded-aware `BreakArrays`
following this change (needed for #26064).
Se also the new Note [ModBreaks vs InternalModBreaks]
On i386-linux:
-------------------------
Metric Decrease:
interpreter_steplocal
-------------------------
- - - - -
bf03bbaa by Simon Hengel at 2025-08-01T04:39:05-04:00
Don't use MCDiagnostic for `ghcExit`
This changes the error message of `ghcExit` from
```
<no location info>: error:
Compilation had errors
```
to
```
Compilation had errors
```
- - - - -
a889ec75 by Simon Hengel at 2025-08-01T04:39:05-04:00
Respect `-fdiagnostics-as-json` for driver diagnostics (see #24113)
- - - - -
81577fe7 by Ben Gamari at 2025-08-02T04:29:39-04:00
configure: Allow override of CrossCompiling
As noted in #26236, the current inference logic is a bit simplistic. In
particular, there are many cases (e.g. building for a new libc) where
the target and host triples may differ yet we are still able to run the
produced artifacts as native code.
Closes #26236.
- - - - -
01136779 by Andreas Klebinger at 2025-08-02T04:30:20-04:00
rts: Support COFF BigObj files in archives.
- - - - -
1f9e4f54 by Stephen Morgan at 2025-08-03T15:14:08+10:00
refactor: Modify Data.List.sortOn to use (>) instead of compare. (#26184)
This lets a more efficient (>) operation be used if one exists.
This is technically a breaking change for malformed Ord instances, where
x > y is not equivalent to compare x y == GT.
Discussed by the CLC in issue #332: https://github.com/haskell/core-libraries-committee/issues/332
- - - - -
4f6bc9cf by fendor at 2025-08-04T17:50:06-04:00
Revert "base: Expose Backtraces constructor and fields"
This reverts commit 17db44c5b32fff82ea988fa4f1a233d1a27bdf57.
- - - - -
bcdec657 by Zubin Duggal at 2025-08-05T10:37:29+05:30
compiler: Export a version of `newNameCache` that is not prone to footguns.
`newNameCache` must be initialized with both a non-"reserved" unique tag, as well
as a list of known key names. Failing to do so results in hard to debug unique conflicts.
It is difficult for API users to tell which unique tags are safe to use. So instead of leaving
this up to the user to decide, we now export a version of `newNameCache` which uses a guaranteed
non-reserved unique tag. In fact, this is now the way the unique tag is initialized for all invocations
of the compiler.
The original version of `newNameCache` is now exported as `newNameCache'` for advanced users.
We also deprecate `initNameCache` as it is also prone to footguns and is completely subsumed in
functionality by `newNameCache` and `newNameCache'`.
Fixes #26135 and #26055
- - - - -
57d3b4a8 by Andrew Lelechenko at 2025-08-05T18:36:31-04:00
hadrian: bump Stackage snapshot to LTS 24.2 / GHC 9.10.2
In line with #25693 we should use GHC 9.10 as a boot compiler,
while Hadrian stack.yaml was stuck on GHC 9.6.
- - - - -
c2a78cea by Peng Fan at 2025-08-05T18:37:27-04:00
NCG/LA64: implement atomic write with finer-grained DBAR hints
Signed-off-by: Peng Fan <fanpeng(a)loongson.cn>
- - - - -
95231c8e by Teo Camarasu at 2025-08-06T08:35:58-04:00
CODEOWNERS: add CLC as codeowner of base
We also remove hvr, since I think he is no longer active
- - - - -
77df0ded by Andrew Lelechenko at 2025-08-06T08:36:39-04:00
Bump submodule text to 2.1.3
- - - - -
8af260d0 by Nikolaos Chatzikonstantinou at 2025-08-06T08:37:23-04:00
docs: fix internal import in getopt examples
This external-facing doc example shouldn't mention GHC internals when
using 'fromMaybe'.
- - - - -
69cc16ca by Marc Scholten at 2025-08-06T15:51:28-04:00
README: Add note on ghc.nix
- - - - -
93a2f450 by Daniel Díaz at 2025-08-06T15:52:14-04:00
Link to the "Strict Bindings" docs from the linear types docs
Strict Bidings are relevant for the kinds of multiplicity annotations
linear lets support.
- - - - -
246b7853 by Matthew Pickering at 2025-08-07T06:58:30-04:00
level imports: Check the level of exported identifiers
The level imports specification states that exported identifiers have to
be at level 0. This patch adds the requird level checks that all
explicitly mentioned identifiers occur at level 0.
For implicit export specifications (T(..) and module B), only level 0
identifiers are selected for re-export.
ghc-proposal: https://github.com/ghc-proposals/ghc-proposals/pull/705
Fixes #26090
- - - - -
358bc4fc by fendor at 2025-08-07T06:59:12-04:00
Bump GHC on darwin CI to 9.10.1
- - - - -
1903ae35 by Matthew Pickering at 2025-08-07T12:21:10+01:00
ipe: Place strings and metadata into specific .ipe section
By placing the .ipe metadata into a specific section it can be stripped
from the final binary if desired.
```
objcopy --remove-section .ipe <binary>
upx <binary>
```
Towards #21766
- - - - -
c80dd91c by Matthew Pickering at 2025-08-07T12:22:42+01:00
ipe: Place magic word at the start of entries in the .ipe section
The magic word "IPE\nIPE\n" is placed at the start of .ipe sections,
then if the section is stripped, we can check whether the section starts
with the magic word or not to determine whether there is metadata
present or not.
Towards #21766
- - - - -
cab42666 by Matthew Pickering at 2025-08-07T12:22:42+01:00
ipe: Use stable IDs for IPE entries
IPEs have historically been indexed and reported by their address.
This makes it impossible to compare profiles between runs, since the
addresses may change (due to ASLR) and also makes it tricky to separate
out the IPE map from the binary.
This small patch adds a stable identifier for each IPE entry.
The stable identifier is a single 64 bit word. The high-bits are a
per-module identifier and the low bits identify which entry in each
module.
1. When a node is added into the IPE buffer it is assigned a unique
identifier from an incrementing global counter.
2. Each entry already has an index by it's position in the
`IpeBufferListNode`.
The two are combined together by the `IPE_ENTRY_KEY` macro.
Info table profiling uses the stable identifier rather than the address
of the info table.
The benefits of this change are:
* Profiles from different runs can be easily compared
* The metadata can be extracted from the binary (via the eventlog for
example) and then stripped from the executable.
Fixes #21766
- - - - -
2860a9a5 by Simon Peyton Jones at 2025-08-07T20:29:18-04:00
In TcSShortCut, typechecker plugins should get empty Givens
Solving in TcShortCut mode means /ignoring the Givens/. So we
should not pass them to typechecker plugins!
Fixes #26258.
This is a fixup to the earlier MR:
commit 1bd12371feacc52394a0e660ef9349f9e8ee1c06
Author: Simon Peyton Jones <simon.peytonjones(a)gmail.com>
Date: Mon Jul 21 10:04:49 2025 +0100
Improve treatment of SPECIALISE pragmas -- again!
- - - - -
2157db2d by sterni at 2025-08-08T15:32:39-04:00
hadrian: enable terminfo if --with-curses-* flags are given
The GHC make build system used to support WITH_TERMINFO in ghc.mk which
allowed controlling whether to build GHC with terminfo or not. hadrian
has replaced this with a system where this is effectively controlled by
the cross-compiling setting (the default WITH_TERMINFO value was bassed
on CrossCompiling, iirc).
This behavior is undesireable in some cases and there is not really a
good way to work around it. Especially for downstream packagers,
modifying this via UserSettings is not really feasible since such a
source file has to be kept in sync with Settings/Default.hs manually
since it can't import Settings.Default or any predefined Flavour
definitions.
To avoid having to add a new setting to cfg/system.config and/or a new
configure flag (though I'm happy to implement both if required), I've
chosen to take --with-curses-* being set explicitly as an indication
that the user wants to have terminfo enabled. This would work for
Nixpkgs which sets these flags [1] as well as haskell.nix [2] (which
goes to some extreme measures [3] [4] to force terminfo in all scenarios).
In general, I'm an advocate for making the GHC build be the same for
native and cross insofar it is possible since it makes packaging GHC and
Haskell related things while still supporting cross much less
compilicated. A more minimal GHC with reduced dependencies should
probably be a specific flavor, not the default.
Partially addresses #26288 by forcing terminfo to be built if the user
explicitly passes configure flags related to it. However, it isn't built
by default when cross-compiling yet nor is there an explicit way to
control the package being built.
[1]: https://github.com/NixOS/nixpkgs/blob/3a7266fcefcb9ce353df49ba3f292d0644376…
[2]: https://github.com/input-output-hk/haskell.nix/blob/6eaafcdf04bab7be745d1aa…
[3]: https://github.com/input-output-hk/haskell.nix/blob/6eaafcdf04bab7be745d1aa…
[4]: https://github.com/input-output-hk/haskell.nix/blob/6eaafcdf04bab7be745d1aa…
- - - - -
b3c31488 by David Feuer at 2025-08-08T15:33:21-04:00
Add default QuasiQuoters
Add `defaultQuasiQuoter` and `namedDefaultQuasiQuoter` to make it easier
to write `QuasiQuoters` that give helpful error messages when they're
used in inappropriate contexts.
Closes #24434.
- - - - -
03555ed8 by Sylvain Henry at 2025-08-10T22:20:57-04:00
Handle non-fractional CmmFloats in Cmm's CBE (#26229)
Since f8d9d016305be355f518c141f6c6d4826f2de9a2, toRational for Float and
Double converts float's infinity and NaN into Rational's infinity and
NaN (respectively 1%0 and 0%0).
Cmm CommonBlockEliminator hashing function needs to take these values
into account as they can appear as literals now. See added testcase.
- - - - -
6c956af3 by J. Ryan Stinnett at 2025-08-10T22:21:42-04:00
Fix extensions list in `DoAndIfThenElse` docs
- - - - -
6dc420b1 by J. Ryan Stinnett at 2025-08-10T22:21:42-04:00
Document status of `RelaxedPolyRec` extension
This adds a brief extension page explaining the status of the
`RelaxedPolyRec` extension. The behaviour of this mode is already
explained elsewhere, so this page is mainly for completeness so that
various lists of extensions have somewhere to point to for this flag.
Fixes #18630
- - - - -
18036d52 by Simon Peyton Jones at 2025-08-11T11:31:20-04:00
Take more care in zonkEqTypes on AppTy/AppTy
This patch fixes #26256.
See Note [zonkEqTypes and the PKTI] in GHC.Tc.Solver.Equality
- - - - -
c8d76a29 by Zubin Duggal at 2025-08-11T11:32:02-04:00
ci: upgrade bootstrap compiler on windows to 9.10.1
- - - - -
34fc50c1 by Ben Gamari at 2025-08-11T13:36:25-04:00
Kill IOPort#
This type is unnecessary, having been superceded by `MVar` and a rework
of WinIO's blocking logic.
See #20947.
See https://github.com/haskell/core-libraries-committee/issues/213.
- - - - -
56b32c5a by sheaf at 2025-08-12T10:00:19-04:00
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.
For example, we now are properly able to prove the subtyping relationship
((∀ a. a->a) -> Int) -> Bool <= β[tau] Bool
for an unfilled metavariable β. In this case (with an AppTy on the right),
we used to fall back to unification. No longer: now, given that the LHS
is a FunTy and that the RHS is a deep rho type (does not need any instantiation),
we try to make the RHS into a FunTy, viz.
β := (->) γ
We can then continue using covariance & contravariance of the function
arrow, which allows us to prove the subtyping relationship, instead of
trying to unify which would cause us to error out with:
Couldn't match expected type ‘β’ with actual type ‘(->) ((∀ a. a -> a) -> Int)
See Note [FunTy vs non-FunTy case in tc_sub_type_deep] in GHC.Tc.Utils.Unify.
The other main improvement in this patch concerns type inference.
The main subsumption logic happens (before & after this patch) in
GHC.Tc.Gen.App.checkResultTy. However, before this patch, all of the
DeepSubsumption logic only kicked in in 'check' mode, not in 'infer' mode.
This patch adds deep instantiation in the 'infer' mode of checkResultTy
when we are doing deep subsumption, which allows us to accept programs
such as:
f :: Int -> (forall a. a->a)
g :: Int -> Bool -> Bool
test1 b =
case b of
True -> f
False -> g
test2 b =
case b of
True -> g
False -> f
See Note [Deeply instantiate in checkResultTy when inferring].
Finally, we add representation-polymorphism checks to ensure that the
lambda abstractions we introduce when doing subsumption obey the
representation polymorphism invariants of Note [Representation polymorphism invariants]
in GHC.Core. See Note [FunTy vs FunTy case in tc_sub_type_deep].
This is accompanied by a courtesy change to `(<.>) :: HsWrapper -> HsWrapper -> HsWrapper`,
adding the equation:
WpCast c1 <.> WpCast c2 = WpCast (c1 `mkTransCo` c2)
This is useful because mkWpFun does not introduce an eta-expansion when
both of the argument & result wrappers are casts; so this change allows
us to avoid introducing lambda abstractions when casts suffice.
Fixes #26225
- - - - -
d175aff8 by Sylvain Henry at 2025-08-12T10:01:31-04:00
Add regression test for #18619
- - - - -
a3983a26 by Sylvain Henry at 2025-08-12T10:02:20-04:00
RTS: remove some TSAN annotations (#20464)
Use RELAXED_LOAD_ALWAYS macro instead.
- - - - -
0434af81 by Ben Gamari at 2025-08-12T10:03:02-04:00
Bump time submodule to 1.15
Also required bumps of Cabal, directory, and hpc.
- - - - -
62899117 by Florian Ragwitz at 2025-08-13T21:01:34-04:00
Extend record-selector usage ticking to all binds using a record field
This extends the previous handling of ticking for RecordWildCards and
NamedFieldPuns to all var bindings that involve record selectors.
Note that certain patterns such as `Foo{foo = 42}` will currently not tick the
`foo` selector, as ticking is triggered by `HsVar`s.
Closes #26191.
- - - - -
b37b3af7 by Florian Ragwitz at 2025-08-13T21:01:34-04:00
Add release notes for 9.16.1 and move description of latest HPC changes there.
- - - - -
a5e4b7d9 by Ben Gamari at 2025-08-13T21:02:18-04:00
rts: Clarify rationale for undefined atomic wrappers
Since c06e3f46d24ef69f3a3d794f5f604cb8c2a40cbc the RTS has declared
various atomic operation wrappers defined by ghc-internal as undefined.
While the rationale for this isn't clear from the commit message, I
believe that this is necessary due to the unregisterised backend.
Specifically, the code generator will reference these symbols when
compiling RTS Cmm sources.
- - - - -
50842f83 by Andreas Klebinger at 2025-08-13T21:03:01-04:00
Make unexpected LLVM versions a warning rather than an error.
Typically a newer LLVM version *will* work so erroring out if
a user uses a newer LLVM version is too aggressive.
Fixes #25915
- - - - -
c91e2650 by fendor at 2025-08-13T21:03:43-04:00
Store `StackTrace` and `StackSnapshot` in `Backtraces`
Instead of decoding the stack traces when collecting the `Backtraces`,
defer this decoding until actually showing the `Backtraces`.
This allows users to customise how `Backtraces` are displayed by
using a custom implementation of `displayExceptionWithInfo`, overwriting
the default implementation for `Backtraces` (`displayBacktraces`).
- - - - -
dee28cdd by fendor at 2025-08-13T21:03:43-04:00
Allow users to customise the collection of exception annotations
Add a global `CollectExceptionAnnotationMechanism` which determines how
`ExceptionAnnotation`s are collected upon throwing an `Exception`.
This API is exposed via `ghc-experimental`.
By overriding how we collect `Backtraces`, we can control how the
`Backtraces` are displayed to the user by newtyping `Backtraces` and
giving a different instance for `ExceptionAnnotation`.
A concrete use-case for this feature is allowing us to experiment with
alternative stack decoders, without having to modify `base`, which take
additional information from the stack frames.
This commit does not modify how `Backtraces` are currently
collected or displayed.
- - - - -
66024722 by fendor at 2025-08-13T21:03:43-04:00
Expose Backtraces internals from ghc-experimental
Additionally, expose the same API `base:Control.Exception.Backtrace`
to make it easier to use as a drop-in replacement.
- - - - -
a766286f by Reed Mullanix at 2025-08-13T21:04:36-04:00
ghc-internal: Fix naturalAndNot for NB/NS case
When the first argument to `naturalAndNot` is larger than a `Word` and the second is `Word`-sized, `naturalAndNot` will truncate the
result:
```
>>> naturalAndNot ((2 ^ 65) .|. (2 ^ 3)) (2 ^ 3)
0
```
In contrast, `naturalAndNot` does not truncate when both arguments are larger than a `Word`, so this appears to be a bug.
Luckily, the fix is pretty easy: we just need to call `bigNatAndNotWord#` instead of truncating.
Fixes #26230
- - - - -
3506fa7d by Simon Hengel at 2025-08-13T21:05:18-04:00
Report -pgms as a deprecated flag
(instead of reporting an unspecific warning)
Before:
on the commandline: warning:
Object splitting was removed in GHC 8.8
After:
on the commandline: warning: [GHC-53692] [-Wdeprecated-flags]
-pgms is deprecated: Object splitting was removed in GHC 8.8
- - - - -
51c701fe by Zubin Duggal at 2025-08-13T21:06:00-04:00
testsuite: Be more permissive when filtering out GNU_PROPERTY_TYPE linker warnings
The warning text is slightly different with ld.bfd.
Fixes #26249
- - - - -
dfe6f464 by Simon Hengel at 2025-08-13T21:06:43-04:00
Refactoring: Don't misuse `MCDiagnostic` for lint messages
`MCDiagnostic` is meant to be used for compiler diagnostics.
Any code that creates `MCDiagnostic` directly, without going through
`GHC.Driver.Errors.printMessage`, side steps `-fdiagnostics-as-json`
(see e.g. !14475, !14492 !14548).
To avoid this in the future I want to control more narrowly who creates
`MCDiagnostic` (see #24113).
Some parts of the compiler use `MCDiagnostic` purely for formatting
purposes, without creating any real compiler diagnostics. This change
introduces a helper function, `formatDiagnostic`, that can be used in
such cases instead of constructing `MCDiagnostic`.
- - - - -
a8b2fbae by Teo Camarasu at 2025-08-13T21:07:24-04:00
rts: ensure MessageBlackHole.link is always a valid closure
We turn a MessageBlackHole into an StgInd in wakeBlockingQueue().
Therefore it's important that the link field, which becomes the
indirection field, always points to a valid closure.
It's unclear whether it's currently possible for the previous behaviour
to lead to a crash, but it's good to be consistent about this invariant nonetheless.
Co-authored-by: Andreas Klebinger <klebinger.andreas(a)gmx.at>
- - - - -
4021181e by Teo Camarasu at 2025-08-13T21:07:24-04:00
rts: spin if we see a WHITEHOLE in messageBlackHole
When a BLACKHOLE gets cancelled in raiseAsync, we indirect to a THUNK.
GC can then shortcut this, replacing our BLACKHOLE with a fresh THUNK.
This THUNK is not guaranteed to have a valid indirectee field.
If at the same time, a message intended for the previous BLACKHOLE is
processed and concurrently we BLACKHOLE the THUNK, thus temporarily
turning it into a WHITEHOLE, we can get a segfault, since we look at the
undefined indirectee field of the THUNK
The fix is simple: spin if we see a WHITEHOLE, and it will soon be
replaced with a valid BLACKHOLE.
Resolves #26205
- - - - -
1107af89 by Oleg Grenrus at 2025-08-13T21:08:06-04:00
Allow defining HasField instances for naughty fields
Resolves #26295
... as HasField solver doesn't solve for fields with "naughty"
selectors, we could as well allow defining HasField instances for these
fields.
- - - - -
020e7587 by Sylvain Henry at 2025-08-13T21:09:00-04:00
Fix Data.List unqualified import warning
- - - - -
a19a9c74 by Cheng Shao at 2025-08-14T03:35:30+02:00
rts: remove libbfd logic
- - - - -
c3957fd6 by Cheng Shao at 2025-08-14T04:09:53+02:00
compiler/rts: add debug symbolizer
- - - - -
435 changed files:
- .gitlab/darwin/toolchain.nix
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- CODEOWNERS
- README.md
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/PrimOps/Ids.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Breakpoints.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm.hs
- compiler/GHC/Cmm/CommonBlockElim.hs
- + compiler/GHC/Cmm/GenerateDebugSymbolStub.hs
- compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- compiler/GHC/CmmToAsm/LA64/Instr.hs
- compiler/GHC/CmmToAsm/LA64/Ppr.hs
- compiler/GHC/CmmToAsm/PPC/Ppr.hs
- compiler/GHC/CmmToAsm/Ppr.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- compiler/GHC/CmmToAsm/X86/Ppr.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/LateCC/OverloadedCalls.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/Monad.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/Driver/CmdLine.hs
- compiler/GHC/Driver/CodeOutput.hs
- compiler/GHC/Driver/Errors.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Parser.y
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Stg/Lint.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm/InfoTableProv.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/SysTools/Process.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/GHC/Tc/Deriv.hs
- compiler/GHC/Tc/Deriv/Infer.hs
- compiler/GHC/Tc/Deriv/Utils.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Rewrite.hs
- compiler/GHC/Tc/Solver/Solve.hs
- + compiler/GHC/Tc/Solver/Solve.hs-boot
- compiler/GHC/Tc/Solver/Types.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Concrete.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/Validity.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Types/Error.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/Name/Cache.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/Var.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Utils/Error.hs
- compiler/GHC/Utils/Logger.hs
- compiler/ghc.cabal.in
- configure.ac
- − docs/users_guide/9.14.1-notes.rst
- + docs/users_guide/9.16.1-notes.rst
- docs/users_guide/conf.py
- docs/users_guide/debug-info.rst
- + docs/users_guide/diagnostics-as-json-schema-1_2.json
- docs/users_guide/eventlog-formats.rst
- docs/users_guide/expected-undocumented-flags.txt
- docs/users_guide/exts/doandifthenelse.rst
- docs/users_guide/exts/linear_types.rst
- + docs/users_guide/exts/relaxed_poly_rec.rst
- docs/users_guide/exts/strict.rst
- docs/users_guide/exts/types.rst
- docs/users_guide/profiling.rst
- docs/users_guide/release-notes.rst
- docs/users_guide/runtime_control.rst
- docs/users_guide/using-optimisation.rst
- docs/users_guide/using.rst
- docs/users_guide/win32-dlls.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Monad.hs
- ghc/ghc-bin.cabal.in
- hadrian/cfg/system.config.in
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Packages.hs
- hadrian/stack.yaml
- hadrian/stack.yaml.lock
- libraries/Cabal
- libraries/Win32
- libraries/array
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- libraries/base/src/Control/Exception.hs
- libraries/base/src/Control/Exception/Backtrace.hs
- libraries/base/src/Data/List/NonEmpty.hs
- libraries/base/src/GHC/Exts.hs
- libraries/base/src/GHC/Generics.hs
- − libraries/base/src/GHC/IOPort.hs
- libraries/base/src/GHC/Weak/Finalize.hs
- libraries/base/src/System/Console/GetOpt.hs
- libraries/binary
- libraries/deepseq
- libraries/directory
- libraries/exceptions
- libraries/filepath
- libraries/ghc-bignum/changelog.md
- libraries/ghc-boot-th/ghc-boot-th.cabal.in
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-compact/GHC/Compact.hs
- libraries/ghc-compact/GHC/Compact/Serialized.hs
- libraries/ghc-compact/ghc-compact.cabal
- libraries/ghc-experimental/ghc-experimental.cabal.in
- + libraries/ghc-experimental/src/GHC/Exception/Backtrace/Experimental.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- libraries/ghc-heap/GHC/Exts/Heap/Utils.hsc
- libraries/ghc-heap/ghc-heap.cabal.in
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Base.hs
- libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs
- libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs
- libraries/ghc-internal/src/GHC/Internal/Event/Windows.hsc
- libraries/ghc-internal/src/GHC/Internal/Event/Windows/Thread.hs
- libraries/ghc-internal/src/GHC/Internal/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs-boot
- libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs
- libraries/ghc-internal/src/GHC/Internal/Exts.hs
- libraries/ghc-internal/src/GHC/Internal/Float.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Buffer.hs
- libraries/ghc-internal/src/GHC/Internal/IO/Windows/Handle.hsc
- − libraries/ghc-internal/src/GHC/Internal/IOPort.hs
- libraries/ghc-internal/src/GHC/Internal/Prim/PtrEq.hs
- libraries/ghc-internal/src/GHC/Internal/Real.hs
- libraries/ghc-internal/src/GHC/Internal/System/IO.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Quote.hs
- + libraries/ghc-internal/tests/Makefile
- + libraries/ghc-internal/tests/all.T
- + libraries/ghc-internal/tests/backtraces/Makefile
- + libraries/ghc-internal/tests/backtraces/T14532a.hs
- + libraries/ghc-internal/tests/backtraces/T14532a.stdout
- + libraries/ghc-internal/tests/backtraces/T14532b.hs
- + libraries/ghc-internal/tests/backtraces/T14532b.stdout
- + libraries/ghc-internal/tests/backtraces/all.T
- libraries/ghc-prim/changelog.md
- libraries/ghc-prim/ghc-prim.cabal
- libraries/ghci/GHCi/Debugger.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- libraries/ghci/ghci.cabal.in
- libraries/haskeline
- libraries/hpc
- libraries/os-string
- libraries/parsec
- libraries/process
- libraries/semaphore-compat
- libraries/stm
- libraries/template-haskell/Language/Haskell/TH/Quote.hs
- libraries/template-haskell/changelog.md
- libraries/template-haskell/template-haskell.cabal.in
- libraries/terminfo
- libraries/text
- libraries/time
- libraries/unix
- m4/find_ld.m4
- − m4/fp_bfd_support.m4
- mk/get-win32-tarballs.py
- rts/Disassembler.c
- rts/Exception.cmm
- rts/IPE.c
- rts/Interpreter.c
- rts/Messages.c
- rts/Prelude.h
- rts/PrimOps.cmm
- rts/Printer.c
- rts/Printer.h
- rts/ProfHeap.c
- rts/RaiseAsync.c
- rts/RetainerSet.c
- rts/RtsFlags.c
- rts/RtsStartup.c
- rts/RtsSymbols.c
- rts/STM.c
- rts/StgMiscClosures.cmm
- rts/Timer.c
- rts/Trace.c
- rts/Trace.h
- rts/Updates.h
- rts/configure.ac
- rts/eventlog/EventLog.c
- rts/eventlog/EventLog.h
- rts/external-symbols.list.in
- rts/include/rts/Config.h
- rts/include/rts/Flags.h
- rts/include/rts/IPE.h
- rts/include/stg/MiscClosures.h
- rts/include/stg/SMP.h
- rts/linker/LoadArchive.c
- rts/linker/PEi386.c
- rts/posix/ticker/Pthread.c
- rts/posix/ticker/TimerFd.c
- rts/rts.cabal
- rts/sm/NonMoving.c
- rts/sm/NonMoving.h
- rts/sm/NonMovingAllocate.c
- rts/sm/Sanity.c
- rts/win32/AsyncWinIO.c
- rts/win32/libHSghc-internal.def
- testsuite/driver/testlib.py
- testsuite/tests/arrows/should_compile/T21301.stderr
- testsuite/tests/corelint/LintEtaExpand.stderr
- testsuite/tests/corelint/T21115b.stderr
- + testsuite/tests/cpranal/sigs/T25944.hs
- + testsuite/tests/cpranal/sigs/T25944.stderr
- testsuite/tests/cpranal/sigs/all.T
- testsuite/tests/deSugar/should_fail/DsStrictFail.stderr
- testsuite/tests/deSugar/should_run/T20024.stderr
- testsuite/tests/deSugar/should_run/dsrun005.stderr
- testsuite/tests/deSugar/should_run/dsrun007.stderr
- testsuite/tests/deSugar/should_run/dsrun008.stderr
- testsuite/tests/deriving/should_compile/T20815.hs
- testsuite/tests/deriving/should_fail/T12768.stderr
- testsuite/tests/deriving/should_fail/T1496.stderr
- testsuite/tests/deriving/should_fail/T5498.stderr
- testsuite/tests/deriving/should_fail/T7148.stderr
- testsuite/tests/deriving/should_fail/T7148a.stderr
- testsuite/tests/deriving/should_run/T9576.stderr
- testsuite/tests/dmdanal/should_compile/T23398.hs
- testsuite/tests/dmdanal/should_compile/T23398.stderr
- testsuite/tests/driver/json.stderr
- testsuite/tests/driver/json_warn.stderr
- testsuite/tests/driver/recomp015/all.T
- testsuite/tests/ghci/scripts/Defer02.stderr
- testsuite/tests/ghci/scripts/T15325.stderr
- testsuite/tests/haddock/haddock_testsuite/Makefile
- + testsuite/tests/haddock/haddock_testsuite/T26114.hs
- + testsuite/tests/haddock/haddock_testsuite/T26114.stdout
- testsuite/tests/haddock/haddock_testsuite/all.T
- testsuite/tests/hiefile/should_run/HieQueries.stdout
- testsuite/tests/hiefile/should_run/TestUtils.hs
- testsuite/tests/hpc/recsel/recsel.hs
- testsuite/tests/hpc/recsel/recsel.stdout
- testsuite/tests/impredicative/T17332.stderr
- testsuite/tests/indexed-types/should_fail/T5439.stderr
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- testsuite/tests/interface-stability/ghc-prim-exports.stdout
- testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32
- testsuite/tests/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/numeric/should_compile/T26229.hs
- testsuite/tests/numeric/should_compile/all.T
- + testsuite/tests/numeric/should_run/T18619.hs
- + testsuite/tests/numeric/should_run/T18619.stderr
- + testsuite/tests/numeric/should_run/T26230.hs
- + testsuite/tests/numeric/should_run/T26230.stdout
- testsuite/tests/numeric/should_run/T9810.stdout
- testsuite/tests/numeric/should_run/all.T
- + testsuite/tests/overloadedrecflds/should_run/T26295.hs
- + testsuite/tests/overloadedrecflds/should_run/T26295.stdout
- testsuite/tests/overloadedrecflds/should_run/all.T
- testsuite/tests/partial-sigs/should_compile/T10403.stderr
- + testsuite/tests/partial-sigs/should_compile/T26256.hs
- + testsuite/tests/partial-sigs/should_compile/T26256.stderr
- testsuite/tests/partial-sigs/should_compile/all.T
- testsuite/tests/partial-sigs/should_fail/T10615.stderr
- testsuite/tests/patsyn/should_run/ghci.stderr
- + testsuite/tests/perf/should_run/SpecTyFamRun.hs
- + testsuite/tests/perf/should_run/SpecTyFamRun.stdout
- + testsuite/tests/perf/should_run/SpecTyFam_Import.hs
- testsuite/tests/perf/should_run/all.T
- testsuite/tests/primops/should_run/UnliftedIOPort.hs
- testsuite/tests/primops/should_run/all.T
- testsuite/tests/printer/Makefile
- + testsuite/tests/printer/TestLevelImports.hs
- + testsuite/tests/printer/TestNamedDefaults.hs
- testsuite/tests/printer/all.T
- testsuite/tests/quantified-constraints/T15290a.stderr
- testsuite/tests/quantified-constraints/T19690.stderr
- testsuite/tests/quantified-constraints/T19921.stderr
- testsuite/tests/quantified-constraints/T21006.stderr
- testsuite/tests/quotes/LiftErrMsgDefer.stderr
- + testsuite/tests/rep-poly/NoEtaRequired.hs
- testsuite/tests/rep-poly/T21906.stderr
- testsuite/tests/rep-poly/all.T
- testsuite/tests/roles/should_fail/RolesIArray.stderr
- testsuite/tests/rts/all.T
- testsuite/tests/rts/flags/all.T
- testsuite/tests/rts/ipe/ipeMap.c
- testsuite/tests/rts/ipe/ipe_lib.c
- testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-32-mingw32
- testsuite/tests/rts/linker/T11223/T11223_link_order_a_b_2_fail.stderr-ws-64-mingw32
- testsuite/tests/safeHaskell/safeLanguage/SafeLang15.stderr
- testsuite/tests/simd/should_run/all.T
- + testsuite/tests/simd/should_run/doublex2_shuffle.hs
- + testsuite/tests/simd/should_run/doublex2_shuffle.stdout
- + testsuite/tests/simd/should_run/doublex2_shuffle_baseline.hs
- + testsuite/tests/simd/should_run/doublex2_shuffle_baseline.stdout
- + testsuite/tests/simd/should_run/floatx4_shuffle.hs
- + testsuite/tests/simd/should_run/floatx4_shuffle.stdout
- + testsuite/tests/simd/should_run/floatx4_shuffle_baseline.hs
- + testsuite/tests/simd/should_run/floatx4_shuffle_baseline.stdout
- + testsuite/tests/simplCore/should_compile/T26051.hs
- + testsuite/tests/simplCore/should_compile/T26051.stderr
- + testsuite/tests/simplCore/should_compile/T26051_Import.hs
- + testsuite/tests/simplCore/should_compile/T26115.hs
- + testsuite/tests/simplCore/should_compile/T26115.stderr
- + testsuite/tests/simplCore/should_compile/T26116.hs
- + testsuite/tests/simplCore/should_compile/T26116.stderr
- + testsuite/tests/simplCore/should_compile/T26117.hs
- + testsuite/tests/simplCore/should_compile/T26117.stderr
- testsuite/tests/simplCore/should_compile/all.T
- + testsuite/tests/splice-imports/DodgyLevelExport.hs
- + testsuite/tests/splice-imports/DodgyLevelExport.stderr
- + testsuite/tests/splice-imports/DodgyLevelExportA.hs
- + testsuite/tests/splice-imports/LevelImportExports.hs
- + testsuite/tests/splice-imports/LevelImportExports.stdout
- + testsuite/tests/splice-imports/LevelImportExportsA.hs
- testsuite/tests/splice-imports/Makefile
- + testsuite/tests/splice-imports/ModuleExport.hs
- + testsuite/tests/splice-imports/ModuleExport.stderr
- + testsuite/tests/splice-imports/ModuleExportA.hs
- + testsuite/tests/splice-imports/ModuleExportB.hs
- + testsuite/tests/splice-imports/T26087.stderr
- + testsuite/tests/splice-imports/T26087A.hs
- + testsuite/tests/splice-imports/T26087B.hs
- + testsuite/tests/splice-imports/T26088.stderr
- + testsuite/tests/splice-imports/T26088A.hs
- + testsuite/tests/splice-imports/T26088B.hs
- + testsuite/tests/splice-imports/T26090.hs
- + testsuite/tests/splice-imports/T26090.stderr
- + testsuite/tests/splice-imports/T26090A.hs
- testsuite/tests/splice-imports/all.T
- testsuite/tests/type-data/should_run/T22332a.stderr
- testsuite/tests/typecheck/should_compile/T12427a.stderr
- testsuite/tests/typecheck/should_compile/T23171.hs
- + testsuite/tests/typecheck/should_compile/T26225.hs
- + testsuite/tests/typecheck/should_compile/T26225b.hs
- + testsuite/tests/typecheck/should_compile/T26256a.hs
- testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr
- testsuite/tests/typecheck/should_compile/all.T
- − testsuite/tests/typecheck/should_fail/T12563.stderr
- testsuite/tests/typecheck/should_fail/T14605.hs
- testsuite/tests/typecheck/should_fail/T14605.stderr
- testsuite/tests/typecheck/should_fail/T14618.stderr
- testsuite/tests/typecheck/should_fail/T15801.stderr
- testsuite/tests/typecheck/should_fail/T18640a.stderr
- testsuite/tests/typecheck/should_fail/T18640b.stderr
- testsuite/tests/typecheck/should_fail/T19627.stderr
- testsuite/tests/typecheck/should_fail/T21530b.stderr
- testsuite/tests/typecheck/should_fail/T22912.stderr
- testsuite/tests/typecheck/should_fail/T6022.stderr
- testsuite/tests/typecheck/should_fail/T8883.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail140.stderr
- testsuite/tests/typecheck/should_fail/tcfail174.stderr
- testsuite/tests/typecheck/should_run/T10284.stderr
- testsuite/tests/typecheck/should_run/T13838.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/unsatisfiable/T23816.stderr
- testsuite/tests/unsatisfiable/UnsatDefer.stderr
- utils/check-exact/ExactPrint.hs
- utils/genprimopcode/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
- utils/haddock/haddock-api/haddock-api.cabal
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs
- utils/haddock/haddock-library/haddock-library.cabal
- utils/haddock/haddock-test/haddock-test.cabal
- utils/haddock/haddock.cabal
- utils/hsc2hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a3ab9b1560b6ee95a19fb550a0b7ae…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a3ab9b1560b6ee95a19fb550a0b7ae…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 23 commits: Extend record-selector usage ticking to all binds using a record field
by Marge Bot (@marge-bot) 13 Aug '25
by Marge Bot (@marge-bot) 13 Aug '25
13 Aug '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
62899117 by Florian Ragwitz at 2025-08-13T21:01:34-04:00
Extend record-selector usage ticking to all binds using a record field
This extends the previous handling of ticking for RecordWildCards and
NamedFieldPuns to all var bindings that involve record selectors.
Note that certain patterns such as `Foo{foo = 42}` will currently not tick the
`foo` selector, as ticking is triggered by `HsVar`s.
Closes #26191.
- - - - -
b37b3af7 by Florian Ragwitz at 2025-08-13T21:01:34-04:00
Add release notes for 9.16.1 and move description of latest HPC changes there.
- - - - -
a5e4b7d9 by Ben Gamari at 2025-08-13T21:02:18-04:00
rts: Clarify rationale for undefined atomic wrappers
Since c06e3f46d24ef69f3a3d794f5f604cb8c2a40cbc the RTS has declared
various atomic operation wrappers defined by ghc-internal as undefined.
While the rationale for this isn't clear from the commit message, I
believe that this is necessary due to the unregisterised backend.
Specifically, the code generator will reference these symbols when
compiling RTS Cmm sources.
- - - - -
50842f83 by Andreas Klebinger at 2025-08-13T21:03:01-04:00
Make unexpected LLVM versions a warning rather than an error.
Typically a newer LLVM version *will* work so erroring out if
a user uses a newer LLVM version is too aggressive.
Fixes #25915
- - - - -
c91e2650 by fendor at 2025-08-13T21:03:43-04:00
Store `StackTrace` and `StackSnapshot` in `Backtraces`
Instead of decoding the stack traces when collecting the `Backtraces`,
defer this decoding until actually showing the `Backtraces`.
This allows users to customise how `Backtraces` are displayed by
using a custom implementation of `displayExceptionWithInfo`, overwriting
the default implementation for `Backtraces` (`displayBacktraces`).
- - - - -
dee28cdd by fendor at 2025-08-13T21:03:43-04:00
Allow users to customise the collection of exception annotations
Add a global `CollectExceptionAnnotationMechanism` which determines how
`ExceptionAnnotation`s are collected upon throwing an `Exception`.
This API is exposed via `ghc-experimental`.
By overriding how we collect `Backtraces`, we can control how the
`Backtraces` are displayed to the user by newtyping `Backtraces` and
giving a different instance for `ExceptionAnnotation`.
A concrete use-case for this feature is allowing us to experiment with
alternative stack decoders, without having to modify `base`, which take
additional information from the stack frames.
This commit does not modify how `Backtraces` are currently
collected or displayed.
- - - - -
66024722 by fendor at 2025-08-13T21:03:43-04:00
Expose Backtraces internals from ghc-experimental
Additionally, expose the same API `base:Control.Exception.Backtrace`
to make it easier to use as a drop-in replacement.
- - - - -
a766286f by Reed Mullanix at 2025-08-13T21:04:36-04:00
ghc-internal: Fix naturalAndNot for NB/NS case
When the first argument to `naturalAndNot` is larger than a `Word` and the second is `Word`-sized, `naturalAndNot` will truncate the
result:
```
>>> naturalAndNot ((2 ^ 65) .|. (2 ^ 3)) (2 ^ 3)
0
```
In contrast, `naturalAndNot` does not truncate when both arguments are larger than a `Word`, so this appears to be a bug.
Luckily, the fix is pretty easy: we just need to call `bigNatAndNotWord#` instead of truncating.
Fixes #26230
- - - - -
3506fa7d by Simon Hengel at 2025-08-13T21:05:18-04:00
Report -pgms as a deprecated flag
(instead of reporting an unspecific warning)
Before:
on the commandline: warning:
Object splitting was removed in GHC 8.8
After:
on the commandline: warning: [GHC-53692] [-Wdeprecated-flags]
-pgms is deprecated: Object splitting was removed in GHC 8.8
- - - - -
51c701fe by Zubin Duggal at 2025-08-13T21:06:00-04:00
testsuite: Be more permissive when filtering out GNU_PROPERTY_TYPE linker warnings
The warning text is slightly different with ld.bfd.
Fixes #26249
- - - - -
dfe6f464 by Simon Hengel at 2025-08-13T21:06:43-04:00
Refactoring: Don't misuse `MCDiagnostic` for lint messages
`MCDiagnostic` is meant to be used for compiler diagnostics.
Any code that creates `MCDiagnostic` directly, without going through
`GHC.Driver.Errors.printMessage`, side steps `-fdiagnostics-as-json`
(see e.g. !14475, !14492 !14548).
To avoid this in the future I want to control more narrowly who creates
`MCDiagnostic` (see #24113).
Some parts of the compiler use `MCDiagnostic` purely for formatting
purposes, without creating any real compiler diagnostics. This change
introduces a helper function, `formatDiagnostic`, that can be used in
such cases instead of constructing `MCDiagnostic`.
- - - - -
a8b2fbae by Teo Camarasu at 2025-08-13T21:07:24-04:00
rts: ensure MessageBlackHole.link is always a valid closure
We turn a MessageBlackHole into an StgInd in wakeBlockingQueue().
Therefore it's important that the link field, which becomes the
indirection field, always points to a valid closure.
It's unclear whether it's currently possible for the previous behaviour
to lead to a crash, but it's good to be consistent about this invariant nonetheless.
Co-authored-by: Andreas Klebinger <klebinger.andreas(a)gmx.at>
- - - - -
4021181e by Teo Camarasu at 2025-08-13T21:07:24-04:00
rts: spin if we see a WHITEHOLE in messageBlackHole
When a BLACKHOLE gets cancelled in raiseAsync, we indirect to a THUNK.
GC can then shortcut this, replacing our BLACKHOLE with a fresh THUNK.
This THUNK is not guaranteed to have a valid indirectee field.
If at the same time, a message intended for the previous BLACKHOLE is
processed and concurrently we BLACKHOLE the THUNK, thus temporarily
turning it into a WHITEHOLE, we can get a segfault, since we look at the
undefined indirectee field of the THUNK
The fix is simple: spin if we see a WHITEHOLE, and it will soon be
replaced with a valid BLACKHOLE.
Resolves #26205
- - - - -
1107af89 by Oleg Grenrus at 2025-08-13T21:08:06-04:00
Allow defining HasField instances for naughty fields
Resolves #26295
... as HasField solver doesn't solve for fields with "naughty"
selectors, we could as well allow defining HasField instances for these
fields.
- - - - -
020e7587 by Sylvain Henry at 2025-08-13T21:09:00-04:00
Fix Data.List unqualified import warning
- - - - -
b546c9ad by Simon Peyton Jones at 2025-08-13T21:40:55-04:00
Make injecting implicit bindings into its own pass
Previously we were injecting "impliicit bindings" (data constructor
worker and wrappers etc)
- both at the end of CoreTidy,
- and at the start of CorePrep
This is unpleasant and confusing. This patch puts it it its own pass,
addImplicitBinds, which runs between the two.
The function `GHC.CoreToStg.AddImplicitBinds.addImplicitBinds` now takes /all/
TyCons, not just the ones for algebraic data types. That change ripples
through to
- corePrepPgm
- doCodeGen
- byteCodeGen
All take [TyCon] which includes all TyCons
- - - - -
0e7c03a8 by Simon Peyton Jones at 2025-08-13T21:40:55-04:00
Implement unary classes
The big change is described exhaustively in
Note [Unary class magic] in GHC.Core.TyCon
Other changes
* We never unbox class dictionaries in worker/wrapper. This has been true for some
time now, but the logic is now centralised in functions in
GHC.Core.Opt.WorkWrap.Utils, namely `canUnboxTyCon`, and `canUnboxArg`
See Note [Do not unbox class dictionaries] in GHC.Core.Opt.WorkWrap.Utils.
* Refactored the `notWorthFloating` logic in GHc.Core.Opt.SetLevels.
I can't remember if I actually changed any behaviour here, but if so it's
only in a corner cases.
* Fixed a bug in `GHC.Core.TyCon.isEnumerationTyCon`, which was wrongly returning
True for (##).
* Remove redundant Role argument to `liftCoSubstWithEx`. It was always
Representational.
* I refactored evidence generation in the constraint solver:
* Made GHC.Tc.Types.Evidence contain better abstactions for evidence
generation.
* I deleted the file `GHC.Tc.Types.EvTerm` and merged its (small) contents
elsewhere. It wasn't paying its way.
* Made evidence for implicit parameters go via a proper abstraction.
* Fix inlineBoringOk; see (IB6) in Note [inlineBoringOk]
This fixes a slowdown in `countdownEffectfulDynLocal`
in the `effectful` library.
Smaller things
* Rename `isDataTyCon` to `isBoxedDataTyCon`.
* GHC.Core.Corecion.liftCoSubstWithEx was only called with Representational role,
so I baked that into the function and removed the argument.
* Get rid of `GHC.Core.TyCon.tyConSingleAlgDataCon_maybe` in favour of calling
`not isNewTyCon` at the call sites; more explicit.
* Refatored `GHC.Core.TyCon.isInjectiveTyCon`; but I don't think I changed its
behaviour
* Moved `decomposeIPPred` to GHC.Core.Predicate
Compile time performance changes:
geo. mean +0.1%
minimum -6.8%
maximum +14.4%
The +14% one is in T21839c, where it seems that a bit more inlining
is taking place. That seems acceptable; and the average change is small
Metric Decrease:
LargeRecord
T12227
T12707
T16577
T21839r
T5642
Metric Increase:
T15164
T21839c
T3294
T5321FD
T5321Fun
WWRec
- - - - -
f07ce677 by Simon Peyton Jones at 2025-08-13T21:40:55-04:00
Slight improvement to pre/postInlineUnconditionally
Avoids an extra simplifier iteration
- - - - -
8d00d9a3 by Simon Peyton Jones at 2025-08-13T21:40:56-04:00
Fix a long-standing assertion error in normSplitTyConApp_maybe
- - - - -
bc5c02a1 by Simon Peyton Jones at 2025-08-13T21:40:56-04:00
Add comment to coercion optimiser
- - - - -
cae8e591 by Recursion Ninja at 2025-08-13T21:40:57-04:00
Resolving issues #20645 and #26109
Correctly sign extending and casting smaller bit width types for LLVM operations:
- bitReverse8#
- bitReverse16#
- bitReverse32#
- byteSwap16#
- byteSwap32#
- pdep8#
- pdep16#
- pext8#
- pext16#
- - - - -
39e34e64 by Sylvain Henry at 2025-08-13T21:41:02-04:00
JS: export HEAP8 symbol (#26290)
Newer Emscripten requires this.
- - - - -
2d2a971a by Cheng Shao at 2025-08-13T21:41:04-04:00
hadrian: enforce have_llvm=False for wasm32/js
This patch fixes hadrian to always pass have_llvm=False to the
testsuite driver for wasm32/js targets. These targets don't really
support the LLVM backend, and the optllvm test way doesn't work. We
used to special-case wasm32/js to avoid auto-adding optllvm way in
testsuite/config/ghc, but this is still problematic if someone writes
a new LLVM-related test and uses something like when(have_llvm(),
extra_ways(["optllvm"])). So better just enforce have_llvm=False for
these targets here.
- - - - -
172 changed files:
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unfold.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg.hs
- + compiler/GHC/CoreToStg/AddImplicitBinds.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/Call.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Stg/Lint.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Instance/Family.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- − compiler/GHC/Tc/Types/EvTerm.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Error.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/RepType.hs
- compiler/GHC/Types/TyThing.hs
- compiler/GHC/Utils/Error.hs
- compiler/ghc.cabal.in
- − docs/users_guide/9.14.1-notes.rst
- + docs/users_guide/9.16.1-notes.rst
- docs/users_guide/release-notes.rst
- hadrian/src/Settings/Builders/RunTest.hs
- libraries/base/changelog.md
- libraries/ghc-bignum/changelog.md
- + libraries/ghc-experimental/src/GHC/Exception/Backtrace/Experimental.hs
- libraries/ghc-internal/cbits/pdep.c
- libraries/ghc-internal/cbits/pext.c
- libraries/ghc-internal/src/GHC/Internal/Bignum/Natural.hs
- libraries/ghc-internal/src/GHC/Internal/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs-boot
- + libraries/ghc-internal/tests/Makefile
- + libraries/ghc-internal/tests/all.T
- + libraries/ghc-internal/tests/backtraces/Makefile
- + libraries/ghc-internal/tests/backtraces/T14532a.hs
- + libraries/ghc-internal/tests/backtraces/T14532a.stdout
- + libraries/ghc-internal/tests/backtraces/T14532b.hs
- + libraries/ghc-internal/tests/backtraces/T14532b.stdout
- + libraries/ghc-internal/tests/backtraces/all.T
- rts/Messages.c
- rts/StgMiscClosures.cmm
- rts/Updates.h
- rts/external-symbols.list.in
- rts/js/mem.js
- rts/rts.cabal
- testsuite/config/ghc
- testsuite/driver/testlib.py
- testsuite/tests/arrows/should_compile/T21301.stderr
- testsuite/tests/core-to-stg/T24124.stderr
- testsuite/tests/deSugar/should_compile/T2431.stderr
- testsuite/tests/deSugar/should_fail/DsStrictFail.stderr
- testsuite/tests/deSugar/should_run/T20024.stderr
- testsuite/tests/deSugar/should_run/dsrun005.stderr
- testsuite/tests/deSugar/should_run/dsrun007.stderr
- testsuite/tests/deSugar/should_run/dsrun008.stderr
- testsuite/tests/deriving/should_run/T9576.stderr
- testsuite/tests/dmdanal/should_compile/T16029.stdout
- testsuite/tests/dmdanal/sigs/T21119.stderr
- testsuite/tests/dmdanal/sigs/T21888.stderr
- testsuite/tests/ghci.debugger/scripts/break011.stdout
- testsuite/tests/ghci.debugger/scripts/break024.stdout
- testsuite/tests/ghci/scripts/Defer02.stderr
- testsuite/tests/ghci/scripts/T15325.stderr
- testsuite/tests/hpc/recsel/recsel.hs
- testsuite/tests/hpc/recsel/recsel.stdout
- testsuite/tests/indexed-types/should_compile/T2238.hs
- + testsuite/tests/llvm/should_run/T20645.hs
- + testsuite/tests/llvm/should_run/T20645.stdout
- testsuite/tests/llvm/should_run/all.T
- testsuite/tests/numeric/should_compile/T15547.stderr
- testsuite/tests/numeric/should_compile/T23907.stderr
- + testsuite/tests/numeric/should_run/T26230.hs
- + testsuite/tests/numeric/should_run/T26230.stdout
- testsuite/tests/numeric/should_run/all.T
- testsuite/tests/numeric/should_run/foundation.hs
- + testsuite/tests/overloadedrecflds/should_run/T26295.hs
- + testsuite/tests/overloadedrecflds/should_run/T26295.stdout
- testsuite/tests/overloadedrecflds/should_run/all.T
- testsuite/tests/patsyn/should_run/ghci.stderr
- testsuite/tests/quotes/LiftErrMsgDefer.stderr
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/safeHaskell/safeLanguage/SafeLang15.stderr
- testsuite/tests/simplCore/should_compile/DataToTagFamilyScrut.stderr
- testsuite/tests/simplCore/should_compile/T15205.stderr
- testsuite/tests/simplCore/should_compile/T17366.stderr
- testsuite/tests/simplCore/should_compile/T17966.stderr
- testsuite/tests/simplCore/should_compile/T22309.stderr
- testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr
- testsuite/tests/simplCore/should_compile/T23307.stderr
- testsuite/tests/simplCore/should_compile/T23307a.stderr
- testsuite/tests/simplCore/should_compile/T25389.stderr
- testsuite/tests/simplCore/should_compile/T25713.stderr
- testsuite/tests/simplCore/should_compile/T7360.stderr
- testsuite/tests/simplStg/should_compile/T15226b.stderr
- testsuite/tests/tcplugins/CtIdPlugin.hs
- testsuite/tests/type-data/should_run/T22332a.stderr
- testsuite/tests/typecheck/should_compile/Makefile
- testsuite/tests/typecheck/should_compile/T12763.stderr
- testsuite/tests/typecheck/should_compile/T14774.stdout
- testsuite/tests/typecheck/should_compile/T18406b.stderr
- testsuite/tests/typecheck/should_compile/T18529.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_run/T10284.stderr
- testsuite/tests/typecheck/should_run/T13838.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/unboxedsums/unpack_sums_7.stdout
- testsuite/tests/unsatisfiable/T23816.stderr
- testsuite/tests/unsatisfiable/UnsatDefer.stderr
- testsuite/tests/wasm/should_run/control-flow/LoadCmmGroup.hs
- testsuite/tests/wasm/should_run/control-flow/RunWasm.hs
- utils/genprimopcode/Lexer.x
- utils/genprimopcode/Main.hs
- utils/genprimopcode/Parser.y
- utils/genprimopcode/ParserM.hs
- utils/genprimopcode/Syntax.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e77a8e014f3eb768b9bcfca33bbbae…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e77a8e014f3eb768b9bcfca33bbbae…
You're receiving this email because of your account on gitlab.haskell.org.
1
0