Simon Peyton Jones pushed new branch wip/T26004 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T26004
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T23109] 27 commits: driver: Use ModuleGraph for oneshot and --make mode
by Simon Peyton Jones (@simonpj) 29 Apr '25
by Simon Peyton Jones (@simonpj) 29 Apr '25
29 Apr '25
Simon Peyton Jones pushed to branch wip/T23109 at Glasgow Haskell Compiler / GHC
Commits:
d47bf776 by Matthew Pickering at 2025-04-14T16:44:41+01:00
driver: Use ModuleGraph for oneshot and --make mode
This patch uses the `hsc_mod_graph` field for both oneshot and --make
mode. Therefore, if part of the compiler requires usage of the module
graph, you do so in a uniform way for the two different modes.
The `ModuleGraph` describes the relationship between the modules in the
home package and units in external packages. The `ModuleGraph` can be
queried when information about the transitive closure of a package is
needed. For example, the primary use of the ModuleGraph from within the
compiler is in the loader, which needs to know the transitive closure of
a module so it can load all the relevant objects for evaluation.
In --make mode, downsweep computes the ModuleGraph before any
compilation starts.
In oneshot mode, a thunk is created at the start of compilation, which
when forced will compute the module graph beneath the current module.
The thunk is only forced at the moment when the user uses Template
Haskell.
Finally, there are some situations where we need to discover what
dependencies to load but haven't loaded a module graph at all. In this
case, there is a fallback which computes the transitive closure on the
fly and doesn't cache the result. Presumably if you are going to call
getLinkDeps a lot, you would compute the right ModuleGraph before you
started.
Importantly, this removes the ExternalModuleGraph abstraction. This was quite
awkward to work with since it stored information about the home package
inside the EPS.
This patch will also be very useful when implementing explicit level
imports, which requires more significant use of the module graph in
order to determine which level instances are available at.
Towards #25795
-------------------------
Metric Decrease:
MultiLayerModulesTH_Make
MultiLayerModulesTH_OneShot
-------------------------
- - - - -
395e0ad1 by sheaf at 2025-04-16T12:33:26-04:00
base: remove .Internal modules (e.g. GHC.TypeLits)
This commit removes the following internal modules from base,
as per CLC proposal 217:
- GHC.TypeNats.Internal
- GHC.TypeLits.Internal
- GHC.ExecutionStack.Internal
Fixes #25007
- - - - -
e0f3ff11 by Patrick at 2025-04-17T04:31:12-04:00
Refactor Handling of Multiple Default Declarations
Fixes: #25912, #25914, #25934
Previously, GHC discarded all loaded defaults (tcg_default) when local
defaults were encountered during typechecking. According to the
exportable-named-default proposal (sections 2.4.2 and 2.4.3), local
defaults should be merged into tcg_default, retaining any defaults
already present while overriding where necessary.
Key Changes:
* Introduce DefaultProvenance to track the origin of default declarations
(local, imported, or built-in), replacing the original cd_module
in ClassDefaults with cd_provenance :: DefaultProvenance.
* Rename tcDefaults to tcDefaultDecls, limiting its responsibility to only
converting renamed class defaults into ClassDefaults.
* Add extendDefaultEnvWithLocalDefaults to merge local defaults into the
environment, with proper duplication checks:
- Duplicate local defaults for a class trigger an error.
- Local defaults override imported or built-in defaults.
* Update and add related notes: Note [Builtin class defaults],
Note [DefaultProvenance].
* Add regression tests: T25912, T25914, T25934.
Thanks sam and simon for the help on this patch.
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
- - - - -
386f1854 by Teo Camarasu at 2025-04-17T04:31:55-04:00
template-haskell: Remove `addrToByteArrayName` and `addrToByteArray`
These were part of the implementation of the `Lift ByteArray` instance and were errornously exported because this module lacked an explicit export list. They have no usages on Hackage.
Resolves #24782
- - - - -
b96e2f77 by Sylvain Henry at 2025-04-18T20:46:33-04:00
RTS: remove target info and fix host info (#24058)
The RTS isn't a compiler, hence it doesn't have a target and we remove
the reported target info displayed by "+RTS --info". We also fix the
host info displayed by "+RTS --info": the host of the RTS is the
RTS-building compiler's target, not the compiler's host (wrong when
doing cross-compilation).
- - - - -
6d9965f4 by Sylvain Henry at 2025-04-18T20:46:33-04:00
RTS: remove build info
As per the discussion in !13967, there is no reason to tag the RTS with
information about the build platform.
- - - - -
d52e9b3f by Vladislav Zavialov at 2025-04-18T20:47:15-04:00
Diagnostics: remove the KindMismatch constructor (#25957)
The KindMismatch constructor was only used as an intermediate
representation in pretty-printing.
Its removal addresses a problem detected by the "codes" test case:
[GHC-89223] is untested (constructor = KindMismatch)
In a concious deviation from the usual procedure, the error code
GHC-89223 is removed entirely rather than marked as Outdated.
The reason is that it never was user-facing in the first place.
- - - - -
e2f2f9d0 by Vladislav Zavialov at 2025-04-20T10:53:39-04:00
Add name for -Wunusable-unpack-pragmas
This warning had no name or flag and was triggered unconditionally.
Now it is part of -Wdefault.
In GHC.Tc.TyCl.tcTyClGroupsPass's strict mode, we now have to
force-enable this warning to ensure that detection of flawed groups
continues to work even if the user disables the warning with the
-Wno-unusable-unpack-pragmas option. Test case: T3990c
Also, the misnamed BackpackUnpackAbstractType is now called
UnusableUnpackPragma.
- - - - -
6caa6508 by Adam Gundry at 2025-04-20T10:54:22-04:00
Fix specialisation of incoherent instances (fixes #25883)
GHC normally assumes that class constraints are canonical, meaning that
the specialiser is allowed to replace one dictionary argument with another
provided that they have the same type. The `-fno-specialise-incoherents`
flag alters INCOHERENT instance definitions so that they will prevent
specialisation in some cases, by inserting `nospec`.
This commit fixes a bug in 7124e4ad76d98f1fc246ada4fd7bf64413ff2f2e, which
treated some INCOHERENT instance matches as if `-fno-specialise-incoherents`
was in effect, thereby unnecessarily preventing specialisation. In addition
it updates the relevant `Note [Rules for instance lookup]` and adds a new
`Note [Canonicity for incoherent matches]`.
- - - - -
0426fd6c by Adam Gundry at 2025-04-20T10:54:23-04:00
Add regression test for #23429
- - - - -
eec96527 by Adam Gundry at 2025-04-20T10:54:23-04:00
user's guide: update specification of overlapping/incoherent instances
The description of the instance resolution algorithm in the user's
guide was slightly out of date, because it mentioned in-scope given
constraints only at the end, whereas the implementation checks for
their presence before any of the other steps.
This also adds a warning to the user's guide about the impact of
incoherent instances on specialisation, and more clearly documents
some of the other effects of `-XIncoherentInstances`.
- - - - -
a00eeaec by Matthew Craven at 2025-04-20T10:55:03-04:00
Fix bytecode generation for `tagToEnum# <LITERAL>`
Fixes #25975.
- - - - -
2e204269 by Andreas Klebinger at 2025-04-22T12:20:41+02:00
Simplifier: Constant fold invald tagToEnum# calls to bottom expr.
When applying tagToEnum# to a out-of-range value it's best to simply
constant fold it to a bottom expression. That potentially allows more
dead code elimination and makes debugging easier.
Fixes #25976
- - - - -
7250fc0c by Matthew Pickering at 2025-04-22T16:24:04-04:00
Move -fno-code note into Downsweep module
This note was left behind when all the code which referred to it was
moved into the GHC.Driver.Downsweep module
- - - - -
d2dc89b4 by Matthew Pickering at 2025-04-22T16:24:04-04:00
Apply editing notes to Note [-fno-code mode] suggested by sheaf
These notes were suggested in https://gitlab.haskell.org/ghc/ghc/-/merge_requests/14241
- - - - -
91564daf by Matthew Pickering at 2025-04-24T00:29:02-04:00
ghci: Use loadInterfaceForModule rather than loadSrcInterface in mkTopLevEnv
loadSrcInterface takes a user given `ModuleName` and resolves it to the
module which needs to be loaded (taking into account module
renaming/visibility etc).
loadInterfaceForModule takes a specific module and loads it.
The modules in `ImpDeclSpec` have already been resolved to the actual
module to get the information from during renaming. Therefore we just
need to fetch the precise interface from disk (and not attempt to rename
it again).
Fixes #25951
- - - - -
2e0c07ab by Simon Peyton Jones at 2025-04-24T00:29:43-04:00
Test for #23298
- - - - -
0eef99b0 by Sven Tennie at 2025-04-24T07:34:36-04:00
RV64: Introduce J instruction (non-local jumps) and don't deallocate stack slots for J_TBL (#25738)
J_TBL result in local jumps, there should not deallocate stack slots
(see Note [extra spill slots].)
J is for non-local jumps, these may need to deallocate stack slots.
- - - - -
1bd3d13e by fendor at 2025-04-24T07:35:17-04:00
Add `UnitId` to `EvalBreakpoint`
The `EvalBreakpoint` is used to communicate that a breakpoint was
encountered during code evaluation.
This `EvalBreakpoint` needs to be converted to an `InternalBreakpointId`
which stores a `Module` to uniquely find the correct `Module` in the
Home Package Table.
The `EvalBreakpoint` used to store only a `ModuleName` which is then
converted to a `Module` based on the currently active home unit.
This is incorrect in the face of multiple home units, the break point
could be in an entirely other home unit!
To fix this, we additionally store the `UnitId` of the `Module` in
`EvalBreakpoint` to later reconstruct the correct `Module`
All of the changes are the consequence of extending `EvalBreakpoint`
with the additional `ShortByteString` of the `UnitId`.
For performance reasons, we store the `ShortByteString` backing the
`UnitId` directly, avoiding marshalling overhead.
- - - - -
fe6ed8d9 by Sylvain Henry at 2025-04-24T18:04:12-04:00
Doc: add doc for JS interruptible calling convention (#24444)
- - - - -
6111c5e4 by Ben Gamari at 2025-04-24T18:04:53-04:00
compiler: Ensure that Panic.Plain.assertPanic' provides callstack
In 36cddd2ce1a3bc62ea8a1307d8bc6006d54109cf @alt-romes removed CallStack
output from `GHC.Utils.Panic.Plain.assertPanic'`. While this output is
redundant due to the exception backtrace proposal, we may be
bootstrapping with a compiler which does not yet include this machinery.
Reintroduce the output for now.
Fixes #25898.
- - - - -
217caad1 by Matthew Pickering at 2025-04-25T18:58:42+01:00
Implement Explicit Level Imports for Template Haskell
This commit introduces the `ExplicitLevelImports` and
`ImplicitStagePersistence` language extensions as proposed in GHC
Proposal #682.
Key Features
------------
- `ExplicitLevelImports` adds two new import modifiers - `splice` and
`quote` - allowing precise control over the level at which imported
identifiers are available
- `ImplicitStagePersistence` (enabled by default) preserves existing
path-based cross-stage persistence behavior
- `NoImplicitStagePersistence` disables implicit cross-stage
persistence, requiring explicit level imports
Benefits
--------
- Improved compilation performance by reducing unnecessary code generation
- Enhanced IDE experience with faster feedback in `-fno-code` mode
- Better dependency tracking by distinguishing compile-time and runtime dependencies
- Foundation for future cross-compilation improvements
This implementation enables the separation of modules needed at
compile-time from those needed at runtime, allowing for more efficient
compilation pipelines and clearer code organization in projects using
Template Haskell.
Implementation Notes
--------------------
The level which a name is availble at is stored in the 'GRE', in the normal
GlobalRdrEnv. The function `greLevels` returns the levels which a specific GRE
is imported at. The level information for a 'Name' is computed by `getCurrentAndBindLevel`.
The level validity is checked by `checkCrossLevelLifting`.
Instances are checked by `checkWellLevelledDFun`, which computes the level an
instance by calling `checkWellLevelledInstanceWhat`, which sees what is
available at by looking at the module graph.
Modifications to downsweep
--------------------------
Code generation is now only enabled for modules which are needed at
compile time.
See the Note [-fno-code mode] for more information.
Uniform error messages for level errors
---------------------------------------
All error messages to do with levels are now reported uniformly using
the `TcRnBadlyStaged` constructor.
Error messages are uniformly reported in terms of levels.
0 - top-level
1 - quote level
-1 - splice level
The only level hard-coded into the compiler is the top-level in
GHC.Types.ThLevelIndex.topLevelIndex.
Uniformly refer to levels and stages
------------------------------------
There was much confusion about levels vs stages in the compiler.
A level is a semantic concept, used by the typechecker to ensure a
program can be evaluated in a well-staged manner.
A stage is an operational construct, program evaluation proceeds in
stages.
Deprecate -Wbadly-staged-types
------------------------------
`-Wbadly-staged-types` is deprecated in favour of `-Wbadly-levelled-types`.
Lift derivation changed
-----------------------
Derived lift instances will now not generate code with expression
quotations.
Before:
```
data A = A Int deriving Lift
=>
lift (A x) = [| A $(lift x) |]
```
After:
```
lift (A x) = conE 'A `appE` (lift x)
```
This is because if you attempt to derive `Lift` in a module where
`NoImplicitStagePersistence` is enabled, you would get an infinite loop
where a constructor was attempted to be persisted using the instance you
are currently defining.
GHC API Changes
---------------
The ModuleGraph now contains additional information about the type of
the edges (normal, quote or splice) between modules. This is abstracted
using the `ModuleGraphEdge` data type.
Fixes #25828
-------------------------
Metric Increase:
MultiLayerModulesTH_Make
-------------------------
- - - - -
7641a74a by Simon Peyton Jones at 2025-04-26T22:05:19-04:00
Get a decent MatchContext for pattern synonym bindings
In particular when we have a pattern binding
K p1 .. pn = rhs
where K is a pattern synonym. (It might be nested.)
This small MR fixes #25995. It's a tiny fix, to an error message,
removing an always-dubious `unkSkol`.
The bug report was in the context of horde-ad, a big program,
and I didn't manage to make a small repro case quickly. I decided
not to bother further.
- - - - -
ce616f49 by Simon Peyton Jones at 2025-04-27T21:10:25+01:00
Fix infelicities in the Specialiser
On the way to #23109 (unary classes) I discovered some infelicities
(or maybe tiny bugs, I forget) in the type-class specialiser.
I also tripped over #25965, an outright bug in the rule matcher
Specifically:
* Refactor: I enhanced `wantCallsFor`, whih previously always said
`True`, to discard calls of class-ops, data constructors etc. This is
a bit more efficient; and it means we don't need to worry about
filtering them out later.
* Fix: I tidied up some tricky logic that eliminated redundant
specialisations. It wasn't working correctly. See the expanded
Note [Specialisations already covered], and
(MP3) in Note [Specialising polymorphic dictionaries].
See also the new top-level `alreadyCovered`
function, which now goes via `GHC.Core.Rules.ruleLhsIsMoreSpecific`
I also added a useful Note [The (CI-KEY) invariant]
* Fix #25965: fixed a tricky bug in the `go_fam_fam` in
`GHC.Core.Unify.uVarOrFam`, which allows matching to succeed
without binding all type varibles.
I enhanced Note [Apartness and type families] some more
* #25703. This ticket "just works" with -fpolymorphic-specialisation;
but I was surprised that it worked! In this MR I added documentation
to Note [Interesting dictionary arguments] to explain; and tests to
ensure it stays fixed.
- - - - -
22d11fa8 by Simon Peyton Jones at 2025-04-28T18:05:19-04:00
Track rewriter sets more accurately in constraint solving
The key change, which fixed #25440, is to call `recordRewriter` in
GHC.Tc.Solver.Rewrite.rewrite_exact_fam_app. This missing call meant
that we were secretly rewriting a Wanted with a Wanted, but not really
noticing; and that led to a very bad error message, as you can see
in the ticket.
But of course that led me into rabbit hole of other refactoring around
the RewriteSet code:
* Improve Notes [Wanteds rewrite Wanteds]
* Zonk the RewriterSet in `zonkCtEvidence` rather than only in GHC.Tc.Errors.
This is tidier anyway (e.g. de-clutters debug output), and helps with the
next point.
* In GHC.Tc.Solver.Equality.inertsCanDischarge, don't replace a constraint
with no rewriters with an equal constraint that has many. See
See (CE4) in Note [Combining equalities]
* Move zonkRewriterSet and friends from GHC.Tc.Zonk.Type into
GHC.Tc.Zonk.TcType, where they properly belong.
A handful of tests get better error messages.
For some reason T24984 gets 12% less compiler allocation -- good
Metric Decrease:
T24984
- - - - -
cb5ed017 by Simon Peyton Jones at 2025-04-29T11:27:58+01: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
- - - - -
3a62ad7e by Simon Peyton Jones at 2025-04-29T11:29:29+01: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.
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
- - - - -
460 changed files:
- compiler/GHC.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/ConstantFold.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/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/Rules.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/Unify.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg.hs
- + compiler/GHC/CoreToStg/AddImplicitBinds.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Data/Graph/Directed/Reachability.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Env/Types.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeAction.hs
- compiler/GHC/Driver/MakeFile.hs
- + compiler/GHC/Driver/Messager.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline.hs-boot
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/Call.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Loader.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Utils.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Default.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Instance/Family.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Plugin.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/Rewrite.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.hs
- compiler/GHC/Tc/Types/Constraint.hs
- − compiler/GHC/Tc/Types/EvTerm.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/LclEnv.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Types/TH.hs
- compiler/GHC/Tc/Utils/Backpack.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/Env.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Zonk/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/DefaultEnv.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/RepType.hs
- + compiler/GHC/Types/ThLevelIndex.hs
- compiler/GHC/Types/TyThing.hs
- compiler/GHC/Unit/External.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Home/PackageTable.hs
- compiler/GHC/Unit/Module/Deps.hs
- − compiler/GHC/Unit/Module/External/Graph.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Unit/Module/Imported.hs
- compiler/GHC/Unit/Module/ModNodeKey.hs
- compiler/GHC/Unit/Module/ModSummary.hs
- + compiler/GHC/Unit/Module/Stage.hs
- compiler/GHC/Unit/Types.hs
- compiler/GHC/Utils/Binary.hs
- compiler/GHC/Utils/Outputable.hs
- compiler/GHC/Utils/Panic/Plain.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- + compiler/Language/Haskell/Syntax/ImpExp/IsBoot.hs
- compiler/ghc.cabal.in
- configure.ac
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/exts/control.rst
- docs/users_guide/exts/instances.rst
- docs/users_guide/exts/template_haskell.rst
- docs/users_guide/javascript.rst
- docs/users_guide/phases.rst
- docs/users_guide/using-warnings.rst
- ghc/GHCi/UI.hs
- hadrian/src/Settings/Packages.hs
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- − libraries/base/src/GHC/ExecutionStack/Internal.hs
- − libraries/base/src/GHC/TypeLits/Internal.hs
- − libraries/base/src/GHC/TypeNats/Internal.hs
- libraries/base/tests/IO/Makefile
- libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- libraries/template-haskell/changelog.md
- rts/Exception.cmm
- rts/Interpreter.c
- rts/RtsUtils.c
- testsuite/ghc-config/ghc-config.hs
- testsuite/tests/ado/ado004.stderr
- testsuite/tests/annotations/should_fail/annfail03.stderr
- testsuite/tests/annotations/should_fail/annfail04.stderr
- testsuite/tests/annotations/should_fail/annfail06.stderr
- testsuite/tests/annotations/should_fail/annfail09.stderr
- + testsuite/tests/bytecode/T25975.hs
- + testsuite/tests/bytecode/T25975.stdout
- testsuite/tests/bytecode/all.T
- testsuite/tests/core-to-stg/T24124.stderr
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/deSugar/should_compile/T2431.stderr
- + testsuite/tests/default/T25912.hs
- + testsuite/tests/default/T25912.stdout
- + testsuite/tests/default/T25912_helper.hs
- + testsuite/tests/default/T25914.hs
- + testsuite/tests/default/T25934.hs
- testsuite/tests/default/all.T
- testsuite/tests/default/default-fail03.stderr
- testsuite/tests/dependent/should_compile/T14729.stderr
- testsuite/tests/dependent/should_compile/T15743.stderr
- testsuite/tests/dependent/should_compile/T15743e.stderr
- testsuite/tests/dependent/should_fail/T13135_simple.stderr
- testsuite/tests/deriving/should_compile/T14682.stderr
- testsuite/tests/determinism/determ021/determ021.stdout
- testsuite/tests/diagnostic-codes/codes.stdout
- testsuite/tests/dmdanal/should_compile/T16029.stdout
- testsuite/tests/dmdanal/sigs/T21119.stderr
- testsuite/tests/dmdanal/sigs/T21888.stderr
- + testsuite/tests/driver/T4437.stdout
- testsuite/tests/driver/json2.stderr
- testsuite/tests/gadt/T19847a.stderr
- + testsuite/tests/gadt/T23298.hs
- + testsuite/tests/gadt/T23298.stderr
- testsuite/tests/gadt/all.T
- testsuite/tests/ghc-api/fixed-nodes/FixedNodes.hs
- + testsuite/tests/ghc-api/fixed-nodes/InterfaceModuleGraph.hs
- + testsuite/tests/ghc-api/fixed-nodes/InterfaceModuleGraph.stdout
- testsuite/tests/ghc-api/fixed-nodes/ModuleGraphInvariants.hs
- testsuite/tests/ghc-api/fixed-nodes/all.T
- + testsuite/tests/ghci/scripts/GhciPackageRename.hs
- + testsuite/tests/ghci/scripts/GhciPackageRename.script
- + testsuite/tests/ghci/scripts/GhciPackageRename.stdout
- testsuite/tests/ghci/scripts/all.T
- testsuite/tests/indexed-types/should_compile/T15711.stderr
- testsuite/tests/indexed-types/should_compile/T15852.stderr
- testsuite/tests/indexed-types/should_compile/T2238.hs
- testsuite/tests/indexed-types/should_compile/T3017.stderr
- testsuite/tests/indexed-types/should_fail/T3330c.stderr
- testsuite/tests/indexed-types/should_fail/T4174.stderr
- testsuite/tests/indexed-types/should_fail/T8227.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/template-haskell-exports.stdout
- testsuite/tests/linters/notes.stdout
- testsuite/tests/module/mod185.stderr
- testsuite/tests/module/mod58.stderr
- testsuite/tests/numeric/should_compile/T15547.stderr
- testsuite/tests/numeric/should_compile/T23907.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/partial-sigs/should_compile/ADT.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr1.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr2.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr3.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr4.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr5.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr6.stderr
- testsuite/tests/partial-sigs/should_compile/BoolToBool.stderr
- testsuite/tests/partial-sigs/should_compile/DataFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting1MROn.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting2MROff.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting2MROn.stderr
- testsuite/tests/partial-sigs/should_compile/Either.stderr
- testsuite/tests/partial-sigs/should_compile/EqualityConstraint.stderr
- testsuite/tests/partial-sigs/should_compile/Every.stderr
- testsuite/tests/partial-sigs/should_compile/EveryNamed.stderr
- testsuite/tests/partial-sigs/should_compile/ExpressionSig.stderr
- testsuite/tests/partial-sigs/should_compile/ExpressionSigNamed.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints1.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints2.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints3.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROff.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROn.stderr
- testsuite/tests/partial-sigs/should_compile/Forall1.stderr
- testsuite/tests/partial-sigs/should_compile/GenNamed.stderr
- testsuite/tests/partial-sigs/should_compile/HigherRank1.stderr
- testsuite/tests/partial-sigs/should_compile/HigherRank2.stderr
- testsuite/tests/partial-sigs/should_compile/LocalDefinitionBug.stderr
- testsuite/tests/partial-sigs/should_compile/Meltdown.stderr
- testsuite/tests/partial-sigs/should_compile/MonoLocalBinds.stderr
- testsuite/tests/partial-sigs/should_compile/NamedTyVar.stderr
- testsuite/tests/partial-sigs/should_compile/NamedWildcardInDataFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/NamedWildcardInTypeFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/ParensAroundContext.stderr
- testsuite/tests/partial-sigs/should_compile/PatBind.stderr
- testsuite/tests/partial-sigs/should_compile/PatBind2.stderr
- testsuite/tests/partial-sigs/should_compile/PatternSig.stderr
- testsuite/tests/partial-sigs/should_compile/Recursive.stderr
- testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcards.stderr
- testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcardsGood.stderr
- testsuite/tests/partial-sigs/should_compile/ShowNamed.stderr
- testsuite/tests/partial-sigs/should_compile/SimpleGen.stderr
- testsuite/tests/partial-sigs/should_compile/SkipMany.stderr
- testsuite/tests/partial-sigs/should_compile/SomethingShowable.stderr
- testsuite/tests/partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/Uncurry.stderr
- testsuite/tests/partial-sigs/should_compile/UncurryNamed.stderr
- testsuite/tests/partial-sigs/should_compile/WarningWildcardInstantiations.stderr
- testsuite/tests/plugins/defaulting-plugin/DefaultLifted.hs
- testsuite/tests/polykinds/T15592.stderr
- testsuite/tests/polykinds/T15592b.stderr
- testsuite/tests/printer/T18052a.stderr
- testsuite/tests/quasiquotation/qq001/qq001.stderr
- testsuite/tests/quasiquotation/qq002/qq002.stderr
- testsuite/tests/quasiquotation/qq003/qq003.stderr
- testsuite/tests/quasiquotation/qq004/qq004.stderr
- + testsuite/tests/quotes/T5721.stderr
- testsuite/tests/roles/should_compile/Roles1.stderr
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles2.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/roles/should_compile/T8958.stderr
- testsuite/tests/showIface/DocsInHiFile1.stdout
- testsuite/tests/showIface/DocsInHiFileTH.stdout
- testsuite/tests/showIface/HaddockIssue849.stdout
- testsuite/tests/showIface/HaddockOpts.stdout
- testsuite/tests/showIface/HaddockSpanIssueT24378.stdout
- testsuite/tests/showIface/LanguageExts.stdout
- testsuite/tests/showIface/MagicHashInHaddocks.stdout
- testsuite/tests/showIface/NoExportList.stdout
- testsuite/tests/showIface/PragmaDocs.stdout
- testsuite/tests/showIface/ReExports.stdout
- testsuite/tests/simplCore/should_compile/DataToTagFamilyScrut.stderr
- testsuite/tests/simplCore/should_compile/Makefile
- 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/T23307c.stderr
- testsuite/tests/simplCore/should_compile/T25389.stderr
- + testsuite/tests/simplCore/should_compile/T25703.hs
- + testsuite/tests/simplCore/should_compile/T25703.stderr
- + testsuite/tests/simplCore/should_compile/T25703a.hs
- + testsuite/tests/simplCore/should_compile/T25703a.stderr
- testsuite/tests/simplCore/should_compile/T25713.stderr
- + testsuite/tests/simplCore/should_compile/T25883.hs
- + testsuite/tests/simplCore/should_compile/T25883.substr-simpl
- + testsuite/tests/simplCore/should_compile/T25883b.hs
- + testsuite/tests/simplCore/should_compile/T25883b.substr-simpl
- + testsuite/tests/simplCore/should_compile/T25883c.hs
- + testsuite/tests/simplCore/should_compile/T25883c.substr-simpl
- + testsuite/tests/simplCore/should_compile/T25883d.hs
- + testsuite/tests/simplCore/should_compile/T25883d.stderr
- + testsuite/tests/simplCore/should_compile/T25883d_import.hs
- + testsuite/tests/simplCore/should_compile/T25965.hs
- + testsuite/tests/simplCore/should_compile/T25976.hs
- + testsuite/tests/simplCore/should_compile/T3990c.hs
- + testsuite/tests/simplCore/should_compile/T3990c.stdout
- testsuite/tests/simplCore/should_compile/T7360.stderr
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/simplCore/should_fail/T25672.stderr
- + testsuite/tests/simplCore/should_run/T23429.hs
- + testsuite/tests/simplCore/should_run/T23429.stdout
- testsuite/tests/simplCore/should_run/all.T
- testsuite/tests/simplStg/should_compile/T15226b.stderr
- + testsuite/tests/splice-imports/ClassA.hs
- + testsuite/tests/splice-imports/InstanceA.hs
- + testsuite/tests/splice-imports/Makefile
- + testsuite/tests/splice-imports/SI01.hs
- + testsuite/tests/splice-imports/SI01A.hs
- + testsuite/tests/splice-imports/SI02.hs
- + testsuite/tests/splice-imports/SI03.hs
- + testsuite/tests/splice-imports/SI03.stderr
- + testsuite/tests/splice-imports/SI04.hs
- + testsuite/tests/splice-imports/SI05.hs
- + testsuite/tests/splice-imports/SI05.stderr
- + testsuite/tests/splice-imports/SI05A.hs
- + testsuite/tests/splice-imports/SI06.hs
- + testsuite/tests/splice-imports/SI07.hs
- + testsuite/tests/splice-imports/SI07.stderr
- + testsuite/tests/splice-imports/SI07A.hs
- + testsuite/tests/splice-imports/SI08.hs
- + testsuite/tests/splice-imports/SI08.stderr
- + testsuite/tests/splice-imports/SI08_oneshot.stderr
- + testsuite/tests/splice-imports/SI09.hs
- + testsuite/tests/splice-imports/SI10.hs
- + testsuite/tests/splice-imports/SI13.hs
- + testsuite/tests/splice-imports/SI14.hs
- + testsuite/tests/splice-imports/SI14.stderr
- + testsuite/tests/splice-imports/SI15.hs
- + testsuite/tests/splice-imports/SI15.stderr
- + testsuite/tests/splice-imports/SI16.hs
- + testsuite/tests/splice-imports/SI16.stderr
- + testsuite/tests/splice-imports/SI17.hs
- + testsuite/tests/splice-imports/SI18.hs
- + testsuite/tests/splice-imports/SI18.stderr
- + testsuite/tests/splice-imports/SI19.hs
- + testsuite/tests/splice-imports/SI19A.hs
- + testsuite/tests/splice-imports/SI20.hs
- + testsuite/tests/splice-imports/SI20.stderr
- + testsuite/tests/splice-imports/SI21.hs
- + testsuite/tests/splice-imports/SI21.stderr
- + testsuite/tests/splice-imports/SI22.hs
- + testsuite/tests/splice-imports/SI22.stderr
- + testsuite/tests/splice-imports/SI23.hs
- + testsuite/tests/splice-imports/SI23A.hs
- + testsuite/tests/splice-imports/SI24.hs
- + testsuite/tests/splice-imports/SI25.hs
- + testsuite/tests/splice-imports/SI25.stderr
- + testsuite/tests/splice-imports/SI25Helper.hs
- + testsuite/tests/splice-imports/SI26.hs
- + testsuite/tests/splice-imports/SI27.hs
- + testsuite/tests/splice-imports/SI27.stderr
- + testsuite/tests/splice-imports/SI28.hs
- + testsuite/tests/splice-imports/SI28.stderr
- + testsuite/tests/splice-imports/SI29.hs
- + testsuite/tests/splice-imports/SI29.stderr
- + testsuite/tests/splice-imports/SI30.script
- + testsuite/tests/splice-imports/SI30.stdout
- + testsuite/tests/splice-imports/SI31.script
- + testsuite/tests/splice-imports/SI31.stderr
- + testsuite/tests/splice-imports/SI32.script
- + testsuite/tests/splice-imports/SI32.stdout
- + testsuite/tests/splice-imports/SI33.script
- + testsuite/tests/splice-imports/SI33.stdout
- + testsuite/tests/splice-imports/SI34.hs
- + testsuite/tests/splice-imports/SI34.stderr
- + testsuite/tests/splice-imports/SI34M1.hs
- + testsuite/tests/splice-imports/SI34M2.hs
- + testsuite/tests/splice-imports/SI35.hs
- + testsuite/tests/splice-imports/SI35A.hs
- + testsuite/tests/splice-imports/SI36.hs
- + testsuite/tests/splice-imports/SI36.stderr
- + testsuite/tests/splice-imports/SI36_A.hs
- + testsuite/tests/splice-imports/SI36_B1.hs
- + testsuite/tests/splice-imports/SI36_B2.hs
- + testsuite/tests/splice-imports/SI36_B3.hs
- + testsuite/tests/splice-imports/SI36_C1.hs
- + testsuite/tests/splice-imports/SI36_C2.hs
- + testsuite/tests/splice-imports/SI36_C3.hs
- + testsuite/tests/splice-imports/all.T
- testsuite/tests/tcplugins/CtIdPlugin.hs
- testsuite/tests/th/T16976z.stderr
- testsuite/tests/th/T17820a.stderr
- testsuite/tests/th/T17820b.stderr
- testsuite/tests/th/T17820c.stderr
- testsuite/tests/th/T17820d.stderr
- testsuite/tests/th/T17820e.stderr
- testsuite/tests/th/T21547.stderr
- testsuite/tests/th/T23829_hasty.stderr
- testsuite/tests/th/T23829_hasty_b.stderr
- testsuite/tests/th/T23829_tardy.ghc.stderr
- testsuite/tests/th/T5795.stderr
- testsuite/tests/th/TH_Roles2.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/T21023.stderr
- testsuite/tests/typecheck/should_compile/T25266a.stderr
- testsuite/tests/typecheck/should_compile/T7050.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/T18851.stderr
- testsuite/tests/typecheck/should_fail/T3966.stderr
- + testsuite/tests/typecheck/should_fail/T3966b.hs
- + testsuite/tests/typecheck/should_fail/T3966b.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/unboxedsums/unpack_sums_5.stderr
- testsuite/tests/unboxedsums/unpack_sums_7.stdout
- testsuite/tests/wasm/should_run/control-flow/LoadCmmGroup.hs
- utils/check-exact/ExactPrint.hs
- utils/count-deps/Main.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b11e62985b07845b18ba520fec9bb3…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b11e62985b07845b18ba520fec9bb3…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/strict-level] Add -fverbose-core-names flag to control generated name verbosity
by Zubin (@wz1000) 29 Apr '25
by Zubin (@wz1000) 29 Apr '25
29 Apr '25
Zubin pushed to branch wip/strict-level at Glasgow Haskell Compiler / GHC
Commits:
f70ba2e8 by Zubin Duggal at 2025-04-29T17:34:04+05:30
Add -fverbose-core-names flag to control generated name verbosity
- - - - -
6 changed files:
- compiler/GHC/Core/Opt/FloatOut.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
Changes:
=====================================
compiler/GHC/Core/Opt/FloatOut.hs
=====================================
@@ -18,6 +18,7 @@ import GHC.Core.Make
-- import GHC.Core.Opt.Arity ( exprArity, etaExpand )
import GHC.Core.Opt.Monad ( FloatOutSwitches(..) )
+import GHC.Driver.DynFlags ( DynFlags )
import GHC.Driver.Flags ( DumpFlag (..) )
import GHC.Utils.Logger
import GHC.Types.Id ( Id, idType,
@@ -117,14 +118,15 @@ Well, maybe. We don't do this at the moment.
************************************************************************
-}
-floatOutwards :: Logger
+floatOutwards :: DynFlags
+ -> Logger
-> FloatOutSwitches
-> UniqSupply
-> CoreProgram -> IO CoreProgram
-floatOutwards logger float_sws us pgm
+floatOutwards dflags logger float_sws us pgm
= do {
- let { annotated_w_levels = setLevels float_sws pgm us ;
+ let { annotated_w_levels = setLevels (initLevelOpts dflags) float_sws pgm us ;
(fss, binds_s') = unzip (map floatTopBind annotated_w_levels)
} ;
=====================================
compiler/GHC/Core/Opt/Pipeline.hs
=====================================
@@ -491,7 +491,7 @@ doCorePass pass guts = do
updateBinds (floatInwards platform)
CoreDoFloatOutwards f -> {-# SCC "FloatOutwards" #-}
- updateBindsM (liftIO . floatOutwards logger f us)
+ updateBindsM (liftIO . floatOutwards dflags logger f us)
CoreDoStaticArgs -> {-# SCC "StaticArgs" #-}
updateBinds (doStaticArgs us)
=====================================
compiler/GHC/Core/Opt/SetLevels.hs
=====================================
@@ -76,6 +76,8 @@
module GHC.Core.Opt.SetLevels (
setLevels,
+ initLevelOpts, LevelOpts (..),
+
Level(..), tOP_LEVEL,
LevelledBind, LevelledExpr, LevelledBndr,
FloatSpec(..), floatSpecLevel,
@@ -98,6 +100,8 @@ import GHC.Core.Type ( Type, tyCoVarsOfType
)
import GHC.Core.Multiplicity ( pattern ManyTy )
+import GHC.Driver.DynFlags ( DynFlags, GeneralFlag(..), gopt)
+
import GHC.Types.Id
import GHC.Types.Id.Info
import GHC.Types.Var
@@ -256,15 +260,16 @@ instance Eq Level where
************************************************************************
-}
-setLevels :: FloatOutSwitches
+setLevels :: LevelOpts
+ -> FloatOutSwitches
-> CoreProgram
-> UniqSupply
-> [LevelledBind]
-setLevels float_lams binds us
+setLevels opts float_lams binds us
= initLvl us (do_them binds)
where
- env = initialEnv float_lams binds
+ env = initialEnv opts float_lams binds
do_them :: [CoreBind] -> LvlM [LevelledBind]
do_them [] = return []
@@ -1636,9 +1641,14 @@ countFreeIds = nonDetStrictFoldUDFM add 0 . getUniqDSet
************************************************************************
-}
+newtype LevelOpts = LevelOpts { verboseInternalNames :: Bool }
+
+initLevelOpts :: DynFlags -> LevelOpts
+initLevelOpts = LevelOpts . gopt Opt_VerboseCoreNames
+
data LevelEnv
= LE { le_switches :: FloatOutSwitches
- , le_bind_ctxt :: [Id]
+ , le_bind_ctxt :: Maybe [Id]
, le_ctxt_lvl :: !Level -- The current level
, le_lvl_env :: VarEnv Level -- Domain is *post-cloned* TyVars and Ids
@@ -1681,10 +1691,10 @@ The domain of the both envs is *pre-cloned* Ids, though
The domain of the le_lvl_env is the *post-cloned* Ids
-}
-initialEnv :: FloatOutSwitches -> CoreProgram -> LevelEnv
-initialEnv float_lams binds
+initialEnv :: LevelOpts -> FloatOutSwitches -> CoreProgram -> LevelEnv
+initialEnv opts float_lams binds
= LE { le_switches = float_lams
- , le_bind_ctxt = []
+ , le_bind_ctxt = if verboseInternalNames opts then Just [] else Nothing
, le_ctxt_lvl = tOP_LEVEL
, le_lvl_env = emptyVarEnv
, le_subst = mkEmptySubst in_scope_toplvl
@@ -1698,7 +1708,7 @@ initialEnv float_lams binds
-- we start, to satisfy the lookupIdSubst invariants (#20200 and #20294)
pushBindContext :: LevelEnv -> Id -> LevelEnv
-pushBindContext env i = env { le_bind_ctxt = i : le_bind_ctxt env }
+pushBindContext env i = env { le_bind_ctxt = fmap (i :) (le_bind_ctxt env) }
addLvl :: Level -> VarEnv Level -> OutVar -> VarEnv Level
addLvl dest_lvl env v' = extendVarEnv env v' dest_lvl
@@ -1863,8 +1873,8 @@ newLvlVar env lvld_rhs join_arity_maybe is_mk_static
stem =
case le_bind_ctxt env of
- [] -> mkFastString "lvl"
- ctx -> mkFastString $ intercalate "_" ("lvl" : map (occNameString . getOccName) ctx)
+ Nothing -> mkFastString "lvl"
+ Just ctx -> mkFastString $ intercalate "_" ("lvl" : map (occNameString . getOccName) ctx)
-- | Clone the binders bound by a single-alternative case.
cloneCaseBndrs :: LevelEnv -> Level -> [Var] -> LvlM (LevelEnv, [Var])
=====================================
compiler/GHC/Driver/DynFlags.hs
=====================================
@@ -1157,7 +1157,8 @@ defaultFlags settings
Opt_SuppressStgReps,
Opt_UnoptimizedCoreForInterpreter,
Opt_SpecialiseIncoherents,
- Opt_WriteSelfRecompInfo
+ Opt_WriteSelfRecompInfo,
+ Opt_VerboseCoreNames
]
++ [f | (ns,f) <- optLevelFlags, 0 `elem` ns]
=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -853,6 +853,9 @@ data GeneralFlag
-- Object code determinism
| Opt_ObjectDeterminism
+ -- Should core names be verbose and include information about their context
+ | Opt_VerboseCoreNames
+
-- temporary flags
| Opt_AutoLinkPackages
| Opt_ImplicitImportQualified
@@ -968,6 +971,7 @@ codeGenFlags = EnumSet.fromList
, Opt_NoTypeableBinds
, Opt_ObjectDeterminism
, Opt_Haddock
+ , Opt_VerboseCoreNames
-- Flags that affect catching of runtime errors
, Opt_CatchNonexhaustiveCases
=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -2591,6 +2591,7 @@ fFlagsDeps = [
flagSpec "byte-code-and-object-code" Opt_ByteCodeAndObjectCode,
flagSpec "prefer-byte-code" Opt_UseBytecodeRatherThanObjects,
flagSpec "object-determinism" Opt_ObjectDeterminism,
+ flagSpec "verbose-core-names" Opt_VerboseCoreNames,
flagSpec' "compact-unwind" Opt_CompactUnwind
(\turn_on -> updM (\dflags -> do
unless (platformOS (targetPlatform dflags) == OSDarwin && turn_on)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f70ba2e8e6d7a02d01e2f0a5272d911…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f70ba2e8e6d7a02d01e2f0a5272d911…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T23109a] 3 commits: Improve the Simplifier
by Simon Peyton Jones (@simonpj) 29 Apr '25
by Simon Peyton Jones (@simonpj) 29 Apr '25
29 Apr '25
Simon Peyton Jones pushed to branch wip/T23109a at Glasgow Haskell Compiler / GHC
Commits:
d4279916 by Simon Peyton Jones at 2025-04-29T11:25:18+01:00
Improve the Simplifier
While working on #23109, I made two improvements to the Simplifier
* I found that the Simplifier was sometimes iterating more than it should.
I fixed this by improving postInlineUnconditionally.
* I refactored tryCastWorkerWrapper. It is now clearer, and does less
repeated work. This allowed me to call it from makeTrivial, which again
does a bit more in one pass, elminating a potential extra Simplifier
iteration
More care in postInline
Don't inline data con apps so vigorously
needs more docs
Wibbles
Be more careful in mkDupableContWithDmds
to not create a binding that will immediately be inlined
Do post-inline used-once bindings
This makes cacheprof not regress and seems generally a good plan
More eperiments
* Don't inline toplevel things so much
* Don't float constants so vigorously in the first float-out
Comments only
Refator GHC.Core.Opt.SetLevels.notWorthFloating
I refactored `notWorthFloating` while I was doing something else.
I don't think there's a change in behaviour, but if so it's very much
a corner case.
Always float bottoming expressions to the top
...regardless of floatConsts
Comments only
Wibble SetLevels
Try getting rid of this early-phase business
Don't float PAPs to top level
...and treat case alternatives as strict contexts
Wibble to postInlineUnconditionally
Small wibbles
Don't make error calls interesting.
Literals say True too isSaturatedConApp
Import wibble
Tiny change to saves_alloc
Float lambdas (and PAPs) out of lambdas to top level
This improves spectral/cse
But the old comment was
-- is_con_app: don't float PAPs to the top; they may well end
-- up getting eta-expanded and re-inlined
-- E.g. f = \x -> (++) ys
-- If we float, then eta-expand we get
-- lvl = (++) ys
-- f = \x \zs -> lvl zs
-- and now we'll inline lvl. Silly.
Let's see what CI says
- - - - -
2d087046 by Simon Peyton Jones at 2025-04-29T11:25:28+01:00
Specialise the (higher order) showSignedFloat
- - - - -
680f1b60 by Simon Peyton Jones at 2025-04-29T11:25:28+01:00
Eta reduce augment and its rules
... to match foldr. I found this reduced some simplifer iterations
Fix `augment`!
- - - - -
10 changed files:
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Utils.hs
- libraries/ghc-internal/src/GHC/Internal/Base.hs
- libraries/ghc-internal/src/GHC/Internal/Float.hs
- testsuite/tests/simplCore/should_run/simplrun009.hs
Changes:
=====================================
compiler/GHC/Core/Opt/OccurAnal.hs
=====================================
@@ -55,7 +55,7 @@ import GHC.Types.Tickish
import GHC.Types.Var.Set
import GHC.Types.Var.Env
import GHC.Types.Var
-import GHC.Types.Demand ( argOneShots, argsOneShots, isDeadEndSig )
+import GHC.Types.Demand ( argOneShots, argsOneShots {- , isDeadEndSig -} )
import GHC.Utils.Outputable
import GHC.Utils.Panic
@@ -1096,14 +1096,14 @@ mkNonRecRhsCtxt lvl bndr unf
certainly_inline -- See Note [Cascading inlines]
= -- mkNonRecRhsCtxt is only used for non-join points, so occAnalBind
-- has set the OccInfo for this binder before calling occAnalNonRecRhs
+ -- Distressing delicacy ... has to line up with preInlineUnconditionally
case idOccInfo bndr of
OneOcc { occ_in_lam = NotInsideLam, occ_n_br = 1 }
- -> active && not stable_unf && not top_bottoming
+ -> active && not (isTopLevel lvl) && not stable_unf
_ -> False
active = isAlwaysActive (idInlineActivation bndr)
stable_unf = isStableUnfolding unf
- top_bottoming = isTopLevel lvl && isDeadEndId bndr
-----------------
occAnalRecBind :: OccEnv -> TopLevelFlag -> ImpRuleEdges -> [(Var,CoreExpr)]
@@ -2580,8 +2580,9 @@ occAnalArgs !env fun args !one_shots
-- Make bottoming functions interesting
-- See Note [Bottoming function calls]
- encl | Var f <- fun, isDeadEndSig (idDmdSig f) = OccScrut
- | otherwise = OccVanilla
+-- encl | Var f <- fun, isDeadEndSig (idDmdSig f) = OccScrut
+-- | otherwise = OccVanilla
+ encl = OccVanilla
go uds fun [] _ = WUD uds fun
go uds fun (arg:args) one_shots
@@ -2606,7 +2607,8 @@ Consider
let x = (a,b) in
case p of
A -> ...(error x)..
- B -> ...(ertor x)...
+ B -> ...(error x)...
+ C -> ..blah...
postInlineUnconditionally may duplicate x's binding, but sometimes it
does so only if the use site IsInteresting. Pushing allocation into error
@@ -2616,6 +2618,9 @@ setting occ_encl = OccScrut for such calls.
The slightly-artificial test T21128 is a good example. It's probably
not a huge deal.
+ToDo!!! Fix comment. Now postinlineUnconditionally ignores intersting-ness for
+non-top-level things.
+
Note [Arguments of let-bound constructors]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Consider
=====================================
compiler/GHC/Core/Opt/Pipeline.hs
=====================================
@@ -217,7 +217,7 @@ getCoreToDo dflags hpt_rule_base extra_vars
if full_laziness then
CoreDoFloatOutwards $ FloatOutSwitches
{ floatOutLambdas = Just 0
- , floatOutConstants = True
+ , floatOutConstants = False -- Initially
, floatOutOverSatApps = False
, floatToTopLevelOnly = False
, floatJoinsToTop = False -- Initially, don't float join points at all
@@ -284,7 +284,7 @@ getCoreToDo dflags hpt_rule_base extra_vars
-- f_el22 (f_el21 r_midblock)
runWhen full_laziness $ CoreDoFloatOutwards $ FloatOutSwitches
{ floatOutLambdas = floatLamArgs dflags
- , floatOutConstants = True
+ , floatOutConstants = True -- For SpecConstr and CSE
, floatOutOverSatApps = True
, floatToTopLevelOnly = False
, floatJoinsToTop = True },
=====================================
compiler/GHC/Core/Opt/SetLevels.hs
=====================================
@@ -406,7 +406,7 @@ lvlApp env orig_expr ((_,AnnVar fn), args)
, arity < n_val_args
, Nothing <- isClassOpId_maybe fn
= do { rargs' <- mapM (lvlNonTailMFE env False) rargs
- ; lapp' <- lvlNonTailMFE env False lapp
+ ; lapp' <- lvlNonTailMFE env True lapp
; return (foldl' App lapp' rargs') }
| otherwise
@@ -482,14 +482,14 @@ Consider this:
f :: T Int -> blah
f x vs = case x of { MkT y ->
let f vs = ...(case y of I# w -> e)...f..
- in f vs
+ in f vs }
Here we can float the (case y ...) out, because y is sure
to be evaluated, to give
f x vs = case x of { MkT y ->
- case y of I# w ->
+ case y of { I# w ->
let f vs = ...(e)...f..
- in f vs
+ in f vs }}
That saves unboxing it every time round the loop. It's important in
some DPH stuff where we really want to avoid that repeated unboxing in
@@ -614,7 +614,8 @@ lvlMFE env strict_ctxt e@(_, AnnCase {})
= lvlExpr env e -- See Note [Case MFEs]
lvlMFE env strict_ctxt ann_expr
- | not float_me
+ | notWorthFloating expr abs_vars
+ || not float_me
|| floatTopLvlOnly env && not (isTopLvl dest_lvl)
-- Only floating to the top level is allowed.
|| hasFreeJoin env fvs -- If there is a free join, don't float
@@ -623,9 +624,6 @@ lvlMFE env strict_ctxt ann_expr
-- We can't let-bind an expression if we don't know
-- how it will be represented at runtime.
-- See Note [Representation polymorphism invariants] in GHC.Core
- || notWorthFloating expr abs_vars
- -- Test notWorhtFloating last;
- -- See Note [Large free-variable sets]
= -- Don't float it out
lvlExpr env ann_expr
@@ -676,12 +674,11 @@ lvlMFE env strict_ctxt ann_expr
is_function = isFunction ann_expr
mb_bot_str = exprBotStrictness_maybe expr
-- See Note [Bottoming floats]
- -- esp Bottoming floats (2)
+ -- esp Bottoming floats (BF2)
expr_ok_for_spec = exprOkForSpeculation expr
abs_vars = abstractVars dest_lvl env fvs
dest_lvl = destLevel env fvs fvs_ty is_function is_bot_lam
- -- NB: is_bot_lam not is_bot; see (3) in
- -- Note [Bottoming floats]
+ -- NB: is_bot_lam not is_bot; see (BF2) in Note [Bottoming floats]
-- float_is_new_lam: the floated thing will be a new value lambda
-- replacing, say (g (x+4)) by (lvl x). No work is saved, nor is
@@ -698,20 +695,32 @@ lvlMFE env strict_ctxt ann_expr
-- A decision to float entails let-binding this thing, and we only do
-- that if we'll escape a value lambda, or will go to the top level.
+ -- Never float trivial expressions;
+ -- notably, save_work might be true of a lone evaluated variable.
float_me = saves_work || saves_alloc || is_mk_static
-- See Note [Saving work]
- saves_work = escapes_value_lam -- (a)
- && not (exprIsHNF expr) -- (b)
- && not float_is_new_lam -- (c)
+ is_hnf = exprIsHNF expr
+ saves_work = escapes_value_lam -- (SW-a)
+ && not is_hnf -- (SW-b)
+ && not float_is_new_lam -- (SW-c)
escapes_value_lam = dest_lvl `ltMajLvl` (le_ctxt_lvl env)
- -- See Note [Saving allocation] and Note [Floating to the top]
- saves_alloc = isTopLvl dest_lvl
- && floatConsts env
- && ( not strict_ctxt -- (a)
- || exprIsHNF expr -- (b)
- || (is_bot_lam && escapes_value_lam)) -- (c)
+ -- See Note [Floating to the top]
+-- is_con_app = isSaturatedConApp expr -- True of literal strings too
+ saves_alloc = isTopLvl dest_lvl
+ && (escapes_value_lam || floatConsts env)
+ -- Always float allocation out of a value lambda
+ -- if it gets to top level
+ && (not strict_ctxt || is_hnf || is_bot_lam)
+ -- is_con_app: don't float PAPs to the top; they may well end
+ -- up getting eta-expanded and re-inlined
+ -- E.g. f = \x -> (++) ys
+ -- If we float, then eta-expand we get
+ -- lvl = (++) ys
+ -- f = \x \zs -> lvl zs
+ -- and now we'll inline lvl. Silly.
+
hasFreeJoin :: LevelEnv -> DVarSet -> Bool
-- Has a free join point which is not being floated to top level.
@@ -726,22 +735,22 @@ hasFreeJoin env fvs
The key idea in let-floating is to
* float a redex out of a (value) lambda
Doing so can save an unbounded amount of work.
-But see also Note [Saving allocation].
+But see also Note [Floating to the top].
So we definitely float an expression out if
-(a) It will escape a value lambda (escapes_value_lam)
-(b) The expression is not a head-normal form (exprIsHNF); see (SW1, SW2).
-(c) Floating does not require wrapping it in value lambdas (float_is_new_lam).
+(SW-a) It will escape a value lambda (escapes_value_lam)
+(SW-b) The expression is not a head-normal form (exprIsHNF); see (SW1, SW2).
+(SW-c) Floating does not require wrapping it in value lambdas (float_is_new_lam).
See (SW3) below
Wrinkles:
-(SW1) Concerning (b) I experimented with using `exprIsCheap` rather than
+(SW1) Concerning (SW-b) I experimented with using `exprIsCheap` rather than
`exprIsHNF` but the latter seems better, according to nofib
(`spectral/mate` got 10% worse with exprIsCheap). It's really a bit of a
heuristic.
-(SW2) What about omitting (b), and hence floating HNFs as well? The danger of
+(SW2) What about omitting (SW-b), and hence floating HNFs as well? The danger of
doing so is that we end up floating out a HNF from a cold path (where it
might never get allocated at all) and allocating it all the time
regardless. Example
@@ -760,7 +769,7 @@ Wrinkles:
- Occasionally decreases runtime allocation (T12996 -2.5%)
- Slightly mixed effect on nofib: (puzzle -10%, mate -5%, cichelli +5%)
but geometric mean is -0.09%.
- Overall, a win.
+ Overall, a small win.
(SW3) Concerning (c), if we are wrapping the thing in extra value lambdas (in
abs_vars), then nothing is saved. E.g.
@@ -771,10 +780,12 @@ Wrinkles:
we have saved nothing: one pair will still be allocated for each
call of `f`. Hence the (not float_is_new_lam) in saves_work.
-Note [Saving allocation]
-~~~~~~~~~~~~~~~~~~~~~~~~
+Note [Floating to the top]
+~~~~~~~~~~~~~~~~~~~~~~~~~~
Even if `saves_work` is false, we we may want to float even cheap/HNF
-expressions out of value lambdas, for several reasons:
+expressions out of value lambdas. Data suggests, however, that it is better
+/only/ to do so, /if/ they can go to top level. If the expression goes to top
+level we don't pay the cost of allocating cold-path thunks described in (SW2).
* Doing so may save allocation. Consider
f = \x. .. (\y.e) ...
@@ -782,6 +793,11 @@ expressions out of value lambdas, for several reasons:
(assuming e does not mention x). An example where this really makes a
difference is simplrun009.
+* In principle this would be true even if the (\y.e) didn't go to top level; but
+ in practice we only float a HNF if it goes all way to the top. We don't pay
+ /any/ allocation cost for a top-level floated expression; it just becomes
+ static data.
+
* It may allow SpecContr to fire on functions. Consider
f = \x. ....(f (\y.e))....
After floating we get
@@ -793,21 +809,7 @@ expressions out of value lambdas, for several reasons:
a big difference for string literals and bottoming expressions: see Note
[Floating to the top]
-Data suggests, however, that it is better /only/ to float HNFS, /if/ they can go
-to top level. See (SW2) of Note [Saving work]. If the expression goes to top
-level we don't pay the cost of allocating cold-path thunks described in (SW2).
-
-Hence `isTopLvl dest_lvl` in `saves_alloc`.
-
-Note [Floating to the top]
-~~~~~~~~~~~~~~~~~~~~~~~~~~
-Even though Note [Saving allocation] suggests that we should not, in
-general, float HNFs, the balance change if it goes to the top:
-
-* We don't pay an allocation cost for the floated expression; it
- just becomes static data.
-
-* Floating string literal is valuable -- no point in duplicating the
+* Floating string literals is valuable -- no point in duplicating the
at each call site!
* Floating bottoming expressions is valuable: they are always cold
@@ -815,32 +817,32 @@ general, float HNFs, the balance change if it goes to the top:
can be quite big, inhibiting inlining. See Note [Bottoming floats]
So we float an expression to the top if:
- (a) the context is lazy (so we get allocation), or
- (b) the expression is a HNF (so we get allocation), or
- (c) the expression is bottoming and floating would escape a
- value lambda (NB: if the expression itself is a lambda, (b)
- will apply; so this case only catches bottoming thunks)
+ (FT1) the context is lazy (so we get allocation), or
+ (FT2) the expression is a HNF (so we get allocation), or
+ (FT3) the expression is bottoming and floating would escape a
+ value lambda (NB: if the expression itself is a lambda, (b)
+ will apply; so this case only catches bottoming thunks)
Examples:
-* (a) Strict. Case scrutinee
+* (FT1) Strict. Case scrutinee
f = case g True of ....
Don't float (g True) to top level; then we have the admin of a
top-level thunk to worry about, with zero gain.
-* (a) Strict. Case alternative
+* (FT1) Strict. Case alternative
h = case y of
True -> g True
False -> False
Don't float (g True) to the top level
-* (b) HNF
+* (FT2) HNF
f = case y of
True -> p:q
False -> blah
We may as well float the (p:q) so it becomes a static data structure.
-* (c) Bottoming expressions; see also Note [Bottoming floats]
+* (FT3) Bottoming expressions; see also Note [Bottoming floats]
f x = case x of
0 -> error <big thing>
_ -> x+1
@@ -853,7 +855,7 @@ Examples:
'foo' anyway. So float bottoming things only if they escape
a lambda.
-* Arguments
+* (FT4) Arguments
t = f (g True)
Prior to Apr 22 we didn't float (g True) to the top if f was strict.
But (a) this only affected CAFs, because if it escapes a value lambda
@@ -868,28 +870,6 @@ early loses opportunities for RULES which (needless to say) are
important in some nofib programs (gcd is an example). [SPJ note:
I think this is obsolete; the flag seems always on.]
-Note [Large free-variable sets]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-In #24471 we had something like
- x1 = I# 1
- ...
- x1000 = I# 1000
- foo = f x1 (f x2 (f x3 ....))
-So every sub-expression in `foo` has lots and lots of free variables. But
-none of these sub-expressions float anywhere; the entire float-out pass is a
-no-op.
-
-In lvlMFE, we want to find out quickly if the MFE is not-floatable; that is
-the common case. In #24471 it turned out that we were testing `abs_vars` (a
-relatively complicated calculation that takes at least O(n-free-vars) time to
-compute) for every sub-expression.
-
-Better instead to test `float_me` early. That still involves looking at
-dest_lvl, which means looking at every free variable, but the constant factor
-is a lot better.
-
-ToDo: find a way to fix the bad asymptotic complexity.
-
Note [Floating join point bindings]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Mostly we don't float join points at all -- we want them to /stay/ join points.
@@ -1053,30 +1033,36 @@ we'd like to float the call to error, to get
But, as ever, we need to be careful:
-(1) We want to float a bottoming
+(BF1) We want to float a bottoming
expression even if it has free variables:
f = \x. g (let v = h x in error ("urk" ++ v))
Then we'd like to abstract over 'x', and float the whole arg of g:
lvl = \x. let v = h x in error ("urk" ++ v)
f = \x. g (lvl x)
- To achieve this we pass is_bot to destLevel
-
-(2) We do not do this for lambdas that return
- bottom. Instead we treat the /body/ of such a function specially,
- via point (1). For example:
+ To achieve this we pass `is_bot` to destLevel
+
+(BF2) We do the same for /lambdas/ that return bottom.
+ Suppose the original lambda had /no/ free vars:
+ f = \x. ....(\y z. error (y++z))...
+ then we'd like to float that whole lambda
+ lvl = \y z. error (y++z)
+ f = \x. ....lvl....
+ If we just floated its bottom-valued body, we might abstract the arguments in
+ the "wrong" order and end up with this bad result
+ lvl = \z y. error (y++z)
+ f = \x. ....(\y z. lvl z y)....
+
+ If the lambda does have free vars, this will happen:
f = \x. ....(\y z. if x then error y else error z)....
- If we float the whole lambda thus
+ We float the whole lambda thus
lvl = \x. \y z. if x then error y else error z
f = \x. ...(lvl x)...
- we may well end up eta-expanding that PAP to
+ And we may well end up eta-expanding that PAP to
+ lvl = \x. \y z. if b then error y else error z
f = \x. ...(\y z. lvl x y z)...
+ so we get a (small) closure. So be it.
- ===>
- lvl = \x z y. if b then error y else error z
- f = \x. ...(\y z. lvl x z y)...
- (There is no guarantee that we'll choose the perfect argument order.)
-
-(3) If we have a /binding/ that returns bottom, we want to float it to top
+(BF3) If we have a /binding/ that returns bottom, we want to float it to top
level, even if it has free vars (point (1)), and even it has lambdas.
Example:
... let { v = \y. error (show x ++ show y) } in ...
@@ -1092,7 +1078,6 @@ But, as ever, we need to be careful:
join points (#24768), and floating to the top would abstract over those join
points, which we should never do.
-
See Maessen's paper 1999 "Bottom extraction: factoring error handling out
of functional programs" (unpublished I think).
@@ -1135,7 +1120,6 @@ float the case (as advocated here) we won't float the (build ...y..)
either, so fusion will happen. It can be a big effect, esp in some
artificial benchmarks (e.g. integer, queens), but there is no perfect
answer.
-
-}
annotateBotStr :: Id -> Arity -> Maybe (Arity, DmdSig, CprSig) -> Id
@@ -1152,69 +1136,124 @@ annotateBotStr id n_extra mb_bot_str
= id
notWorthFloating :: CoreExpr -> [Var] -> Bool
--- Returns True if the expression would be replaced by
--- something bigger than it is now. For example:
--- abs_vars = tvars only: return True if e is trivial,
--- but False for anything bigger
--- abs_vars = [x] (an Id): return True for trivial, or an application (f x)
--- but False for (f x x)
---
--- One big goal is that floating should be idempotent. Eg if
--- we replace e with (lvl79 x y) and then run FloatOut again, don't want
--- to replace (lvl79 x y) with (lvl83 x y)!
-
+-- See Note [notWorthFloating]
notWorthFloating e abs_vars
- = go e (count isId abs_vars)
+ = go e 0
where
- go (Var {}) n = n >= 0
- go (Lit lit) n = assert (n==0) $
- litIsTrivial lit -- Note [Floating literals]
- go (Type {}) _ = True
- go (Coercion {}) _ = True
+ n_abs_vars = count isId abs_vars -- See (NWF5)
+
+ go :: CoreExpr -> Int -> Bool
+ -- (go e n) return True if (e x1 .. xn) is not worth floating
+ -- where `e` has n trivial value arguments x1..xn
+ -- See (NWF4)
+ go (Lit lit) n = assert (n==0) $
+ litIsTrivial lit -- See (NWF1)
+ go (Type {}) _ = True
+ go (Tick t e) n = not (tickishIsCode t) && go e n
+ go (Cast e _) n = n==0 || go e n -- See (NWF3)
+ go (Coercion {}) _ = True
go (App e arg) n
- -- See Note [Floating applications to coercions]
- | not (isRuntimeArg arg) = go e n
- | n==0 = False
- | exprIsTrivial arg = go e (n-1) -- NB: exprIsTrivial arg = go arg 0
- | otherwise = False
- go (Tick t e) n = not (tickishIsCode t) && go e n
- go (Cast e _) n = go e n
- go (Case e b _ as) n
+ | Type {} <- arg = go e n -- Just types, not coercions (NWF2)
+ | exprIsTrivial arg = go e (n+1)
+ | otherwise = False -- (f non-triv) is worth floating
+
+ go (Case e b _ as) _
+ -- Do not float the `case` part of trivial cases (NWF3)
+ -- We'll have a look at the RHS when we get there
| null as
- = go e n -- See Note [Empty case is trivial]
- | Just rhs <- isUnsafeEqualityCase e b as
- = go rhs n -- See (U2) of Note [Implementing unsafeCoerce] in base:Unsafe.Coerce
- go _ _ = False
+ = True -- See Note [Empty case is trivial]
+ | Just {} <- isUnsafeEqualityCase e b as
+ = True -- See (U2) of Note [Implementing unsafeCoerce] in base:Unsafe.Coerce
+ | otherwise
+ = False
-{-
-Note [Floating literals]
-~~~~~~~~~~~~~~~~~~~~~~~~
-It's important to float Integer literals, so that they get shared,
-rather than being allocated every time round the loop.
-Hence the litIsTrivial.
+ go (Var _) n
+ | n==0 = True -- Naked variable
+ | n <= n_abs_vars = True -- (f a b c) is not worth floating if
+ | otherwise = False -- a,b,c are all abstracted; see (NWF5)
-Ditto literal strings (LitString), which we'd like to float to top
-level, which is now possible.
+ go _ _ = False -- Let etc is worth floating
-Note [Floating applications to coercions]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-We don’t float out variables applied only to type arguments, since the
-extra binding would be pointless: type arguments are completely erased.
-But *coercion* arguments aren’t (see Note [Coercion tokens] in
-"GHC.CoreToStg" and Note [inlineBoringOk] in"GHC.Core.Unfold"),
-so we still want to float out variables applied only to
-coercion arguments.
+{- Note [notWorthFloating]
+~~~~~~~~~~~~~~~~~~~~~~~~~~
+`notWorthFloating` returns True if the expression would be replaced by something
+bigger than it is now. One big goal is that floating should be idempotent. Eg
+if we replace e with (lvl79 x y) and then run FloatOut again, don't want to
+replace (lvl79 x y) with (lvl83 x y)!
+For example:
+ abs_vars = tvars only: return True if e is trivial,
+ but False for anything bigger
+ abs_vars = [x] (an Id): return True for trivial, or an application (f x)
+ but False for (f x x)
+
+(NWF1) It's important to float Integer literals, so that they get shared, rather
+ than being allocated every time round the loop. Hence the litIsTrivial.
+
+ Ditto literal strings (LitString), which we'd like to float to top
+ level, which is now possible.
+
+(NWF2) We don’t float out variables applied only to type arguments, since the
+ extra binding would be pointless: type arguments are completely erased.
+ But *coercion* arguments aren’t (see Note [Coercion tokens] in
+ "GHC.CoreToStg" and Note [inlineBoringOk] in"GHC.Core.Unfold"),
+ so we still want to float out variables applied only to
+ coercion arguments.
+
+(NWF3) Some expressions have trivial wrappers:
+ - Casts (e |> co)
+ - Unary-class applications:
+ - Dictionary applications (MkC meth)
+ - Class-op applictions (op dict)
+ - Case of empty alts
+ - Unsafe-equality case
+ In all these cases we say "not worth floating", and we do so /regardless/
+ of the wrapped expression. The SetLevels stuff may subsequently float the
+ components of the expression.
+
+ Example: is it worth floating (f x |> co)? No! If we did we'd get
+ lvl = f x |> co
+ ...lvl....
+ Then we'd do cast worker/wrapper and end up with.
+ lvl' = f x
+ ...(lvl' |> co)...
+ Silly! Better not to float it in the first place. If we say "no" here,
+ we'll subsequently say "yes" for (f x) and get
+ lvl = f x
+ ....(lvl |> co)...
+ which is what we want. In short: don't float trivial wrappers.
+
+(NWF4) The only non-trivial expression that we say "not worth floating" for
+ is an application
+ f x y z
+ where the number of value arguments is <= the number of abstracted Ids.
+ This is what makes floating idempotent. Hence counting the number of
+ value arguments in `go`
+
+(NWF5) In #24471 we had something like
+ x1 = I# 1
+ ...
+ x1000 = I# 1000
+ foo = f x1 (f x2 (f x3 ....))
+ So every sub-expression in `foo` has lots and lots of free variables. But
+ none of these sub-expressions float anywhere; the entire float-out pass is a
+ no-op.
-************************************************************************
-* *
-\subsection{Bindings}
-* *
-************************************************************************
+ So `notWorthFloating` tries to avoid evaluating `n_abs_vars`, in cases where
+ it obviously /is/ worth floating. (In #24471 it turned out that we were
+ testing `abs_vars` (a relatively complicated calculation that takes at least
+ O(n-free-vars) time to compute) for every sub-expression.)
-The binding stuff works for top level too.
+ Hence testing `n_abs_vars only` at the very end.
-}
+{- *********************************************************************
+* *
+ Bindings
+ This binding stuff works for top level too.
+* *
+********************************************************************* -}
+
lvlBind :: LevelEnv
-> CoreBindWithFVs
-> LvlM (LevelledBind, LevelEnv)
@@ -1261,7 +1300,7 @@ lvlBind env (AnnNonRec bndr rhs)
-- is_bot_lam: looks like (\xy. bot), maybe zero lams
-- NB: not isBottomThunk!
-- NB: not is_join: don't send bottoming join points to the top.
- -- See Note [Bottoming floats] point (3)
+ -- See Note [Bottoming floats] (BF3)
is_top_bindable = exprIsTopLevelBindable deann_rhs bndr_ty
n_extra = count isId abs_vars
@@ -1552,9 +1591,8 @@ destLevel env fvs fvs_ty is_function is_bot
-- See Note [Floating join point bindings]
= tOP_LEVEL
- | is_bot -- Send bottoming bindings to the top
- = as_far_as_poss -- regardless; see Note [Bottoming floats]
- -- Esp Bottoming floats (1) and (3)
+ | is_bot -- Send bottoming bindings to the top regardless;
+ = as_far_as_poss -- see (BF1) and (BF2) in Note [Bottoming floats]
| Just n_args <- floatLams env
, n_args > 0 -- n=0 case handled uniformly by the 'otherwise' case
@@ -1568,8 +1606,13 @@ destLevel env fvs fvs_ty is_function is_bot
max_fv_id_level = maxFvLevel isId env fvs -- Max over Ids only; the
-- tyvars will be abstracted
+ -- as_far_as_poss: destination level depends only on the free Ids (more
+ -- precisely, free CoVars) of the /type/, not the free Ids of the /term/.
+ -- Why worry about the free CoVars? See Note [Floating and kind casts]
+ --
+ -- There may be free Ids in the term, but then we'll just
+ -- lambda-abstract over them
as_far_as_poss = maxFvLevel' isId env fvs_ty
- -- See Note [Floating and kind casts]
{- Note [Floating and kind casts]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -1732,10 +1775,9 @@ maxFvLevel max_me env var_set
-- It's OK to use a non-deterministic fold here because maxIn commutes.
maxFvLevel' :: (Var -> Bool) -> LevelEnv -> TyCoVarSet -> Level
--- Same but for TyCoVarSet
+-- Precisely the same as `maxFvLevel` but for TyCoVarSet rather than DVarSet
maxFvLevel' max_me env var_set
= nonDetStrictFoldUniqSet (maxIn max_me env) tOP_LEVEL var_set
- -- It's OK to use a non-deterministic fold here because maxIn commutes.
maxIn :: (Var -> Bool) -> LevelEnv -> InVar -> Level -> Level
maxIn max_me (LE { le_lvl_env = lvl_env, le_env = id_env }) in_var lvl
=====================================
compiler/GHC/Core/Opt/Simplify/Env.hs
=====================================
@@ -11,7 +11,7 @@ module GHC.Core.Opt.Simplify.Env (
SimplMode(..), updMode, smPlatform,
-- * Environments
- SimplEnv(..), pprSimplEnv, -- Temp not abstract
+ SimplEnv(..), StaticEnv, pprSimplEnv,
seArityOpts, seCaseCase, seCaseFolding, seCaseMerge, seCastSwizzle,
seDoEtaReduction, seEtaExpand, seFloatEnable, seInline, seNames,
seOptCoercionOpts, sePhase, sePlatform, sePreInline,
@@ -170,6 +170,8 @@ coercion we don't apply optCoercion to it if seInlineDepth>0.
Reason: it has already been optimised once, no point in doing so again.
-}
+type StaticEnv = SimplEnv -- Just the static part is relevant
+
data SimplEnv
= SimplEnv {
----------- Static part of the environment -----------
@@ -407,7 +409,6 @@ data SimplSR
-- and ja = Just a <=> x is a join-point of arity a
-- See Note [Join arity in SimplIdSubst]
-
| DoneId OutId
-- If x :-> DoneId v is in the SimplIdSubst
-- then replace occurrences of x by v
@@ -778,7 +779,7 @@ emptyJoinFloats = nilOL
isEmptyJoinFloats :: JoinFloats -> Bool
isEmptyJoinFloats = isNilOL
-unitLetFloat :: OutBind -> LetFloats
+unitLetFloat :: HasDebugCallStack => OutBind -> LetFloats
-- This key function constructs a singleton float with the right form
unitLetFloat bind = assert (all (not . isJoinId) (bindersOf bind)) $
LetFloats (unitOL bind) (flag bind)
=====================================
compiler/GHC/Core/Opt/Simplify/Iteration.hs
=====================================
@@ -447,7 +447,7 @@ we want to do something very similar to worker/wrapper:
We call this making a cast worker/wrapper in tryCastWorkerWrapper.
-The main motivaiton is that x can be inlined freely. There's a chance
+The main motivation is that x can be inlined freely. There's a chance
that e will be a constructor application or function, or something
like that, so moving the coercion to the usage site may well cancel
the coercions and lead to further optimisation. Example:
@@ -576,11 +576,13 @@ Note [Concrete types] in GHC.Tc.Utils.Concrete.
-}
tryCastWorkerWrapper :: SimplEnv -> BindContext
- -> InId -> OutId -> OutExpr
- -> SimplM (SimplFloats, SimplEnv)
+ -> OutId -> OutExpr
+ -> SimplM (Maybe (LetFloats, OutId, OutExpr))
-- See Note [Cast worker/wrapper]
-tryCastWorkerWrapper env bind_cxt old_bndr bndr (Cast rhs co)
- | BC_Let top_lvl is_rec <- bind_cxt -- Not join points
+-- Given input x = rhs |> co, the result will be
+-- (x' = rhs, x, x' |> co))
+tryCastWorkerWrapper env bind_cxt bndr (Cast rhs co)
+ | BC_Let top_lvl _ <- bind_cxt -- Not join points
, not (isDFunId bndr) -- nor DFuns; cast w/w is no help, and we can't transform
-- a DFunUnfolding in mk_worker_unfolding
, not (exprIsTrivial rhs) -- Not x = y |> co; Wrinkle 1
@@ -588,38 +590,23 @@ tryCastWorkerWrapper env bind_cxt old_bndr bndr (Cast rhs co)
, typeHasFixedRuntimeRep work_ty -- Don't peel off a cast if doing so would
-- lose the underlying runtime representation.
-- See Note [Preserve RuntimeRep info in cast w/w]
- , not (isOpaquePragma (idInlinePragma old_bndr)) -- Not for OPAQUE bindings
- -- See Note [OPAQUE pragma]
+ , not (isOpaquePragma (idInlinePragma bndr)) -- Not for OPAQUE bindings
+ -- See Note [OPAQUE pragma]
= do { uniq <- getUniqueM
; let work_name = mkSystemVarName uniq occ_fs
work_id = mkLocalIdWithInfo work_name ManyTy work_ty work_info
- is_strict = isStrictId bndr
- ; (rhs_floats, work_rhs) <- prepareBinding env top_lvl is_rec is_strict
- work_id (emptyFloats env) rhs
-
- ; work_unf <- mk_worker_unfolding top_lvl work_id work_rhs
+ ; work_unf <- mk_worker_unfolding top_lvl work_id rhs
; let work_id_w_unf = work_id `setIdUnfolding` work_unf
- floats = rhs_floats `addLetFloats`
- unitLetFloat (NonRec work_id_w_unf work_rhs)
-
- triv_rhs = Cast (Var work_id_w_unf) co
-
- ; if postInlineUnconditionally env bind_cxt old_bndr bndr triv_rhs
- -- Almost always True, because the RHS is trivial
- -- In that case we want to eliminate the binding fast
- -- We conservatively use postInlineUnconditionally so that we
- -- check all the right things
- then do { tick (PostInlineUnconditionally bndr)
- ; return ( floats
- , extendIdSubst (setInScopeFromF env floats) old_bndr $
- DoneEx triv_rhs NotJoinPoint ) }
-
- else do { wrap_unf <- mkLetUnfolding env top_lvl VanillaSrc bndr False triv_rhs
- ; let bndr' = bndr `setInlinePragma` mkCastWrapperInlinePrag (idInlinePragma bndr)
- `setIdUnfolding` wrap_unf
- floats' = floats `extendFloats` NonRec bndr' triv_rhs
- ; return ( floats', setInScopeFromF env floats' ) } }
+ work_bind = NonRec work_id_w_unf rhs
+ triv_rhs = Cast (Var work_id_w_unf) co
+
+ ; wrap_unf <- mkLetUnfolding env top_lvl VanillaSrc bndr False triv_rhs
+ ; let wrap_prag = mkCastWrapperInlinePrag (inlinePragInfo info)
+ bndr' = bndr `setInlinePragma` wrap_prag
+ `setIdUnfolding` wrap_unf
+
+ ; return (Just (unitLetFloat work_bind, bndr', triv_rhs)) }
where
-- Force the occ_fs so that the old Id is not retained in the new Id.
!occ_fs = getOccFS bndr
@@ -647,10 +634,10 @@ tryCastWorkerWrapper env bind_cxt old_bndr bndr (Cast rhs co)
| isStableSource src -> return (unf { uf_tmpl = mkCast unf_rhs (mkSymCo co) })
_ -> mkLetUnfolding env top_lvl VanillaSrc work_id False work_rhs
-tryCastWorkerWrapper env _ _ bndr rhs -- All other bindings
+tryCastWorkerWrapper _ _ bndr rhs -- All other bindings
= do { traceSmpl "tcww:no" (vcat [ text "bndr:" <+> ppr bndr
, text "rhs:" <+> ppr rhs ])
- ; return (mkFloatBind env (NonRec bndr rhs)) }
+ ; return Nothing }
mkCastWrapperInlinePrag :: InlinePragma -> InlinePragma
-- See Note [Cast worker/wrapper]
@@ -810,39 +797,40 @@ makeTrivial :: HasDebugCallStack
-- Binds the expression to a variable, if it's not trivial, returning the variable
-- For the Demand argument, see Note [Keeping demand info in StrictArg Plan A]
makeTrivial env top_lvl dmd occ_fs expr
- | exprIsTrivial expr -- Already trivial
- || not (bindingOk top_lvl expr expr_ty) -- Cannot trivialise
- -- See Note [Cannot trivialise]
+ | exprIsTrivial expr -- Already trivial
= return (emptyLetFloats, expr)
- | Cast expr' co <- expr
- = do { (floats, triv_expr) <- makeTrivial env top_lvl dmd occ_fs expr'
- ; return (floats, Cast triv_expr co) }
+ | not (bindingOk top_lvl expr expr_ty) -- Cannot trivialise
+ = return (emptyLetFloats, expr) -- See Note [Cannot trivialise]
- | otherwise -- 'expr' is not of form (Cast e co)
+ | otherwise
= do { (floats, expr1) <- prepareRhs env top_lvl occ_fs expr
; uniq <- getUniqueM
; let name = mkSystemVarName uniq occ_fs
- var = mkLocalIdWithInfo name ManyTy expr_ty id_info
+ bndr = mkLocalIdWithInfo name ManyTy expr_ty id_info
+ bind_ctxt = BC_Let top_lvl NonRecursive
-- Now something very like completeBind,
-- but without the postInlineUnconditionally part
- ; (arity_type, expr2) <- tryEtaExpandRhs env (BC_Let top_lvl NonRecursive) var expr1
+ ; (arity_type, expr2) <- tryEtaExpandRhs env bind_ctxt bndr expr1
-- Technically we should extend the in-scope set in 'env' with
-- the 'floats' from prepareRHS; but they are all fresh, so there is
-- no danger of introducing name shadowing in eta expansion
- ; unf <- mkLetUnfolding env top_lvl VanillaSrc var False expr2
-
- ; let final_id = addLetBndrInfo var arity_type unf
- bind = NonRec final_id expr2
+ ; unf <- mkLetUnfolding env top_lvl VanillaSrc bndr False expr2
+ ; let bndr' = addLetBndrInfo bndr arity_type unf
+ anf_bind = NonRec bndr' expr2
- ; traceSmpl "makeTrivial" (vcat [text "final_id" <+> ppr final_id, text "rhs" <+> ppr expr2 ])
- ; return ( floats `addLetFlts` unitLetFloat bind, Var final_id ) }
+ ; mb_cast_ww <- tryCastWorkerWrapper env bind_ctxt bndr' expr2
+ ; case mb_cast_ww of
+ Nothing -> return (floats `addLetFlts` unitLetFloat anf_bind, Var bndr')
+ Just (work_flts, _, triv_rhs)
+ -> return (floats `addLetFlts` work_flts, triv_rhs) }
where
id_info = vanillaIdInfo `setDemandInfo` dmd
expr_ty = exprType expr
+
bindingOk :: TopLevelFlag -> CoreExpr -> Type -> Bool
-- True iff we can have a binding of this expression at this level
-- Precondition: the type is the type of the expression
@@ -936,26 +924,50 @@ completeBind bind_cxt (old_bndr, unf_se) (new_bndr, new_rhs, env)
eta_rhs (idType new_bndr) new_arity old_unf
; let new_bndr_w_info = addLetBndrInfo new_bndr new_arity new_unfolding
- -- See Note [In-scope set as a substitution]
+ -- See Note [In-scope set as a substitution]
+ occ_anald_rhs = maybeUnfoldingTemplate new_unfolding `orElse` eta_rhs
+ -- occ_anald_rhs: see Note [Use occ-anald RHS in postInlineUnconditionally]
+ -- Try postInlineUnconditionally for (x = rhs)
+ -- If that succeeds we don't want to do tryCastWorkerWrapper
; if postInlineUnconditionally env bind_cxt old_bndr new_bndr_w_info eta_rhs
-
- then -- Inline and discard the binding
- do { tick (PostInlineUnconditionally old_bndr)
- ; let unf_rhs = maybeUnfoldingTemplate new_unfolding `orElse` eta_rhs
- -- See Note [Use occ-anald RHS in postInlineUnconditionally]
- ; simplTrace "PostInlineUnconditionally" (ppr new_bndr <+> ppr unf_rhs) $
- return ( emptyFloats env
- , extendIdSubst env old_bndr $
- DoneEx unf_rhs (idJoinPointHood new_bndr)) }
+ then post_inline_it (emptyFloats env) occ_anald_rhs
+ else
+
+ do { -- Try cast worker-wrapper
+ mb_cast_ww <- tryCastWorkerWrapper env bind_cxt new_bndr_w_info eta_rhs
+ ; case mb_cast_ww of
+ Nothing -> no_post_inline (emptyFloats env) new_bndr_w_info eta_rhs
+
+ Just (cast_let_flts, new_bndr, new_rhs)
+ -- Try postInlineUnconditionally for (new_bndr = new_rhs)
+ -- Almost always fires, because `new_rhs` is small, but we conservatively
+ -- use `postInlineUnconditionally` so that we check all the right things
+ | postInlineUnconditionally env bind_cxt old_bndr new_bndr new_rhs
+ -> post_inline_it cast_floats new_rhs
+ -- new_rhs is (x |> co) so no need to occ-anal
+ | otherwise
+ -> no_post_inline cast_floats new_bndr new_rhs
+ where
+ cast_floats = emptyFloats env `addLetFloats` cast_let_flts
+ } }
+ where
+ no_post_inline floats new_bndr new_rhs
+ = do { let the_bind = NonRec new_bndr new_rhs
+ floats' = floats `extendFloats` the_bind
+ env' = env `setInScopeFromF` floats'
+ ; return (floats', env') }
+
+ post_inline_it floats rhs
+ = do { simplTrace "PostInlineUnconditionally" (ppr old_bndr <+> ppr rhs) $
+ tick (PostInlineUnconditionally old_bndr)
+ ; let env' = env `setInScopeFromF` floats
+ ; return ( floats
+ , extendIdSubst env' old_bndr $
+ DoneEx rhs (idJoinPointHood old_bndr)) }
-- Use the substitution to make quite, quite sure that the
-- substitution will happen, since we are going to discard the binding
- else -- Keep the binding; do cast worker/wrapper
--- simplTrace "completeBind" (vcat [ text "bndrs" <+> ppr old_bndr <+> ppr new_bndr
--- , text "eta_rhs" <+> ppr eta_rhs ]) $
- tryCastWorkerWrapper env bind_cxt old_bndr new_bndr_w_info eta_rhs }
-
addLetBndrInfo :: OutId -> ArityType -> Unfolding -> OutId
addLetBndrInfo new_bndr new_arity_type new_unf
= new_bndr `setIdInfo` info5
@@ -3955,7 +3967,17 @@ mkDupableContWithDmds env dmds
; (floats1, cont') <- mkDupableContWithDmds env cont_dmds cont
; let env' = env `setInScopeFromF` floats1
; (_, se', arg') <- simplLazyArg env' dup hole_ty Nothing se arg
- ; (let_floats2, arg'') <- makeTrivial env NotTopLevel dmd (fsLit "karg") arg'
+
+ -- Make the argument duplicable. Danger: if arg is small and we let-bind
+ -- it, then postInlineUnconditionally will just inline it again, perhaps
+ -- taking an extra Simplifier iteration (e.g. in test T21839c). So make
+ -- a `let` only if `couldBeSmallEnoughToInline` says that it is big enough
+ ; let uf_opts = seUnfoldingOpts env
+ ; (let_floats2, arg'')
+ <- if couldBeSmallEnoughToInline uf_opts (unfoldingUseThreshold uf_opts) arg'
+ then return (emptyLetFloats, arg')
+ else makeTrivial env NotTopLevel dmd (fsLit "karg") arg'
+
; let all_floats = floats1 `addLetFloats` let_floats2
; return ( all_floats
, ApplyToVal { sc_arg = arg''
@@ -4592,7 +4614,8 @@ mkLetUnfolding :: SimplEnv -> TopLevelFlag -> UnfoldingSource
-> InId -> Bool -- True <=> this is a join point
-> OutExpr -> SimplM Unfolding
mkLetUnfolding env top_lvl src id is_join new_rhs
- = return (mkUnfolding uf_opts src is_top_lvl is_bottoming is_join new_rhs Nothing)
+ = -- Monadic to force those where-bindings
+ return (mkUnfolding uf_opts src is_top_lvl is_bottoming is_join new_rhs Nothing)
-- We make an unfolding *even for loop-breakers*.
-- Reason: (a) It might be useful to know that they are WHNF
-- (b) In GHC.Iface.Tidy we currently assume that, if we want to
=====================================
compiler/GHC/Core/Opt/Simplify/Utils.hs
=====================================
@@ -216,8 +216,6 @@ data SimplCont
CoreTickish -- Tick tickish <hole>
SimplCont
-type StaticEnv = SimplEnv -- Just the static part is relevant
-
data FromWhat = FromLet | FromBeta Levity
-- See Note [DupFlag invariants]
@@ -723,7 +721,6 @@ which it is on the LHS of a rule (see updModeForRules), then don't
make use of the strictness info for the function.
-}
-
{-
************************************************************************
* *
@@ -1423,8 +1420,12 @@ preInlineUnconditionally for
Note [Top-level bottoming Ids]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Don't inline top-level Ids that are bottoming, even if they are used just
-once, because FloatOut has gone to some trouble to extract them out.
-Inlining them won't make the program run faster!
+once, because FloatOut has gone to some trouble to extract them out. e.g.
+ report x y = error (..lots of stuff...)
+ f x y z = if z then report x y else ...blah...
+Here `f` might be small enough to inline; but if we put all the `report`
+stuff inside it, it'll look to big. In general we don't want to duplicate
+all the error-reporting goop.
Note [Do not inline CoVars unconditionally]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -1460,51 +1461,25 @@ preInlineUnconditionally env top_lvl bndr rhs rhs_env
extend_subst_with inl_rhs = extendIdSubst env bndr $! (mkContEx rhs_env inl_rhs)
one_occ IAmDead = True -- Happens in ((\x.1) v)
- one_occ OneOcc{ occ_n_br = 1
- , occ_in_lam = NotInsideLam } = isNotTopLevel top_lvl || early_phase
+ one_occ OneOcc{ occ_n_br = 1
+ , occ_in_lam = NotInsideLam
+ , occ_int_cxt = int_cxt }
+ = isNotTopLevel top_lvl -- Get rid of allocation
+ || (int_cxt==IsInteresting) -- Function is applied
+ -- || (early_phase && not (isConLikeUnfolding unf)) -- See early_phase
one_occ OneOcc{ occ_n_br = 1
, occ_in_lam = IsInsideLam
- , occ_int_cxt = IsInteresting } = canInlineInLam rhs
- one_occ _ = False
+ , occ_int_cxt = IsInteresting }
+ = canInlineInLam rhs
+ one_occ _
+ = False
pre_inline_unconditionally = sePreInline env
active = isActive (sePhase env) (inlinePragmaActivation inline_prag)
-- See Note [pre/postInlineUnconditionally in gentle mode]
inline_prag = idInlinePragma bndr
--- Be very careful before inlining inside a lambda, because (a) we must not
--- invalidate occurrence information, and (b) we want to avoid pushing a
--- single allocation (here) into multiple allocations (inside lambda).
--- Inlining a *function* with a single *saturated* call would be ok, mind you.
--- || (if is_cheap && not (canInlineInLam rhs) then pprTrace "preinline" (ppr bndr <+> ppr rhs) ok else ok)
--- where
--- is_cheap = exprIsCheap rhs
--- ok = is_cheap && int_cxt
-
- -- int_cxt The context isn't totally boring
- -- E.g. let f = \ab.BIG in \y. map f xs
- -- Don't want to substitute for f, because then we allocate
- -- its closure every time the \y is called
- -- But: let f = \ab.BIG in \y. map (f y) xs
- -- Now we do want to substitute for f, even though it's not
- -- saturated, because we're going to allocate a closure for
- -- (f y) every time round the loop anyhow.
-
- -- canInlineInLam => free vars of rhs are (Once in_lam) or Many,
- -- so substituting rhs inside a lambda doesn't change the occ info.
- -- Sadly, not quite the same as exprIsHNF.
- canInlineInLam (Lit _) = True
- canInlineInLam (Lam b e) = isRuntimeVar b || canInlineInLam e
- canInlineInLam (Tick t e) = not (tickishIsCode t) && canInlineInLam e
- canInlineInLam (Var v) = case idOccInfo v of
- OneOcc { occ_in_lam = IsInsideLam } -> True
- ManyOccs {} -> True
- _ -> False
- canInlineInLam _ = False
- -- not ticks. Counting ticks cannot be duplicated, and non-counting
- -- ticks around a Lam will disappear anyway.
-
- early_phase = sePhase env /= FinalPhase
+-- early_phase = sePhase env /= FinalPhase
-- If we don't have this early_phase test, consider
-- x = length [1,2,3]
-- The full laziness pass carefully floats all the cons cells to
@@ -1532,6 +1507,52 @@ preInlineUnconditionally env top_lvl bndr rhs rhs_env
-- (Nor can we check for `exprIsExpandable rhs`, because that needs to look
-- at the non-existent unfolding for the `I# 2#` which is also floated out.)
+
+-- Be very careful before inlining inside a lambda, because (a) we must not
+-- invalidate occurrence information, and (b) we want to avoid pushing a
+-- single allocation (here) into multiple allocations (inside lambda).
+-- Inlining a *function* with a single *saturated* call would be ok, mind you.
+-- || (if is_cheap && not (canInlineInLam rhs) then pprTrace "preinline" (ppr bndr <+> ppr rhs) ok else ok)
+-- where
+-- is_cheap = exprIsCheap rhs
+-- ok = is_cheap && int_cxt
+
+ -- int_cxt The context isn't totally boring
+ -- E.g. let f = \ab.BIG in \y. map f xs
+ -- Don't want to substitute for f, because then we allocate
+ -- its closure every time the \y is called
+ -- But: let f = \ab.BIG in \y. map (f y) xs
+ -- Now we do want to substitute for f, even though it's not
+ -- saturated, because we're going to allocate a closure for
+ -- (f y) every time round the loop anyhow.
+
+ -- canInlineInLam => free vars of rhs are (Once in_lam) or Many,
+ -- so substituting rhs inside a lambda doesn't change the occ info.
+ -- Sadly, not quite the same as exprIsHNF.
+canInlineInLam ::CoreExpr -> Bool
+canInlineInLam e
+ = go e
+ where
+ go (Lit _) = True
+ go (Lam b e) = isRuntimeVar b || go e
+ go (Cast e _) = go e
+ go (Tick t e) = not (tickishIsCode t) && go e
+ -- This matters only for:
+ -- x = y -- or y|>co
+ -- f = \p. ..x.. -- One occurrence of x
+ -- ..y.. -- Multiple other occurrences of y
+ -- Then it is safe to inline x unconditionally
+ -- For postInlineUncondionally we have already tested exprIsTrivial
+ -- so this Var case never arises
+ go (Var v) = case idOccInfo v of
+ OneOcc { occ_in_lam = IsInsideLam } -> True
+ ManyOccs {} -> True
+ _ -> False
+ go _ = False
+ -- not ticks. Counting ticks cannot be duplicated, and non-counting
+ -- ticks around a Lam will disappear anyway.
+
+
{-
************************************************************************
* *
@@ -1582,71 +1603,77 @@ postInlineUnconditionally
-- Reason: we don't want to inline single uses, or discard dead bindings,
-- for unlifted, side-effect-ful bindings
postInlineUnconditionally env bind_cxt old_bndr bndr rhs
- | not active = False
- | isWeakLoopBreaker occ_info = False -- If it's a loop-breaker of any kind, don't inline
- -- because it might be referred to "earlier"
- | isStableUnfolding unfolding = False -- Note [Stable unfoldings and postInlineUnconditionally]
- | isTopLevel (bindContextLevel bind_cxt)
- = False -- Note [Top level and postInlineUnconditionally]
- | exprIsTrivial rhs = True
- | BC_Join {} <- bind_cxt = False -- See point (1) of Note [Duplicating join points]
+ | not active = False
+ | isWeakLoopBreaker occ_info = False -- If it's a loop-breaker of any kind, don't inline
+ -- because it might be referred to "earlier"
+ | isStableUnfolding unfolding = False -- Note [Stable unfoldings and postInlineUnconditionally]
+ | BC_Join {} <- bind_cxt = exprIsTrivial rhs
+ -- See point (DJ1) of Note [Duplicating join points]
-- in GHC.Core.Opt.Simplify.Iteration
+ | is_top_lvl, isDeadEndId bndr = False -- Note [Top-level bottoming Ids]
| otherwise
= case occ_info of
- OneOcc { occ_in_lam = in_lam, occ_int_cxt = int_cxt, occ_n_br = n_br }
- -- See Note [Inline small things to avoid creating a thunk]
+ IAmALoopBreaker {} -> False
+ ManyOccs {} | is_top_lvl -> False -- Note [Top level and postInlineUnconditionally]
+ | otherwise -> exprIsTrivial rhs
- | n_br >= 100 -> False -- See #23627
+ OneOcc { occ_in_lam = in_lam, occ_int_cxt = int_cxt, occ_n_br = n_br }
+ | exprIsTrivial rhs -> True
+ | otherwise -> check_one_occ in_lam int_cxt n_br
- | n_br == 1, NotInsideLam <- in_lam -- One syntactic occurrence
- -> True -- See Note [Post-inline for single-use things]
+ IAmDead -> True -- This happens; for example, the case_bndr during case of
+ -- known constructor: case (a,b) of x { (p,q) -> ... }
+ -- Here x isn't mentioned in the RHS, so we don't want to
+ -- create the (dead) let-binding let x = (a,b) in ...
+ where
+ is_top_lvl = isTopLevel (bindContextLevel bind_cxt)
+ is_demanded = isStrUsedDmd (idDemandInfo bndr)
+ occ_info = idOccInfo old_bndr
+ unfolding = idUnfolding bndr
+ arity = idArity bndr
+-- is_cheap = isCheapUnfolding unfolding
+ uf_opts = seUnfoldingOpts env
+ phase = sePhase env
+ active = isActive phase (idInlineActivation bndr)
+ -- See Note [pre/postInlineUnconditionally in gentle mode]
+ -- Check for code-size blow-up from inlining in multiple places
+ code_dup_ok n_br
+ | n_br == 1 = True -- No duplication
+ | n_br >= 100 = False -- See #23627
+ | is_demanded = False -- Demanded => no allocation (it'll be a case expression
+ -- in the end) so inlining duplicates code but nothing more
+ | otherwise = smallEnoughToInline uf_opts unfolding
+
+ -- See Note [Post-inline for single-use things]
+ check_one_occ NotInsideLam NotInteresting n_br = not is_top_lvl && code_dup_ok n_br
+ check_one_occ NotInsideLam IsInteresting n_br = code_dup_ok n_br
+ check_one_occ IsInsideLam NotInteresting _ = False
+ check_one_occ IsInsideLam IsInteresting n_br = arity > 0 && code_dup_ok n_br
+ -- IsInteresting: inlining inside a lambda only with good reason
+ -- See the notes on int_cxt in preInlineUnconditionally
+ -- arity>0: do not inline data strutures under lambdas, only functions
+
+---------------
+-- A wrong bit of code, left here in case you are tempted to do this
-- | is_unlifted -- Unlifted binding, hence ok-for-spec
-- -> True -- hence cheap to inline probably just a primop
--- -- Not a big deal either way
-- No, this is wrong. {v = p +# q; x = K v}.
-- Don't inline v; it'll just get floated out again. Stupid.
+---------------
- | is_demanded
- -> False -- No allocation (it'll be a case expression in the end)
- -- so inlining duplicates code but nothing more
- | otherwise
- -> work_ok in_lam int_cxt && smallEnoughToInline uf_opts unfolding
- -- Multiple syntactic occurences; but lazy, and small enough to dup
- -- ToDo: consider discount on smallEnoughToInline if int_cxt is true
-
- IAmDead -> True -- This happens; for example, the case_bndr during case of
- -- known constructor: case (a,b) of x { (p,q) -> ... }
- -- Here x isn't mentioned in the RHS, so we don't want to
- -- create the (dead) let-binding let x = (a,b) in ...
-
- _ -> False
-
- where
- work_ok NotInsideLam _ = True
- work_ok IsInsideLam IsInteresting = isCheapUnfolding unfolding
- work_ok IsInsideLam NotInteresting = False
- -- NotInsideLam: outside a lambda, we want to be reasonably aggressive
- -- about inlining into multiple branches of case
+ -- NotInsideLam: outside a lambda, when not at top-level we want to be
+ -- reasonably aggressive about inlining into multiple branches of case
-- e.g. let x = <non-value>
-- in case y of { C1 -> ..x..; C2 -> ..x..; C3 -> ... }
-- Inlining can be a big win if C3 is the hot-spot, even if
-- the uses in C1, C2 are not 'interesting'
-- An example that gets worse if you add int_cxt here is 'clausify'
- -- InsideLam: check for acceptable work duplication, using isCheapUnfoldign
- -- int_cxt to prevent us inlining inside a lambda without some
- -- good reason. See the notes on int_cxt in preInlineUnconditionally
+ -- InsideLam:
-- is_unlifted = isUnliftedType (idType bndr)
- is_demanded = isStrUsedDmd (idDemandInfo bndr)
- occ_info = idOccInfo old_bndr
- unfolding = idUnfolding bndr
- uf_opts = seUnfoldingOpts env
- phase = sePhase env
- active = isActive phase (idInlineActivation bndr)
- -- See Note [pre/postInlineUnconditionally in gentle mode]
{- Note [Inline small things to avoid creating a thunk]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -1669,23 +1696,24 @@ where GHC.Driver.CmdLine.$wprocessArgs allocated hugely more.
Note [Post-inline for single-use things]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
If we have
-
let x = rhs in ...x...
-
and `x` is used exactly once, and not inside a lambda, then we will usually
preInlineUnconditinally. But we can still get this situation in
postInlineUnconditionally:
-
case K rhs of K x -> ...x....
-
Here we'll use `simplAuxBind` to bind `x` to (the already-simplified) `rhs`;
and `x` is used exactly once. It's beneficial to inline right away; otherwise
we risk creating
-
let x = rhs in ...x...
+which will take another iteration of the Simplifier to eliminate.
-which will take another iteration of the Simplifier to eliminate. We do this in
-two places
+A similar, but less frequent, case is
+ let f = \x.blah in ...(\y. ...(f e)...) ...
+Again `preInlineUnconditionally will usually inline `f`, but it can arise
+via `simplAuxBind` if we have something like
+ (\f \y. ...(f e)..) (\x.blah)
+
+We do unconditional post-inlining in two places:
1. In the full `postInlineUnconditionally` look for the special case
of "one occurrence, not under a lambda", and inline unconditionally then.
@@ -1714,24 +1742,20 @@ Alas!
Note [Top level and postInlineUnconditionally]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-We don't do postInlineUnconditionally for top-level things (even for
-ones that are trivial):
+We must take care when considering postInlineUnconditionally for top-level things
- * Doing so will inline top-level error expressions that have been
- carefully floated out by FloatOut. More generally, it might
- replace static allocation with dynamic.
+ * Don't inline top-level error expressions that have been carefully floated
+ out by FloatOut. See Note [Top-level bottoming Ids].
- * Even for trivial expressions there's a problem. Consider
+ * Even for trivial expressions we need to take care: we must not
+ postInlineUnconditionally a top-level ManyOccs binder, even if its
+ RHS is trivial. Consider
{-# RULE "foo" forall (xs::[T]). reverse xs = ruggle xs #-}
blah xs = reverse xs
ruggle = sort
- In one simplifier pass we might fire the rule, getting
+ We must not postInlineUnconditionally `ruggle`, because in the same
+ simplifier pass we might fire the rule, getting
blah xs = ruggle xs
- but in *that* simplifier pass we must not do postInlineUnconditionally
- on 'ruggle' because then we'll have an unbound occurrence of 'ruggle'
-
- If the rhs is trivial it'll be inlined by callSiteInline, and then
- the binding will be dead and discarded by the next use of OccurAnal
* There is less point, because the main goal is to get rid of local
bindings used in multiple case branches.
=====================================
compiler/GHC/Core/Utils.hs
=====================================
@@ -397,10 +397,12 @@ mkTicks :: [CoreTickish] -> CoreExpr -> CoreExpr
mkTicks ticks expr = foldr mkTick expr ticks
isSaturatedConApp :: CoreExpr -> Bool
+-- Also includes literals
isSaturatedConApp e = go e []
where go (App f a) as = go f (a:as)
go (Var fun) args
= isConLikeId fun && idArity fun == valArgCount args
+ go (Lit {}) _ = True
go (Cast f _) as = go f as
go _ _ = False
=====================================
libraries/ghc-internal/src/GHC/Internal/Base.hs
=====================================
@@ -1809,7 +1809,12 @@ build g = g (:) []
augment :: forall a. (forall b. (a->b->b) -> b -> b) -> [a] -> [a]
{-# INLINE [1] augment #-}
-augment g xs = g (:) xs
+-- Give it one argument so that it inlines with one arg
+-- But (crucially) the body is a lambda so that `g` is visibly applied
+-- to two args, and hence we know that in a call
+-- augment (\c n. blah)
+-- both c and n are OneShot
+augment g = \xs -> g (:) xs
{-# RULES
"fold/build" forall k z (g::forall b. (a->b->b) -> b -> b) .
@@ -1975,7 +1980,7 @@ The rules for map work like this.
"++/literal_utf8" forall x. (++) (unpackCStringUtf8# x) = unpackAppendCStringUtf8# x #-}
{-# RULES
-"++" [~1] forall xs ys. xs ++ ys = augment (\c n -> foldr c n xs) ys
+"++" [~1] forall xs. (++) xs = augment (\c n -> foldr c n xs)
#-}
=====================================
libraries/ghc-internal/src/GHC/Internal/Float.hs
=====================================
@@ -5,6 +5,7 @@
, MagicHash
, UnboxedTuples
, UnliftedFFITypes
+ , TypeApplications
#-}
{-# LANGUAGE CApiFFI #-}
-- We believe we could deorphan this module, by moving lots of things
@@ -1696,6 +1697,16 @@ showSignedFloat showPos p x
= showParen (p > 6) (showChar '-' . showPos (-x))
| otherwise = showPos x
+
+-- Speicialise showSignedFloat for (a) the type and (b) the argument function
+-- The particularly targets are the calls in `instance Show Float` and
+-- `instance Show Double`
+-- Specialising for both (a) and (b) is obviously more efficient; and if you
+-- don't you find that the `x` argument is strict, but boxed, and that can cause
+-- functions calling showSignedFloat to have box their argument.
+{-# SPECIALISE showSignedFloat @Float showFloat #-}
+{-# SPECIALISE showSignedFloat @Double showFloat #-}
+
{-
We need to prevent over/underflow of the exponent in encodeFloat when
called from scaleFloat, hence we clamp the scaling parameter.
=====================================
testsuite/tests/simplCore/should_run/simplrun009.hs
=====================================
@@ -6,7 +6,10 @@
-- It produces a nested unfold that should look something
-- like the code below. Note the 'lvl1_shW'. It is BAD
-- if this is a lambda instead; you get a lot more allocation
--- See Note [Saving allocation] in GHC.Core.Opt.SetLevels
+--
+-- LATER (2025): But in the end it seems better NOT to float lambdas,
+-- unless they go to top level.
+-- See (SW2) in Note [Saving work] in GHC.Core.Opt.SetLevels
{-
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/536aa79dddeb1627340a50809381b5…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/536aa79dddeb1627340a50809381b5…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T23109a] 86 commits: Driver: make MonadComprehensions imply ParallelListComp
by Simon Peyton Jones (@simonpj) 29 Apr '25
by Simon Peyton Jones (@simonpj) 29 Apr '25
29 Apr '25
Simon Peyton Jones pushed to branch wip/T23109a at Glasgow Haskell Compiler / GHC
Commits:
34a9b55d by lazyLambda at 2025-04-04T06:22:26-04:00
Driver: make MonadComprehensions imply ParallelListComp
This commit changes GHC.Driver.Flags.impliedXFlags to make the
MonadComprehensions extension enable the ParallelListComp extension.
Fixes #25645
- - - - -
d99eb7cd by sheaf at 2025-04-04T06:23:28-04:00
NamedDefaults: handle poly-kinded unary classes
With this commit, we accept named default declarations for poly-kinded
classes such as Typeable, e.g.
default Typeable (Char)
This used to fail because we assumed the kind of the class was monomorphic,
e.g.
Type -> Constraint
(Type -> Type) -> Constraint
Nat -> Constraint
Now, we can handle a simple polymorphic class such as
Typeable :: forall k. k -> Constraint
Note that we keep the restriction that the class must only have
one visible argument.
This is all explained in the new Note [Instance check for default declarations]
in GHC.Tc.Gen.Default.
Fixes #25882
- - - - -
4cbc90de by sheaf at 2025-04-04T11:39:05-04:00
LLVM: add type annotations to AtomicFetch_cmm.cmm
- - - - -
e2237305 by sheaf at 2025-04-04T11:39:05-04:00
Cmm lint: lint argument types of CallishMachOps
This commit adds a new check to Cmm lint to ensure that the argument
types to a CallishMachOp are correct. The lack of this check was
detected in the AtomicFetch test: the literals being passed as the
second arguments to operations such as 'fetch_add', 'fetch_and'... were
of the wrong width, which tripped up the LLVM backend.
- - - - -
9363e547 by Cheng Shao at 2025-04-04T11:39:50-04:00
ci: add ghc-wasm-meta integration testing jobs
This patch adds ghc-wasm-meta integration testing jobs to the CI
pipeline, which are only triggered via the `test-wasm` MR label or
manually when the `wasm` label is set.
These jobs will fetch the wasm bindists and test them against a
variety of downstream projects, similarly to head.hackage jobs for
native bindists, offering a convenient way to catch potential
downstream breakage while refactoring the wasm backend.
- - - - -
27029e60 by Adam Gundry at 2025-04-04T11:40:36-04:00
base: Minor fixes to GHC.Records haddocks
This corrects a stale reference to OverloadedRecordFields (which should
be OverloadedRecordDot), fixes the haddock link syntax and adds an
@since pragma.
- - - - -
f827c4c6 by Rodrigo Mesquita at 2025-04-07T11:22:10-04:00
Parametrize default logger action with Handles
Introduce `defaultLogActionWithHandles` to allow GHC applications to use
GHC's formatting but using custom handles.
`defaultLogAction` is then trivially reimplemented as
```
defaultLogActionWithHandles stdout stderr
```
- - - - -
5dade5fd by sheaf at 2025-04-07T11:23:02-04:00
Finer-grained recompilation checking for exports
This commit refines the recompilation checking logic, to avoid
recompiling modules with an explicit import list when the modules they
import start exporting new items.
More specifically, when:
1. module N imports module M,
2. M is changed, but in a way that:
a. preserves the exports that N imports
b. does not introduce anything that forces recompilation downstream,
such as orphan instances
then we no longer require recompilation of N.
Note that there is more to (2a) as initially meets the eye:
- if N includes a whole module or "import hiding" import of M,
then we require that the export list of M does not change,
- if N only includes explicit imports, we check that the imported
items don't change, e.g.
- if we have @import M(T(K, f), g)@, we must check that N
continues to export all these identifiers, with the same Avail
structure (i.e. we should error if N stops bundling K or f with
T)
- if we have @import M(T(..))@, we must check that the children
of T have not changed
See Note [When to recompile when export lists change?] in GHC.Iface.Recomp.
This is all tested in the new tests RecompExports{1,2,3,4,5}
Fixes #25881
- - - - -
f32d6c2b by Andreas Klebinger at 2025-04-07T22:01:25-04:00
NCG: AArch64 - Add -finter-module-far-jumps.
When enabled the arm backend will assume jumps to targets outside of the
current module are further than 128MB away.
This will allow for code to work if:
* The current module results in less than 128MB of code.
* The whole program is loaded within a 4GB memory region.
We have seen a few reports of broken linkers (#24648) where this flag might allow
a program to compile/run successfully at a very small performance cost.
-------------------------
Metric Increase:
T783
-------------------------
- - - - -
553c280b by Andreas Klebinger at 2025-04-07T22:02:11-04:00
Revert "rts: fix small argument passing on big-endian arch (fix #23387)"
Based on analysis documented in #25791 this doesn't fully fix the big
while introducing new bugs on little endian architectures.
A more complete fix will have to be implemented to fix #23387
This reverts commit 4f02d3c1a7b707e609bb3aea1dc6324fa19a5c39.
- - - - -
b0dc6599 by Andreas Klebinger at 2025-04-07T22:02:11-04:00
Interpreter: Fixes to handling of subword value reads/writes.
Load subword values as full words from the stack truncating/expanding as
neccesary when dealing with subwords. This way byte order is implicitly
correct.
This commit also fixes the order in which we are pushing literals onto
the stack on big endian archs.
Last but not least we enable a test for ghci which actually tests these
subword operations.
- - - - -
ed38c09b by Cheng Shao at 2025-04-07T22:02:53-04:00
testsuite: don't test WasmControlFlow stdout
This patch solves a potential test flakiness in `WasmControlFlow` by
removing `WasmControlFlow.stdout` which is not so portable/stable as
it seems. See added `Note [WasmControlFlow]` for more detailed
explanation.
- - - - -
f807c590 by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00
debugger: Add docs to obtainTermFromId
- - - - -
5dba052d by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00
Move logic to find and set Breakpoint to GHC
Breakpoints are uniquely identified by a module and an index unique
within that module. `ModBreaks` of a Module contains arrays mapping from
this unique breakpoint index to information about each breakpoint. For
instance, `modBreaks_locs` stores the `SrcSpan` for each breakpoint.
To find a breakpoint using the line number you need to go through all
breakpoints in the array for a given module and look at the line and
column stored in the `SrcSpan`s. Similarly for columns and finding
breakpoints by name.
This logic previously lived within the `GHCi` application sources,
however, it is common to any GHC applications wanting to set
breakpoints, like the upcoming `ghc-debugger`.
This commit moves this logic for finding and setting breakpoints to the
GHC library so it can be used by both `ghci` and `ghc-debugger`.
- - - - -
bc0b9f73 by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00
Refactor and move logic for identifier breakpoints
Breakpoints can be set on functions using syntax of the form
`[Module.]function`. The parsing, resolution (e.g. inferring implicit
module), and validation of this syntax for referring to functions was
tightly coupled with its GHCi use.
This commit extracts the general purpose bits of resolving this syntax
into `GHC.Runtime.Debugger.Breakpoints` so it can be further used by
other GHC applications and to improve the code structure of GHCi.
Moreover, a few utilities that do splitting and joining of identifiers
as strings were moved to `GHC.Runtime.Eval.Utils`, which also can be
used in the future to clean up `GHC.Runtime.Eval` a bit.
- - - - -
4f728d21 by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00
debugger: derive Ord for BreakpointIds
- - - - -
5528771c by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00
debugger: Move context utils from GHCi to GHC
Moves `enclosingTickSpan`, `getCurrentBreakSpan`, and
`getCurrentBreakModule`, general utilities on the internal debugger
state, into the GHC library.
- - - - -
4871f543 by sheaf at 2025-04-08T17:42:43-04:00
Implicit quantification in type synonyms: add test
This adds a test for ticket #24090, which involves implicit
quantification in type synonyms.
The underlying issue was fixed in 0d4ee209dfe53e5074d786487f531dabc36d561c.
- - - - -
48917d3c by sheaf at 2025-04-08T17:42:44-04:00
Turn on implicit-rhs-quantification by default
This flag was added to GHC 9.8, and will be removed in a future GHC
release. In preparation, this commit adds it to the default warning
flags.
- - - - -
629be068 by Rodrigo Mesquita at 2025-04-08T17:43:26-04:00
debugger: Add breakpoints to every Stmt
While single-stepping through a Haskell program we stop at every
breakpoint. However, we don't introduce breakpoints at every single
expression (e.g. single variables) because they would be too many and
uninteresting.
That said, in a do-block, it is expected that stepping over would break
at every line, even if it isn't particularly interesting (e.g. a single
arg like getArgs). Moreover, let-statements in do-blocks, despite only
being evaluated once needed, lead to surprising jumps while stepping
through because some have outermost (outside the let) breakpoints
while others don't.
This commit makes every statement in a do-block have a breakpoint.
This leads to predictable stepping through in a do-block.
Duplicate breakpoints in the same location are avoided using the
existing blacklist mechanism, which was missing a check in one relevant place.
Fixes #25932
- - - - -
99a3affd by Matthew Pickering at 2025-04-08T17:44:08-04:00
driver: refactor: Split downsweep and MakeAction into separate modules.
This will facilitate using the downsweep functions in other parts of
the compiler than just --make mode.
Also, the GHC.Driver.Make module was huge. Now it's still huge but
slightly smaller!
- - - - -
ecfec4df by sheaf at 2025-04-09T14:13:12-04:00
Store user-written qualification in the GhcRn AST
This commit ensures we store the original user-written module
qualification in the renamed AST. This allows us to take into account
the user-written qualification in error messages.
Fixes #25877
- - - - -
97c884e2 by sheaf at 2025-04-09T14:13:12-04:00
TcRnIllegalTermLevelUse: simpler error when possible
This commit makes GHC emit a simple error message in the case of an
illegal term-level use of a data constructor: we will try to report an
out-of-scope error instead of a "Illegal term level use" error, as the
latter might be a bit overwhelming for newcomers.
We do this when we have a data constructor import suggestion to provide
to the user. For example:
module M where { data A = A }
module N where
import M(A)
x = Bool
-- Illegal term-level use of Bool
y = A
-- Data constructor not in scope: A.
-- Perhaps add 'A' to the import list of 'M'.
This commit also revamps the "similar names" suggestion mechanism,
and in particular its treatment of name spaces. Now, which name spaces
we suggest is based solely on what we are looking for, and no longer on
the NameSpace of the Name we have. This is because, for illegal term-level
use errors, it doesn't make much sense to change the suggestions based
on the fact that we resolved to e.g. a type constructor/class; what
matters is what we were expecting to see in this position.
See GHC.Rename.Unbound.{suggestionIsRelevant,relevantNameSpace} as well
as the new constructors to GHC.Tc.Errors.Types.WhatLooking.
Fixes #23982
- - - - -
bff645ab by Rodrigo Mesquita at 2025-04-09T14:13:57-04:00
driver: Split Session functions out of Main
This commit moves out functions that help in creating and validating a
GHC multi session from Main into the ghc library where they can be used by
other GHC applications.
Moreover, `Mode` processing and `checkOptions` linting were moved to
separate modules within the ghc-bin executable package.
In particular:
- Move `Mode` types and functions (referring to the mode GHC is running
on) to `ghc-bin:GHC.Driver.Session.Mode`
- Move `checkOptions` and aux functions, which validates GHC DynFlags
based on the mode, to `ghc-bin:GHC.Driver.Session.Lint`
- Moves `initMulti`, `initMake`, and aux functions, which initializes a make/multi-unit
session, into `ghc:GHC.Driver.Session.Units`.
- - - - -
501b015e by Rodrigo Mesquita at 2025-04-09T14:13:57-04:00
docs: Improve haddock of ExecComplete
- - - - -
dea98988 by Andreas Klebinger at 2025-04-09T19:23:57-04:00
Avoid oversaturing constructor workers.
Constructor applications always need to take the exact number of
arguments. If we can't ensure that instead apply the constructor worker
like a regular function.
Fixes #23865
- - - - -
f1acdd2c by sheaf at 2025-04-09T19:25:41-04:00
NamedDefaults: require the class to be standard
We now only default type variables if they only appear in constraints
of the form `C v`, where `C` is either a standard class or a class with
an in-scope default declaration.
This rectifies an oversight in the original implementation of the
NamedDefault extensions that was remarked in #25775; that implementation
allowed type variables to appear in unary constraints which had arbitrary
classes at the head.
See the rewritten Note [How type-class constraints are defaulted] for
details of the implementation.
Fixes #25775
Fixes #25778
- - - - -
5712e0d6 by Vladislav Zavialov at 2025-04-10T05:17:38+00:00
Retry type/class declarations and instances (#12088)
Retry type/class declarations and instances to account for non-lexical
dependencies arising from type/data family instances.
This patch improves the kind checker's ability to use type instances in kind
checking of other declarations in the same module.
* Key change: tcTyAndClassDecls now does multiple passes over the TyClGroups,
as long as it is able to make progress.
See the new Note [Retrying TyClGroups] in GHC.Tc.TyCl
* Supporting change: FVs of a TyClGroup are now recorded in its extension
field, namely XCTyClGroup.
See the new Note [Prepare TyClGroup FVs] in GHC.Rename.Module
* Instances are no longer inserted at the earliest positions where their FVs
are bound. This is a simplification.
See the new Note [Put instances at the end] in GHC.Rename.Module
* Automatic unpacking is now more predictable, but fewer fields get unpacked
by default. Use explicit {-# UNPACK #-} pragmas instead.
See the new Note [Flaky -funbox-strict-fields with type/data families]
For the wide range of newly accepted programs, consult the added test cases.
Fixed tickets:
#12088, #12239, #14668, #15561, #16410, #16448, #16693,
#19611, #20875, #21172, #22257, #25238, #25834
Metric Decrease:
T8095
- - - - -
bc73a78d by sheaf at 2025-04-10T15:07:24-04:00
checkFamApp: don't be so eager to cycle break
As remarked in #25933, a pure refactoring of checkTyEqRhs in
ab77fc8c7adebd610aa0bd99d653f9a6cc78a374 inadvertently changed behaviour,
as it caused GHC to introduce cycle-breaker variables in some
unnecessary circumstances.
This commit refactors 'GHC.Tc.Utils.Unify.checkFamApp' in a way that
should restore the old behaviour, so that, when possible, we first
recur into the arguments and only introduce a cycle breaker if this
recursion fails (e.g. due to an occurs check failure).
Fixes #25933
- - - - -
3acd8182 by Andreas Klebinger at 2025-04-10T22:32:12-04:00
Expand docs for RTS flag `-M`.
The behaviour of how/when exceptions are raised was not really covered
in the docs.
- - - - -
026c1a39 by Adam Sandberg Ericsson at 2025-04-10T22:32:56-04:00
add cases for more SchedulerStatus codes in rts_checkSchedStatus
- - - - -
5977c6a1 by sheaf at 2025-04-10T22:33:46-04:00
Squash warnings in GHC.Runtime.Heap.Inspect
There were incomplete record selector warnings in GHC.Runtime.Heap.Inspect
due to the use of the partial 'dataArgs' record selector. This is fixed
by passing the fields to the 'extractSubTerms' function directly,
rather than passing a value of the parent data type.
- - - - -
6a3e38f5 by Andreas Klebinger at 2025-04-11T15:13:53-04:00
hadrian: Make ghcWithInterpreter the universal source of truth about availability of the interpreter
We were doing some ad-hoc checks in different places in hadrian to
determine whether we supported the interprter or not. Now this check if
confined to one function, `ghcWithInterpreter`, and all the places which
use this information consult `ghcWithInterpreter` to determine what to
do.
Fixes #25533.
- - - - -
207de6f1 by Matthew Pickering at 2025-04-11T15:14:37-04:00
testsuite: Fix running TH tests with profiled dynamic compiler
Previously, I had failed to update the ghc_th_way_flags logic for the
profiled dynamic compiler.
In addition to this `ghc_dynamic` was incorrectly set for profiled
dynamic compiler.
I also updated MultiLayerModulesTH_OneShot test to work for any compiler
linkage rather than just dynamic.
Fixes #25947
-------------------------
Metric Decrease:
MultiLayerModulesTH_Make
-------------------------
- - - - -
5455f2b9 by Matthew Pickering at 2025-04-12T08:31:36-04:00
driver: Add support for "Fixed" nodes in the ModuleGraph
A fixed node in the module graph is one which we presume is already
built. It's therefore up to the user to make sure that the interface
file and any relevant artifacts are available for a fixed node.
Fixed/Compile nodes are represented by the ModuleNodeInfo type, which
abstracts the common parts of Fixed/Compile nodes with accessor
functions of type `ModuleNodeInfo -> ...`.
Fixed nodes can only depend on other fixed nodes. This invariant can be
checked by the function `checkModuleGraph` or `mkModuleGraphChecked`.
--make mode is modified to work with fixed mode. In order to "compile" a
fixed node, the artifacts are just loaded into the HomePackageTable.
Currently nothing in the compiler will produce Fixed nodes but this is
tested with the FixedNodes GHC API test.
In subsequent patches we are going to remove the ExternalModuleGraph and
use Fixed nodes for modules in the module graph in oneshot mode.
Fixes #25920
- - - - -
ad64d5c2 by Cheng Shao at 2025-04-12T08:32:19-04:00
ci: remove manual case of ghc-wasm-meta downstream testing jobs
This patch removes the manual case of ghc-wasm-meta downstream testing
jobs; now the only way of including them in the pipeline and running
them is via the test-wasm label.
The reason of the removal is it proves to be problematic for MRs with
only the wasm label; the wasm job would succeed, then the pipeline
status would be waiting for manual action instead of succeeding. There
needs to be separate jobs for the label-triggered and manual-triggered
cases, but I don't think it's worth that extra complexity, the
label-triggered case is already sufficient.
- - - - -
b34890c7 by Vladislav Zavialov at 2025-04-13T01:08:21+03:00
Fix EmptyCase panic in tcMatches (#25960)
Due to faulty reasoning in Note [Pattern types for EmptyCase],
tcMatches was too keen to panic.
* Old (incorrect) assumption: pat_tys is a singleton list.
This does not hold when \case{} is checked against a function type
preceded by invisible forall. See the new T25960 test case.
* New (hopefully correct) assumption: vis_pat_tys is a singleton list.
This should follow from:
checkArgCounts :: MatchGroup GhcRn ... -> TcM VisArity
checkArgCounts (MG { mg_alts = L _ [] })
= return 1
...
- - - - -
84806ebc by Vladislav Zavialov at 2025-04-13T11:40:08-04:00
Remove unused type: TokenLocation
- - - - -
05eb50df by Vladislav Zavialov at 2025-04-13T19:16:38-04:00
Register EpToken in Parser.PostProcess.Haddock (#22558)
This change allows us to reject more badly placed Haddock comments.
Examples:
module
-- | Bad comment for the module
T17544_kw where
data Foo -- | Bad comment for MkFoo
where MkFoo :: Foo
newtype Bar -- | Bad comment for MkBar
where MkBar :: () -> Bar
class Cls a
-- | Bad comment for clsmethod
where
clsmethod :: a
- - - - -
01944e5e by Vladislav Zavialov at 2025-04-13T19:17:21-04:00
Reject puns in T2T (#24153)
This patch implements pun detection in T2T. Consider:
x = 42
f, g :: forall a -> ...
f (type x) = g x
In accordance with the specification, the `g x` function call is renamed
as a term, so `x` refers to the top-level binding `x = 42`, not to the
type variable binding `type x` as one might expect.
This is somewhat counterintuitive because `g` expects a type argument.
Forbidding puns in T2T allows us to produce a helpful error message:
Test.hs:5:16: error: [GHC-09591]
Illegal punned variable occurrence in a required type argument.
The name ‘x’ could refer to:
‘x’ defined at Test.hs:3:1
‘x’ bound at Test.hs:5:9
This commit is a follow up to 0dfb1fa799af254c8a1e1045fc3996af2d57a613
where checking for puns was left as future work.
- - - - -
cc580552 by Vladislav Zavialov at 2025-04-13T19:18:02-04:00
Additional test cases for #12088, #13790
Extract more test cases from ticket discussions, including multi-module
examples. Follow up to 5712e0d646f611dfbfedfd7ef6dff3a18c016edb
- - - - -
d47bf776 by Matthew Pickering at 2025-04-14T16:44:41+01:00
driver: Use ModuleGraph for oneshot and --make mode
This patch uses the `hsc_mod_graph` field for both oneshot and --make
mode. Therefore, if part of the compiler requires usage of the module
graph, you do so in a uniform way for the two different modes.
The `ModuleGraph` describes the relationship between the modules in the
home package and units in external packages. The `ModuleGraph` can be
queried when information about the transitive closure of a package is
needed. For example, the primary use of the ModuleGraph from within the
compiler is in the loader, which needs to know the transitive closure of
a module so it can load all the relevant objects for evaluation.
In --make mode, downsweep computes the ModuleGraph before any
compilation starts.
In oneshot mode, a thunk is created at the start of compilation, which
when forced will compute the module graph beneath the current module.
The thunk is only forced at the moment when the user uses Template
Haskell.
Finally, there are some situations where we need to discover what
dependencies to load but haven't loaded a module graph at all. In this
case, there is a fallback which computes the transitive closure on the
fly and doesn't cache the result. Presumably if you are going to call
getLinkDeps a lot, you would compute the right ModuleGraph before you
started.
Importantly, this removes the ExternalModuleGraph abstraction. This was quite
awkward to work with since it stored information about the home package
inside the EPS.
This patch will also be very useful when implementing explicit level
imports, which requires more significant use of the module graph in
order to determine which level instances are available at.
Towards #25795
-------------------------
Metric Decrease:
MultiLayerModulesTH_Make
MultiLayerModulesTH_OneShot
-------------------------
- - - - -
395e0ad1 by sheaf at 2025-04-16T12:33:26-04:00
base: remove .Internal modules (e.g. GHC.TypeLits)
This commit removes the following internal modules from base,
as per CLC proposal 217:
- GHC.TypeNats.Internal
- GHC.TypeLits.Internal
- GHC.ExecutionStack.Internal
Fixes #25007
- - - - -
e0f3ff11 by Patrick at 2025-04-17T04:31:12-04:00
Refactor Handling of Multiple Default Declarations
Fixes: #25912, #25914, #25934
Previously, GHC discarded all loaded defaults (tcg_default) when local
defaults were encountered during typechecking. According to the
exportable-named-default proposal (sections 2.4.2 and 2.4.3), local
defaults should be merged into tcg_default, retaining any defaults
already present while overriding where necessary.
Key Changes:
* Introduce DefaultProvenance to track the origin of default declarations
(local, imported, or built-in), replacing the original cd_module
in ClassDefaults with cd_provenance :: DefaultProvenance.
* Rename tcDefaults to tcDefaultDecls, limiting its responsibility to only
converting renamed class defaults into ClassDefaults.
* Add extendDefaultEnvWithLocalDefaults to merge local defaults into the
environment, with proper duplication checks:
- Duplicate local defaults for a class trigger an error.
- Local defaults override imported or built-in defaults.
* Update and add related notes: Note [Builtin class defaults],
Note [DefaultProvenance].
* Add regression tests: T25912, T25914, T25934.
Thanks sam and simon for the help on this patch.
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
- - - - -
386f1854 by Teo Camarasu at 2025-04-17T04:31:55-04:00
template-haskell: Remove `addrToByteArrayName` and `addrToByteArray`
These were part of the implementation of the `Lift ByteArray` instance and were errornously exported because this module lacked an explicit export list. They have no usages on Hackage.
Resolves #24782
- - - - -
b96e2f77 by Sylvain Henry at 2025-04-18T20:46:33-04:00
RTS: remove target info and fix host info (#24058)
The RTS isn't a compiler, hence it doesn't have a target and we remove
the reported target info displayed by "+RTS --info". We also fix the
host info displayed by "+RTS --info": the host of the RTS is the
RTS-building compiler's target, not the compiler's host (wrong when
doing cross-compilation).
- - - - -
6d9965f4 by Sylvain Henry at 2025-04-18T20:46:33-04:00
RTS: remove build info
As per the discussion in !13967, there is no reason to tag the RTS with
information about the build platform.
- - - - -
d52e9b3f by Vladislav Zavialov at 2025-04-18T20:47:15-04:00
Diagnostics: remove the KindMismatch constructor (#25957)
The KindMismatch constructor was only used as an intermediate
representation in pretty-printing.
Its removal addresses a problem detected by the "codes" test case:
[GHC-89223] is untested (constructor = KindMismatch)
In a concious deviation from the usual procedure, the error code
GHC-89223 is removed entirely rather than marked as Outdated.
The reason is that it never was user-facing in the first place.
- - - - -
e2f2f9d0 by Vladislav Zavialov at 2025-04-20T10:53:39-04:00
Add name for -Wunusable-unpack-pragmas
This warning had no name or flag and was triggered unconditionally.
Now it is part of -Wdefault.
In GHC.Tc.TyCl.tcTyClGroupsPass's strict mode, we now have to
force-enable this warning to ensure that detection of flawed groups
continues to work even if the user disables the warning with the
-Wno-unusable-unpack-pragmas option. Test case: T3990c
Also, the misnamed BackpackUnpackAbstractType is now called
UnusableUnpackPragma.
- - - - -
6caa6508 by Adam Gundry at 2025-04-20T10:54:22-04:00
Fix specialisation of incoherent instances (fixes #25883)
GHC normally assumes that class constraints are canonical, meaning that
the specialiser is allowed to replace one dictionary argument with another
provided that they have the same type. The `-fno-specialise-incoherents`
flag alters INCOHERENT instance definitions so that they will prevent
specialisation in some cases, by inserting `nospec`.
This commit fixes a bug in 7124e4ad76d98f1fc246ada4fd7bf64413ff2f2e, which
treated some INCOHERENT instance matches as if `-fno-specialise-incoherents`
was in effect, thereby unnecessarily preventing specialisation. In addition
it updates the relevant `Note [Rules for instance lookup]` and adds a new
`Note [Canonicity for incoherent matches]`.
- - - - -
0426fd6c by Adam Gundry at 2025-04-20T10:54:23-04:00
Add regression test for #23429
- - - - -
eec96527 by Adam Gundry at 2025-04-20T10:54:23-04:00
user's guide: update specification of overlapping/incoherent instances
The description of the instance resolution algorithm in the user's
guide was slightly out of date, because it mentioned in-scope given
constraints only at the end, whereas the implementation checks for
their presence before any of the other steps.
This also adds a warning to the user's guide about the impact of
incoherent instances on specialisation, and more clearly documents
some of the other effects of `-XIncoherentInstances`.
- - - - -
a00eeaec by Matthew Craven at 2025-04-20T10:55:03-04:00
Fix bytecode generation for `tagToEnum# <LITERAL>`
Fixes #25975.
- - - - -
2e204269 by Andreas Klebinger at 2025-04-22T12:20:41+02:00
Simplifier: Constant fold invald tagToEnum# calls to bottom expr.
When applying tagToEnum# to a out-of-range value it's best to simply
constant fold it to a bottom expression. That potentially allows more
dead code elimination and makes debugging easier.
Fixes #25976
- - - - -
7250fc0c by Matthew Pickering at 2025-04-22T16:24:04-04:00
Move -fno-code note into Downsweep module
This note was left behind when all the code which referred to it was
moved into the GHC.Driver.Downsweep module
- - - - -
d2dc89b4 by Matthew Pickering at 2025-04-22T16:24:04-04:00
Apply editing notes to Note [-fno-code mode] suggested by sheaf
These notes were suggested in https://gitlab.haskell.org/ghc/ghc/-/merge_requests/14241
- - - - -
91564daf by Matthew Pickering at 2025-04-24T00:29:02-04:00
ghci: Use loadInterfaceForModule rather than loadSrcInterface in mkTopLevEnv
loadSrcInterface takes a user given `ModuleName` and resolves it to the
module which needs to be loaded (taking into account module
renaming/visibility etc).
loadInterfaceForModule takes a specific module and loads it.
The modules in `ImpDeclSpec` have already been resolved to the actual
module to get the information from during renaming. Therefore we just
need to fetch the precise interface from disk (and not attempt to rename
it again).
Fixes #25951
- - - - -
2e0c07ab by Simon Peyton Jones at 2025-04-24T00:29:43-04:00
Test for #23298
- - - - -
0eef99b0 by Sven Tennie at 2025-04-24T07:34:36-04:00
RV64: Introduce J instruction (non-local jumps) and don't deallocate stack slots for J_TBL (#25738)
J_TBL result in local jumps, there should not deallocate stack slots
(see Note [extra spill slots].)
J is for non-local jumps, these may need to deallocate stack slots.
- - - - -
1bd3d13e by fendor at 2025-04-24T07:35:17-04:00
Add `UnitId` to `EvalBreakpoint`
The `EvalBreakpoint` is used to communicate that a breakpoint was
encountered during code evaluation.
This `EvalBreakpoint` needs to be converted to an `InternalBreakpointId`
which stores a `Module` to uniquely find the correct `Module` in the
Home Package Table.
The `EvalBreakpoint` used to store only a `ModuleName` which is then
converted to a `Module` based on the currently active home unit.
This is incorrect in the face of multiple home units, the break point
could be in an entirely other home unit!
To fix this, we additionally store the `UnitId` of the `Module` in
`EvalBreakpoint` to later reconstruct the correct `Module`
All of the changes are the consequence of extending `EvalBreakpoint`
with the additional `ShortByteString` of the `UnitId`.
For performance reasons, we store the `ShortByteString` backing the
`UnitId` directly, avoiding marshalling overhead.
- - - - -
fe6ed8d9 by Sylvain Henry at 2025-04-24T18:04:12-04:00
Doc: add doc for JS interruptible calling convention (#24444)
- - - - -
6111c5e4 by Ben Gamari at 2025-04-24T18:04:53-04:00
compiler: Ensure that Panic.Plain.assertPanic' provides callstack
In 36cddd2ce1a3bc62ea8a1307d8bc6006d54109cf @alt-romes removed CallStack
output from `GHC.Utils.Panic.Plain.assertPanic'`. While this output is
redundant due to the exception backtrace proposal, we may be
bootstrapping with a compiler which does not yet include this machinery.
Reintroduce the output for now.
Fixes #25898.
- - - - -
217caad1 by Matthew Pickering at 2025-04-25T18:58:42+01:00
Implement Explicit Level Imports for Template Haskell
This commit introduces the `ExplicitLevelImports` and
`ImplicitStagePersistence` language extensions as proposed in GHC
Proposal #682.
Key Features
------------
- `ExplicitLevelImports` adds two new import modifiers - `splice` and
`quote` - allowing precise control over the level at which imported
identifiers are available
- `ImplicitStagePersistence` (enabled by default) preserves existing
path-based cross-stage persistence behavior
- `NoImplicitStagePersistence` disables implicit cross-stage
persistence, requiring explicit level imports
Benefits
--------
- Improved compilation performance by reducing unnecessary code generation
- Enhanced IDE experience with faster feedback in `-fno-code` mode
- Better dependency tracking by distinguishing compile-time and runtime dependencies
- Foundation for future cross-compilation improvements
This implementation enables the separation of modules needed at
compile-time from those needed at runtime, allowing for more efficient
compilation pipelines and clearer code organization in projects using
Template Haskell.
Implementation Notes
--------------------
The level which a name is availble at is stored in the 'GRE', in the normal
GlobalRdrEnv. The function `greLevels` returns the levels which a specific GRE
is imported at. The level information for a 'Name' is computed by `getCurrentAndBindLevel`.
The level validity is checked by `checkCrossLevelLifting`.
Instances are checked by `checkWellLevelledDFun`, which computes the level an
instance by calling `checkWellLevelledInstanceWhat`, which sees what is
available at by looking at the module graph.
Modifications to downsweep
--------------------------
Code generation is now only enabled for modules which are needed at
compile time.
See the Note [-fno-code mode] for more information.
Uniform error messages for level errors
---------------------------------------
All error messages to do with levels are now reported uniformly using
the `TcRnBadlyStaged` constructor.
Error messages are uniformly reported in terms of levels.
0 - top-level
1 - quote level
-1 - splice level
The only level hard-coded into the compiler is the top-level in
GHC.Types.ThLevelIndex.topLevelIndex.
Uniformly refer to levels and stages
------------------------------------
There was much confusion about levels vs stages in the compiler.
A level is a semantic concept, used by the typechecker to ensure a
program can be evaluated in a well-staged manner.
A stage is an operational construct, program evaluation proceeds in
stages.
Deprecate -Wbadly-staged-types
------------------------------
`-Wbadly-staged-types` is deprecated in favour of `-Wbadly-levelled-types`.
Lift derivation changed
-----------------------
Derived lift instances will now not generate code with expression
quotations.
Before:
```
data A = A Int deriving Lift
=>
lift (A x) = [| A $(lift x) |]
```
After:
```
lift (A x) = conE 'A `appE` (lift x)
```
This is because if you attempt to derive `Lift` in a module where
`NoImplicitStagePersistence` is enabled, you would get an infinite loop
where a constructor was attempted to be persisted using the instance you
are currently defining.
GHC API Changes
---------------
The ModuleGraph now contains additional information about the type of
the edges (normal, quote or splice) between modules. This is abstracted
using the `ModuleGraphEdge` data type.
Fixes #25828
-------------------------
Metric Increase:
MultiLayerModulesTH_Make
-------------------------
- - - - -
7641a74a by Simon Peyton Jones at 2025-04-26T22:05:19-04:00
Get a decent MatchContext for pattern synonym bindings
In particular when we have a pattern binding
K p1 .. pn = rhs
where K is a pattern synonym. (It might be nested.)
This small MR fixes #25995. It's a tiny fix, to an error message,
removing an always-dubious `unkSkol`.
The bug report was in the context of horde-ad, a big program,
and I didn't manage to make a small repro case quickly. I decided
not to bother further.
- - - - -
ce616f49 by Simon Peyton Jones at 2025-04-27T21:10:25+01:00
Fix infelicities in the Specialiser
On the way to #23109 (unary classes) I discovered some infelicities
(or maybe tiny bugs, I forget) in the type-class specialiser.
I also tripped over #25965, an outright bug in the rule matcher
Specifically:
* Refactor: I enhanced `wantCallsFor`, whih previously always said
`True`, to discard calls of class-ops, data constructors etc. This is
a bit more efficient; and it means we don't need to worry about
filtering them out later.
* Fix: I tidied up some tricky logic that eliminated redundant
specialisations. It wasn't working correctly. See the expanded
Note [Specialisations already covered], and
(MP3) in Note [Specialising polymorphic dictionaries].
See also the new top-level `alreadyCovered`
function, which now goes via `GHC.Core.Rules.ruleLhsIsMoreSpecific`
I also added a useful Note [The (CI-KEY) invariant]
* Fix #25965: fixed a tricky bug in the `go_fam_fam` in
`GHC.Core.Unify.uVarOrFam`, which allows matching to succeed
without binding all type varibles.
I enhanced Note [Apartness and type families] some more
* #25703. This ticket "just works" with -fpolymorphic-specialisation;
but I was surprised that it worked! In this MR I added documentation
to Note [Interesting dictionary arguments] to explain; and tests to
ensure it stays fixed.
- - - - -
22d11fa8 by Simon Peyton Jones at 2025-04-28T18:05:19-04:00
Track rewriter sets more accurately in constraint solving
The key change, which fixed #25440, is to call `recordRewriter` in
GHC.Tc.Solver.Rewrite.rewrite_exact_fam_app. This missing call meant
that we were secretly rewriting a Wanted with a Wanted, but not really
noticing; and that led to a very bad error message, as you can see
in the ticket.
But of course that led me into rabbit hole of other refactoring around
the RewriteSet code:
* Improve Notes [Wanteds rewrite Wanteds]
* Zonk the RewriterSet in `zonkCtEvidence` rather than only in GHC.Tc.Errors.
This is tidier anyway (e.g. de-clutters debug output), and helps with the
next point.
* In GHC.Tc.Solver.Equality.inertsCanDischarge, don't replace a constraint
with no rewriters with an equal constraint that has many. See
See (CE4) in Note [Combining equalities]
* Move zonkRewriterSet and friends from GHC.Tc.Zonk.Type into
GHC.Tc.Zonk.TcType, where they properly belong.
A handful of tests get better error messages.
For some reason T24984 gets 12% less compiler allocation -- good
Metric Decrease:
T24984
- - - - -
865ba1a8 by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Improve the Simplifier
While working on #23109, I made two improvements to the Simplifier
* I found that the Simplifier was sometimes iterating more than it should.
I fixed this by improving postInlineUnconditionally.
* I refactored tryCastWorkerWrapper. It is now clearer, and does less
repeated work. This allowed me to call it from makeTrivial, which again
does a bit more in one pass, elminating a potential extra Simplifier
iteration
- - - - -
bad1623f by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
More care in postInline
Don't inline data con apps so vigorously
needs more docs
- - - - -
b2cb2e32 by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Wibbles
- - - - -
486e9265 by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Be more careful in mkDupableContWithDmds
to not create a binding that will immediately be inlined
- - - - -
02627f29 by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Do post-inline used-once bindings
This makes cacheprof not regress and seems generally a good plan
- - - - -
07daeae0 by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
More eperiments
* Don't inline toplevel things so much
* Don't float constants so vigorously in the first float-out
- - - - -
783cb70d by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Comments only
- - - - -
9b0f654c by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Refator GHC.Core.Opt.SetLevels.notWorthFloating
I refactored `notWorthFloating` while I was doing something else.
I don't think there's a change in behaviour, but if so it's very much
a corner case.
- - - - -
6b7a63b3 by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Always float bottoming expressions to the top
...regardless of floatConsts
- - - - -
b6c5dc5a by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Comments only
- - - - -
c7564d28 by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Wibble SetLevels
- - - - -
ee8e7442 by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Specialise the (higher order) showSignedFloat
- - - - -
d39ff923 by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Eta reduce augment and its rules
... to match foldr. I found this reduced some simplifer iterations
- - - - -
4245bf67 by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Try getting rid of this early-phase business
- - - - -
b3cb6109 by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Don't float PAPs to top level
...and treat case alternatives as strict contexts
- - - - -
63c39e03 by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Wibble to postInlineUnconditionally
- - - - -
46bca683 by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Small wibbles
Don't make error calls interesting.
Literals say True too isSaturatedConApp
- - - - -
432f7c05 by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Import wibble
- - - - -
d884af50 by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Fix `augment`!
- - - - -
536aa79d by Simon Peyton Jones at 2025-04-29T11:19:58+01:00
Tiny change to saves_alloc
Float lambdas (and PAPs) out of lambdas to top level
This improves spectral/cse
But the old comment was
-- is_con_app: don't float PAPs to the top; they may well end
-- up getting eta-expanded and re-inlined
-- E.g. f = \x -> (++) ys
-- If we float, then eta-expand we get
-- lvl = (++) ys
-- f = \x \zs -> lvl zs
-- and now we'll inline lvl. Silly.
Let's see what CI says
- - - - -
656 changed files:
- .gitlab-ci.yml
- compiler/GHC.hs
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm/Lint.hs
- compiler/GHC/Cmm/MachOp.hs
- compiler/GHC/Cmm/Type.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/Config.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Core/Opt/ConstantFold.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg.hs
- compiler/GHC/Data/Graph/Directed/Reachability.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- + compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Env/Types.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- + compiler/GHC/Driver/MakeAction.hs
- compiler/GHC/Driver/MakeFile.hs
- + compiler/GHC/Driver/Messager.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline.hs-boot
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- + compiler/GHC/Driver/Session/Units.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/HsToCore/Usage.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Rename/Unbound.hs
- compiler/GHC/Rename/Utils.hs
- + compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Eval/Types.hs
- + compiler/GHC/Runtime/Eval/Utils.hs
- compiler/GHC/Runtime/Heap/Inspect.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Loader.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/Tc/Deriv.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Utils.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Default.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Plugin.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/Monad.hs
- compiler/GHC/Tc/Solver/Rewrite.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/ErrCtxt.hs
- compiler/GHC/Tc/Types/LclEnv.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Types/TH.hs
- compiler/GHC/Tc/Utils/Backpack.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/Env.hs
- compiler/GHC/Tc/Utils/Instantiate.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/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Avail.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/Breakpoint.hs
- compiler/GHC/Types/DefaultEnv.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/GREInfo.hs
- compiler/GHC/Types/Name.hs
- compiler/GHC/Types/Name/Occurrence.hs
- compiler/GHC/Types/Name/Ppr.hs
- compiler/GHC/Types/Name/Reader.hs
- + compiler/GHC/Types/ThLevelIndex.hs
- compiler/GHC/Types/TyThing/Ppr.hs
- compiler/GHC/Unit/External.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Home/PackageTable.hs
- compiler/GHC/Unit/Module/Deps.hs
- − compiler/GHC/Unit/Module/External/Graph.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Unit/Module/Imported.hs
- compiler/GHC/Unit/Module/ModIface.hs
- compiler/GHC/Unit/Module/ModNodeKey.hs
- compiler/GHC/Unit/Module/ModSummary.hs
- + compiler/GHC/Unit/Module/Stage.hs
- compiler/GHC/Unit/Types.hs
- compiler/GHC/Utils/Binary.hs
- compiler/GHC/Utils/Logger.hs
- compiler/GHC/Utils/Outputable.hs
- compiler/GHC/Utils/Panic/Plain.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- + compiler/Language/Haskell/Syntax/ImpExp/IsBoot.hs
- compiler/Language/Haskell/Syntax/Type.hs
- compiler/ghc.cabal.in
- configure.ac
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/exts/control.rst
- docs/users_guide/exts/instances.rst
- docs/users_guide/exts/monad_comprehensions.rst
- docs/users_guide/exts/named_defaults.rst
- docs/users_guide/exts/parallel_list_comprehensions.rst
- docs/users_guide/exts/template_haskell.rst
- docs/users_guide/javascript.rst
- docs/users_guide/phases.rst
- docs/users_guide/runtime_control.rst
- docs/users_guide/using-optimisation.rst
- docs/users_guide/using-warnings.rst
- + ghc/GHC/Driver/Session/Lint.hs
- + ghc/GHC/Driver/Session/Mode.hs
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Monad.hs
- ghc/Main.hs
- ghc/ghc-bin.cabal.in
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Settings/Builders/Cabal.hs
- hadrian/src/Settings/Builders/RunTest.hs
- hadrian/src/Settings/Packages.hs
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- − libraries/base/src/GHC/ExecutionStack/Internal.hs
- libraries/base/src/GHC/Records.hs
- − libraries/base/src/GHC/TypeLits/Internal.hs
- − libraries/base/src/GHC/TypeNats/Internal.hs
- libraries/base/tests/IO/Makefile
- libraries/ghc-internal/src/GHC/Internal/Base.hs
- libraries/ghc-internal/src/GHC/Internal/Float.hs
- libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ResolvedBCO.hs
- libraries/ghci/GHCi/Run.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- libraries/template-haskell/changelog.md
- rts/Exception.cmm
- rts/Interpreter.c
- rts/RtsAPI.c
- rts/RtsUtils.c
- rts/include/RtsAPI.h
- testsuite/config/ghc
- testsuite/driver/testlib.py
- testsuite/ghc-config/ghc-config.hs
- testsuite/mk/boilerplate.mk
- testsuite/tests/ado/ado004.stderr
- testsuite/tests/annotations/should_fail/annfail03.stderr
- testsuite/tests/annotations/should_fail/annfail04.stderr
- testsuite/tests/annotations/should_fail/annfail06.stderr
- testsuite/tests/annotations/should_fail/annfail09.stderr
- testsuite/tests/backpack/should_fail/bkpfail51.stderr
- + testsuite/tests/bytecode/T25975.hs
- + testsuite/tests/bytecode/T25975.stdout
- testsuite/tests/bytecode/all.T
- testsuite/tests/cmm/should_run/AtomicFetch_cmm.cmm
- + testsuite/tests/core-to-stg/T23865.hs
- testsuite/tests/core-to-stg/all.T
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- + testsuite/tests/default/T25775.hs
- + testsuite/tests/default/T25775.stderr
- + testsuite/tests/default/T25882.hs
- + testsuite/tests/default/T25912.hs
- + testsuite/tests/default/T25912.stdout
- + testsuite/tests/default/T25912_helper.hs
- + testsuite/tests/default/T25914.hs
- + testsuite/tests/default/T25934.hs
- testsuite/tests/default/all.T
- testsuite/tests/default/default-fail01.stderr
- testsuite/tests/default/default-fail02.stderr
- testsuite/tests/default/default-fail03.stderr
- testsuite/tests/default/default-fail04.stderr
- testsuite/tests/default/default-fail08.stderr
- + testsuite/tests/dependent/should_compile/GADTSingletons.hs
- + testsuite/tests/dependent/should_compile/T12088a.hs
- + testsuite/tests/dependent/should_compile/T12088b.hs
- + testsuite/tests/dependent/should_compile/T12088c.hs
- + testsuite/tests/dependent/should_compile/T12088d.hs
- + testsuite/tests/dependent/should_compile/T12088e.hs
- + testsuite/tests/dependent/should_compile/T12088f.hs
- + testsuite/tests/dependent/should_compile/T12088g.hs
- + testsuite/tests/dependent/should_compile/T12088i.hs
- + testsuite/tests/dependent/should_compile/T12088j.hs
- + testsuite/tests/dependent/should_compile/T12088mm1.hs
- + testsuite/tests/dependent/should_compile/T12088mm1_helper.hs
- + testsuite/tests/dependent/should_compile/T12088mm2.hs
- + testsuite/tests/dependent/should_compile/T12088mm2_helper.hs
- + testsuite/tests/dependent/should_compile/T12088mm3.hs
- + testsuite/tests/dependent/should_compile/T12088mm3_helper.hs
- + testsuite/tests/dependent/should_compile/T12088sg1.hs
- + testsuite/tests/dependent/should_compile/T12088sg2.hs
- + testsuite/tests/dependent/should_compile/T12088sg3.hs
- + testsuite/tests/dependent/should_compile/T12239.hs
- + testsuite/tests/dependent/should_compile/T13790.hs
- + testsuite/tests/dependent/should_compile/T14668a.hs
- + testsuite/tests/dependent/should_compile/T14668b.hs
- testsuite/tests/dependent/should_compile/T14729.stderr
- + testsuite/tests/dependent/should_compile/T15561.hs
- testsuite/tests/dependent/should_compile/T15743.stderr
- testsuite/tests/dependent/should_compile/T15743e.stderr
- + testsuite/tests/dependent/should_compile/T16410.hs
- + testsuite/tests/dependent/should_compile/T16448.hs
- + testsuite/tests/dependent/should_compile/T16693.hs
- + testsuite/tests/dependent/should_compile/T19611.hs
- + testsuite/tests/dependent/should_compile/T20875.hs
- + testsuite/tests/dependent/should_compile/T21172.hs
- + testsuite/tests/dependent/should_compile/T22257a.hs
- + testsuite/tests/dependent/should_compile/T22257b.hs
- + testsuite/tests/dependent/should_compile/T25238.hs
- + testsuite/tests/dependent/should_compile/T25834.hs
- testsuite/tests/dependent/should_compile/all.T
- testsuite/tests/deriving/should_compile/T14682.stderr
- testsuite/tests/deriving/should_compile/T17339.stderr
- testsuite/tests/determinism/determ021/determ021.stdout
- testsuite/tests/diagnostic-codes/codes.stdout
- testsuite/tests/driver/RecompCompletePragma/Makefile
- + testsuite/tests/driver/RecompCompletePragma/RecompCompletePragma2.stdout
- + testsuite/tests/driver/RecompExports/Makefile
- + testsuite/tests/driver/RecompExports/RecompExports1.stderr
- + testsuite/tests/driver/RecompExports/RecompExports1.stdout
- + testsuite/tests/driver/RecompExports/RecompExports1_M.hs_1
- + testsuite/tests/driver/RecompExports/RecompExports1_M.hs_2
- + testsuite/tests/driver/RecompExports/RecompExports1_M.hs_3
- + testsuite/tests/driver/RecompExports/RecompExports1_N.hs
- + testsuite/tests/driver/RecompExports/RecompExports2.stderr
- + testsuite/tests/driver/RecompExports/RecompExports2.stdout
- + testsuite/tests/driver/RecompExports/RecompExports2_M.hs_1
- + testsuite/tests/driver/RecompExports/RecompExports2_M.hs_2
- + testsuite/tests/driver/RecompExports/RecompExports2_M.hs_3
- + testsuite/tests/driver/RecompExports/RecompExports2_N.hs
- + testsuite/tests/driver/RecompExports/RecompExports3.stderr
- + testsuite/tests/driver/RecompExports/RecompExports3.stdout
- + testsuite/tests/driver/RecompExports/RecompExports3_M.hs_1
- + testsuite/tests/driver/RecompExports/RecompExports3_M.hs_2
- + testsuite/tests/driver/RecompExports/RecompExports3_M.hs_3
- + testsuite/tests/driver/RecompExports/RecompExports3_N.hs
- + testsuite/tests/driver/RecompExports/RecompExports4.stderr
- + testsuite/tests/driver/RecompExports/RecompExports4.stdout
- + testsuite/tests/driver/RecompExports/RecompExports4_M.hs_1
- + testsuite/tests/driver/RecompExports/RecompExports4_M.hs_2
- + testsuite/tests/driver/RecompExports/RecompExports4_N.hs
- + testsuite/tests/driver/RecompExports/RecompExports5.stdout
- + testsuite/tests/driver/RecompExports/RecompExports5_M.hs_1
- + testsuite/tests/driver/RecompExports/RecompExports5_M.hs_2
- + testsuite/tests/driver/RecompExports/RecompExports5_N.hs
- + testsuite/tests/driver/RecompExports/all.T
- testsuite/tests/driver/T20459.stderr
- testsuite/tests/driver/T24196/T24196.stderr
- testsuite/tests/driver/T24275/T24275.stderr
- + testsuite/tests/driver/T4437.stdout
- testsuite/tests/driver/json2.stderr
- testsuite/tests/gadt/T19847a.stderr
- + testsuite/tests/gadt/T23298.hs
- + testsuite/tests/gadt/T23298.stderr
- testsuite/tests/gadt/all.T
- + testsuite/tests/ghc-api/fixed-nodes/FixedNodes.hs
- + testsuite/tests/ghc-api/fixed-nodes/FixedNodes.stdout
- + testsuite/tests/ghc-api/fixed-nodes/InterfaceModuleGraph.hs
- + testsuite/tests/ghc-api/fixed-nodes/InterfaceModuleGraph.stdout
- + testsuite/tests/ghc-api/fixed-nodes/Makefile
- + testsuite/tests/ghc-api/fixed-nodes/ModuleGraphInvariants.hs
- + testsuite/tests/ghc-api/fixed-nodes/ModuleGraphInvariants.stdout
- + testsuite/tests/ghc-api/fixed-nodes/T1.hs
- + testsuite/tests/ghc-api/fixed-nodes/T1A.hs
- + testsuite/tests/ghc-api/fixed-nodes/T1B.hs
- + testsuite/tests/ghc-api/fixed-nodes/T1C.hs
- + testsuite/tests/ghc-api/fixed-nodes/all.T
- testsuite/tests/ghc-e/should_fail/T9930fail.stderr
- + testsuite/tests/ghci.debugger/scripts/T25932.hs
- + testsuite/tests/ghci.debugger/scripts/T25932.script
- + testsuite/tests/ghci.debugger/scripts/T25932.stdout
- testsuite/tests/ghci.debugger/scripts/T8487.script
- testsuite/tests/ghci.debugger/scripts/all.T
- testsuite/tests/ghci.debugger/scripts/break018.script
- testsuite/tests/ghci.debugger/scripts/break018.stdout
- testsuite/tests/ghci.debugger/scripts/dynbrk004.stdout
- testsuite/tests/ghci.debugger/scripts/dynbrk007.script
- testsuite/tests/ghci.debugger/scripts/dynbrk007.stdout
- + testsuite/tests/ghci/scripts/GhciPackageRename.hs
- + testsuite/tests/ghci/scripts/GhciPackageRename.script
- + testsuite/tests/ghci/scripts/GhciPackageRename.stdout
- testsuite/tests/ghci/scripts/T12550.stdout
- testsuite/tests/ghci/scripts/T4175.stdout
- testsuite/tests/ghci/scripts/all.T
- testsuite/tests/ghci/scripts/ghci024.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
- testsuite/tests/ghci/scripts/ghci064.stdout
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.hs
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/hpc/fork/hpc_fork.stdout
- testsuite/tests/hpc/function/tough.stdout
- testsuite/tests/hpc/function2/tough2.stdout
- testsuite/tests/indexed-types/should_compile/T15711.stderr
- testsuite/tests/indexed-types/should_compile/T15852.stderr
- testsuite/tests/indexed-types/should_compile/T3017.stderr
- testsuite/tests/indexed-types/should_fail/T3330c.stderr
- testsuite/tests/indexed-types/should_fail/T4174.stderr
- testsuite/tests/indexed-types/should_fail/T8227.stderr
- testsuite/tests/indexed-types/should_fail/T8550.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/template-haskell-exports.stdout
- testsuite/tests/linters/notes.stdout
- testsuite/tests/module/all.T
- testsuite/tests/module/mod132.stderr
- testsuite/tests/module/mod147.stderr
- testsuite/tests/module/mod185.stderr
- testsuite/tests/module/mod58.stderr
- testsuite/tests/module/mod73.hs
- testsuite/tests/module/mod73.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_fail/readFail038.stderr
- testsuite/tests/partial-sigs/should_compile/ADT.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr1.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr2.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr3.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr4.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr5.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr6.stderr
- testsuite/tests/partial-sigs/should_compile/BoolToBool.stderr
- testsuite/tests/partial-sigs/should_compile/DataFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting1MROn.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting2MROff.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting2MROn.stderr
- testsuite/tests/partial-sigs/should_compile/Either.stderr
- testsuite/tests/partial-sigs/should_compile/EqualityConstraint.stderr
- testsuite/tests/partial-sigs/should_compile/Every.stderr
- testsuite/tests/partial-sigs/should_compile/EveryNamed.stderr
- testsuite/tests/partial-sigs/should_compile/ExpressionSig.stderr
- testsuite/tests/partial-sigs/should_compile/ExpressionSigNamed.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints1.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints2.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints3.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROff.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROn.stderr
- testsuite/tests/partial-sigs/should_compile/Forall1.stderr
- testsuite/tests/partial-sigs/should_compile/GenNamed.stderr
- testsuite/tests/partial-sigs/should_compile/HigherRank1.stderr
- testsuite/tests/partial-sigs/should_compile/HigherRank2.stderr
- testsuite/tests/partial-sigs/should_compile/LocalDefinitionBug.stderr
- testsuite/tests/partial-sigs/should_compile/Meltdown.stderr
- testsuite/tests/partial-sigs/should_compile/MonoLocalBinds.stderr
- testsuite/tests/partial-sigs/should_compile/NamedTyVar.stderr
- testsuite/tests/partial-sigs/should_compile/NamedWildcardInDataFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/NamedWildcardInTypeFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/ParensAroundContext.stderr
- testsuite/tests/partial-sigs/should_compile/PatBind.stderr
- testsuite/tests/partial-sigs/should_compile/PatBind2.stderr
- testsuite/tests/partial-sigs/should_compile/PatternSig.stderr
- testsuite/tests/partial-sigs/should_compile/Recursive.stderr
- testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcards.stderr
- testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcardsGood.stderr
- testsuite/tests/partial-sigs/should_compile/ShowNamed.stderr
- testsuite/tests/partial-sigs/should_compile/SimpleGen.stderr
- testsuite/tests/partial-sigs/should_compile/SkipMany.stderr
- testsuite/tests/partial-sigs/should_compile/SomethingShowable.stderr
- testsuite/tests/partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/Uncurry.stderr
- testsuite/tests/partial-sigs/should_compile/UncurryNamed.stderr
- testsuite/tests/partial-sigs/should_compile/WarningWildcardInstantiations.stderr
- testsuite/tests/perf/compiler/Makefile
- testsuite/tests/perf/compiler/WWRec.hs
- testsuite/tests/perf/compiler/all.T
- testsuite/tests/perf/compiler/hard_hole_fits.stderr
- testsuite/tests/plugins/defaulting-plugin/DefaultLifted.hs
- testsuite/tests/polykinds/T15592.stderr
- testsuite/tests/polykinds/T15592b.stderr
- testsuite/tests/polykinds/T18300.hs
- testsuite/tests/polykinds/T18300.stderr
- testsuite/tests/primops/should_run/all.T
- testsuite/tests/printer/T18052a.stderr
- testsuite/tests/quasiquotation/T7918.hs
- testsuite/tests/quasiquotation/qq001/qq001.stderr
- testsuite/tests/quasiquotation/qq002/qq002.stderr
- testsuite/tests/quasiquotation/qq003/qq003.stderr
- testsuite/tests/quasiquotation/qq004/qq004.stderr
- + testsuite/tests/quotes/T5721.stderr
- testsuite/tests/rename/should_fail/SimilarNamesImport.stderr
- testsuite/tests/rename/should_fail/T19843c.stderr
- testsuite/tests/rename/should_fail/T23510a.hs
- testsuite/tests/rename/should_fail/T23510a.stderr
- + testsuite/tests/rename/should_fail/T23982.hs
- + testsuite/tests/rename/should_fail/T23982.stderr
- + testsuite/tests/rename/should_fail/T23982_aux.hs
- + testsuite/tests/rename/should_fail/T23982b.hs
- + testsuite/tests/rename/should_fail/T23982b.stderr
- + testsuite/tests/rename/should_fail/T23982b_aux.hs
- + testsuite/tests/rename/should_fail/T25877.hs
- + testsuite/tests/rename/should_fail/T25877.stderr
- + testsuite/tests/rename/should_fail/T25877_aux.hs
- testsuite/tests/rename/should_fail/all.T
- testsuite/tests/roles/should_compile/Roles1.stderr
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles2.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/roles/should_compile/T8958.stderr
- testsuite/tests/showIface/DocsInHiFile1.stdout
- testsuite/tests/showIface/DocsInHiFileTH.stdout
- testsuite/tests/showIface/HaddockIssue849.stdout
- testsuite/tests/showIface/HaddockOpts.stdout
- testsuite/tests/showIface/HaddockSpanIssueT24378.stdout
- testsuite/tests/showIface/LanguageExts.stdout
- testsuite/tests/showIface/MagicHashInHaddocks.stdout
- testsuite/tests/showIface/NoExportList.stdout
- testsuite/tests/showIface/Orphans.stdout
- testsuite/tests/showIface/PragmaDocs.stdout
- testsuite/tests/showIface/ReExports.stdout
- testsuite/tests/simplCore/should_compile/Makefile
- testsuite/tests/simplCore/should_compile/T23307c.stderr
- + testsuite/tests/simplCore/should_compile/T25703.hs
- + testsuite/tests/simplCore/should_compile/T25703.stderr
- + testsuite/tests/simplCore/should_compile/T25703a.hs
- + testsuite/tests/simplCore/should_compile/T25703a.stderr
- + testsuite/tests/simplCore/should_compile/T25883.hs
- + testsuite/tests/simplCore/should_compile/T25883.substr-simpl
- + testsuite/tests/simplCore/should_compile/T25883b.hs
- + testsuite/tests/simplCore/should_compile/T25883b.substr-simpl
- + testsuite/tests/simplCore/should_compile/T25883c.hs
- + testsuite/tests/simplCore/should_compile/T25883c.substr-simpl
- + testsuite/tests/simplCore/should_compile/T25883d.hs
- + testsuite/tests/simplCore/should_compile/T25883d.stderr
- + testsuite/tests/simplCore/should_compile/T25883d_import.hs
- + testsuite/tests/simplCore/should_compile/T25965.hs
- + testsuite/tests/simplCore/should_compile/T25976.hs
- + testsuite/tests/simplCore/should_compile/T3990b.hs
- + testsuite/tests/simplCore/should_compile/T3990b.stdout
- + testsuite/tests/simplCore/should_compile/T3990c.hs
- + testsuite/tests/simplCore/should_compile/T3990c.stdout
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/simplCore/should_fail/T25672.stderr
- + testsuite/tests/simplCore/should_run/T23429.hs
- + testsuite/tests/simplCore/should_run/T23429.stdout
- testsuite/tests/simplCore/should_run/all.T
- testsuite/tests/simplCore/should_run/simplrun009.hs
- + testsuite/tests/splice-imports/ClassA.hs
- + testsuite/tests/splice-imports/InstanceA.hs
- + testsuite/tests/splice-imports/Makefile
- + testsuite/tests/splice-imports/SI01.hs
- + testsuite/tests/splice-imports/SI01A.hs
- + testsuite/tests/splice-imports/SI02.hs
- + testsuite/tests/splice-imports/SI03.hs
- + testsuite/tests/splice-imports/SI03.stderr
- + testsuite/tests/splice-imports/SI04.hs
- + testsuite/tests/splice-imports/SI05.hs
- + testsuite/tests/splice-imports/SI05.stderr
- + testsuite/tests/splice-imports/SI05A.hs
- + testsuite/tests/splice-imports/SI06.hs
- + testsuite/tests/splice-imports/SI07.hs
- + testsuite/tests/splice-imports/SI07.stderr
- + testsuite/tests/splice-imports/SI07A.hs
- + testsuite/tests/splice-imports/SI08.hs
- + testsuite/tests/splice-imports/SI08.stderr
- + testsuite/tests/splice-imports/SI08_oneshot.stderr
- + testsuite/tests/splice-imports/SI09.hs
- + testsuite/tests/splice-imports/SI10.hs
- + testsuite/tests/splice-imports/SI13.hs
- + testsuite/tests/splice-imports/SI14.hs
- + testsuite/tests/splice-imports/SI14.stderr
- + testsuite/tests/splice-imports/SI15.hs
- + testsuite/tests/splice-imports/SI15.stderr
- + testsuite/tests/splice-imports/SI16.hs
- + testsuite/tests/splice-imports/SI16.stderr
- + testsuite/tests/splice-imports/SI17.hs
- + testsuite/tests/splice-imports/SI18.hs
- + testsuite/tests/splice-imports/SI18.stderr
- + testsuite/tests/splice-imports/SI19.hs
- + testsuite/tests/splice-imports/SI19A.hs
- + testsuite/tests/splice-imports/SI20.hs
- + testsuite/tests/splice-imports/SI20.stderr
- + testsuite/tests/splice-imports/SI21.hs
- + testsuite/tests/splice-imports/SI21.stderr
- + testsuite/tests/splice-imports/SI22.hs
- + testsuite/tests/splice-imports/SI22.stderr
- + testsuite/tests/splice-imports/SI23.hs
- + testsuite/tests/splice-imports/SI23A.hs
- + testsuite/tests/splice-imports/SI24.hs
- + testsuite/tests/splice-imports/SI25.hs
- + testsuite/tests/splice-imports/SI25.stderr
- + testsuite/tests/splice-imports/SI25Helper.hs
- + testsuite/tests/splice-imports/SI26.hs
- + testsuite/tests/splice-imports/SI27.hs
- + testsuite/tests/splice-imports/SI27.stderr
- + testsuite/tests/splice-imports/SI28.hs
- + testsuite/tests/splice-imports/SI28.stderr
- + testsuite/tests/splice-imports/SI29.hs
- + testsuite/tests/splice-imports/SI29.stderr
- + testsuite/tests/splice-imports/SI30.script
- + testsuite/tests/splice-imports/SI30.stdout
- + testsuite/tests/splice-imports/SI31.script
- + testsuite/tests/splice-imports/SI31.stderr
- + testsuite/tests/splice-imports/SI32.script
- + testsuite/tests/splice-imports/SI32.stdout
- + testsuite/tests/splice-imports/SI33.script
- + testsuite/tests/splice-imports/SI33.stdout
- + testsuite/tests/splice-imports/SI34.hs
- + testsuite/tests/splice-imports/SI34.stderr
- + testsuite/tests/splice-imports/SI34M1.hs
- + testsuite/tests/splice-imports/SI34M2.hs
- + testsuite/tests/splice-imports/SI35.hs
- + testsuite/tests/splice-imports/SI35A.hs
- + testsuite/tests/splice-imports/SI36.hs
- + testsuite/tests/splice-imports/SI36.stderr
- + testsuite/tests/splice-imports/SI36_A.hs
- + testsuite/tests/splice-imports/SI36_B1.hs
- + testsuite/tests/splice-imports/SI36_B2.hs
- + testsuite/tests/splice-imports/SI36_B3.hs
- + testsuite/tests/splice-imports/SI36_C1.hs
- + testsuite/tests/splice-imports/SI36_C2.hs
- + testsuite/tests/splice-imports/SI36_C3.hs
- + testsuite/tests/splice-imports/all.T
- testsuite/tests/th/T15365.stderr
- testsuite/tests/th/T16976z.stderr
- testsuite/tests/th/T17820a.stderr
- testsuite/tests/th/T17820b.stderr
- testsuite/tests/th/T17820c.stderr
- testsuite/tests/th/T17820d.stderr
- testsuite/tests/th/T17820e.stderr
- testsuite/tests/th/T1835.stdout
- testsuite/tests/th/T21547.stderr
- testsuite/tests/th/T23829_hasty.stderr
- testsuite/tests/th/T23829_hasty_b.stderr
- testsuite/tests/th/T23829_tardy.ghc.stderr
- testsuite/tests/th/T5795.stderr
- testsuite/tests/th/TH_Roles2.stderr
- testsuite/tests/typecheck/should_compile/LoopOfTheDay1.hs
- testsuite/tests/typecheck/should_compile/LoopOfTheDay2.hs
- testsuite/tests/typecheck/should_compile/LoopOfTheDay3.hs
- testsuite/tests/typecheck/should_compile/T12763.stderr
- testsuite/tests/typecheck/should_compile/T18406b.stderr
- testsuite/tests/typecheck/should_compile/T18529.stderr
- testsuite/tests/typecheck/should_compile/T21023.stderr
- testsuite/tests/typecheck/should_compile/T25266a.stderr
- + testsuite/tests/typecheck/should_compile/T25960.hs
- testsuite/tests/typecheck/should_compile/T7050.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/T12729.stderr
- testsuite/tests/typecheck/should_fail/T12921.stderr
- testsuite/tests/typecheck/should_fail/T18851.stderr
- testsuite/tests/typecheck/should_fail/T19978.stderr
- + testsuite/tests/typecheck/should_fail/T24090a.hs
- + testsuite/tests/typecheck/should_fail/T24090a.stderr
- + testsuite/tests/typecheck/should_fail/T24090b.hs
- testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr → testsuite/tests/typecheck/should_fail/T24090b.stderr
- + testsuite/tests/typecheck/should_fail/T25004k.hs
- + testsuite/tests/typecheck/should_fail/T25004k.stderr
- testsuite/tests/typecheck/should_fail/T3966.stderr
- + testsuite/tests/typecheck/should_fail/T3966b.hs
- + testsuite/tests/typecheck/should_fail/T3966b.stderr
- testsuite/tests/typecheck/should_fail/T6018fail.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/unboxedsums/unpack_sums_5.stderr
- + testsuite/tests/vdq-rta/should_fail/T23738_fail_pun.hs
- + testsuite/tests/vdq-rta/should_fail/T23738_fail_pun.stderr
- testsuite/tests/vdq-rta/should_fail/all.T
- testsuite/tests/warnings/should_compile/WarnNoncanonical.stderr
- testsuite/tests/wasm/should_run/control-flow/README.md
- − testsuite/tests/wasm/should_run/control-flow/WasmControlFlow.stdout
- testsuite/tests/wasm/should_run/control-flow/all.T
- testsuite/tests/wcompat-warnings/Template.hs
- utils/check-exact/ExactPrint.hs
- utils/count-deps/Main.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/GhcUtils.hs
- utils/haddock/haddock-api/src/Haddock/Interface.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/Interface/RenameType.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ce5db8f652b48a613e55d0738bcc7a…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ce5db8f652b48a613e55d0738bcc7a…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/andreask/spec_tyfams] 7 commits: Doc: add doc for JS interruptible calling convention (#24444)
by Simon Peyton Jones (@simonpj) 29 Apr '25
by Simon Peyton Jones (@simonpj) 29 Apr '25
29 Apr '25
Simon Peyton Jones pushed to branch wip/andreask/spec_tyfams at Glasgow Haskell Compiler / GHC
Commits:
fe6ed8d9 by Sylvain Henry at 2025-04-24T18:04:12-04:00
Doc: add doc for JS interruptible calling convention (#24444)
- - - - -
6111c5e4 by Ben Gamari at 2025-04-24T18:04:53-04:00
compiler: Ensure that Panic.Plain.assertPanic' provides callstack
In 36cddd2ce1a3bc62ea8a1307d8bc6006d54109cf @alt-romes removed CallStack
output from `GHC.Utils.Panic.Plain.assertPanic'`. While this output is
redundant due to the exception backtrace proposal, we may be
bootstrapping with a compiler which does not yet include this machinery.
Reintroduce the output for now.
Fixes #25898.
- - - - -
217caad1 by Matthew Pickering at 2025-04-25T18:58:42+01:00
Implement Explicit Level Imports for Template Haskell
This commit introduces the `ExplicitLevelImports` and
`ImplicitStagePersistence` language extensions as proposed in GHC
Proposal #682.
Key Features
------------
- `ExplicitLevelImports` adds two new import modifiers - `splice` and
`quote` - allowing precise control over the level at which imported
identifiers are available
- `ImplicitStagePersistence` (enabled by default) preserves existing
path-based cross-stage persistence behavior
- `NoImplicitStagePersistence` disables implicit cross-stage
persistence, requiring explicit level imports
Benefits
--------
- Improved compilation performance by reducing unnecessary code generation
- Enhanced IDE experience with faster feedback in `-fno-code` mode
- Better dependency tracking by distinguishing compile-time and runtime dependencies
- Foundation for future cross-compilation improvements
This implementation enables the separation of modules needed at
compile-time from those needed at runtime, allowing for more efficient
compilation pipelines and clearer code organization in projects using
Template Haskell.
Implementation Notes
--------------------
The level which a name is availble at is stored in the 'GRE', in the normal
GlobalRdrEnv. The function `greLevels` returns the levels which a specific GRE
is imported at. The level information for a 'Name' is computed by `getCurrentAndBindLevel`.
The level validity is checked by `checkCrossLevelLifting`.
Instances are checked by `checkWellLevelledDFun`, which computes the level an
instance by calling `checkWellLevelledInstanceWhat`, which sees what is
available at by looking at the module graph.
Modifications to downsweep
--------------------------
Code generation is now only enabled for modules which are needed at
compile time.
See the Note [-fno-code mode] for more information.
Uniform error messages for level errors
---------------------------------------
All error messages to do with levels are now reported uniformly using
the `TcRnBadlyStaged` constructor.
Error messages are uniformly reported in terms of levels.
0 - top-level
1 - quote level
-1 - splice level
The only level hard-coded into the compiler is the top-level in
GHC.Types.ThLevelIndex.topLevelIndex.
Uniformly refer to levels and stages
------------------------------------
There was much confusion about levels vs stages in the compiler.
A level is a semantic concept, used by the typechecker to ensure a
program can be evaluated in a well-staged manner.
A stage is an operational construct, program evaluation proceeds in
stages.
Deprecate -Wbadly-staged-types
------------------------------
`-Wbadly-staged-types` is deprecated in favour of `-Wbadly-levelled-types`.
Lift derivation changed
-----------------------
Derived lift instances will now not generate code with expression
quotations.
Before:
```
data A = A Int deriving Lift
=>
lift (A x) = [| A $(lift x) |]
```
After:
```
lift (A x) = conE 'A `appE` (lift x)
```
This is because if you attempt to derive `Lift` in a module where
`NoImplicitStagePersistence` is enabled, you would get an infinite loop
where a constructor was attempted to be persisted using the instance you
are currently defining.
GHC API Changes
---------------
The ModuleGraph now contains additional information about the type of
the edges (normal, quote or splice) between modules. This is abstracted
using the `ModuleGraphEdge` data type.
Fixes #25828
-------------------------
Metric Increase:
MultiLayerModulesTH_Make
-------------------------
- - - - -
7641a74a by Simon Peyton Jones at 2025-04-26T22:05:19-04:00
Get a decent MatchContext for pattern synonym bindings
In particular when we have a pattern binding
K p1 .. pn = rhs
where K is a pattern synonym. (It might be nested.)
This small MR fixes #25995. It's a tiny fix, to an error message,
removing an always-dubious `unkSkol`.
The bug report was in the context of horde-ad, a big program,
and I didn't manage to make a small repro case quickly. I decided
not to bother further.
- - - - -
ce616f49 by Simon Peyton Jones at 2025-04-27T21:10:25+01:00
Fix infelicities in the Specialiser
On the way to #23109 (unary classes) I discovered some infelicities
(or maybe tiny bugs, I forget) in the type-class specialiser.
I also tripped over #25965, an outright bug in the rule matcher
Specifically:
* Refactor: I enhanced `wantCallsFor`, whih previously always said
`True`, to discard calls of class-ops, data constructors etc. This is
a bit more efficient; and it means we don't need to worry about
filtering them out later.
* Fix: I tidied up some tricky logic that eliminated redundant
specialisations. It wasn't working correctly. See the expanded
Note [Specialisations already covered], and
(MP3) in Note [Specialising polymorphic dictionaries].
See also the new top-level `alreadyCovered`
function, which now goes via `GHC.Core.Rules.ruleLhsIsMoreSpecific`
I also added a useful Note [The (CI-KEY) invariant]
* Fix #25965: fixed a tricky bug in the `go_fam_fam` in
`GHC.Core.Unify.uVarOrFam`, which allows matching to succeed
without binding all type varibles.
I enhanced Note [Apartness and type families] some more
* #25703. This ticket "just works" with -fpolymorphic-specialisation;
but I was surprised that it worked! In this MR I added documentation
to Note [Interesting dictionary arguments] to explain; and tests to
ensure it stays fixed.
- - - - -
22d11fa8 by Simon Peyton Jones at 2025-04-28T18:05:19-04:00
Track rewriter sets more accurately in constraint solving
The key change, which fixed #25440, is to call `recordRewriter` in
GHC.Tc.Solver.Rewrite.rewrite_exact_fam_app. This missing call meant
that we were secretly rewriting a Wanted with a Wanted, but not really
noticing; and that led to a very bad error message, as you can see
in the ticket.
But of course that led me into rabbit hole of other refactoring around
the RewriteSet code:
* Improve Notes [Wanteds rewrite Wanteds]
* Zonk the RewriterSet in `zonkCtEvidence` rather than only in GHC.Tc.Errors.
This is tidier anyway (e.g. de-clutters debug output), and helps with the
next point.
* In GHC.Tc.Solver.Equality.inertsCanDischarge, don't replace a constraint
with no rewriters with an equal constraint that has many. See
See (CE4) in Note [Combining equalities]
* Move zonkRewriterSet and friends from GHC.Tc.Zonk.Type into
GHC.Tc.Zonk.TcType, where they properly belong.
A handful of tests get better error messages.
For some reason T24984 gets 12% less compiler allocation -- good
Metric Decrease:
T24984
- - - - -
1fb071db by Andreas Klebinger at 2025-04-29T10:17:02+01:00
Try to relax specialization requirements we put on args.
Dont make comment seem like haddock
Test things
Wibble
Try simons version of isInterestingDict
Disable trace for ci checks
use inscope set
Add test cases
Polishing up from Simon
Rmoved accidentally committed traces
and add missing import
Typos
Remove a special case that appears to do nothing
See the commented-out block of `specCase`
Wibbles
Another subtle wibble: (ID8)
- - - - -
302 changed files:
- compiler/GHC.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Data/Graph/Directed/Reachability.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Runtime/Loader.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Utils.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Plugin.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/TyCl/Instance.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/LclEnv.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Types/TH.hs
- compiler/GHC/Tc/Utils/Backpack.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/Env.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Zonk/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Name/Reader.hs
- + compiler/GHC/Types/ThLevelIndex.hs
- compiler/GHC/Unit/Home/PackageTable.hs
- compiler/GHC/Unit/Module/Deps.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Unit/Module/Imported.hs
- compiler/GHC/Unit/Module/ModSummary.hs
- + compiler/GHC/Unit/Module/Stage.hs
- compiler/GHC/Unit/Types.hs
- compiler/GHC/Utils/Binary.hs
- compiler/GHC/Utils/Outputable.hs
- compiler/GHC/Utils/Panic/Plain.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- + compiler/Language/Haskell/Syntax/ImpExp/IsBoot.hs
- compiler/ghc.cabal.in
- docs/users_guide/exts/control.rst
- docs/users_guide/exts/template_haskell.rst
- docs/users_guide/javascript.rst
- docs/users_guide/phases.rst
- docs/users_guide/using-warnings.rst
- ghc/GHCi/UI.hs
- libraries/base/tests/IO/Makefile
- libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs
- testsuite/tests/ado/ado004.stderr
- testsuite/tests/annotations/should_fail/annfail03.stderr
- testsuite/tests/annotations/should_fail/annfail04.stderr
- testsuite/tests/annotations/should_fail/annfail06.stderr
- testsuite/tests/annotations/should_fail/annfail09.stderr
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/dependent/should_compile/T14729.stderr
- testsuite/tests/dependent/should_compile/T15743.stderr
- testsuite/tests/dependent/should_compile/T15743e.stderr
- testsuite/tests/deriving/should_compile/T14682.stderr
- testsuite/tests/determinism/determ021/determ021.stdout
- + testsuite/tests/driver/T4437.stdout
- testsuite/tests/driver/json2.stderr
- testsuite/tests/gadt/T19847a.stderr
- testsuite/tests/ghc-api/fixed-nodes/FixedNodes.hs
- testsuite/tests/ghc-api/fixed-nodes/ModuleGraphInvariants.hs
- testsuite/tests/indexed-types/should_compile/T15711.stderr
- testsuite/tests/indexed-types/should_compile/T15852.stderr
- testsuite/tests/indexed-types/should_compile/T3017.stderr
- testsuite/tests/indexed-types/should_fail/T3330c.stderr
- testsuite/tests/indexed-types/should_fail/T4174.stderr
- testsuite/tests/indexed-types/should_fail/T8227.stderr
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- testsuite/tests/module/mod185.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/partial-sigs/should_compile/ADT.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr1.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr2.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr3.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr4.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr5.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr6.stderr
- testsuite/tests/partial-sigs/should_compile/BoolToBool.stderr
- testsuite/tests/partial-sigs/should_compile/DataFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting1MROn.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting2MROff.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting2MROn.stderr
- testsuite/tests/partial-sigs/should_compile/Either.stderr
- testsuite/tests/partial-sigs/should_compile/EqualityConstraint.stderr
- testsuite/tests/partial-sigs/should_compile/Every.stderr
- testsuite/tests/partial-sigs/should_compile/EveryNamed.stderr
- testsuite/tests/partial-sigs/should_compile/ExpressionSig.stderr
- testsuite/tests/partial-sigs/should_compile/ExpressionSigNamed.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints1.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints2.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints3.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROff.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROn.stderr
- testsuite/tests/partial-sigs/should_compile/Forall1.stderr
- testsuite/tests/partial-sigs/should_compile/GenNamed.stderr
- testsuite/tests/partial-sigs/should_compile/HigherRank1.stderr
- testsuite/tests/partial-sigs/should_compile/HigherRank2.stderr
- testsuite/tests/partial-sigs/should_compile/LocalDefinitionBug.stderr
- testsuite/tests/partial-sigs/should_compile/Meltdown.stderr
- testsuite/tests/partial-sigs/should_compile/MonoLocalBinds.stderr
- testsuite/tests/partial-sigs/should_compile/NamedTyVar.stderr
- testsuite/tests/partial-sigs/should_compile/NamedWildcardInDataFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/NamedWildcardInTypeFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/ParensAroundContext.stderr
- testsuite/tests/partial-sigs/should_compile/PatBind.stderr
- testsuite/tests/partial-sigs/should_compile/PatBind2.stderr
- testsuite/tests/partial-sigs/should_compile/PatternSig.stderr
- testsuite/tests/partial-sigs/should_compile/Recursive.stderr
- testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcards.stderr
- testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcardsGood.stderr
- testsuite/tests/partial-sigs/should_compile/ShowNamed.stderr
- testsuite/tests/partial-sigs/should_compile/SimpleGen.stderr
- testsuite/tests/partial-sigs/should_compile/SkipMany.stderr
- testsuite/tests/partial-sigs/should_compile/SomethingShowable.stderr
- testsuite/tests/partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/Uncurry.stderr
- testsuite/tests/partial-sigs/should_compile/UncurryNamed.stderr
- testsuite/tests/partial-sigs/should_compile/WarningWildcardInstantiations.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/polykinds/T15592.stderr
- testsuite/tests/polykinds/T15592b.stderr
- testsuite/tests/printer/T18052a.stderr
- testsuite/tests/quasiquotation/qq001/qq001.stderr
- testsuite/tests/quasiquotation/qq002/qq002.stderr
- testsuite/tests/quasiquotation/qq003/qq003.stderr
- testsuite/tests/quasiquotation/qq004/qq004.stderr
- + testsuite/tests/quotes/T5721.stderr
- testsuite/tests/roles/should_compile/Roles1.stderr
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles2.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/roles/should_compile/T8958.stderr
- testsuite/tests/showIface/DocsInHiFile1.stdout
- testsuite/tests/showIface/DocsInHiFileTH.stdout
- testsuite/tests/showIface/HaddockIssue849.stdout
- testsuite/tests/showIface/HaddockOpts.stdout
- testsuite/tests/showIface/HaddockSpanIssueT24378.stdout
- testsuite/tests/showIface/LanguageExts.stdout
- testsuite/tests/showIface/MagicHashInHaddocks.stdout
- testsuite/tests/showIface/NoExportList.stdout
- testsuite/tests/showIface/PragmaDocs.stdout
- testsuite/tests/showIface/ReExports.stdout
- + testsuite/tests/simplCore/should_compile/SpecTyFam.hs
- + testsuite/tests/simplCore/should_compile/SpecTyFam.stderr
- + testsuite/tests/simplCore/should_compile/SpecTyFam_Import.hs
- + testsuite/tests/simplCore/should_compile/T25703.hs
- + testsuite/tests/simplCore/should_compile/T25703.stderr
- + testsuite/tests/simplCore/should_compile/T25703a.hs
- + testsuite/tests/simplCore/should_compile/T25703a.stderr
- + testsuite/tests/simplCore/should_compile/T25965.hs
- testsuite/tests/simplCore/should_compile/all.T
- + testsuite/tests/splice-imports/ClassA.hs
- + testsuite/tests/splice-imports/InstanceA.hs
- + testsuite/tests/splice-imports/Makefile
- + testsuite/tests/splice-imports/SI01.hs
- + testsuite/tests/splice-imports/SI01A.hs
- + testsuite/tests/splice-imports/SI02.hs
- + testsuite/tests/splice-imports/SI03.hs
- + testsuite/tests/splice-imports/SI03.stderr
- + testsuite/tests/splice-imports/SI04.hs
- + testsuite/tests/splice-imports/SI05.hs
- + testsuite/tests/splice-imports/SI05.stderr
- + testsuite/tests/splice-imports/SI05A.hs
- + testsuite/tests/splice-imports/SI06.hs
- + testsuite/tests/splice-imports/SI07.hs
- + testsuite/tests/splice-imports/SI07.stderr
- + testsuite/tests/splice-imports/SI07A.hs
- + testsuite/tests/splice-imports/SI08.hs
- + testsuite/tests/splice-imports/SI08.stderr
- + testsuite/tests/splice-imports/SI08_oneshot.stderr
- + testsuite/tests/splice-imports/SI09.hs
- + testsuite/tests/splice-imports/SI10.hs
- + testsuite/tests/splice-imports/SI13.hs
- + testsuite/tests/splice-imports/SI14.hs
- + testsuite/tests/splice-imports/SI14.stderr
- + testsuite/tests/splice-imports/SI15.hs
- + testsuite/tests/splice-imports/SI15.stderr
- + testsuite/tests/splice-imports/SI16.hs
- + testsuite/tests/splice-imports/SI16.stderr
- + testsuite/tests/splice-imports/SI17.hs
- + testsuite/tests/splice-imports/SI18.hs
- + testsuite/tests/splice-imports/SI18.stderr
- + testsuite/tests/splice-imports/SI19.hs
- + testsuite/tests/splice-imports/SI19A.hs
- + testsuite/tests/splice-imports/SI20.hs
- + testsuite/tests/splice-imports/SI20.stderr
- + testsuite/tests/splice-imports/SI21.hs
- + testsuite/tests/splice-imports/SI21.stderr
- + testsuite/tests/splice-imports/SI22.hs
- + testsuite/tests/splice-imports/SI22.stderr
- + testsuite/tests/splice-imports/SI23.hs
- + testsuite/tests/splice-imports/SI23A.hs
- + testsuite/tests/splice-imports/SI24.hs
- + testsuite/tests/splice-imports/SI25.hs
- + testsuite/tests/splice-imports/SI25.stderr
- + testsuite/tests/splice-imports/SI25Helper.hs
- + testsuite/tests/splice-imports/SI26.hs
- + testsuite/tests/splice-imports/SI27.hs
- + testsuite/tests/splice-imports/SI27.stderr
- + testsuite/tests/splice-imports/SI28.hs
- + testsuite/tests/splice-imports/SI28.stderr
- + testsuite/tests/splice-imports/SI29.hs
- + testsuite/tests/splice-imports/SI29.stderr
- + testsuite/tests/splice-imports/SI30.script
- + testsuite/tests/splice-imports/SI30.stdout
- + testsuite/tests/splice-imports/SI31.script
- + testsuite/tests/splice-imports/SI31.stderr
- + testsuite/tests/splice-imports/SI32.script
- + testsuite/tests/splice-imports/SI32.stdout
- + testsuite/tests/splice-imports/SI33.script
- + testsuite/tests/splice-imports/SI33.stdout
- + testsuite/tests/splice-imports/SI34.hs
- + testsuite/tests/splice-imports/SI34.stderr
- + testsuite/tests/splice-imports/SI34M1.hs
- + testsuite/tests/splice-imports/SI34M2.hs
- + testsuite/tests/splice-imports/SI35.hs
- + testsuite/tests/splice-imports/SI35A.hs
- + testsuite/tests/splice-imports/SI36.hs
- + testsuite/tests/splice-imports/SI36.stderr
- + testsuite/tests/splice-imports/SI36_A.hs
- + testsuite/tests/splice-imports/SI36_B1.hs
- + testsuite/tests/splice-imports/SI36_B2.hs
- + testsuite/tests/splice-imports/SI36_B3.hs
- + testsuite/tests/splice-imports/SI36_C1.hs
- + testsuite/tests/splice-imports/SI36_C2.hs
- + testsuite/tests/splice-imports/SI36_C3.hs
- + testsuite/tests/splice-imports/all.T
- testsuite/tests/th/T16976z.stderr
- testsuite/tests/th/T17820a.stderr
- testsuite/tests/th/T17820b.stderr
- testsuite/tests/th/T17820c.stderr
- testsuite/tests/th/T17820d.stderr
- testsuite/tests/th/T17820e.stderr
- testsuite/tests/th/T21547.stderr
- testsuite/tests/th/T23829_hasty.stderr
- testsuite/tests/th/T23829_hasty_b.stderr
- testsuite/tests/th/T23829_tardy.ghc.stderr
- testsuite/tests/th/T5795.stderr
- testsuite/tests/th/TH_Roles2.stderr
- testsuite/tests/typecheck/should_compile/T12763.stderr
- testsuite/tests/typecheck/should_compile/T18406b.stderr
- testsuite/tests/typecheck/should_compile/T18529.stderr
- testsuite/tests/typecheck/should_compile/T21023.stderr
- testsuite/tests/typecheck/should_compile/T25266a.stderr
- testsuite/tests/typecheck/should_fail/T18851.stderr
- utils/check-exact/ExactPrint.hs
- utils/count-deps/Main.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dc677e8d65cec9787d22d5742bc146…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dc677e8d65cec9787d22d5742bc146…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T26003] 4 commits: Fix infelicities in the Specialiser
by Simon Peyton Jones (@simonpj) 29 Apr '25
by Simon Peyton Jones (@simonpj) 29 Apr '25
29 Apr '25
Simon Peyton Jones pushed to branch wip/T26003 at Glasgow Haskell Compiler / GHC
Commits:
ce616f49 by Simon Peyton Jones at 2025-04-27T21:10:25+01:00
Fix infelicities in the Specialiser
On the way to #23109 (unary classes) I discovered some infelicities
(or maybe tiny bugs, I forget) in the type-class specialiser.
I also tripped over #25965, an outright bug in the rule matcher
Specifically:
* Refactor: I enhanced `wantCallsFor`, whih previously always said
`True`, to discard calls of class-ops, data constructors etc. This is
a bit more efficient; and it means we don't need to worry about
filtering them out later.
* Fix: I tidied up some tricky logic that eliminated redundant
specialisations. It wasn't working correctly. See the expanded
Note [Specialisations already covered], and
(MP3) in Note [Specialising polymorphic dictionaries].
See also the new top-level `alreadyCovered`
function, which now goes via `GHC.Core.Rules.ruleLhsIsMoreSpecific`
I also added a useful Note [The (CI-KEY) invariant]
* Fix #25965: fixed a tricky bug in the `go_fam_fam` in
`GHC.Core.Unify.uVarOrFam`, which allows matching to succeed
without binding all type varibles.
I enhanced Note [Apartness and type families] some more
* #25703. This ticket "just works" with -fpolymorphic-specialisation;
but I was surprised that it worked! In this MR I added documentation
to Note [Interesting dictionary arguments] to explain; and tests to
ensure it stays fixed.
- - - - -
22d11fa8 by Simon Peyton Jones at 2025-04-28T18:05:19-04:00
Track rewriter sets more accurately in constraint solving
The key change, which fixed #25440, is to call `recordRewriter` in
GHC.Tc.Solver.Rewrite.rewrite_exact_fam_app. This missing call meant
that we were secretly rewriting a Wanted with a Wanted, but not really
noticing; and that led to a very bad error message, as you can see
in the ticket.
But of course that led me into rabbit hole of other refactoring around
the RewriteSet code:
* Improve Notes [Wanteds rewrite Wanteds]
* Zonk the RewriterSet in `zonkCtEvidence` rather than only in GHC.Tc.Errors.
This is tidier anyway (e.g. de-clutters debug output), and helps with the
next point.
* In GHC.Tc.Solver.Equality.inertsCanDischarge, don't replace a constraint
with no rewriters with an equal constraint that has many. See
See (CE4) in Note [Combining equalities]
* Move zonkRewriterSet and friends from GHC.Tc.Zonk.Type into
GHC.Tc.Zonk.TcType, where they properly belong.
A handful of tests get better error messages.
For some reason T24984 gets 12% less compiler allocation -- good
Metric Decrease:
T24984
- - - - -
4ab20fe4 by Simon Peyton Jones at 2025-04-29T09:36:41+01:00
Wip on #26003
- - - - -
c31925a1 by Simon Peyton Jones at 2025-04-29T10:04:02+01:00
Wibbles
- - - - -
27 changed files:
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Solver/Default.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/Types/Constraint.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Zonk/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Types/Basic.hs
- testsuite/tests/indexed-types/should_fail/T3330c.stderr
- testsuite/tests/indexed-types/should_fail/T4174.stderr
- testsuite/tests/indexed-types/should_fail/T8227.stderr
- + testsuite/tests/simplCore/should_compile/T25703.hs
- + testsuite/tests/simplCore/should_compile/T25703.stderr
- + testsuite/tests/simplCore/should_compile/T25703a.hs
- + testsuite/tests/simplCore/should_compile/T25703a.stderr
- + testsuite/tests/simplCore/should_compile/T25965.hs
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/typecheck/should_compile/T25266a.stderr
- testsuite/tests/typecheck/should_fail/T18851.stderr
Changes:
=====================================
compiler/GHC/Core/Coercion.hs
=====================================
@@ -120,7 +120,7 @@ module GHC.Core.Coercion (
multToCo, mkRuntimeRepCo,
- hasCoercionHoleTy, hasCoercionHoleCo, hasThisCoercionHoleTy,
+ hasHeteroKindCoercionHoleTy, hasHeteroKindCoercionHoleCo,
setCoHoleType
) where
@@ -2795,24 +2795,12 @@ has_co_hole_co :: Coercion -> Monoid.Any
-- | Is there a hetero-kind coercion hole in this type?
-- (That is, a coercion hole with ch_hetero_kind=True.)
-- See wrinkle (EIK2) of Note [Equalities with incompatible kinds] in GHC.Tc.Solver.Equality
-hasCoercionHoleTy :: Type -> Bool
-hasCoercionHoleTy = Monoid.getAny . has_co_hole_ty
+hasHeteroKindCoercionHoleTy :: Type -> Bool
+hasHeteroKindCoercionHoleTy = Monoid.getAny . has_co_hole_ty
-- | Is there a hetero-kind coercion hole in this coercion?
-hasCoercionHoleCo :: Coercion -> Bool
-hasCoercionHoleCo = Monoid.getAny . has_co_hole_co
-
-hasThisCoercionHoleTy :: Type -> CoercionHole -> Bool
-hasThisCoercionHoleTy ty hole = Monoid.getAny (f ty)
- where
- (f, _, _, _) = foldTyCo folder ()
-
- folder = TyCoFolder { tcf_view = noView
- , tcf_tyvar = const2 (Monoid.Any False)
- , tcf_covar = const2 (Monoid.Any False)
- , tcf_hole = \ _ h -> Monoid.Any (getUnique h == getUnique hole)
- , tcf_tycobinder = const2
- }
+hasHeteroKindCoercionHoleCo :: Coercion -> Bool
+hasHeteroKindCoercionHoleCo = Monoid.getAny . has_co_hole_co
-- | Set the type of a 'CoercionHole'
setCoHoleType :: CoercionHole -> Type -> CoercionHole
=====================================
compiler/GHC/Core/Opt/Specialise.hs
=====================================
@@ -1243,14 +1243,15 @@ specExpr env (Let bind body)
-- Note [Fire rules in the specialiser]
fireRewriteRules :: SpecEnv -> InExpr -> [OutExpr] -> (InExpr, [OutExpr])
fireRewriteRules env (Var f) args
- | Just (rule, expr) <- specLookupRule env f args InitialPhase (getRules (se_rules env) f)
+ | let rules = getRules (se_rules env) f
+ , Just (rule, expr) <- specLookupRule env f args activeInInitialPhase rules
, let rest_args = drop (ruleArity rule) args -- See Note [Extra args in the target]
zapped_subst = Core.zapSubst (se_subst env)
expr' = simpleOptExprWith defaultSimpleOpts zapped_subst expr
-- simplOptExpr needed because lookupRule returns
-- (\x y. rhs) arg1 arg2
- , (fun, args) <- collectArgs expr'
- = fireRewriteRules env fun (args++rest_args)
+ , (fun', args') <- collectArgs expr'
+ = fireRewriteRules env fun' (args'++rest_args)
fireRewriteRules _ fun args = (fun, args)
--------------
@@ -1620,7 +1621,7 @@ specCalls :: Bool -- True => specialising imported fn
-- This function checks existing rules, and does not create
-- duplicate ones. So the caller does not need to do this filtering.
--- See 'already_covered'
+-- See `alreadyCovered`
type SpecInfo = ( [CoreRule] -- Specialisation rules
, [(Id,CoreExpr)] -- Specialised definition
@@ -1644,15 +1645,13 @@ specCalls spec_imp env existing_rules calls_for_me fn rhs
= -- pprTrace "specCalls: some" (vcat
-- [ text "function" <+> ppr fn
- -- , text "calls:" <+> ppr calls_for_me
- -- , text "subst" <+> ppr (se_subst env) ]) $
+ -- , text "calls:" <+> ppr calls_for_me
+ -- , text "subst" <+> ppr (se_subst env) ]) $
foldlM spec_call ([], [], emptyUDs) calls_for_me
| otherwise -- No calls or RHS doesn't fit our preconceptions
- = warnPprTrace (not (exprIsTrivial rhs) && notNull calls_for_me && not (isClassOpId fn))
+ = warnPprTrace (not (exprIsTrivial rhs) && notNull calls_for_me)
"Missed specialisation opportunity for" (ppr fn $$ trace_doc) $
- -- isClassOpId: class-op Ids never inline; we specialise them
- -- through fireRewriteRules. So don't complain about missed opportunities
-- Note [Specialisation shape]
-- pprTrace "specCalls: none" (ppr fn <+> ppr calls_for_me) $
return ([], [], emptyUDs)
@@ -1664,6 +1663,10 @@ specCalls spec_imp env existing_rules calls_for_me fn rhs
fn_unf = realIdUnfolding fn -- Ignore loop-breaker-ness here
inl_prag = idInlinePragma fn
inl_act = inlinePragmaActivation inl_prag
+ is_active = isActive (beginPhase inl_act) :: Activation -> Bool
+ -- is_active: inl_act is the activation we are going to put in the new
+ -- SPEC rule; so we want to see if it is covered by another rule with
+ -- that same activation.
is_local = isLocalId fn
is_dfun = isDFunId fn
dflags = se_dflags env
@@ -1674,16 +1677,6 @@ specCalls spec_imp env existing_rules calls_for_me fn rhs
(rhs_bndrs, rhs_body) = collectBindersPushingCo rhs
-- See Note [Account for casts in binding]
- already_covered :: SpecEnv -> [CoreRule] -> [CoreExpr] -> Bool
- already_covered env new_rules args -- Note [Specialisations already covered]
- = isJust (specLookupRule env fn args (beginPhase inl_act)
- (new_rules ++ existing_rules))
- -- Rules: we look both in the new_rules (generated by this invocation
- -- of specCalls), and in existing_rules (passed in to specCalls)
- -- inl_act: is the activation we are going to put in the new SPEC
- -- rule; so we want to see if it is covered by another rule with
- -- that same activation.
-
----------------------------------------------------------
-- Specialise to one particular call pattern
spec_call :: SpecInfo -- Accumulating parameter
@@ -1717,8 +1710,12 @@ specCalls spec_imp env existing_rules calls_for_me fn rhs
-- , ppr dx_binds ]) $
-- return ()
+ ; let all_rules = rules_acc ++ existing_rules
+ -- all_rules: we look both in the rules_acc (generated by this invocation
+ -- of specCalls), and in existing_rules (passed in to specCalls)
; if not useful -- No useful specialisation
- || already_covered rhs_env2 rules_acc rule_lhs_args
+ || alreadyCovered rhs_env2 rule_bndrs fn rule_lhs_args is_active all_rules
+ -- See (SC1) in Note [Specialisations already covered]
then return spec_acc
else
do { -- Run the specialiser on the specialised RHS
@@ -1780,7 +1777,7 @@ specCalls spec_imp env existing_rules calls_for_me fn rhs
spec_fn_details
= case idDetails fn of
JoinId join_arity _ -> JoinId (join_arity - join_arity_decr) Nothing
- DFunId is_nt -> DFunId is_nt
+ DFunId unary -> DFunId unary
_ -> VanillaId
; spec_fn <- newSpecIdSM (idName fn) spec_fn_ty spec_fn_details spec_fn_info
@@ -1804,6 +1801,8 @@ specCalls spec_imp env existing_rules calls_for_me fn rhs
, ppr spec_fn <+> dcolon <+> ppr spec_fn_ty
, ppr rhs_bndrs, ppr call_args
, ppr spec_rule
+ , text "acc" <+> ppr rules_acc
+ , text "existing" <+> ppr existing_rules
]
; -- pprTrace "spec_call: rule" _rule_trace_doc
@@ -1812,19 +1811,35 @@ specCalls spec_imp env existing_rules calls_for_me fn rhs
, spec_uds `thenUDs` uds_acc
) } }
+alreadyCovered :: SpecEnv
+ -> [Var] -> Id -> [CoreExpr] -- LHS of possible new rule
+ -> (Activation -> Bool) -- Which rules are active
+ -> [CoreRule] -> Bool
+-- Note [Specialisations already covered] esp (SC2)
+alreadyCovered env bndrs fn args is_active rules
+ = case specLookupRule env fn args is_active rules of
+ Nothing -> False
+ Just (rule, _)
+ | isAutoRule rule -> -- Discard identical rules
+ -- We know that (fn args) is an instance of RULE
+ -- Check if RULE is an instance of (fn args)
+ ruleLhsIsMoreSpecific in_scope bndrs args rule
+ | otherwise -> True -- User rules dominate
+ where
+ in_scope = substInScopeSet (se_subst env)
+
-- Convenience function for invoking lookupRule from Specialise
-- The SpecEnv's InScopeSet should include all the Vars in the [CoreExpr]
specLookupRule :: SpecEnv -> Id -> [CoreExpr]
- -> CompilerPhase -- Look up rules as if we were in this phase
+ -> (Activation -> Bool) -- Which rules are active
-> [CoreRule] -> Maybe (CoreRule, CoreExpr)
-specLookupRule env fn args phase rules
+specLookupRule env fn args is_active rules
= lookupRule ropts in_scope_env is_active fn args rules
where
dflags = se_dflags env
in_scope = substInScopeSet (se_subst env)
in_scope_env = ISE in_scope (whenActiveUnfoldingFun is_active)
ropts = initRuleOpts dflags
- is_active = isActive phase
{- Note [Specialising DFuns]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -2323,21 +2338,24 @@ This plan is implemented in the Rec case of specBindItself.
Note [Specialisations already covered]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
We obviously don't want to generate two specialisations for the same
-argument pattern. There are two wrinkles
-
-1. We do the already-covered test in specDefn, not when we generate
-the CallInfo in mkCallUDs. We used to test in the latter place, but
-we now iterate the specialiser somewhat, and the Id at the call site
-might therefore not have all the RULES that we can see in specDefn
-
-2. What about two specialisations where the second is an *instance*
-of the first? If the more specific one shows up first, we'll generate
-specialisations for both. If the *less* specific one shows up first,
-we *don't* currently generate a specialisation for the more specific
-one. (See the call to lookupRule in already_covered.) Reasons:
- (a) lookupRule doesn't say which matches are exact (bad reason)
- (b) if the earlier specialisation is user-provided, it's
- far from clear that we should auto-specialise further
+argument pattern. Wrinkles
+
+(SC1) We do the already-covered test in specDefn, not when we generate
+ the CallInfo in mkCallUDs. We used to test in the latter place, but
+ we now iterate the specialiser somewhat, and the Id at the call site
+ might therefore not have all the RULES that we can see in specDefn
+
+(SC2) What about two specialisations where the second is an *instance*
+ of the first? It's a bit arbitrary, but here's what we do:
+ * If the existing one is user-specified, via a SPECIALISE pragma, we
+ suppress the further specialisation.
+ * If the existing one is auto-generated, we generate a second RULE
+ for the more specialised version.
+ The latter is important because we don't want the accidental order
+ of calls to determine what specialisations we generate.
+
+(SC3) Annoyingly, we /also/ eliminate duplicates in `filterCalls`.
+ See (MP3) in Note [Specialising polymorphic dictionaries]
Note [Auto-specialisation and RULES]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -2800,12 +2818,10 @@ non-dictionary bindings too.
Note [Specialising polymorphic dictionaries]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-
Note June 2023: This has proved to be quite a tricky optimisation to get right
see (#23469, #23109, #21229, #23445) so it is now guarded by a flag
`-fpolymorphic-specialisation`.
-
Consider
class M a where { foo :: a -> Int }
@@ -2845,11 +2861,26 @@ Here are the moving parts:
function.
(MP3) If we have f :: forall m. Monoid m => blah, and two calls
- (f @(Endo b) (d :: Monoid (Endo b))
- (f @(Endo (c->c)) (d :: Monoid (Endo (c->c)))
+ (f @(Endo b) (d1 :: Monoid (Endo b))
+ (f @(Endo (c->c)) (d2 :: Monoid (Endo (c->c)))
we want to generate a specialisation only for the first. The second
is just a substitution instance of the first, with no greater specialisation.
- Hence the call to `remove_dups` in `filterCalls`.
+ Hence the use of `removeDupCalls` in `filterCalls`.
+
+ You might wonder if `d2` might be more specialised than `d1`; but no.
+ This `removeDupCalls` thing is at the definition site of `f`, and both `d1`
+ and `d2` are in scope. So `d1` is simply more polymorphic than `d2`, but
+ is just as specialised.
+
+ This distinction is sadly lost once we build a RULE, so `alreadyCovered`
+ can't be so clever. E.g if we have an existing RULE
+ forall @a (d1:Ord Int) (d2: Eq a). f @a @Int d1 d2 = ...
+ and a putative new rule
+ forall (d1:Ord Int) (d2: Eq Int). f @Int @Int d1 d2 = ...
+ we /don't/ want the existing rule to subsume the new one.
+
+ So we sadly put up with having two rather different places where we
+ eliminate duplicates: `alreadyCovered` and `removeDupCalls`.
All this arose in #13873, in the unexpected form that a SPECIALISE
pragma made the program slower! The reason was that the specialised
@@ -2947,16 +2978,29 @@ data CallInfoSet = CIS Id (Bag CallInfo)
-- The list of types and dictionaries is guaranteed to
-- match the type of f
-- The Bag may contain duplicate calls (i.e. f @T and another f @T)
- -- These dups are eliminated by already_covered in specCalls
+ -- These dups are eliminated by alreadyCovered in specCalls
data CallInfo
- = CI { ci_key :: [SpecArg] -- All arguments
+ = CI { ci_key :: [SpecArg] -- Arguments of the call
+ -- See Note [The (CI-KEY) invariant]
+
, ci_fvs :: IdSet -- Free Ids of the ci_key call
-- /not/ including the main id itself, of course
-- NB: excluding tyvars:
-- See Note [Specialising polymorphic dictionaries]
}
+{- Note [The (CI-KEY) invariant]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Invariant (CI-KEY):
+ In the `ci_key :: [SpecArg]` field of `CallInfo`,
+ * The list is non-empty
+ * The least element is always a `SpecDict`
+
+In this way the RULE has as few args as possible, which broadens its
+applicability, since rules only fire when saturated.
+-}
+
type DictExpr = CoreExpr
ciSetFilter :: (CallInfo -> Bool) -> CallInfoSet -> CallInfoSet
@@ -3045,10 +3089,7 @@ mkCallUDs' env f args
ci_key :: [SpecArg]
ci_key = dropWhileEndLE (not . isSpecDict) $
zipWith mk_spec_arg args pis
- -- Drop trailing args until we get to a SpecDict
- -- In this way the RULE has as few args as possible,
- -- which broadens its applicability, since rules only
- -- fire when saturated
+ -- Establish (CI-KEY): drop trailing args until we get to a SpecDict
mk_spec_arg :: OutExpr -> PiTyBinder -> SpecArg
mk_spec_arg arg (Named bndr)
@@ -3086,34 +3127,76 @@ site, so we only look through ticks that RULE matching looks through
-}
wantCallsFor :: SpecEnv -> Id -> Bool
-wantCallsFor _env _f = True
- -- We could reduce the size of the UsageDetails by being less eager
- -- about collecting calls for LocalIds: there is no point for
- -- ones that are lambda-bound. We can't decide this by looking at
- -- the (absence of an) unfolding, because unfoldings for local
- -- functions are discarded by cloneBindSM, so no local binder will
- -- have an unfolding at this stage. We'd have to keep a candidate
- -- set of let-binders.
- --
- -- Not many lambda-bound variables have dictionary arguments, so
- -- this would make little difference anyway.
- --
- -- For imported Ids we could check for an unfolding, but we have to
- -- do so anyway in canSpecImport, and it seems better to have it
- -- all in one place. So we simply collect usage info for imported
- -- overloaded functions.
-
-{- Note [Interesting dictionary arguments]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Consider this
- \a.\d:Eq a. let f = ... in ...(f d)...
-There really is not much point in specialising f wrt the dictionary d,
-because the code for the specialised f is not improved at all, because
-d is lambda-bound. We simply get junk specialisations.
-
-What is "interesting"? Just that it has *some* structure. But what about
-variables? We look in the variable's /unfolding/. And that means
-that we must be careful to ensure that dictionaries have unfoldings,
+-- See Note [wantCallsFor]
+wantCallsFor _env f
+ = case idDetails f of
+ RecSelId {} -> False
+ DataConWorkId {} -> False
+ DataConWrapId {} -> False
+ ClassOpId {} -> False
+ PrimOpId {} -> False
+ FCallId {} -> False
+ TickBoxOpId {} -> False
+ CoVarId {} -> False
+
+ DFunId {} -> True
+ VanillaId {} -> True
+ JoinId {} -> True
+ WorkerLikeId {} -> True
+ RepPolyId {} -> True
+
+{- Note [wantCallsFor]
+~~~~~~~~~~~~~~~~~~~~~~
+`wantCallsFor env f` says whether the Specialiser should collect calls for
+function `f`; other thing being equal, the fewer calls we collect the better. It
+is False for things we can't specialise:
+
+* ClassOpId: never inline and we don't have a defn to specialise; we specialise
+ them through fireRewriteRules.
+* PrimOpId: are never overloaded
+* Data constructors: we never specialise them
+
+We could reduce the size of the UsageDetails by being less eager about
+collecting calls for some LocalIds: there is no point for ones that are
+lambda-bound. We can't decide this by looking at the (absence of an) unfolding,
+because unfoldings for local functions are discarded by cloneBindSM, so no local
+binder will have an unfolding at this stage. We'd have to keep a candidate set
+of let-binders.
+
+Not many lambda-bound variables have dictionary arguments, so this would make
+little difference anyway.
+
+For imported Ids we could check for an unfolding, but we have to do so anyway in
+canSpecImport, and it seems better to have it all in one place. So we simply
+collect usage info for imported overloaded functions.
+
+Note [Interesting dictionary arguments]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+In `mkCallUDs` we only use `SpecDict` for dictionaries of which
+`interestingDict` holds. Otherwise we use `UnspecArg`. Two reasons:
+
+* Consider this
+ \a.\d:Eq a. let f = ... in ...(f d)...
+ There really is not much point in specialising f wrt the dictionary d,
+ because the code for the specialised f is not improved at all, because
+ d is lambda-bound. We simply get junk specialisations.
+
+* Consider this (#25703):
+ f :: (Eq a, Show b) => a -> b -> INt
+ goo :: forall x. (Eq x) => x -> blah
+ goo @x (d:Eq x) (arg:x) = ...(f @x @Int d $fShowInt)...
+ If we built a `ci_key` with a (SpecDict d) for `d`, we would end up
+ discarding the call at the `\d`. But if we use `UnspecArg` for that
+ uninteresting `d`, we'll get a `ci_key` of
+ f @x @Int UnspecArg (SpecDict $fShowInt)
+ and /that/ can float out to f's definition and specialise nicely.
+ Hooray. (NB: the call can float only if `-fpolymorphic-specialisation`
+ is on; otherwise it'll be trapped by the `\@x -> ...`.)(
+
+What is "interesting"? (See `interestingDict`.) Just that it has *some*
+structure. But what about variables? We look in the variable's /unfolding/.
+And that means that we must be careful to ensure that dictionaries /have/
+unfoldings,
* cloneBndrSM discards non-Stable unfoldings
* specBind updates the unfolding after specialisation
@@ -3159,7 +3242,7 @@ Now `f` turns into:
meth @a dc ....
When we specialise `f`, at a=Int say, that superclass selection can
-nfire (via rewiteClassOps), but that info (that 'dc' is now a
+fire (via rewiteClassOps), but that info (that 'dc' is now a
particular dictionary `C`, of type `C Int`) must be available to
the call `meth @a dc`, so that we can fire the `meth` class-op, and
thence specialise `wombat`.
@@ -3286,7 +3369,11 @@ dumpUDs :: [CoreBndr] -> UsageDetails -> (UsageDetails, OrdList DictBind)
-- Used at a lambda or case binder; just dump anything mentioning the binder
dumpUDs bndrs uds@(MkUD { ud_binds = orig_dbs, ud_calls = orig_calls })
| null bndrs = (uds, nilOL) -- Common in case alternatives
- | otherwise = -- pprTrace "dumpUDs" (ppr bndrs $$ ppr free_uds $$ ppr dump_dbs) $
+ | otherwise = -- pprTrace "dumpUDs" (vcat
+ -- [ text "bndrs" <+> ppr bndrs
+ -- , text "uds" <+> ppr uds
+ -- , text "free_uds" <+> ppr free_uds
+ -- , text "dump-dbs" <+> ppr dump_dbs ]) $
(free_uds, dump_dbs)
where
free_uds = uds { ud_binds = free_dbs, ud_calls = free_calls }
@@ -3325,20 +3412,17 @@ callsForMe fn uds@MkUD { ud_binds = orig_dbs, ud_calls = orig_calls }
calls_for_me = case lookupDVarEnv orig_calls fn of
Nothing -> []
Just cis -> filterCalls cis orig_dbs
- -- filterCalls: drop calls that (directly or indirectly)
- -- refer to fn. See Note [Avoiding loops (DFuns)]
----------------------
filterCalls :: CallInfoSet -> FloatedDictBinds -> [CallInfo]
--- Remove dominated calls (Note [Specialising polymorphic dictionaries])
--- and loopy DFuns (Note [Avoiding loops (DFuns)])
+-- Remove
+-- (a) dominated calls: (MP3) in Note [Specialising polymorphic dictionaries]
+-- (b) loopy DFuns: Note [Avoiding loops (DFuns)]
filterCalls (CIS fn call_bag) (FDB { fdb_binds = dbs })
- | isDFunId fn -- Note [Avoiding loops (DFuns)] applies only to DFuns
- = filter ok_call de_dupd_calls
- | otherwise -- Do not apply it to non-DFuns
- = de_dupd_calls -- See Note [Avoiding loops (non-DFuns)]
+ | isDFunId fn = filter ok_call de_dupd_calls -- Deals with (b)
+ | otherwise = de_dupd_calls
where
- de_dupd_calls = remove_dups call_bag
+ de_dupd_calls = removeDupCalls call_bag -- Deals with (a)
dump_set = foldl' go (unitVarSet fn) dbs
-- This dump-set could also be computed by splitDictBinds
@@ -3352,10 +3436,10 @@ filterCalls (CIS fn call_bag) (FDB { fdb_binds = dbs })
ok_call (CI { ci_fvs = fvs }) = fvs `disjointVarSet` dump_set
-remove_dups :: Bag CallInfo -> [CallInfo]
+removeDupCalls :: Bag CallInfo -> [CallInfo]
-- Calls involving more generic instances beat more specific ones.
-- See (MP3) in Note [Specialising polymorphic dictionaries]
-remove_dups calls = foldr add [] calls
+removeDupCalls calls = foldr add [] calls
where
add :: CallInfo -> [CallInfo] -> [CallInfo]
add ci [] = [ci]
@@ -3364,12 +3448,20 @@ remove_dups calls = foldr add [] calls
| otherwise = ci2 : add ci1 cis
beats_or_same :: CallInfo -> CallInfo -> Bool
+-- (beats_or_same ci1 ci2) is True if specialising on ci1 subsumes ci2
+-- That is: ci1's types are less specialised than ci2
+-- ci1 specialises on the same dict args as ci2
beats_or_same (CI { ci_key = args1 }) (CI { ci_key = args2 })
= go args1 args2
where
- go [] _ = True
+ go [] [] = True
go (arg1:args1) (arg2:args2) = go_arg arg1 arg2 && go args1 args2
- go (_:_) [] = False
+
+ -- If one or the other runs dry, the other must still have a SpecDict
+ -- because of the (CI-KEY) invariant. So neither subsumes the other;
+ -- one is more specialised (faster code) but the other is more generally
+ -- applicable.
+ go _ _ = False
go_arg (SpecType ty1) (SpecType ty2) = isJust (tcMatchTy ty1 ty2)
go_arg UnspecType UnspecType = True
=====================================
compiler/GHC/Core/Rules.hs
=====================================
@@ -9,7 +9,7 @@
-- The 'CoreRule' datatype itself is declared elsewhere.
module GHC.Core.Rules (
-- ** Looking up rules
- lookupRule, matchExprs,
+ lookupRule, matchExprs, ruleLhsIsMoreSpecific,
-- ** RuleBase, RuleEnv
RuleBase, RuleEnv(..), mkRuleEnv, emptyRuleEnv,
@@ -587,8 +587,8 @@ findBest :: InScopeSet -> (Id, [CoreExpr])
findBest _ _ (rule,ans) [] = (rule,ans)
findBest in_scope target (rule1,ans1) ((rule2,ans2):prs)
- | isMoreSpecific in_scope rule1 rule2 = findBest in_scope target (rule1,ans1) prs
- | isMoreSpecific in_scope rule2 rule1 = findBest in_scope target (rule2,ans2) prs
+ | ruleIsMoreSpecific in_scope rule1 rule2 = findBest in_scope target (rule1,ans1) prs
+ | ruleIsMoreSpecific in_scope rule2 rule1 = findBest in_scope target (rule2,ans2) prs
| debugIsOn = let pp_rule rule
= ifPprDebug (ppr rule)
(doubleQuotes (ftext (ruleName rule)))
@@ -603,15 +603,25 @@ findBest in_scope target (rule1,ans1) ((rule2,ans2):prs)
where
(fn,args) = target
-isMoreSpecific :: InScopeSet -> CoreRule -> CoreRule -> Bool
--- The call (rule1 `isMoreSpecific` rule2)
+ruleIsMoreSpecific :: InScopeSet -> CoreRule -> CoreRule -> Bool
+-- The call (rule1 `ruleIsMoreSpecific` rule2)
-- sees if rule2 can be instantiated to look like rule1
--- See Note [isMoreSpecific]
-isMoreSpecific _ (BuiltinRule {}) _ = False
-isMoreSpecific _ (Rule {}) (BuiltinRule {}) = True
-isMoreSpecific in_scope (Rule { ru_bndrs = bndrs1, ru_args = args1 })
- (Rule { ru_bndrs = bndrs2, ru_args = args2 })
- = isJust (matchExprs in_scope_env bndrs2 args2 args1)
+-- See Note [ruleIsMoreSpecific]
+ruleIsMoreSpecific in_scope rule1 rule2
+ = case rule1 of
+ BuiltinRule {} -> False
+ Rule { ru_bndrs = bndrs1, ru_args = args1 }
+ -> ruleLhsIsMoreSpecific in_scope bndrs1 args1 rule2
+
+ruleLhsIsMoreSpecific :: InScopeSet
+ -> [Var] -> [CoreExpr] -- LHS of a possible new rule
+ -> CoreRule -- An existing rule
+ -> Bool -- New one is more specific
+ruleLhsIsMoreSpecific in_scope bndrs1 args1 rule2
+ = case rule2 of
+ BuiltinRule {} -> True
+ Rule { ru_bndrs = bndrs2, ru_args = args2 }
+ -> isJust (matchExprs in_scope_env bndrs2 args2 args1)
where
full_in_scope = in_scope `extendInScopeSetList` bndrs1
in_scope_env = ISE full_in_scope noUnfoldingFun
@@ -620,9 +630,9 @@ isMoreSpecific in_scope (Rule { ru_bndrs = bndrs1, ru_args = args1 })
noBlackList :: Activation -> Bool
noBlackList _ = False -- Nothing is black listed
-{- Note [isMoreSpecific]
+{- Note [ruleIsMoreSpecific]
~~~~~~~~~~~~~~~~~~~~~~~~
-The call (rule1 `isMoreSpecific` rule2)
+The call (rule1 `ruleIsMoreSpecific` rule2)
sees if rule2 can be instantiated to look like rule1.
Wrinkle:
@@ -825,7 +835,7 @@ bound on the LHS:
The rule looks like
forall (a::*) (d::Eq Char) (x :: Foo a Char).
- f (Foo a Char) d x = True
+ f @(Foo a Char) d x = True
Matching the rule won't bind 'a', and legitimately so. We fudge by
pretending that 'a' is bound to (Any :: *).
=====================================
compiler/GHC/Core/Unify.hs
=====================================
@@ -331,35 +331,57 @@ Wrinkles
`DontBindMe`, the unifier must return `SurelyApart`, not `MaybeApart`. See
`go_fam` in `uVarOrFam`
-(ATF6) You might think that when /matching/ the um_fam_env will always be empty,
- because type-class-instance and type-family-instance heads can't include type
- families. E.g. instance C (F a) where ... -- Illegal
-
- But you'd be wrong: when "improving" type family constraint we may have a
- type family on the LHS of a match. Consider
+(ATF6) When /matching/ can we ever have a type-family application on the LHS, in
+ the template? You might think not, because type-class-instance and
+ type-family-instance heads can't include type families. E.g.
+ instance C (F a) where ... -- Illegal
+
+ But you'd be wrong: even when matching, we can see type families in the LHS template:
+ * In `checkValidClass`, in `check_dm` we check that the default method has the
+ right type, using matching, both ways. And that type may have type-family
+ applications in it. Example in test CoOpt_Singletons.
+
+ * In the specialiser: see the call to `tcMatchTy` in
+ `GHC.Core.Opt.Specialise.beats_or_same`
+
+ * With -fpolymorphic-specialsation, we might get a specialiation rule like
+ RULE forall a (d :: Eq (Maybe (F a))) .
+ f @(Maybe (F a)) d = ...
+ See #25965.
+
+ * A user-written RULE could conceivably have a type-family application
+ in the template. It might not be a good rule, but I don't think we currently
+ check for this.
+
+ In all these cases we are only interested in finding a substitution /for
+ type variables/ that makes the match work. So we simply want to recurse into
+ the arguments of the type family. E.g.
+ Template: forall a. Maybe (F a)
+ Target: Mabybe (F Int)
+ We want to succeed with substitution [a :-> Int]. See (ATF9).
+
+ Conclusion: where we enter via `tcMatchTy`, `tcMatchTys`, `tc_match_tys`,
+ etc, we always end up in `tc_match_tys_x`. There we invoke the unifier
+ but we do not distinguish between `SurelyApart` and `MaybeApart`. So in
+ these cases we can set `um_bind_fam_fun` to `neverBindFam`.
+
+(ATF7) There is one other, very special case of matching where we /do/ want to
+ bind type families in `um_fam_env`, namely in GHC.Tc.Solver.Equality, the call
+ to `tcUnifyTyForInjectivity False` in `improve_injective_wanted_top`.
+ Consider
+ of a match. Consider
type family G6 a = r | r -> a
type instance G6 [a] = [G a]
type instance G6 Bool = Int
- and the Wanted constraint [W] G6 alpha ~ [Int]. We /match/ each type instance
- RHS against [Int]! So we try
- [G a] ~ [Int]
+ and suppose we haev a Wanted constraint
+ [W] G6 alpha ~ [Int]
+. According to Section 5.2 of "Injective type families for Haskell", we /match/
+ the RHS each type instance [Int]. So we try
+ Template: [G a] Target: [Int]
and we want to succeed with MaybeApart, so that we can generate the improvement
- constraint [W] alpha ~ [beta] where beta is fresh.
- See Section 5.2 of "Injective type families for Haskell".
-
- A second place that we match with type-fams on the LHS is in `checkValidClass`.
- In `check_dm` we check that the default method has the right type, using matching,
- both ways. And that type may have type-family applications in it. Example in
- test CoOpt_Singletons.
-
-(ATF7) You might think that (ATF6) is a very special case, and in /other/ uses of
- matching, where we enter via `tc_match_tys_x` we will never see a type-family
- in the template. But actually we do see that case in the specialiser: see
- the call to `tcMatchTy` in `GHC.Core.Opt.Specialise.beats_or_same`
-
- Also: a user-written RULE could conceivably have a type-family application
- in the template. It might not be a good rule, but I don't think we currently
- check for this.
+ constraint
+ [W] alpha ~ [beta]
+ where beta is fresh. We do this by binding [G a :-> Int]
(ATF8) The treatment of type families is governed by
um_bind_fam_fun :: BindFamFun
@@ -399,6 +421,8 @@ Wrinkles
Key point: when decomposing (F tys1 ~ F tys2), we should /also/ extend the
type-family substitution.
+ (ATF11-1) All this cleverness only matters when unifying, not when matching
+
(ATF12) There is a horrid exception for the injectivity check. See (UR1) in
in Note [Specification of unification].
@@ -595,7 +619,7 @@ tc_match_tys_x :: HasDebugCallStack
-> [Type]
-> Maybe Subst
tc_match_tys_x bind_tv match_kis (Subst in_scope id_env tv_env cv_env) tys1 tys2
- = case tc_unify_tys alwaysBindFam -- (ATF7) in Note [Apartness and type families]
+ = case tc_unify_tys neverBindFam -- (ATF7) in Note [Apartness and type families]
bind_tv
False -- Matching, not unifying
False -- Not an injectivity check
@@ -1857,6 +1881,7 @@ uVarOrFam env ty1 ty2 kco
= go_fam_fam tc1 tys1 tys2 kco
-- Now check if we can bind the (F tys) to the RHS
+ -- This can happen even when matching: see (ATF7)
| BindMe <- um_bind_fam_fun env tc1 tys1 rhs
= -- ToDo: do we need an occurs check here?
do { extendFamEnv tc1 tys1 rhs
@@ -1881,11 +1906,6 @@ uVarOrFam env ty1 ty2 kco
-- go_fam_fam: LHS and RHS are both saturated type-family applications,
-- for the same type-family F
go_fam_fam tc tys1 tys2 kco
- | tcEqTyConAppArgs tys1 tys2
- -- Detect (F tys ~ F tys); otherwise we'd build an infinite substitution
- = return ()
-
- | otherwise
-- Decompose (F tys1 ~ F tys2): (ATF9)
-- Use injectivity information of F: (ATF10)
-- But first bind the type-fam if poss: (ATF11)
@@ -1902,13 +1922,19 @@ uVarOrFam env ty1 ty2 kco
(inj_tys1, noninj_tys1) = partitionByList inj tys1
(inj_tys2, noninj_tys2) = partitionByList inj tys2
- bind_fam_if_poss | BindMe <- um_bind_fam_fun env tc tys1 rhs1
- = extendFamEnv tc tys1 rhs1
- | um_unif env
- , BindMe <- um_bind_fam_fun env tc tys2 rhs2
- = extendFamEnv tc tys2 rhs2
- | otherwise
- = return ()
+ bind_fam_if_poss
+ | not (um_unif env) -- Not when matching (ATF11-1)
+ = return ()
+ | tcEqTyConAppArgs tys1 tys2 -- Detect (F tys ~ F tys);
+ = return () -- otherwise we'd build an infinite substitution
+ | BindMe <- um_bind_fam_fun env tc tys1 rhs1
+ = extendFamEnv tc tys1 rhs1
+ | um_unif env
+ , BindMe <- um_bind_fam_fun env tc tys2 rhs2
+ = extendFamEnv tc tys2 rhs2
+ | otherwise
+ = return ()
+
rhs1 = mkTyConApp tc tys2 `mkCastTy` mkSymCo kco
rhs2 = mkTyConApp tc tys1 `mkCastTy` kco
@@ -1993,7 +2019,7 @@ data UMState = UMState
-- in um_foralls; i.e. variables bound by foralls inside the types being unified
-- When /matching/ um_fam_env is usually empty; but not quite always.
- -- See (ATF6) and (ATF7) of Note [Apartness and type families]
+ -- See (ATF7) of Note [Apartness and type families]
newtype UM a
= UM' { unUM :: UMState -> UnifyResultM (UMState, a) }
=====================================
compiler/GHC/Tc/Errors.hs
=====================================
@@ -466,13 +466,12 @@ mkErrorItem ct
= do { let loc = ctLoc ct
flav = ctFlavour ct
- ; (suppress, m_evdest) <- case ctEvidence ct of
- -- For this `suppress` stuff
- -- see Note [Wanteds rewrite Wanteds] in GHC.Tc.Types.Constraint
- CtGiven {} -> return (False, Nothing)
- CtWanted (WantedCt { ctev_rewriters = rewriters, ctev_dest = dest })
- -> do { rewriters' <- zonkRewriterSet rewriters
- ; return (not (isEmptyRewriterSet rewriters'), Just dest) }
+ (suppress, m_evdest) = case ctEvidence ct of
+ -- For this `suppress` stuff
+ -- see Note [Wanteds rewrite Wanteds] in GHC.Tc.Types.Constraint
+ CtGiven {} -> (False, Nothing)
+ CtWanted (WantedCt { ctev_rewriters = rws, ctev_dest = dest })
+ -> (not (isEmptyRewriterSet rws), Just dest)
; let m_reason = case ct of
CIrredCan (IrredCt { ir_reason = reason }) -> Just reason
@@ -503,7 +502,7 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics
, text "tidy_errs =" <+> ppr tidy_errs ])
-- Catch an awkward (and probably rare) case in which /all/ errors are
- -- suppressed: see Wrinkle (WRW2) in Note [Prioritise Wanteds with empty
+ -- suppressed: see Wrinkle (PER2) in Note [Prioritise Wanteds with empty
-- RewriterSet] in GHC.Tc.Types.Constraint.
--
-- Unless we are sure that an error will be reported some other way
@@ -1788,7 +1787,8 @@ mkTyVarEqErr ctxt item casted_tv1 ty2
mkTyVarEqErr' :: SolverReportErrCtxt -> ErrorItem
-> (TcTyVar, TcCoercionN) -> TcType -> TcM TcSolverReportMsg
-mkTyVarEqErr' ctxt item (tv1, co1) ty2
+mkTyVarEqErr' ctxt item (tv1, _co1) ty2
+ -- ToDo: eliminate _co1???
-- Is this a representation-polymorphism error, e.g.
-- alpha[conc] ~# rr[sk] ? If so, handle that first.
@@ -1818,11 +1818,13 @@ mkTyVarEqErr' ctxt item (tv1, co1) ty2
-- to be helpful since this is just an unimplemented feature.
return main_msg
+{-
-- Incompatible kinds
-- This is wrinkle (EIK2) in Note [Equalities with incompatible kinds]
-- in GHC.Tc.Solver.Equality
- | hasCoercionHoleCo co1 || hasCoercionHoleTy ty2
+ | hasHeteroKindCoercionHoleCo co1 || hasHeteroKindCoercionHoleTy ty2
= return $ mkBlockedEqErr item
+-}
| isSkolemTyVar tv1 -- ty2 won't be a meta-tyvar; we would have
-- swapped in Solver.Equality.canEqTyVarHomo
@@ -2007,6 +2009,7 @@ misMatchOrCND ctxt item ty1 ty2
-- Keep only UserGivens that have some equalities.
-- See Note [Suppress redundant givens during error reporting]
+{-
-- These are for the "blocked" equalities, as described in GHC.Tc.Solver.Equality
-- Note [Equalities with incompatible kinds], wrinkle (EIK2). There should
-- always be another unsolved wanted around, which will ordinarily suppress
@@ -2014,6 +2017,7 @@ misMatchOrCND ctxt item ty1 ty2
-- (sigh), so we must produce a message.
mkBlockedEqErr :: ErrorItem -> TcSolverReportMsg
mkBlockedEqErr item = BlockedEquality item
+-}
{-
Note [Suppress redundant givens during error reporting]
=====================================
compiler/GHC/Tc/Solver/Default.hs
=====================================
@@ -1081,9 +1081,9 @@ disambigProposalSequences orig_wanteds wanteds proposalSequences allConsistent
; successes <- fmap catMaybes $
nestImplicTcS fake_ev_binds_var (pushTcLevel tclvl) $
mapM firstSuccess proposalSequences
- ; traceTcS "disambigProposalSequences" (vcat [ ppr wanteds
- , ppr proposalSequences
- , ppr successes ])
+ ; traceTcS "disambigProposalSequences {" (vcat [ ppr wanteds
+ , ppr proposalSequences
+ , ppr successes ])
-- Step (4) in Note [How type-class constraints are defaulted]
; case successes of
success@(tvs, subst) : rest
=====================================
compiler/GHC/Tc/Solver/Equality.hs
=====================================
@@ -1613,54 +1613,59 @@ canEqCanLHSHetero ev eq_rel swapped lhs1 ps_xi1 ki1 xi2 ps_xi2 ki2
-- NotSwapped:
-- ev :: (lhs1:ki1) ~r# (xi2:ki2)
-- kind_co :: k11 ~# ki2 -- Same orientation as ev
--- type_ev :: lhs1 ~r# (xi2 |> sym kind_co)
+-- new_ev :: lhs1 ~r# (xi2 |> sym kind_co)
-- Swapped
-- ev :: (xi2:ki2) ~r# (lhs1:ki1)
-- kind_co :: ki2 ~# ki1 -- Same orientation as ev
--- type_ev :: (xi2 |> kind_co) ~r# lhs1
+-- new_ev :: (xi2 |> kind_co) ~r# lhs1
+-- Note that we need the `sym` when we are /not/ swapped; hence `mk_sym_co`
- = do { (kind_co, rewriters, unifs_happened) <- mk_kind_eq -- :: ki1 ~N ki2
- ; if unifs_happened
- -- Unifications happened, so start again to do the zonking
- -- Otherwise we might put something in the inert set that isn't inert
- then startAgainWith (mkNonCanonical ev)
- else
- do { let lhs_redn = mkReflRedn role ps_xi1
- rhs_redn = mkGReflRightRedn role xi2 mb_sym_kind_co
- mb_sym_kind_co = case swapped of
- NotSwapped -> mkSymCo kind_co
- IsSwapped -> kind_co
-
- ; traceTcS "Hetero equality gives rise to kind equality"
- (ppr swapped $$
- ppr kind_co <+> dcolon <+> sep [ ppr ki1, text "~#", ppr ki2 ])
- ; type_ev <- rewriteEqEvidence rewriters ev swapped lhs_redn rhs_redn
-
- ; let new_xi2 = mkCastTy ps_xi2 mb_sym_kind_co
- ; canEqCanLHSHomo type_ev eq_rel NotSwapped lhs1 ps_xi1 new_xi2 new_xi2 }}
-
- where
- mk_kind_eq :: TcS (CoercionN, RewriterSet, Bool)
- -- Returned kind_co has kind (k1 ~ k2) if NotSwapped, (k2 ~ k1) if Swapped
- -- Returned Bool = True if unifications happened, so we should retry
- mk_kind_eq = case ev of
+ = case ev of
CtGiven (GivenCt { ctev_evar = evar, ctev_loc = loc })
-> do { let kind_co = mkKindCo (mkCoVarCo evar)
pred_ty = unSwap swapped mkNomEqPred ki1 ki2
kind_loc = mkKindEqLoc xi1 xi2 loc
; kind_ev <- newGivenEvVar kind_loc (pred_ty, evCoercion kind_co)
; emitWorkNC [CtGiven kind_ev]
- ; return (givenCtEvCoercion kind_ev, emptyRewriterSet, False) }
+ ; finish emptyRewriterSet (givenCtEvCoercion kind_ev) }
CtWanted {}
- -> do { (kind_co, cts, unifs) <- wrapUnifierTcS ev Nominal $ \uenv ->
- let uenv' = updUEnvLoc uenv (mkKindEqLoc xi1 xi2)
- in unSwap swapped (uType uenv') ki1 ki2
- ; return (kind_co, rewriterSetFromCts cts, not (null unifs)) }
-
+ -> do { (kind_co, cts, unifs) <- wrapUnifierTcS ev Nominal $ \uenv ->
+ let uenv' = updUEnvLoc uenv (mkKindEqLoc xi1 xi2)
+ in unSwap swapped (uType uenv') ki1 ki2
+ ; if not (null unifs)
+ then -- Unifications happened, so start again to do the zonking
+ -- Otherwise we might put something in the inert set that isn't inert
+ startAgainWith (mkNonCanonical ev)
+ else
+
+ assertPpr (not (isEmptyCts cts)) (ppr ev $$ ppr ki1 $$ ppr ki2) $
+ -- The constraints won't be empty because the two kinds differ, and there
+ -- are no unifications, so we must have emitted one or more constraints
+ finish (rewriterSetFromCts cts) kind_co }
+ where
xi1 = canEqLHSType lhs1
role = eqRelRole eq_rel
+ finish rewriters kind_co
+ = do { traceTcS "Hetero equality gives rise to kind equality"
+ (ppr swapped $$
+ ppr kind_co <+> dcolon <+> sep [ ppr ki1, text "~#", ppr ki2 ])
+ ; new_ev <- rewriteEqEvidence rewriters ev swapped lhs_redn rhs_redn
+ ; canEqCanLHSHomo new_ev eq_rel NotSwapped lhs1 ps_xi1 new_xi2 new_xi2 }
+
+ where
+ -- kind_co :: ki1 ~N ki2
+ lhs_redn = mkReflRedn role ps_xi1
+ rhs_redn = mkGReflRightRedn role xi2 sym_kind_co
+ new_xi2 = mkCastTy ps_xi2 sym_kind_co
+
+ -- Apply mkSymCo when /not/ swapped
+ sym_kind_co = case swapped of
+ NotSwapped -> mkSymCo kind_co
+ IsSwapped -> kind_co
+
+
canEqCanLHSHomo :: CtEvidence -- lhs ~ rhs
-- or, if swapped: rhs ~ lhs
-> EqRel -> SwapFlag
@@ -1863,9 +1868,10 @@ canEqCanLHSFinish ev eq_rel swapped lhs rhs
-----------------------
canEqCanLHSFinish_try_unification ev eq_rel swapped lhs rhs
-- Try unification; for Wanted, Nominal equalities with a meta-tyvar on the LHS
- | isWanted ev -- See Note [Do not unify Givens]
- , NomEq <- eq_rel -- See Note [Do not unify representational equalities]
+ | CtWanted wev <- ev -- See Note [Do not unify Givens]
+ , NomEq <- eq_rel -- See Note [Do not unify representational equalities]
, TyVarLHS tv <- lhs
+ , isEmptyRewriterSet (ctev_rewriters wev) -- Only unify if the rewriter set is empty
= do { given_eq_lvl <- getInnermostGivenEqLevel
; if not (touchabilityAndShapeTest given_eq_lvl tv rhs)
then if | Just can_rhs <- canTyFamEqLHS_maybe rhs
@@ -2044,19 +2050,20 @@ What do we do when we have an equality
where k1 and k2 differ? Easy: we create a coercion that relates k1 and
k2 and use this to cast. To wit, from
- [X] (tv :: k1) ~ (rhs :: k2)
+ [X] co1 :: (tv :: k1) ~ (rhs :: k2)
(where [X] is [G] or [W]), we go to
- [X] co :: k1 ~ k2
- [X] (tv :: k1) ~ ((rhs |> sym co) :: k1)
+ co1 = co2 ; sym (GRefl kco)
+ [X] co2 :: (tv :: k1) ~ ((rhs |> sym kco) :: k1)
+ [X] kco :: k1 ~ k2
Wrinkles:
-(EIK1) When X is W, the new type-level wanted is effectively rewritten by the
- kind-level one. We thus include the kind-level wanted in the RewriterSet
- for the type-level one. See Note [Wanteds rewrite Wanteds] in GHC.Tc.Types.Constraint.
- This is done in canEqCanLHSHetero.
+(EIK1) When X=Wanted, the new type-level wanted for `co` is effectively rewritten by
+ the kind-level one. We thus include the kind-level wanted in the RewriterSet
+ for the type-level one. See Note [Wanteds rewrite Wanteds] in
+ GHC.Tc.Types.Constraint. This is done in canEqCanLHSHetero.
(EIK2) Suppose we have [W] (a::Type) ~ (b::Type->Type). The above rewrite will produce
[W] w : a ~ (b |> kw)
@@ -2076,13 +2083,17 @@ Wrinkles:
Instead, it lands in the inert_irreds in the inert set, awaiting solution of
that `kw`.
- (EIK2a) We must later indeed unify if/when the kind-level wanted, `kw` gets
- solved. This is done in kickOutAfterFillingCoercionHole, which kicks out
+ (EIK2a) We must later indeed unify if/when the kind-level wanted, `kw` gets
+ solved. This is done in `kickOutAfterFillingCoercionHole`, which kicks out
all equalities whose RHS mentions the filled-in coercion hole. Note that
it looks for type family equalities, too, because of the use of unifyTest
in canEqTyVarFunEq.
- (EIK2b) What if the RHS mentions /other/ coercion holes? How can that happen? The
+ To do this, we slightly-hackily use the `ctev_rewriters` field of the inert,
+ which records that `w` has been rewritten by `kw`.
+ See (WRW3) in Note [Wanteds rewrite Wanteds] in GHC.Tc.Types.Constraint.
+
+ (EIK2b) What if the RHS mentions /other/ coercion holes? How can that happen? The
main way is like this. Assume F :: forall k. k -> Type
[W] kw : k ~ Type
[W] w : a ~ F k t
@@ -2093,15 +2104,32 @@ Wrinkles:
rewriting. Indeed tests JuanLopez only typechecks if we do. So we'd like to treat
this kind of equality as canonical.
- Hence the ch_hetero_kind field in CoercionHole: it is True of constraints
- created by `canEqCanLHSHetero` to fix up hetero-kinded equalities; and False otherwise:
+ So here is our implementation:
+ * The `ch_hetero_kind` field in CoercionHole identifies a coercion hole created
+ by `canEqCanLHSHetero` to fix up hetero-kinded equalities.
+
+ * An equality constraint is non-canonical if it mentions a /hetero-kind/
+ CoercionHole on the RHS. This (and only this) is the (TyEq:CH) invariant
+ for canonical equalities (see Note [Canonical equalities])
+
+ * The invariant is checked by the `hasHeterKindCoercionHoleCo` test in
+ GHC.Tc.Utils.Unify.checkCo; and not satisfying this invariant is what
+ `cteCoercionHole` in `CheckTyEqResult` means.
- * An equality constraint is non-canonical if it mentions a hetero-kind
- CoercionHole on the RHS. See the `hasCoercionHoleCo` test in GHC.Tc.Utils.checkCo.
+ * These special hetero-kind CoercionHoles are created by the `uType` unifier when
+ the parent's CtOrigin is KindEqOrigin: see GHC.Tc.Utils.TcMType.newCoercionHole
+ and friends.
- * Hetero-kind CoercionHoles are created when the parent's CtOrigin is
- KindEqOrigin: see GHC.Tc.Utils.TcMType.newCoercionHole and friends. We
- set this origin, via `mkKindLoc`, in `mk_kind_eq` in `canEqCanLHSHetero`.
+ We set this origin, via `updUEnvLoc`, in `mk_kind_eq` in `canEqCanLHSHetero`.
+
+ * We /also/ add the coercion hole to the `RewriterSet` of the constraint,
+ in `canEqCanLHSHetero`
+
+ * When filling one of these special hetero-kind coercion holes, we kick out
+ any IrredCt's that mention this hole; maybe it is now canonical.
+ See `kickOutAfterFillingCoercionHole`.
+
+ Gah! This is bizarrely complicated.
(EIK3) Suppose we have [W] (a :: k1) ~ (rhs :: k2). We duly follow the
algorithm detailed here, producing [W] co :: k1 ~ k2, and adding
@@ -2576,17 +2604,17 @@ Suppose we have
Then we can simply solve g2 from g1, thus g2 := g1. Easy!
But it's not so simple:
-* If t is a type variable, the equalties might be oriented differently:
+(CE1) If t is a type variable, the equalties might be oriented differently:
e.g. (g1 :: a~b) and (g2 :: b~a)
So we look both ways round. Hence the SwapFlag result to
inertsCanDischarge.
-* We can only do g2 := g1 if g1 can discharge g2; that depends on
+(CE2) We can only do g2 := g1 if g1 can discharge g2; that depends on
(a) the role and (b) the flavour. E.g. a representational equality
cannot discharge a nominal one; a Wanted cannot discharge a Given.
The predicate is eqCanRewriteFR.
-* Visibility. Suppose S :: forall k. k -> Type, and consider unifying
+(CE3) Visibility. Suppose S :: forall k. k -> Type, and consider unifying
S @Type (a::Type) ~ S @(Type->Type) (b::Type->Type)
From the first argument we get (Type ~ Type->Type); from the second
argument we get (a ~ b) which in turn gives (Type ~ Type->Type).
@@ -2601,6 +2629,24 @@ But it's not so simple:
So when combining two otherwise-identical equalites, we want to
keep the visible one, and discharge the invisible one. Hence the
call to strictly_more_visible.
+
+(CE4) Suppose we have this set up (#25440):
+ Inert: [W] g1: F a ~ a Int (arising from (F a ~ a Int)
+ Work item: [W] g2: F alpha ~ F a (arising from (F alpha ~ F a)
+ We rewrite g2 with g1, to give
+ [W] g2{rw:g1} : F alpha ~ a Int
+ Now if F is injective we can get [W] alpha~a, and hence alpha:=a, and
+ we kick out g1. Now we have two constraints
+ [W] g1 : F a ~ a Int (arising from (F a ~ a Int)
+ [W] g2{rw:g1} : F a ~ a Int (arising from (F alpha ~ F a)
+ If we end up with g2 in the inert set (not g1) we'll get a very confusing
+ error message that we can solve (F a ~ a Int)
+ arising from F a ~ F a
+
+ TL;DR: Better to hang on to `g1` (with no rewriters), in preference
+ to `g2` (which has a rewriter).
+
+ See (WRW1) in Note [Wanteds rewrite Wanteds] in GHC.Tc.Types.Constraint.
-}
tryInertEqs :: EqCt -> SolverStage ()
@@ -2646,21 +2692,27 @@ inertsCanDischarge inerts (EqCt { eq_lhs = lhs_w, eq_rhs = rhs_w
loc_w = ctEvLoc ev_w
flav_w = ctEvFlavour ev_w
fr_w = (flav_w, eq_rel)
+ empty_rw_w = isEmptyRewriterSet (ctEvRewriters ev_w)
inert_beats_wanted ev_i eq_rel
= -- eqCanRewriteFR: see second bullet of Note [Combining equalities]
- -- strictly_more_visible: see last bullet of Note [Combining equalities]
fr_i `eqCanRewriteFR` fr_w
- && not ((loc_w `strictly_more_visible` ctEvLoc ev_i)
- && (fr_w `eqCanRewriteFR` fr_i))
+ && not (prefer_wanted ev_i && (fr_w `eqCanRewriteFR` fr_i))
where
fr_i = (ctEvFlavour ev_i, eq_rel)
- -- See Note [Combining equalities], final bullet
+ -- See (CE3) in Note [Combining equalities]
strictly_more_visible loc1 loc2
= not (isVisibleOrigin (ctLocOrigin loc2)) &&
isVisibleOrigin (ctLocOrigin loc1)
+ prefer_wanted ev_i
+ = (loc_w `strictly_more_visible` ctEvLoc ev_i)
+ -- strictly_more_visible: see (CE3) in Note [Combining equalities]
+ || (empty_rw_w && not (isEmptyRewriterSet (ctEvRewriters ev_i)))
+ -- Prefer the one that has no rewriters
+ -- See (CE4) in Note [Combining equalities]
+
inertsCanDischarge _ _ = Nothing
@@ -3017,6 +3069,7 @@ improve_wanted_top_fun_eqs fam_tc lhs_tys rhs_ty
improve_injective_wanted_top :: FamInstEnvs -> [Bool] -> TyCon -> [TcType] -> Xi -> TcS [TypeEqn]
-- Interact with top-level instance declarations
+-- See Section 5.2 in the Injective Type Families paper
improve_injective_wanted_top fam_envs inj_args fam_tc lhs_tys rhs_ty
= concatMapM do_one branches
where
@@ -3035,6 +3088,7 @@ improve_injective_wanted_top fam_envs inj_args fam_tc lhs_tys rhs_ty
do_one branch@(CoAxBranch { cab_tvs = branch_tvs, cab_lhs = branch_lhs_tys, cab_rhs = branch_rhs })
| let in_scope1 = in_scope `extendInScopeSetList` branch_tvs
, Just subst <- tcUnifyTyForInjectivity False in_scope1 branch_rhs rhs_ty
+ -- False: matching, not unifying
= do { let inSubst tv = tv `elemVarEnv` getTvSubstEnv subst
unsubstTvs = filterOut inSubst branch_tvs
-- The order of unsubstTvs is important; it must be
=====================================
compiler/GHC/Tc/Solver/InertSet.hs
=====================================
@@ -9,9 +9,9 @@ module GHC.Tc.Solver.InertSet (
extendWorkListNonEq, extendWorkListCt,
extendWorkListCts, extendWorkListCtList,
extendWorkListEq, extendWorkListEqs,
+ extendWorkListRewrittenEqs,
appendWorkList, extendWorkListImplic,
workListSize,
- selectWorkItem,
-- * The inert set
InertSet(..),
@@ -172,6 +172,7 @@ See GHC.Tc.Solver.Monad.deferTcSForAllEq
data WorkList
= WL { wl_eqs_N :: [Ct] -- /Nominal/ equalities (s ~#N t), (s ~ t), (s ~~ t)
-- with empty rewriter set
+
, wl_eqs_X :: [Ct] -- CEqCan, CDictCan, CIrredCan
-- with empty rewriter set
-- All other equalities: contains both equality constraints and
@@ -179,9 +180,8 @@ data WorkList
-- See Note [Prioritise equalities]
-- See Note [Prioritise class equalities]
- , wl_rw_eqs :: [Ct] -- Like wl_eqs, but ones that have a non-empty
- -- rewriter set; or, more precisely, did when
- -- added to the WorkList
+ , wl_rw_eqs :: [Ct] -- Like wl_eqs, but ones that may have a non-empty
+ -- rewriter set
-- We prioritise wl_eqs over wl_rw_eqs;
-- see Note [Prioritise Wanteds with empty RewriterSet]
-- in GHC.Tc.Types.Constraint for more details.
@@ -258,6 +258,11 @@ extendWorkListEqs rewriters new_eqs
-- push_on_front puts the new equlities on the front of the queue
push_on_front new_eqs eqs = foldr (:) eqs new_eqs
+extendWorkListRewrittenEqs :: [EqCt] -> WorkList -> WorkList
+-- Don't bother checking the RewriterSet: just pop them into wl_rw_eqs
+extendWorkListRewrittenEqs new_eqs wl@(WL { wl_rw_eqs = rw_eqs })
+ = wl { wl_rw_eqs = foldr ((:) . CEqCan) rw_eqs new_eqs }
+
extendWorkListNonEq :: Ct -> WorkList -> WorkList
-- Extension by non equality
extendWorkListNonEq ct wl = wl { wl_rest = ct : wl_rest wl }
@@ -296,16 +301,6 @@ emptyWorkList :: WorkList
emptyWorkList = WL { wl_eqs_N = [], wl_eqs_X = []
, wl_rw_eqs = [], wl_rest = [], wl_implics = emptyBag }
-selectWorkItem :: WorkList -> Maybe (Ct, WorkList)
--- See Note [Prioritise equalities]
-selectWorkItem wl@(WL { wl_eqs_N = eqs_N, wl_eqs_X = eqs_X
- , wl_rw_eqs = rw_eqs, wl_rest = rest })
- | ct:cts <- eqs_N = Just (ct, wl { wl_eqs_N = cts })
- | ct:cts <- eqs_X = Just (ct, wl { wl_eqs_X = cts })
- | ct:cts <- rw_eqs = Just (ct, wl { wl_rw_eqs = cts })
- | ct:cts <- rest = Just (ct, wl { wl_rest = cts })
- | otherwise = Nothing
-
-- Pretty printing
instance Outputable WorkList where
ppr (WL { wl_eqs_N = eqs_N, wl_eqs_X = eqs_X, wl_rw_eqs = rw_eqs
=====================================
compiler/GHC/Tc/Solver/Monad.hs
=====================================
@@ -150,7 +150,6 @@ import qualified GHC.Tc.Utils.Env as TcM
)
import GHC.Tc.Zonk.Monad ( ZonkM )
import qualified GHC.Tc.Zonk.TcType as TcM
-import qualified GHC.Tc.Zonk.Type as TcM
import GHC.Driver.DynFlags
@@ -475,16 +474,16 @@ kickOutAfterUnification tv_list = case nonEmpty tv_list of
; return n_kicked }
kickOutAfterFillingCoercionHole :: CoercionHole -> TcS ()
--- See Wrinkle (EIK2a) in Note [Equalities with incompatible kinds] in GHC.Tc.Solver.Equality
+-- See Wrinkle (EIK2) in Note [Equalities with incompatible kinds] in GHC.Tc.Solver.Equality
-- It's possible that this could just go ahead and unify, but could there be occurs-check
-- problems? Seems simpler just to kick out.
kickOutAfterFillingCoercionHole hole
= do { ics <- getInertCans
; let (kicked_out, ics') = kick_out ics
- n_kicked = lengthBag kicked_out
+ n_kicked = length kicked_out
; unless (n_kicked == 0) $
- do { updWorkListTcS (extendWorkListCts (fmap CIrredCan kicked_out))
+ do { updWorkListTcS (extendWorkListRewrittenEqs kicked_out)
; csTraceTcS $
hang (text "Kick out, hole =" <+> ppr hole)
2 (vcat [ text "n-kicked =" <+> int n_kicked
@@ -493,24 +492,18 @@ kickOutAfterFillingCoercionHole hole
; setInertCans ics' }
where
- kick_out :: InertCans -> (Bag IrredCt, InertCans)
- kick_out ics@(IC { inert_irreds = irreds })
- = -- We only care about irreds here, because any constraint blocked
- -- by a coercion hole is an irred. See wrinkle (EIK2a) in
- -- Note [Equalities with incompatible kinds] in GHC.Tc.Solver.Canonical
- (irreds_to_kick, ics { inert_irreds = irreds_to_keep })
+ kick_out :: InertCans -> ([EqCt], InertCans)
+ kick_out ics@(IC { inert_eqs = eqs })
+ = (eqs_to_kick, ics { inert_eqs = eqs_to_keep })
where
- (irreds_to_kick, irreds_to_keep) = partitionBag kick_ct irreds
-
- kick_ct :: IrredCt -> Bool
- -- True: kick out; False: keep.
- kick_ct ct
- | IrredCt { ir_ev = ev, ir_reason = reason } <- ct
- , CtWanted (WantedCt { ctev_rewriters = RewriterSet rewriters }) <- ev
- , NonCanonicalReason ctyeq <- reason
- , ctyeq `cterHasProblem` cteCoercionHole
- , hole `elementOfUniqSet` rewriters
- = True
+ (eqs_to_kick, eqs_to_keep) = partitionInertEqs kick_out_eq eqs
+
+ kick_out_eq :: EqCt -> Bool -- True: kick out; False: keep.
+ kick_out_eq (EqCt { eq_ev = ev ,eq_lhs = lhs })
+ | CtWanted (WantedCt { ctev_rewriters = RewriterSet rewriters }) <- ev
+ , TyVarLHS tv <- lhs
+ , isMetaTyVar tv
+ = hole `elementOfUniqSet` rewriters
| otherwise
= False
@@ -847,17 +840,15 @@ removeInertCt is ct
-- | Looks up a family application in the inerts.
lookupFamAppInert :: (CtFlavourRole -> Bool) -- can it rewrite the target?
- -> TyCon -> [Type] -> TcS (Maybe (Reduction, CtFlavourRole))
+ -> TyCon -> [Type] -> TcS (Maybe EqCt)
lookupFamAppInert rewrite_pred fam_tc tys
= do { IS { inert_cans = IC { inert_funeqs = inert_funeqs } } <- getInertSet
; return (lookup_inerts inert_funeqs) }
where
lookup_inerts inert_funeqs
- | Just ecl <- findFunEq inert_funeqs fam_tc tys
- , Just (EqCt { eq_ev = ctev, eq_rhs = rhs })
- <- find (rewrite_pred . eqCtFlavourRole) ecl
- = Just (mkReduction (ctEvCoercion ctev) rhs, ctEvFlavourRole ctev)
- | otherwise = Nothing
+ = case findFunEq inert_funeqs fam_tc tys of
+ Nothing -> Nothing
+ Just (ecl :: [EqCt]) -> find (rewrite_pred . eqCtFlavourRole) ecl
lookupInInerts :: CtLoc -> TcPredType -> TcS (Maybe CtEvidence)
-- Is this exact predicate type cached in the solved or canonicals of the InertSet?
@@ -1418,62 +1409,6 @@ getInertSet = getInertSetRef >>= readTcRef
setInertSet :: InertSet -> TcS ()
setInertSet is = do { r <- getInertSetRef; writeTcRef r is }
-getTcSWorkListRef :: TcS (IORef WorkList)
-getTcSWorkListRef = TcS (return . tcs_worklist)
-
-getWorkListImplics :: TcS (Bag Implication)
-getWorkListImplics
- = do { wl_var <- getTcSWorkListRef
- ; wl_curr <- readTcRef wl_var
- ; return (wl_implics wl_curr) }
-
-pushLevelNoWorkList :: SDoc -> TcS a -> TcS (TcLevel, a)
--- Push the level and run thing_inside
--- However, thing_inside should not generate any work items
-#if defined(DEBUG)
-pushLevelNoWorkList err_doc (TcS thing_inside)
- = TcS (\env -> TcM.pushTcLevelM $
- thing_inside (env { tcs_worklist = wl_panic })
- )
- where
- wl_panic = pprPanic "GHC.Tc.Solver.Monad.buildImplication" err_doc
- -- This panic checks that the thing-inside
- -- does not emit any work-list constraints
-#else
-pushLevelNoWorkList _ (TcS thing_inside)
- = TcS (\env -> TcM.pushTcLevelM (thing_inside env)) -- Don't check
-#endif
-
-updWorkListTcS :: (WorkList -> WorkList) -> TcS ()
-updWorkListTcS f
- = do { wl_var <- getTcSWorkListRef
- ; updTcRef wl_var f }
-
-emitWorkNC :: [CtEvidence] -> TcS ()
-emitWorkNC evs
- | null evs
- = return ()
- | otherwise
- = emitWork (listToBag (map mkNonCanonical evs))
-
-emitWork :: Cts -> TcS ()
-emitWork cts
- | isEmptyBag cts -- Avoid printing, among other work
- = return ()
- | otherwise
- = do { traceTcS "Emitting fresh work" (pprBag cts)
- -- Zonk the rewriter set of Wanteds, because that affects
- -- the prioritisation of the work-list. Suppose a constraint
- -- c1 is rewritten by another, c2. When c2 gets solved,
- -- c1 has no rewriters, and can be prioritised; see
- -- Note [Prioritise Wanteds with empty RewriterSet]
- -- in GHC.Tc.Types.Constraint wrinkle (WRW1)
- ; cts <- wrapTcS $ mapBagM TcM.zonkCtRewriterSet cts
- ; updWorkListTcS (extendWorkListCts cts) }
-
-emitImplication :: Implication -> TcS ()
-emitImplication implic
- = updWorkListTcS (extendWorkListImplic implic)
newTcRef :: a -> TcS (TcRef a)
newTcRef x = wrapTcS (TcM.newTcRef x)
@@ -1532,23 +1467,6 @@ reportUnifications (TcS thing_inside)
getDefaultInfo :: TcS (DefaultEnv, Bool)
getDefaultInfo = wrapTcS TcM.tcGetDefaultTys
-getWorkList :: TcS WorkList
-getWorkList = do { wl_var <- getTcSWorkListRef
- ; wrapTcS (TcM.readTcRef wl_var) }
-
-selectNextWorkItem :: TcS (Maybe Ct)
--- Pick which work item to do next
--- See Note [Prioritise equalities]
-selectNextWorkItem
- = do { wl_var <- getTcSWorkListRef
- ; wl <- readTcRef wl_var
- ; case selectWorkItem wl of {
- Nothing -> return Nothing ;
- Just (ct, new_wl) ->
- do { -- checkReductionDepth (ctLoc ct) (ctPred ct)
- -- This is done by GHC.Tc.Solver.Dict.chooseInstance
- ; writeTcRef wl_var new_wl
- ; return (Just ct) } } }
-- Just get some environments needed for instance looking up and matching
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -1805,6 +1723,116 @@ pprKicked :: Int -> SDoc
pprKicked 0 = empty
pprKicked n = parens (int n <+> text "kicked out")
+
+{- *********************************************************************
+* *
+* The work list
+* *
+********************************************************************* -}
+
+
+getTcSWorkListRef :: TcS (IORef WorkList)
+getTcSWorkListRef = TcS (return . tcs_worklist)
+
+getWorkList :: TcS WorkList
+getWorkList = do { wl_var <- getTcSWorkListRef
+ ; readTcRef wl_var }
+
+getWorkListImplics :: TcS (Bag Implication)
+getWorkListImplics
+ = do { wl_var <- getTcSWorkListRef
+ ; wl_curr <- readTcRef wl_var
+ ; return (wl_implics wl_curr) }
+
+updWorkListTcS :: (WorkList -> WorkList) -> TcS ()
+updWorkListTcS f
+ = do { wl_var <- getTcSWorkListRef
+ ; updTcRef wl_var f }
+
+emitWorkNC :: [CtEvidence] -> TcS ()
+emitWorkNC evs
+ | null evs
+ = return ()
+ | otherwise
+ = emitWork (listToBag (map mkNonCanonical evs))
+
+emitWork :: Cts -> TcS ()
+emitWork cts
+ | isEmptyBag cts -- Avoid printing, among other work
+ = return ()
+ | otherwise
+ = do { traceTcS "Emitting fresh work" (pprBag cts)
+ ; updWorkListTcS (extendWorkListCts cts) }
+
+emitImplication :: Implication -> TcS ()
+emitImplication implic
+ = updWorkListTcS (extendWorkListImplic implic)
+
+selectNextWorkItem :: TcS (Maybe Ct)
+-- Pick which work item to do next
+-- See Note [Prioritise equalities]
+--
+-- Postcondition: if the returned item is a Wanted equality,
+-- then its rewriter set is fully zonked.
+--
+-- Suppose a constraint c1 is rewritten by another, c2. When c2
+-- gets solved, c1 has no rewriters, and can be prioritised; see
+-- Note [Prioritise Wanteds with empty RewriterSet] in
+-- GHC.Tc.Types.Constraint wrinkle (PER1)
+
+-- ToDo: if wl_rw_eqs is long, we'll re-zonk it each time we pick
+-- a new item from wl_rest. Bad.
+selectNextWorkItem
+ = do { wl_var <- getTcSWorkListRef
+ ; wl <- readTcRef wl_var
+
+ ; case wl of { WL { wl_eqs_N = eqs_N, wl_eqs_X = eqs_X
+ , wl_rw_eqs = rw_eqs, wl_rest = rest }
+ | ct:cts <- eqs_N -> pick_me ct (wl { wl_eqs_N = cts })
+ | ct:cts <- eqs_X -> pick_me ct (wl { wl_eqs_X = cts })
+ | otherwise -> try_rws [] rw_eqs
+ where
+ pick_me :: Ct -> WorkList -> TcS (Maybe Ct)
+ pick_me ct new_wl
+ = do { writeTcRef wl_var new_wl
+ ; return (Just ct) }
+ -- NB: no need for checkReductionDepth (ctLoc ct) (ctPred ct)
+ -- This is done by GHC.Tc.Solver.Dict.chooseInstance
+
+ -- try_rws looks through rw_eqs to find one that has an empty
+ -- rewriter set, after zonking. If none such, call try_rest.
+ try_rws acc (ct:cts)
+ = do { ct' <- liftZonkTcS (TcM.zonkCtRewriterSet ct)
+ ; if ctHasNoRewriters ct'
+ then pick_me ct' (wl { wl_rw_eqs = cts ++ acc })
+ else try_rws (ct':acc) cts }
+ try_rws acc [] = try_rest acc
+
+ try_rest zonked_rws
+ | ct:cts <- rest = pick_me ct (wl { wl_rw_eqs = zonked_rws, wl_rest = cts })
+ | ct:cts <- zonked_rws = pick_me ct (wl { wl_rw_eqs = cts })
+ | otherwise = return Nothing
+ } }
+
+
+pushLevelNoWorkList :: SDoc -> TcS a -> TcS (TcLevel, a)
+-- Push the level and run thing_inside
+-- However, thing_inside should not generate any work items
+#if defined(DEBUG)
+pushLevelNoWorkList err_doc (TcS thing_inside)
+ = TcS (\env -> TcM.pushTcLevelM $
+ thing_inside (env { tcs_worklist = wl_panic })
+ )
+ where
+ wl_panic = pprPanic "GHC.Tc.Solver.Monad.buildImplication" err_doc
+ -- This panic checks that the thing-inside
+ -- does not emit any work-list constraints
+#else
+pushLevelNoWorkList _ (TcS thing_inside)
+ = TcS (\env -> TcM.pushTcLevelM (thing_inside env)) -- Don't check
+#endif
+
+
{- *********************************************************************
* *
* The Unification Level Flag *
@@ -2340,7 +2368,7 @@ wrapUnifierX ev role do_unifications
; wrapTcS $
do { defer_ref <- TcM.newTcRef emptyBag
; unified_ref <- TcM.newTcRef []
- ; rewriters <- TcM.zonkRewriterSet (ctEvRewriters ev)
+ ; rewriters <- TcM.liftZonkM (TcM.zonkRewriterSet (ctEvRewriters ev))
; let env = UE { u_role = role
, u_rewriters = rewriters
, u_loc = ctEvLoc ev
=====================================
compiler/GHC/Tc/Solver/Rewrite.hs
=====================================
@@ -150,13 +150,16 @@ bumpDepth (RewriteM thing_inside)
{ let !env' = env { re_loc = bumpCtLocDepth (re_loc env) }
; thing_inside env' }
+recordRewriter :: CtEvidence -> RewriteM ()
+-- Record that we have rewritten the target with this (equality) evidence
-- See Note [Wanteds rewrite Wanteds] in GHC.Tc.Types.Constraint
--- Precondition: the WantedCtEvidence is for an equality constraint
-recordRewriter :: WantedCtEvidence -> RewriteM ()
-recordRewriter (WantedCt { ctev_dest = HoleDest hole })
- = RewriteM $ \env -> updTcRef (re_rewriters env) (`addRewriter` hole)
-recordRewriter other =
- pprPanic "recordRewriter: non-equality constraint" (ppr other)
+-- Precondition: the CtEvidence is for an equality constraint
+recordRewriter (CtGiven {})
+ = return ()
+recordRewriter (CtWanted (WantedCt { ctev_dest = dest }))
+ = case dest of
+ HoleDest hole -> RewriteM $ \env -> updTcRef (re_rewriters env) (`addRewriter` hole)
+ other -> pprPanic "recordRewriter: non-equality constraint" (ppr other)
{- Note [Rewriter EqRels]
~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -848,16 +851,18 @@ rewrite_exact_fam_app tc tys
-- STEP 3: try the inerts
; flavour <- getFlavour
- ; result2 <- liftTcS $ lookupFamAppInert (`eqCanRewriteFR` (flavour, eq_rel)) tc xis
- ; case result2 of
- { Just (redn, (inert_flavour, inert_eq_rel))
+ ; mb_eq <- liftTcS $ lookupFamAppInert (`eqCanRewriteFR` (flavour, eq_rel)) tc xis
+ ; case mb_eq of
+ { Just (EqCt { eq_ev = inert_ev, eq_rhs = inert_rhs, eq_eq_rel = inert_eq_rel })
-> do { traceRewriteM "rewrite family application with inert"
(ppr tc <+> ppr xis $$ ppr redn)
- ; finish (inert_flavour == Given) (homogenise downgraded_redn) }
- -- this will sometimes duplicate an inert in the cache,
+ ; recordRewriter inert_ev
+ ; finish (isGiven inert_ev) (homogenise downgraded_redn) }
+ -- This will sometimes duplicate an inert in the cache,
-- but avoiding doing so had no impact on performance, and
-- it seems easier not to weed out that special case
where
+ redn = mkReduction (ctEvCoercion inert_ev) inert_rhs
inert_role = eqRelRole inert_eq_rel
role = eqRelRole eq_rel
downgraded_redn = downgradeRedn role inert_role redn
@@ -1024,11 +1029,8 @@ rewrite_tyvar2 tv fr@(_, eq_rel)
-> do { traceRewriteM "Following inert tyvar" $
vcat [ ppr tv <+> equals <+> ppr rhs_ty
, ppr ctev ]
- ; case ctev of
- CtGiven {} -> return ()
- CtWanted wtd ->
+ ; recordRewriter ctev
-- See Note [Wanteds rewrite Wanteds] in GHC.Tc.Types.Constraint
- recordRewriter wtd
; let rewriting_co1 = ctEvCoercion ctev
rewriting_co = case (ct_eq_rel, eq_rel) of
=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -17,7 +17,7 @@ module GHC.Tc.Types.Constraint (
isUnsatisfiableCt_maybe,
ctEvidence, updCtEvidence,
ctLoc, ctPred, ctFlavour, ctEqRel, ctOrigin,
- ctRewriters,
+ ctRewriters, ctHasNoRewriters,
ctEvId, wantedEvId_maybe, mkTcEqPredLikeEv,
mkNonCanonical, mkGivens,
tyCoVarsOfCt, tyCoVarsOfCts,
@@ -240,18 +240,24 @@ instance Outputable DictCt where
{- Note [Canonical equalities]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
An EqCt is a canonical equality constraint, one that can live in the inert set,
-and that can be used to rewrite other constrtaints. It satisfies these invariants:
+and that can be used to rewrite other constraints. It satisfies these invariants:
+
* (TyEq:OC) lhs does not occur in rhs (occurs check)
Note [EqCt occurs check]
+
* (TyEq:F) rhs has no foralls
(this avoids substituting a forall for the tyvar in other types)
+
* (TyEq:K) typeKind lhs `tcEqKind` typeKind rhs; Note [Ct kind invariant]
+
* (TyEq:N) If the equality is representational, rhs is not headed by a saturated
application of a newtype TyCon. See GHC.Tc.Solver.Equality
Note [No top-level newtypes on RHS of representational equalities].
(Applies only when constructor of newtype is in scope.)
+
* (TyEq:U) An EqCt is not immediately unifiable. If we can unify a:=ty, we
will not form an EqCt (a ~ ty).
+
* (TyEq:CH) rhs does not mention any coercion holes that resulted from fixing up
a hetero-kinded equality. See Note [Equalities with incompatible kinds] in
GHC.Tc.Solver.Equality, wrinkle (EIK2)
@@ -534,9 +540,12 @@ cteSolubleOccurs = CTEP (bit 3) -- Occurs-check under a type function, or in
-- cteSolubleOccurs must be one bit to the left of cteInsolubleOccurs
-- See also Note [Insoluble mis-match] in GHC.Tc.Errors
-cteCoercionHole = CTEP (bit 4) -- Coercion hole encountered
+cteCoercionHole = CTEP (bit 4) -- Kind-equality coercion hole encountered
+ -- See (EIK2) in Note [Equalities with incompatible kinds]
+
cteConcrete = CTEP (bit 5) -- Type variable that can't be made concrete
-- e.g. alpha[conc] ~ Maybe beta[tv]
+
cteSkolemEscape = CTEP (bit 6) -- Skolem escape e.g. alpha[2] ~ b[sk,4]
cteProblem :: CheckTyEqProblem -> CheckTyEqResult
@@ -2220,6 +2229,12 @@ ctEvRewriters :: CtEvidence -> RewriterSet
ctEvRewriters (CtWanted (WantedCt { ctev_rewriters = rws })) = rws
ctEvRewriters (CtGiven {}) = emptyRewriterSet
+ctHasNoRewriters :: Ct -> Bool
+ctHasNoRewriters ct
+ = case ctEvidence ct of
+ CtWanted (WantedCt { ctev_rewriters = rws }) -> isEmptyRewriterSet rws
+ CtGiven {} -> True
+
-- | Set the rewriter set of a Wanted constraint.
setWantedCtEvRewriters :: WantedCtEvidence -> RewriterSet -> WantedCtEvidence
setWantedCtEvRewriters ev rs = ev { ctev_rewriters = rs }
@@ -2444,19 +2459,29 @@ We thus want Wanteds to rewrite Wanteds in order to accept more programs,
but we don't want Wanteds to rewrite Wanteds because doing so can create
inscrutable error messages. To solve this dilemma:
-* We allow Wanteds to rewrite Wanteds, but...
+* We allow Wanteds to rewrite Wanteds, but each Wanted tracks the set of Wanteds
+ it has been rewritten by, in its RewriterSet, stored in the ctev_rewriters
+ field of the CtWanted constructor of CtEvidence. (Only Wanteds have
+ RewriterSets.)
+
+* A RewriterSet is just a set of unfilled CoercionHoles. This is sufficient
+ because only equalities (evidenced by coercion holes) are used for rewriting;
+ other (dictionary) constraints cannot ever rewrite.
+
+* The rewriter (in e.g. GHC.Tc.Solver.Rewrite.rewrite) tracks and returns a RewriterSet,
+ consisting of the evidence (a CoercionHole) for any Wanted equalities used in
+ rewriting.
-* Each Wanted tracks the set of Wanteds it has been rewritten by, in its
- RewriterSet, stored in the ctev_rewriters field of the CtWanted
- constructor of CtEvidence. (Only Wanteds have RewriterSets.)
+* Then GHC.Tc.Solver.Solve.rewriteEvidence and GHC.Tc.Solver.Equality.rewriteEqEvidence
+ add this RewriterSet to the rewritten constraint's rewriter set.
* In error reporting, we simply suppress any errors that have been rewritten
by /unsolved/ wanteds. This suppression happens in GHC.Tc.Errors.mkErrorItem,
- which uses GHC.Tc.Zonk.Type.zonkRewriterSet to look through any filled
+ which uses `GHC.Tc.Zonk.Type.zonkRewriterSet` to look through any filled
coercion holes. The idea is that we wish to report the "root cause" -- the
error that rewrote all the others.
-* We prioritise Wanteds that have an empty RewriterSet:
+* In error reporting, we prioritise Wanteds that have an empty RewriterSet:
see Note [Prioritise Wanteds with empty RewriterSet].
Let's continue our first example above:
@@ -2471,19 +2496,30 @@ Because Wanteds can rewrite Wanteds, w1 will rewrite w2, yielding
The {w1} in the second line of output is the RewriterSet of w1.
-A RewriterSet is just a set of unfilled CoercionHoles. This is sufficient
-because only equalities (evidenced by coercion holes) are used for rewriting;
-other (dictionary) constraints cannot ever rewrite. The rewriter (in
-e.g. GHC.Tc.Solver.Rewrite.rewrite) tracks and returns a RewriterSet,
-consisting of the evidence (a CoercionHole) for any Wanted equalities used in
-rewriting. Then GHC.Tc.Solver.Solve.rewriteEvidence and
-GHC.Tc.Solver.Equality.rewriteEqEvidence add this RewriterSet to the rewritten
-constraint's rewriter set.
+Wrinkles:
+
+(WRW1) When we find a constraint identical to one already in the inert set,
+ we solve one from the other. Other things being equal, keep the one
+ that has fewer (better still no) rewriters.
+ See (CE4) in Note [Combining equalities] in GHC.Tc.Solver.Equality.
+
+ To this accurately we should use `zonkRewriterSet` during canonicalisation,
+ to eliminate rewriters that have now been solved. Currently we only do so
+ during error reporting; but perhaps we should change that.
+
+(WRW2) When zonking a constraint (with `zonkCt` and `zonkCtEvidence`) we take
+ the opportunity to zonk its `RewriterSet`, which eliminates solved ones.
+ This doesn't guarantee that rewriter sets are always up to date -- see
+ (WRW1) -- but it helps, and it de-clutters debug output.
+
+(WRW3) We use the rewriter set for a slightly different purpose, in (EIK2)
+ of Note [Equalities with incompatible kinds] in GHC.Tc.Solver.Equality.
+ This is a bit of a hack.
Note [Prioritise Wanteds with empty RewriterSet]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
When extending the WorkList, in GHC.Tc.Solver.InertSet.extendWorkListEq,
-we priorities constraints that have no rewriters. Here's why.
+we prioritise constraints that have no rewriters. Here's why.
Consider this, which came up in T22793:
inert: {}
@@ -2527,11 +2563,11 @@ GHC.Tc.Solver.InertSet.extendWorkListEq, and extendWorkListEqs.
Wrinkles
-(WRW1) Before checking for an empty RewriterSet, we zonk the RewriterSet,
+(PER1) Before checking for an empty RewriterSet, we zonk the RewriterSet,
because some of those CoercionHoles may have been filled in since we last
looked: see GHC.Tc.Solver.Monad.emitWork.
-(WRW2) Despite the prioritisation, it is hard to be /certain/ that we can't end up
+(PER2) Despite the prioritisation, it is hard to be /certain/ that we can't end up
in a situation where all of the Wanteds have rewritten each other. In
order to report /some/ error in this case, we simply report all the
Wanteds. The user will get a perhaps-confusing error message, but they've
=====================================
compiler/GHC/Tc/Utils/TcMType.hs
=====================================
@@ -49,7 +49,6 @@ module GHC.Tc.Utils.TcMType (
newCoercionHole, newCoercionHoleO, newVanillaCoercionHole,
fillCoercionHole, isFilledCoercionHole,
- unpackCoercionHole, unpackCoercionHole_maybe,
checkCoercionHole,
newImplication,
@@ -115,7 +114,6 @@ import GHC.Tc.Types.CtLoc( CtLoc, ctLocOrigin )
import GHC.Tc.Utils.Monad -- TcType, amongst others
import GHC.Tc.Utils.TcType
import GHC.Tc.Errors.Types
-import GHC.Tc.Zonk.Type
import GHC.Tc.Zonk.TcType
import GHC.Builtin.Names
@@ -371,6 +369,7 @@ newCoercionHoleO (KindEqOrigin {}) pty = new_coercion_hole True pty
newCoercionHoleO _ pty = new_coercion_hole False pty
new_coercion_hole :: Bool -> TcPredType -> TcM CoercionHole
+-- For the Bool, see (EIK2) in Note [Equalities with incompatible kinds]
new_coercion_hole hetero_kind pred_ty
= do { co_var <- newEvVar pred_ty
; traceTc "New coercion hole:" (ppr co_var <+> dcolon <+> ppr pred_ty)
@@ -1583,7 +1582,7 @@ collect_cand_qtvs_co orig_ty cur_lvl bound = go_co
go_co dv (SubCo co) = go_co dv co
go_co dv (HoleCo hole)
- = do m_co <- unpackCoercionHole_maybe hole
+ = do m_co <- liftZonkM (unpackCoercionHole_maybe hole)
case m_co of
Just co -> go_co dv co
Nothing -> go_cv dv (coHoleCoVar hole)
=====================================
compiler/GHC/Tc/Utils/Unify.hs
=====================================
@@ -2649,8 +2649,9 @@ There are five reasons not to unify:
we can fill beta[tau] := beta[conc]. This is why we call
'makeTypeConcrete' in startSolvingByUnification.
-5. (COERCION-HOLE) Confusing coercion holes
- Suppose our equality is
+5. (COERCION-HOLE) rhs does not mention any coercion holes that resulted from
+ fixing up a hetero-kinded equality. This is the same as (TyEq:CH) in
+ Note [Canonical equalities]. Suppose our equality is
(alpha :: k) ~ (Int |> {co})
where co :: Type ~ k is an unsolved wanted. Note that this equality
is homogeneous; both sides have kind k. We refrain from unifying here, because
@@ -3546,11 +3547,13 @@ checkCo flags co =
| case conc of { CC_None -> False; _ -> True }
-> return $ PuFail (cteProblem cteConcrete)
+{- Trying NOT doing this -- #
-- Check for coercion holes, if unifying.
-- See (COERCION-HOLE) in Note [Unification preconditions]
| case lc of { LC_None {} -> False; _ -> True } -- equivalent to "we are unifying"; see Note [TyEqFlags]
- , hasCoercionHoleCo co
+ , hasHeteroKindCoercionHoleCo co
-> return $ PuFail (cteProblem cteCoercionHole)
+-}
-- Occurs check (can promote)
| OC_Check lhs_tv occ_prob <- occ
=====================================
compiler/GHC/Tc/Zonk/TcType.hs
=====================================
@@ -1,3 +1,5 @@
+{-# LANGUAGE DuplicateRecordFields #-}
+
{-
(c) The University of Glasgow 2006
(c) The AQUA Project, Glasgow University, 1996-1998
@@ -36,6 +38,13 @@ module GHC.Tc.Zonk.TcType
-- ** Zonking constraints
, zonkCt, zonkWC, zonkSimples, zonkImplication
+ -- * Rewriter sets
+ , zonkRewriterSet, zonkCtRewriterSet, zonkCtEvRewriterSet
+
+ -- * Coercion holes
+ , isFilledCoercionHole, unpackCoercionHole, unpackCoercionHole_maybe
+
+
-- * Tidying
, tcInitTidyEnv, tcInitOpenTidyEnv
, tidyCt, tidyEvVar, tidyDelayedError
@@ -81,7 +90,7 @@ import GHC.Core.Coercion
import GHC.Core.Predicate
import GHC.Utils.Constants
-import GHC.Utils.Outputable
+import GHC.Utils.Outputable as Outputable
import GHC.Utils.Misc
import GHC.Utils.Monad ( mapAccumLM )
import GHC.Utils.Panic
@@ -89,6 +98,9 @@ import GHC.Utils.Panic
import GHC.Data.Bag
import GHC.Data.Pair
+import Data.Semigroup
+import Data.Maybe
+
{- *********************************************************************
* *
Writing to metavariables
@@ -366,8 +378,8 @@ checkCoercionHole cv co
; return $
assertPpr (ok cv_ty)
(text "Bad coercion hole" <+>
- ppr cv <> colon <+> vcat [ ppr t1, ppr t2, ppr role
- , ppr cv_ty ])
+ ppr cv Outputable.<> colon
+ <+> vcat [ ppr t1, ppr t2, ppr role, ppr cv_ty ])
co }
| otherwise
= return co
@@ -494,9 +506,15 @@ zonkCt ct
; return (mkNonCanonical fl') }
zonkCtEvidence :: CtEvidence -> ZonkM CtEvidence
-zonkCtEvidence ctev
- = do { pred' <- zonkTcType (ctEvPred ctev)
- ; return (setCtEvPredType ctev pred') }
+-- Zonks the ctev_pred and the ctev_rewriters; but not ctev_evar
+-- For ctev_rewriters, see (WRW2) in Note [Wanteds rewrite Wanteds]
+zonkCtEvidence (CtGiven (GivenCt { ctev_pred = pred, ctev_evar = var, ctev_loc = loc }))
+ = do { pred' <- zonkTcType pred
+ ; return (CtGiven (GivenCt { ctev_pred = pred', ctev_evar = var, ctev_loc = loc })) }
+zonkCtEvidence (CtWanted wanted@(WantedCt { ctev_pred = pred, ctev_rewriters = rws }))
+ = do { pred' <- zonkTcType pred
+ ; rws' <- zonkRewriterSet rws
+ ; return (CtWanted (wanted { ctev_pred = pred', ctev_rewriters = rws' })) }
zonkSkolemInfo :: SkolemInfo -> ZonkM SkolemInfo
zonkSkolemInfo (SkolemInfo u sk) = SkolemInfo u <$> zonkSkolemInfoAnon sk
@@ -530,6 +548,103 @@ win.
But c.f Note [Sharing when zonking to Type] in GHC.Tc.Zonk.Type.
+%************************************************************************
+%* *
+ Zonking rewriter sets
+* *
+************************************************************************
+-}
+
+zonkCtRewriterSet :: Ct -> ZonkM Ct
+zonkCtRewriterSet ct
+ | isGivenCt ct
+ = return ct
+ | otherwise
+ = case ct of
+ CEqCan eq@(EqCt { eq_ev = ev }) -> do { ev' <- zonkCtEvRewriterSet ev
+ ; return (CEqCan (eq { eq_ev = ev' })) }
+ CIrredCan ir@(IrredCt { ir_ev = ev }) -> do { ev' <- zonkCtEvRewriterSet ev
+ ; return (CIrredCan (ir { ir_ev = ev' })) }
+ CDictCan di@(DictCt { di_ev = ev }) -> do { ev' <- zonkCtEvRewriterSet ev
+ ; return (CDictCan (di { di_ev = ev' })) }
+ CQuantCan {} -> return ct
+ CNonCanonical ev -> do { ev' <- zonkCtEvRewriterSet ev
+ ; return (CNonCanonical ev') }
+
+zonkCtEvRewriterSet :: CtEvidence -> ZonkM CtEvidence
+zonkCtEvRewriterSet ev@(CtGiven {})
+ = return ev
+zonkCtEvRewriterSet ev@(CtWanted wtd)
+ = do { rewriters' <- zonkRewriterSet (ctEvRewriters ev)
+ ; return (CtWanted $ setWantedCtEvRewriters wtd rewriters') }
+
+-- | Zonk a rewriter set; if a coercion hole in the set has been filled,
+-- find all the free un-filled coercion holes in the coercion that fills it
+zonkRewriterSet :: RewriterSet -> ZonkM RewriterSet
+zonkRewriterSet (RewriterSet set)
+ = nonDetStrictFoldUniqSet go (return emptyRewriterSet) set
+ -- This does not introduce non-determinism, because the only
+ -- monadic action is to read, and the combining function is
+ -- commutative
+ where
+ go :: CoercionHole -> ZonkM RewriterSet -> ZonkM RewriterSet
+ go hole m_acc = unionRewriterSet <$> check_hole hole <*> m_acc
+
+ check_hole :: CoercionHole -> ZonkM RewriterSet
+ check_hole hole
+ = do { m_co <- unpackCoercionHole_maybe hole
+ ; case m_co of
+ Nothing -> return (unitRewriterSet hole) -- Not filled
+ Just co -> unUCHM (check_co co) } -- Filled: look inside
+
+ check_ty :: Type -> UnfilledCoercionHoleMonoid
+ check_co :: Coercion -> UnfilledCoercionHoleMonoid
+ (check_ty, _, check_co, _) = foldTyCo folder ()
+
+ folder :: TyCoFolder () UnfilledCoercionHoleMonoid
+ folder = TyCoFolder { tcf_view = noView
+ , tcf_tyvar = \ _ tv -> check_ty (tyVarKind tv)
+ , tcf_covar = \ _ cv -> check_ty (varType cv)
+ , tcf_hole = \ _ -> UCHM . check_hole
+ , tcf_tycobinder = \ _ _ _ -> () }
+
+newtype UnfilledCoercionHoleMonoid = UCHM { unUCHM :: ZonkM RewriterSet }
+
+instance Semigroup UnfilledCoercionHoleMonoid where
+ UCHM l <> UCHM r = UCHM (unionRewriterSet <$> l <*> r)
+
+instance Monoid UnfilledCoercionHoleMonoid where
+ mempty = UCHM (return emptyRewriterSet)
+
+
+{-
+************************************************************************
+* *
+ Checking for coercion holes
+* *
+************************************************************************
+-}
+
+-- | Is a coercion hole filled in?
+isFilledCoercionHole :: CoercionHole -> ZonkM Bool
+isFilledCoercionHole (CoercionHole { ch_ref = ref })
+ = isJust <$> readTcRef ref
+
+-- | Retrieve the contents of a coercion hole. Panics if the hole
+-- is unfilled
+unpackCoercionHole :: CoercionHole -> ZonkM Coercion
+unpackCoercionHole hole
+ = do { contents <- unpackCoercionHole_maybe hole
+ ; case contents of
+ Just co -> return co
+ Nothing -> pprPanic "Unfilled coercion hole" (ppr hole) }
+
+-- | Retrieve the contents of a coercion hole, if it is filled
+unpackCoercionHole_maybe :: CoercionHole -> ZonkM (Maybe Coercion)
+unpackCoercionHole_maybe (CoercionHole { ch_ref = ref }) = readTcRef ref
+
+
+{-
%************************************************************************
%* *
Tidying
=====================================
compiler/GHC/Tc/Zonk/Type.hs
=====================================
@@ -28,12 +28,6 @@ module GHC.Tc.Zonk.Type (
-- ** 'ZonkEnv', and the 'ZonkT' and 'ZonkBndrT' monad transformers
module GHC.Tc.Zonk.Env,
- -- * Coercion holes
- isFilledCoercionHole, unpackCoercionHole, unpackCoercionHole_maybe,
-
- -- * Rewriter sets
- zonkRewriterSet, zonkCtRewriterSet, zonkCtEvRewriterSet,
-
-- * Tidying
tcInitTidyEnv, tcInitOpenTidyEnv,
@@ -55,7 +49,6 @@ import GHC.Tc.TyCl.Build ( TcMethInfo, MethInfo )
import GHC.Tc.Utils.Env ( tcLookupGlobalOnly )
import GHC.Tc.Utils.TcType
import GHC.Tc.Utils.Monad ( newZonkAnyType, setSrcSpanA, liftZonkM, traceTc, addErr )
-import GHC.Tc.Types.Constraint
import GHC.Tc.Types.Evidence
import GHC.Tc.Errors.Types
import GHC.Tc.Zonk.Env
@@ -88,7 +81,6 @@ import GHC.Types.Id
import GHC.Types.TypeEnv
import GHC.Types.Basic
import GHC.Types.SrcLoc
-import GHC.Types.Unique.Set
import GHC.Types.Unique.FM
import GHC.Types.TyThing
@@ -99,7 +91,6 @@ import GHC.Data.Bag
import Control.Monad
import Control.Monad.Trans.Class ( lift )
-import Data.Semigroup
import Data.List.NonEmpty ( NonEmpty )
import Data.Foldable ( toList )
@@ -1956,89 +1947,3 @@ finding the free type vars of an expression is necessarily monadic
operation. (consider /\a -> f @ b, where b is side-effected to a)
-}
-{-
-************************************************************************
-* *
- Checking for coercion holes
-* *
-************************************************************************
--}
-
--- | Is a coercion hole filled in?
-isFilledCoercionHole :: CoercionHole -> TcM Bool
-isFilledCoercionHole (CoercionHole { ch_ref = ref })
- = isJust <$> readTcRef ref
-
--- | Retrieve the contents of a coercion hole. Panics if the hole
--- is unfilled
-unpackCoercionHole :: CoercionHole -> TcM Coercion
-unpackCoercionHole hole
- = do { contents <- unpackCoercionHole_maybe hole
- ; case contents of
- Just co -> return co
- Nothing -> pprPanic "Unfilled coercion hole" (ppr hole) }
-
--- | Retrieve the contents of a coercion hole, if it is filled
-unpackCoercionHole_maybe :: CoercionHole -> TcM (Maybe Coercion)
-unpackCoercionHole_maybe (CoercionHole { ch_ref = ref }) = readTcRef ref
-
-zonkCtRewriterSet :: Ct -> TcM Ct
-zonkCtRewriterSet ct
- | isGivenCt ct
- = return ct
- | otherwise
- = case ct of
- CEqCan eq@(EqCt { eq_ev = ev }) -> do { ev' <- zonkCtEvRewriterSet ev
- ; return (CEqCan (eq { eq_ev = ev' })) }
- CIrredCan ir@(IrredCt { ir_ev = ev }) -> do { ev' <- zonkCtEvRewriterSet ev
- ; return (CIrredCan (ir { ir_ev = ev' })) }
- CDictCan di@(DictCt { di_ev = ev }) -> do { ev' <- zonkCtEvRewriterSet ev
- ; return (CDictCan (di { di_ev = ev' })) }
- CQuantCan {} -> return ct
- CNonCanonical ev -> do { ev' <- zonkCtEvRewriterSet ev
- ; return (CNonCanonical ev') }
-
-zonkCtEvRewriterSet :: CtEvidence -> TcM CtEvidence
-zonkCtEvRewriterSet ev@(CtGiven {})
- = return ev
-zonkCtEvRewriterSet ev@(CtWanted wtd)
- = do { rewriters' <- zonkRewriterSet (ctEvRewriters ev)
- ; return (CtWanted $ setWantedCtEvRewriters wtd rewriters') }
-
--- | Check whether any coercion hole in a RewriterSet is still unsolved.
--- Does this by recursively looking through filled coercion holes until
--- one is found that is not yet filled in, at which point this aborts.
-zonkRewriterSet :: RewriterSet -> TcM RewriterSet
-zonkRewriterSet (RewriterSet set)
- = nonDetStrictFoldUniqSet go (return emptyRewriterSet) set
- -- this does not introduce non-determinism, because the only
- -- monadic action is to read, and the combining function is
- -- commutative
- where
- go :: CoercionHole -> TcM RewriterSet -> TcM RewriterSet
- go hole m_acc = unionRewriterSet <$> check_hole hole <*> m_acc
-
- check_hole :: CoercionHole -> TcM RewriterSet
- check_hole hole = do { m_co <- unpackCoercionHole_maybe hole
- ; case m_co of
- Nothing -> return (unitRewriterSet hole)
- Just co -> unUCHM (check_co co) }
-
- check_ty :: Type -> UnfilledCoercionHoleMonoid
- check_co :: Coercion -> UnfilledCoercionHoleMonoid
- (check_ty, _, check_co, _) = foldTyCo folder ()
-
- folder :: TyCoFolder () UnfilledCoercionHoleMonoid
- folder = TyCoFolder { tcf_view = noView
- , tcf_tyvar = \ _ tv -> check_ty (tyVarKind tv)
- , tcf_covar = \ _ cv -> check_ty (varType cv)
- , tcf_hole = \ _ -> UCHM . check_hole
- , tcf_tycobinder = \ _ _ _ -> () }
-
-newtype UnfilledCoercionHoleMonoid = UCHM { unUCHM :: TcM RewriterSet }
-
-instance Semigroup UnfilledCoercionHoleMonoid where
- UCHM l <> UCHM r = UCHM (unionRewriterSet <$> l <*> r)
-
-instance Monoid UnfilledCoercionHoleMonoid where
- mempty = UCHM (return emptyRewriterSet)
=====================================
compiler/GHC/Types/Basic.hs
=====================================
@@ -87,7 +87,7 @@ module GHC.Types.Basic (
CompilerPhase(..), PhaseNum, beginPhase, nextPhase, laterPhase,
Activation(..), isActive, competesWith,
- isNeverActive, isAlwaysActive, activeInFinalPhase,
+ isNeverActive, isAlwaysActive, activeInFinalPhase, activeInInitialPhase,
activateAfterInitial, activateDuringFinal, activeAfter,
RuleMatchInfo(..), isConLike, isFunLike,
=====================================
testsuite/tests/indexed-types/should_fail/T3330c.stderr
=====================================
@@ -1,16 +1,24 @@
-
-T3330c.hs:25:43: error: [GHC-18872]
- • Couldn't match kind ‘* -> *’ with ‘*’
- When matching types
- f1 :: * -> *
- f1 x :: *
- Expected: Der ((->) x) (Der f1 x)
- Actual: R f1
- • In the first argument of ‘plug’, namely ‘rf’
+T3330c.hs:25:38: error: [GHC-25897]
+ • Could not deduce ‘Der f1 ~ f1’
+ from the context: f ~ (f1 :+: g)
+ bound by a pattern with constructor:
+ RSum :: forall (f :: * -> *) (g :: * -> *).
+ R f -> R g -> R (f :+: g),
+ in an equation for ‘plug'’
+ at T3330c.hs:25:8-17
+ Expected: x -> f1 x
+ Actual: x -> Der f1 x
+ ‘f1’ is a rigid type variable bound by
+ a pattern with constructor:
+ RSum :: forall (f :: * -> *) (g :: * -> *).
+ R f -> R g -> R (f :+: g),
+ in an equation for ‘plug'’
+ at T3330c.hs:25:8-17
+ • The function ‘plug’ is applied to three visible arguments,
+ but its type ‘Rep f => Der f x -> x -> f x’ has only two
In the first argument of ‘Inl’, namely ‘(plug rf df x)’
In the expression: Inl (plug rf df x)
• Relevant bindings include
- x :: x (bound at T3330c.hs:25:29)
df :: Der f1 x (bound at T3330c.hs:25:25)
rf :: R f1 (bound at T3330c.hs:25:13)
- plug' :: R f -> Der f x -> x -> f x (bound at T3330c.hs:25:1)
+
=====================================
testsuite/tests/indexed-types/should_fail/T4174.stderr
=====================================
@@ -1,6 +1,16 @@
-
-T4174.hs:45:12: error: [GHC-18872]
- • Couldn't match type ‘False’ with ‘True’
- arising from a use of ‘sync_large_objects’
+T4174.hs:45:12: error: [GHC-25897]
+ • Couldn't match type ‘a’ with ‘SmStep’
+ Expected: m (Field (Way (GHC6'8 minor) n t p) a b)
+ Actual: m (Field (WayOf m) SmStep RtsSpinLock)
+ ‘a’ is a rigid type variable bound by
+ the type signature for:
+ testcase :: forall (m :: * -> *) minor n t p a b.
+ Monad m =>
+ m (Field (Way (GHC6'8 minor) n t p) a b)
+ at T4174.hs:44:1-63
• In the expression: sync_large_objects
In an equation for ‘testcase’: testcase = sync_large_objects
+ • Relevant bindings include
+ testcase :: m (Field (Way (GHC6'8 minor) n t p) a b)
+ (bound at T4174.hs:45:1)
+
=====================================
testsuite/tests/indexed-types/should_fail/T8227.stderr
=====================================
@@ -13,12 +13,3 @@ T8227.hs:24:27: error: [GHC-83865]
absoluteToParam :: Scalar (V a) -> a -> Scalar (V a)
(bound at T8227.hs:24:1)
-T8227.hs:24:48: error: [GHC-27958]
- • Couldn't match type ‘p0’ with ‘Scalar (V p0)’
- arising from a type equality Scalar (V a) ~ Scalar (V p0) -> p0
- The type variable ‘p0’ is ambiguous
- • In the second argument of ‘arcLengthToParam’, namely ‘eps’
- In the expression: arcLengthToParam eps eps
- In an equation for ‘absoluteToParam’:
- absoluteToParam eps seg = arcLengthToParam eps eps
-
=====================================
testsuite/tests/simplCore/should_compile/T25703.hs
=====================================
@@ -0,0 +1,7 @@
+module T25703 where
+
+f :: (Eq a, Show b) => a -> b -> Int
+f x y = f x y
+
+goo :: forall x. (Eq x) => x -> Int
+goo arg = f arg (3::Int)
=====================================
testsuite/tests/simplCore/should_compile/T25703.stderr
=====================================
@@ -0,0 +1,2 @@
+Rule fired: SPEC f @_ @Int (T25703)
+Rule fired: SPEC f @_ @Int (T25703)
=====================================
testsuite/tests/simplCore/should_compile/T25703a.hs
=====================================
@@ -0,0 +1,69 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE GADTs #-}
+
+{-# OPTIONS_GHC -O2 -fspecialise-aggressively #-}
+
+-- This pragma is just here to pretend that the function body of 'foo' is huge
+-- and should never be inlined.
+{-# OPTIONS_GHC -funfolding-use-threshold=-200 #-}
+
+module T25703a where
+
+import Data.Kind
+import Data.Type.Equality
+import Data.Proxy
+import GHC.TypeNats
+
+-- Pretend this is some big dictionary that absolutely must get
+-- specialised away for performance reasons.
+type C :: Nat -> Constraint
+class C i where
+ meth :: Proxy i -> Double
+instance C 0 where
+ meth _ = 0.1
+instance C 1 where
+ meth _ = 1.1
+instance C 2 where
+ meth _ = 2.1
+
+{-# INLINEABLE foo #-}
+foo :: forall a (n :: Nat) (m :: Nat)
+ . ( Eq a, C n, C m )
+ => a -> ( Proxy n, Proxy m ) -> Int -> Double
+-- Pretend this is a big complicated function, too big to inline,
+-- for which we absolutely must specialise away the 'C n', 'C m'
+-- dictionaries for performance reasons.
+foo a b c
+ = if a == a
+ then meth @n Proxy + fromIntegral c
+ else 2 * meth @m Proxy
+
+-- Runtime dispatch to a specialisation of 'foo'
+foo_spec :: forall a (n :: Nat) (m :: Nat)
+ . ( Eq a, KnownNat n, KnownNat m )
+ => a -> ( Proxy n, Proxy m ) -> Int -> Double
+foo_spec a b c
+ | Just Refl <- sameNat @n @0 Proxy Proxy
+ , Just Refl <- sameNat @m @0 Proxy Proxy
+ = foo @a @0 @0 a b c
+ | Just Refl <- sameNat @n @0 Proxy Proxy
+ , Just Refl <- sameNat @m @1 Proxy Proxy
+ = foo @a @0 @1 a b c
+ | Just Refl <- sameNat @n @1 Proxy Proxy
+ , Just Refl <- sameNat @m @1 Proxy Proxy
+ = foo @a @1 @1 a b c
+ | Just Refl <- sameNat @n @0 Proxy Proxy
+ , Just Refl <- sameNat @m @2 Proxy Proxy
+ = foo @a @0 @2 a b c
+ | Just Refl <- sameNat @n @1 Proxy Proxy
+ , Just Refl <- sameNat @m @2 Proxy Proxy
+ = foo @a @1 @2 a b c
+ | Just Refl <- sameNat @n @2 Proxy Proxy
+ , Just Refl <- sameNat @m @2 Proxy Proxy
+ = foo @a @2 @2 a b c
+ | otherwise
+ = error $ unlines
+ [ "f: no specialisation"
+ , "n: " ++ show (natVal @n Proxy)
+ , "m: " ++ show (natVal @m Proxy)
+ ]
=====================================
testsuite/tests/simplCore/should_compile/T25703a.stderr
=====================================
@@ -0,0 +1,6 @@
+Rule fired: SPEC foo @_ @2 @2 (T25703a)
+Rule fired: SPEC foo @_ @1 @2 (T25703a)
+Rule fired: SPEC foo @_ @0 @2 (T25703a)
+Rule fired: SPEC foo @_ @1 @1 (T25703a)
+Rule fired: SPEC foo @_ @0 @1 (T25703a)
+Rule fired: SPEC foo @_ @0 @0 (T25703a)
=====================================
testsuite/tests/simplCore/should_compile/T25965.hs
=====================================
@@ -0,0 +1,18 @@
+{-# LANGUAGE TypeFamilies #-}
+{-# OPTIONS_GHC -O -fpolymorphic-specialisation #-}
+
+module Foo where
+
+type family F a
+
+data T a = T1
+
+instance Eq (T a) where { (==) x y = False }
+
+foo :: Eq a => a -> Bool
+foo x | x==x = True
+ | otherwise = foo x
+
+bar :: forall b. b -> T (F b) -> Bool
+bar y x = foo x
+
=====================================
testsuite/tests/simplCore/should_compile/all.T
=====================================
@@ -543,3 +543,8 @@ test('T25883c', normal, compile_grep_core, [''])
test('T25883d', [extra_files(['T25883d_import.hs'])], multimod_compile_filter, ['T25883d', '-O -ddump-simpl -dno-typeable-binds -dsuppress-all -dsuppress-uniques', r'grep -e "y ="'])
test('T25976', [grep_errmsg('Dead Code')], compile, ['-O -ddump-simpl -dsuppress-uniques -dno-typeable-binds'])
+
+test('T25965', normal, compile, ['-O'])
+test('T25703', [grep_errmsg(r'SPEC')], compile, ['-O -fpolymorphic-specialisation -ddump-rule-firings'])
+test('T25703a', [grep_errmsg(r'SPEC')], compile, ['-O -fpolymorphic-specialisation -ddump-rule-firings'])
+
=====================================
testsuite/tests/typecheck/should_compile/T25266a.stderr
=====================================
@@ -1,16 +1,16 @@
-T25266a.hs:10:41: error: [GHC-25897]
- • Could not deduce ‘p1 ~ p2’
+T25266a.hs:10:39: error: [GHC-25897]
+ • Could not deduce ‘p2 ~ p1’
from the context: a ~ Int
bound by a pattern with constructor: T1 :: T Int,
in a case alternative
at T25266a.hs:10:23-24
- ‘p1’ is a rigid type variable bound by
+ ‘p2’ is a rigid type variable bound by
the inferred type of f :: p1 -> p2 -> T a -> Int
at T25266a.hs:(9,1)-(11,40)
- ‘p2’ is a rigid type variable bound by
+ ‘p1’ is a rigid type variable bound by
the inferred type of f :: p1 -> p2 -> T a -> Int
at T25266a.hs:(9,1)-(11,40)
- • In the expression: y
+ • In the expression: x
In the first argument of ‘length’, namely ‘[x, y]’
In the expression: length [x, y]
• Relevant bindings include
=====================================
testsuite/tests/typecheck/should_fail/T18851.stderr
=====================================
@@ -1,7 +1,7 @@
-
T18851.hs:35:5: error: [GHC-18872]
- • Couldn't match type ‘B’ with ‘A’
- arising from a superclass required to satisfy ‘C int0 A’,
+ • Couldn't match type ‘Bool’ with ‘B’
+ arising from a superclass required to satisfy ‘C Int B’,
arising from a use of ‘f’
• In the expression: f @A @B
In an equation for ‘g’: g = f @A @B
+
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/22070ca0b415d0f9d644033d30538f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/22070ca0b415d0f9d644033d30538f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc] Pushed new branch wip/juhp-disable-hadrian-selftest
by Jens Petersen (@juhp) 28 Apr '25
by Jens Petersen (@juhp) 28 Apr '25
28 Apr '25
Jens Petersen pushed new branch wip/juhp-disable-hadrian-selftest at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/juhp-disable-hadrian-selftest
You're receiving this email because of your account on gitlab.haskell.org.
1
0

28 Apr '25
Jens Petersen deleted branch wip/juhp-disable-hadrian-selftest at Glasgow Haskell Compiler / GHC
--
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc] Pushed new branch wip/juhp-disable-hadrian-selftest
by Jens Petersen (@juhp) 28 Apr '25
by Jens Petersen (@juhp) 28 Apr '25
28 Apr '25
Jens Petersen pushed new branch wip/juhp-disable-hadrian-selftest at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/juhp-disable-hadrian-selftest
You're receiving this email because of your account on gitlab.haskell.org.
1
0