
[Git][ghc/ghc][wip/int-index/visible-forall-gadts] 11 commits: Hadrian: Add option to generate .hie files for stage1 libraries
by Vladislav Zavialov (@int-index) 13 Jun '25
by Vladislav Zavialov (@int-index) 13 Jun '25
13 Jun '25
Vladislav Zavialov pushed to branch wip/int-index/visible-forall-gadts at Glasgow Haskell Compiler / GHC
Commits:
35826d8b by Matthew Pickering at 2025-06-08T22:00:41+01:00
Hadrian: Add option to generate .hie files for stage1 libraries
The +hie_files flavour transformer can be enabled to produce hie files
for stage1 libraries. The hie files are produced in the
"extra-compilation-artifacts" folder and copied into the resulting
bindist.
At the moment the hie files are not produced for the release flavour,
they add about 170M to the final bindist.
Towards #16901
- - - - -
e2467dbd by Ryan Hendrickson at 2025-06-09T13:07:05-04:00
Fix various failures to -fprint-unicode-syntax
- - - - -
1d99d3e4 by maralorn at 2025-06-12T03:47:39-04:00
Add necessary flag for js linking
- - - - -
974d5734 by maralorn at 2025-06-12T03:47:39-04:00
Don’t use additional linker flags to detect presence of -fno-pie in configure.ac
This mirrors the behavior of ghc-toolchain
- - - - -
1e9eb118 by Andrew Lelechenko at 2025-06-12T03:48:21-04:00
Add HasCallStack to Control.Monad.Fail.fail
CLC proposal https://github.com/haskell/core-libraries-committee/issues/327
2% compile-time allocations increase in T3064, likely because `fail`
is now marginally more expensive to compile.
Metric Increase:
T3064
- - - - -
6d12060f by meooow25 at 2025-06-12T14:26:07-04:00
Bump containers submodule to 0.8
Also
* Disable -Wunused-imports for containers
* Allow containers-0.8 for in-tree packages
* Bump some submodules so that they allow containers-0.8. These are not
at any particular versions.
* Remove unused deps containers and split from ucd2haskell
* Fix tests affected by the new containers and hpc-bin
- - - - -
537bd233 by Peng Fan at 2025-06-12T14:27:02-04:00
NCG/LA64: Optimize code generation and reduce build-directory size.
1. makeFarBranches: Prioritize fewer instruction sequences.
2. Prefer instructions with immediate numbers to reduce register moves,
e.g. andi,ori,xori,addi.
3. Ppr: Remove unnecessary judgments.
4. genJump: Avoid "ld+jr" as much as possible.
5. BCOND and BCOND1: Implement conditional jumps with two jump ranges,
with limited choice of the shortest.
6. Implement FSQRT, CLT, CTZ.
7. Remove unnecessary code.
- - - - -
19f20861 by Simon Peyton Jones at 2025-06-13T09:51:11-04:00
Improve redundant constraints for instance decls
Addresses #25992, which showed that the default methods
of an instance decl could make GHC fail to report redundant
constraints.
Figuring out how to do this led me to refactor the computation
of redundant constraints. See the entirely rewritten
Note [Tracking redundant constraints]
in GHC.Tc.Solver.Solve
- - - - -
1d02798e by Matthew Pickering at 2025-06-13T09:51:54-04:00
Refactor the treatment of nested Template Haskell splices
* The difference between a normal splice, a quasiquoter and implicit
splice caused by lifting is stored in the AST after renaming.
* Information that the renamer learns about splices is stored in the
relevant splice extension points (XUntypedSpliceExpr, XQuasiQuote).
* Normal splices and quasi quotes record the flavour of splice
(exp/pat/dec etc)
* Implicit lifting stores information about why the lift was attempted,
so if it fails, that can be reported to the user.
* After renaming, the decision taken to attempt to implicitly lift a
variable is stored in the `XXUntypedSplice` extension field in the
`HsImplicitLiftSplice` constructor.
* Since all the information is stored in the AST, in `HsUntypedSplice`,
the type of `PendingRnSplice` now just stores a `HsUntypedSplice`.
* Error messages since the original program can be easily
printed, this is noticeable in the case of implicit lifting.
* The user-written syntax is directly type-checked. Before, some
desugaring took place in the
* Fixes .hie files to work better with nested splices (nested splices
are not indexed)
* The location of the quoter in a quasiquote is now located, so error
messages will precisely point to it (and again, it is indexed by hie
files)
In the future, the typechecked AST should also retain information about
the splices and the specific desugaring being left to the desugarer.
Also, `runRnSplice` should call `tcUntypedSplice`, otherwise the
typechecking logic is duplicated (see the `QQError` and `QQTopError`
tests for a difference caused by this).
- - - - -
f93798ba by Cheng Shao at 2025-06-13T09:52:35-04:00
libffi: update to 3.5.1
Bumps libffi submodule.
- - - - -
a013284c by Vladislav Zavialov at 2025-06-13T18:24:15+03:00
Visible forall in GADTs
Add support for visible dependent quantification `forall a -> t` in
types of data constructors, e.g.
data KindVal a where
K :: forall k.
forall (a::k) -> -- now allowed!
k ->
KindVal a
For details, see docs/users_guide/exts/required_type_arguments.rst,
which has gained a new subsection.
DataCon in compiler/GHC/Core/DataCon.hs
---------------------------------------
The main change in this patch is that DataCon, the Core representation
of a data constructor, now uses a different type to store user-written
type variable binders:
- dcUserTyVarBinders :: [InvisTVBinder]
+ dcUserTyVarBinders :: [TyVarBinder]
where
type TyVarBinder = VarBndr TyVar ForAllTyFlag
type InvisTVBinder = VarBndr TyVar Specificity
and
data Specificity = InferredSpec | SpecifiedSpec
data ForAllTyFlag = Invisible Specificity | Required
This change necessitates some boring, mechanical changes scattered
throughout the diff:
... is now used in place of ...
-----------------+---------------
TyVarBinder | InvisTVBinder
IfaceForAllBndr | IfaceForAllSpecBndr
Specified | SpecifiedSpec
Inferred | InferredSpec
mkForAllTys | mkInvisForAllTys
additionally,
tyVarSpecToBinders -- added or removed calls
ifaceForAllSpecToBndrs -- removed calls
Visibility casts in mkDataConRep
--------------------------------
Type abstractions in Core (/\a. e) always have type (forall a. t)
because coreTyLamForAllTyFlag = Specified. This is also true of data
constructor workers. So we may be faced with the following:
data con worker: (forall a. blah)
data con wrapper: (forall a -> blah)
In this case the wrapper must use a visibility cast (e |> ForAllCo ...)
with appropriately set fco_vis{L,R}. Relevant functions:
mkDataConRep in compiler/GHC/Types/Id/Make.hs
dataConUserTyVarBindersNeedWrapper in compiler/GHC/Core/DataCon.hs
mkForAllVisCos in compiler/GHC/Core/Coercion.hs
mkCoreTyLams in compiler/GHC/Core/Make.hs
mkWpForAllCast in compiler/GHC/Tc/Types/Evidence.hs
More specifically:
- dataConUserTyVarBindersNeedWrapper has been updated to answer "yes"
if there are visible foralls in the type of the data constructor.
- mkDataConRep now uses mkCoreTyLams to generate the big lambda
abstractions (/\a b c. e) in the data con wrapper.
- mkCoreTyLams is a variant of mkCoreLams that applies visibility casts
as needed. It similar in purpose to the pre-existing mkWpForAllCast,
so the common bits have been factored out into mkForAllVisCos.
ConDecl in compiler/Language/Haskell/Syntax/Decls.hs
----------------------------------------------------
The surface syntax representation of a data constructor declaration is
ConDecl. In accordance with the proposal, only GADT syntax is extended
with support for visible forall, so we are interested in ConDeclGADT.
ConDeclGADT's field con_bndrs has been renamed to con_outer_bndrs
and is now accompanied by con_inner_bndrs:
con_outer_bndrs :: XRec pass (HsOuterSigTyVarBndrs pass)
con_inner_bndrs :: [HsForAllTelescope pass]
Visible foralls always end up in con_inner_bndrs. The outer binders are
stored and processed separately to support implicit quantification and
the forall-or-nothing rule, a design established by HsSigType.
A side effect of this change is that even in absence of visible foralls,
GHC now permits multiple invisible foralls, e.g.
data T a where { MkT :: forall a b. forall c d. ... -> T a }
But of course, this is done in service of making at least some of these
foralls visible. The entire compiler front-end has been updated to deal
with con_inner_bndrs. See the following modified or added functions:
Parser:
mkGadtDecl in compiler/GHC/Parser/PostProcess.hs
splitLHsGadtTy in compiler/GHC/Hs/Type.hs
Pretty-printer:
pprConDecl in compiler/GHC/Hs/Decls.hs
pprHsForAllTelescope in compiler/GHC/Hs/Type.hs
Renamer:
rnConDecl in compiler/GHC/Rename/Module.hs
bindHsForAllTelescopes in compiler/GHC/Rename/HsType.hs
extractHsForAllTelescopes in compiler/GHC/Rename/HsType.hs
Type checker:
tcConDecl in compiler/GHC/Tc/TyCl.hs
tcGadtConTyVarBndrs in compiler/GHC/Tc/Gen/HsType.hs
Template Haskell
----------------
The TH AST is left unchanged for the moment to avoid breakage. An
attempt to quote or reify a data constructor declaration with visible
forall in its type will result an error:
data ThRejectionReason -- in GHC/HsToCore/Errors/Types.hs
= ...
| ThDataConVisibleForall -- new error constructor
However, as noted in the previous section, GHC now permits multiple
invisible foralls, and TH was updated accordingly. Updated code:
repC in compiler/GHC/HsToCore/Quote.hs
reifyDataCon in compiler/GHC/Tc/Gen/Splice.hs
ppr @Con in libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
Pattern matching
----------------
Everything described above concerns data constructor declarations, but
what about their use sites? Now it is trickier to type check a pattern
match fn(Con a b c)=... because we can no longer assume that a,b,c are
all value arguments. Indeed, some or all of them may very well turn out
to be required type arguments.
To that end, see the changes to:
tcDataConPat in compiler/GHC/Tc/Gen/Pat.hs
splitConTyArgs in compiler/GHC/Tc/Gen/Pat.hs
and the new helpers split_con_ty_args, zip_pats_bndrs.
This is also the reason the TcRnTooManyTyArgsInConPattern error
constructor has been removed. The new code emits TcRnArityMismatch
or TcRnIllegalInvisibleTypePattern.
Summary
-------
DataCon, ConDecl, as well as all related functions have been updated to
support required type arguments in data constructors.
Test cases:
HieGadtConSigs GadtConSigs_th_dump1 GadtConSigs_th_pprint1
T25127_data T25127_data_inst T25127_infix
T25127_newtype T25127_fail_th_quote T25127_fail_arity
TyAppPat_Tricky
Co-authored-by: mniip <mniip(a)mniip.com>
- - - - -
195 changed files:
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/CmmToAsm/LA64.hs
- compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- compiler/GHC/CmmToAsm/LA64/Instr.hs
- compiler/GHC/CmmToAsm/LA64/Ppr.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/DataCon.hs-boot
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/PatSyn.hs
- compiler/GHC/Core/TyCo/Ppr.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Expr.hs-boot
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Splice.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/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/Gen/Splice.hs-boot
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/InertSet.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/Utils.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/ErrCtxt.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Types/TH.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/Instantiate.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/ThLevelIndex.hs
- compiler/GHC/Types/Var.hs-boot
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/Pat.hs
- compiler/ghc.cabal.in
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/exts/gadt_syntax.rst
- docs/users_guide/exts/required_type_arguments.rst
- ghc/ghc-bin.cabal.in
- hadrian/doc/flavours.md
- hadrian/doc/user-settings.md
- hadrian/hadrian.cabal
- hadrian/src/Context.hs
- hadrian/src/Context/Path.hs
- hadrian/src/Flavour.hs
- hadrian/src/Flavour/Type.hs
- hadrian/src/Settings/Builders/Ghc.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Flavours/Release.hs
- hadrian/src/Settings/Warnings.hs
- libffi-tarballs
- libraries/base/changelog.md
- libraries/base/tests/IO/withBinaryFile002.stderr
- libraries/base/tests/IO/withFile002.stderr
- libraries/base/tests/IO/withFileBlocking002.stderr
- libraries/containers
- libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-heap/ghc-heap.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs-boot
- libraries/ghc-internal/src/GHC/Internal/IO.hs-boot
- libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs-boot
- libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal
- libraries/ghci/ghci.cabal.in
- libraries/haskeline
- libraries/hpc
- m4/fp_gcc_supports_no_pie.m4
- m4/fptools_set_c_ld_flags.m4
- testsuite/tests/deSugar/should_run/DsDoExprFailMsg.stderr
- testsuite/tests/deSugar/should_run/DsMonadCompFailMsg.stderr
- testsuite/tests/dependent/should_fail/T13135_simple.stderr
- testsuite/tests/dependent/should_fail/T16326_Fail6.stderr
- testsuite/tests/diagnostic-codes/codes.stdout
- testsuite/tests/ghci/scripts/T12550.stdout
- testsuite/tests/ghci/scripts/T8959b.stderr
- testsuite/tests/ghci/scripts/all.T
- + testsuite/tests/ghci/scripts/print-unicode-syntax.script
- + testsuite/tests/ghci/scripts/print-unicode-syntax.stderr
- + testsuite/tests/ghci/scripts/print-unicode-syntax.stdout
- testsuite/tests/ghci/should_run/T11825.stdout
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- + testsuite/tests/hiefile/should_run/HieGadtConSigs.hs
- + testsuite/tests/hiefile/should_run/HieGadtConSigs.stdout
- testsuite/tests/hiefile/should_run/all.T
- testsuite/tests/hpc/fork/hpc_fork.stdout
- testsuite/tests/hpc/function/tough.stdout
- testsuite/tests/hpc/function2/tough2.stdout
- testsuite/tests/hpc/simple/hpc001.stdout
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/linear/should_fail/LinearTHFail.stderr
- testsuite/tests/linters/notes.stdout
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/partial-sigs/should_fail/T10999.stderr
- testsuite/tests/perf/compiler/hard_hole_fits.stderr
- testsuite/tests/printer/T18791.stderr
- testsuite/tests/quasiquotation/T3953.stderr
- + testsuite/tests/quotes/QQError.hs
- + testsuite/tests/quotes/QQError.stderr
- testsuite/tests/quotes/T10384.stderr
- testsuite/tests/quotes/TH_localname.stderr
- testsuite/tests/quotes/all.T
- testsuite/tests/rebindable/DoRestrictedM.hs
- + testsuite/tests/th/GadtConSigs_th_dump1.hs
- + testsuite/tests/th/GadtConSigs_th_dump1.stderr
- + testsuite/tests/th/GadtConSigs_th_pprint1.hs
- + testsuite/tests/th/GadtConSigs_th_pprint1.stderr
- + testsuite/tests/th/QQInQuote.hs
- + testsuite/tests/th/QQTopError.hs
- + testsuite/tests/th/QQTopError.stderr
- testsuite/tests/th/T10598_TH.stderr
- testsuite/tests/th/T14681.stderr
- testsuite/tests/th/T15321.stderr
- testsuite/tests/th/T17804.stderr
- testsuite/tests/th/T20868.stdout
- testsuite/tests/th/T5508.stderr
- testsuite/tests/th/TH_Lift.stderr
- testsuite/tests/th/all.T
- testsuite/tests/th/overloaded/TH_overloaded_constraints_fail.stderr
- testsuite/tests/typecheck/should_compile/T23739a.hs
- + testsuite/tests/typecheck/should_compile/T25992.hs
- + testsuite/tests/typecheck/should_compile/T25992.stderr
- + testsuite/tests/typecheck/should_compile/TyAppPat_Tricky.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_compile/subsumption_sort_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr
- testsuite/tests/typecheck/should_fail/T20443b.stderr
- testsuite/tests/typecheck/should_fail/TyAppPat_TooMany.stderr
- testsuite/tests/typecheck/should_fail/tcfail097.stderr
- + testsuite/tests/vdq-rta/should_compile/T25127_data.hs
- + testsuite/tests/vdq-rta/should_compile/T25127_data_inst.hs
- + testsuite/tests/vdq-rta/should_compile/T25127_infix.hs
- + testsuite/tests/vdq-rta/should_compile/T25127_newtype.hs
- testsuite/tests/vdq-rta/should_compile/all.T
- testsuite/tests/vdq-rta/should_fail/T24159_type_syntax_th_fail.script
- + testsuite/tests/vdq-rta/should_fail/T25127_fail_arity.hs
- + testsuite/tests/vdq-rta/should_fail/T25127_fail_arity.stderr
- + testsuite/tests/vdq-rta/should_fail/T25127_fail_th_quote.hs
- + testsuite/tests/vdq-rta/should_fail/T25127_fail_th_quote.stderr
- testsuite/tests/vdq-rta/should_fail/all.T
- utils/check-exact/ExactPrint.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/GhcUtils.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-library/haddock-library.cabal
- utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
- utils/hpc
- utils/hsc2hs
- utils/iserv/iserv.cabal.in
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c8a533e6a533b7742040aae4757aae…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c8a533e6a533b7742040aae4757aae…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/torsten.schmits/worker-debug] Link package DB bytecode in make mode
by Torsten Schmits (@torsten.schmits) 13 Jun '25
by Torsten Schmits (@torsten.schmits) 13 Jun '25
13 Jun '25
Torsten Schmits pushed to branch wip/torsten.schmits/worker-debug at Glasgow Haskell Compiler / GHC
Commits:
f9587b0f by Torsten Schmits at 2025-06-13T16:30:07+02:00
Link package DB bytecode in make mode
- - - - -
1 changed file:
- compiler/GHC/Linker/Deps.hs
Changes:
=====================================
compiler/GHC/Linker/Deps.hs
=====================================
@@ -156,9 +156,10 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
listToUDFM [(moduleName (mi_module (hm_iface m)), m) | m <- mmods]
link_libs =
uniqDSetToList (unionManyUniqDSets (init_pkg_set : pkgs))
+ deps <- oneshot_deps opts link_libs
pure $
LinkModules (LinkHomeModule <$> link_mods) :
- (LinkLibrary <$> link_libs)
+ deps
-- This code is used in `--make` mode to calculate the home package and unit dependencies
-- for a set of modules.
@@ -168,15 +169,15 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
-- It is also a matter of correctness to use the module graph so that dependencies between home units
-- is resolved correctly.
- make_deps_loop :: (UniqDSet UnitId, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set.Set NodeKey)
+ make_deps_loop :: (UniqDSet Module, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet Module, Set.Set NodeKey)
make_deps_loop found [] = found
make_deps_loop found@(found_units, found_mods) (nk:nexts)
| NodeKey_Module nk `Set.member` found_mods = make_deps_loop found nexts
| otherwise =
case fmap mkNodeKey <$> mgReachable mod_graph (NodeKey_Module nk) of
Nothing ->
- let (ModNodeKeyWithUid _ uid) = nk
- in make_deps_loop (addOneToUniqDSet found_units uid, found_mods) nexts
+ let (ModNodeKeyWithUid GWIB {gwib_mod} uid) = nk
+ in make_deps_loop (addOneToUniqDSet found_units (Module (RealUnit (Definite uid)) gwib_mod), found_mods) nexts
Just trans_deps ->
let deps = Set.insert (NodeKey_Module nk) (Set.fromList trans_deps)
-- See #936 and the ghci.prog007 test for why we have to continue traversing through
@@ -195,7 +196,7 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
let iface = hm_iface hmi
case mi_hsc_src iface of
HsBootFile -> throwProgramError opts $ link_boot_mod_error (mi_module iface)
- _ -> pure (mkUniqDSet $ Set.toList $ dep_direct_pkgs (mi_deps iface), hmi)
+ _ -> pure (mkUniqDSet [usg_mod | UsagePackageModule {usg_mod} <- mi_usages iface, not (unitEnv_member (moduleUnitId usg_mod) (ue_home_unit_graph unit_env))], hmi)
Nothing -> throwProgramError opts $
text "getLinkDeps: Home module not loaded" <+> ppr (gwib_mod gwib) <+> ppr uid
@@ -344,7 +345,7 @@ oneshot_deps_loop opts (mod : mods) acc = do
try_iface =
liftIO (ldLoadIface opts load_reason mod) >>= \case
- Failed err -> throwE (NoInterface err)
+ Failed _ -> add_library
Succeeded iface ->
location >>= \case
InstalledFound loc _ -> with_iface loc iface
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f9587b0fcc14565953326d0032a3e92…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f9587b0fcc14565953326d0032a3e92…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/module_graph_mode] Move ModuleGraph into UnitEnv
by Rodrigo Mesquita (@alt-romes) 13 Jun '25
by Rodrigo Mesquita (@alt-romes) 13 Jun '25
13 Jun '25
Rodrigo Mesquita pushed to branch wip/module_graph_mode at Glasgow Haskell Compiler / GHC
Commits:
0f7cdd19 by Matthew Pickering at 2025-06-13T15:15:30+01:00
Move ModuleGraph into UnitEnv
The ModuleGraph is a piece of information associated with the
ExternalPackageState and HomeUnitGraph. Therefore we should store it
inside the HomeUnitEnv.
- - - - -
12 changed files:
- compiler/GHC.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Env/Types.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Unit/Env.hs
- ghc/GHCi/UI.hs
Changes:
=====================================
compiler/GHC.hs
=====================================
@@ -859,6 +859,7 @@ setProgramDynFlags_ invalidate_needed dflags = do
, ue_namever = ghcNameVersion dflags1
, ue_home_unit_graph = home_unit_graph
, ue_current_unit = ue_currentUnit old_unit_env
+ , ue_module_graph = ue_module_graph old_unit_env
, ue_eps = ue_eps old_unit_env
}
modifySession $ \h -> hscSetFlags dflags1 h{ hsc_unit_env = unit_env }
@@ -996,7 +997,7 @@ setProgramHUG_ invalidate_needed new_hug0 = do
--
invalidateModSummaryCache :: GhcMonad m => m ()
invalidateModSummaryCache =
- modifySession $ \h -> h { hsc_mod_graph = mapMG inval (hsc_mod_graph h) }
+ modifySession $ \hsc_env -> setModuleGraph (mapMG inval (hsc_mod_graph hsc_env)) hsc_env
where
inval ms = ms { ms_hs_hash = fingerprint0 }
=====================================
compiler/GHC/Core/Opt/Pipeline.hs
=====================================
@@ -97,10 +97,11 @@ core2core hsc_env guts@(ModGuts { mg_module = mod
where
dflags = hsc_dflags hsc_env
logger = hsc_logger hsc_env
+ unit_env = hsc_unit_env hsc_env
extra_vars = interactiveInScope (hsc_IC hsc_env)
home_pkg_rules = hugRulesBelow hsc_env (moduleUnitId mod)
(GWIB { gwib_mod = moduleName mod, gwib_isBoot = NotBoot })
- name_ppr_ctx = mkNamePprCtx ptc (hsc_unit_env hsc_env) rdr_env
+ name_ppr_ctx = mkNamePprCtx ptc unit_env rdr_env
ptc = initPromotionTickContext dflags
-- mod: get the module out of the current HscEnv so we can retrieve it from the monad.
-- This is very convienent for the users of the monad (e.g. plugins do not have to
=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -457,6 +457,7 @@ addUnit u = do
(homeUnitId home_unit)
(HUG.mkHomeUnitEnv unit_state (Just dbs) dflags (ue_hpt old_unit_env) (Just home_unit))
, ue_eps = ue_eps old_unit_env
+ , ue_module_graph = ue_module_graph old_unit_env
}
setSession $ hscSetFlags dflags $ hsc_env { hsc_unit_env = unit_env }
=====================================
compiler/GHC/Driver/Env.hs
=====================================
@@ -2,6 +2,8 @@
module GHC.Driver.Env
( Hsc(..)
, HscEnv (..)
+ , hsc_mod_graph
+ , setModuleGraph
, hscUpdateFlags
, hscSetFlags
, hsc_home_unit
@@ -130,6 +132,9 @@ hsc_HUE = ue_currentHomeUnitEnv . hsc_unit_env
hsc_HUG :: HscEnv -> HomeUnitGraph
hsc_HUG = ue_home_unit_graph . hsc_unit_env
+hsc_mod_graph :: HscEnv -> ModuleGraph
+hsc_mod_graph = ue_module_graph . hsc_unit_env
+
hsc_all_home_unit_ids :: HscEnv -> Set.Set UnitId
hsc_all_home_unit_ids = HUG.allUnits . hsc_HUG
@@ -139,6 +144,9 @@ hscInsertHPT hmi hsc_env = UnitEnv.insertHpt hmi (hsc_unit_env hsc_env)
hscUpdateHUG :: (HomeUnitGraph -> HomeUnitGraph) -> HscEnv -> HscEnv
hscUpdateHUG f hsc_env = hsc_env { hsc_unit_env = updateHug f (hsc_unit_env hsc_env) }
+setModuleGraph :: ModuleGraph -> HscEnv -> HscEnv
+setModuleGraph mod_graph hsc_env = hsc_env { hsc_unit_env = (hsc_unit_env hsc_env) { ue_module_graph = mod_graph } }
+
{-
Note [Target code interpreter]
@@ -220,15 +228,15 @@ hscEPS hsc_env = readIORef (euc_eps (ue_eps (hsc_unit_env hsc_env)))
-- | Find all rules in modules that are in the transitive closure of the given
-- module.
hugRulesBelow :: HscEnv -> UnitId -> ModuleNameWithIsBoot -> IO RuleBase
-hugRulesBelow hsc uid mn = foldr (flip extendRuleBaseList) emptyRuleBase <$>
- hugSomeThingsBelowUs (md_rules . hm_details) False hsc uid mn
+hugRulesBelow hsc_env uid mn = foldr (flip extendRuleBaseList) emptyRuleBase <$>
+ hugSomeThingsBelowUs (md_rules . hm_details) False hsc_env uid mn
-- | Get annotations from all modules "below" this one (in the dependency
-- sense) within the home units. If the module is @Nothing@, returns /all/
-- annotations in the home units.
hugAnnsBelow :: HscEnv -> UnitId -> ModuleNameWithIsBoot -> IO AnnEnv
-hugAnnsBelow hsc uid mn = foldr (flip extendAnnEnvList) emptyAnnEnv <$>
- hugSomeThingsBelowUs (md_anns . hm_details) False hsc uid mn
+hugAnnsBelow hsc_env uid mn = foldr (flip extendAnnEnvList) emptyAnnEnv <$>
+ hugSomeThingsBelowUs (md_anns . hm_details) False hsc_env uid mn
-- | Find all COMPLETE pragmas in modules that are in the transitive closure of the
-- given module.
@@ -260,7 +268,8 @@ hugInstancesBelow hsc_env uid mnwib = do
hugSomeThingsBelowUs :: (HomeModInfo -> [a]) -> Bool -> HscEnv -> UnitId -> ModuleNameWithIsBoot -> IO [[a]]
-- An explicit check to see if we are in one-shot mode to avoid poking the ModuleGraph thunk
-- These things are currently stored in the EPS for home packages. (See #25795 for
--- progress in removing these kind of checks)
+-- progress in removing these kind of checks; and making these functions of
+-- `UnitEnv` rather than `HscEnv`)
-- See Note [Downsweep and the ModuleGraph]
hugSomeThingsBelowUs _ _ hsc_env _ _ | isOneShot (ghcMode (hsc_dflags hsc_env)) = return []
hugSomeThingsBelowUs extract include_hi_boot hsc_env uid mn
=====================================
compiler/GHC/Driver/Env/Types.hs
=====================================
@@ -18,7 +18,6 @@ import GHC.Types.Name.Cache
import GHC.Types.Target
import GHC.Types.TypeEnv
import GHC.Unit.Finder.Types
-import GHC.Unit.Module.Graph
import GHC.Unit.Env
import GHC.Utils.Logger
import GHC.Utils.TmpFs
@@ -65,10 +64,6 @@ data HscEnv
hsc_targets :: [Target],
-- ^ The targets (or roots) of the current session
- hsc_mod_graph :: ModuleGraph,
- -- ^ The module graph of the current session
- -- See Note [Downsweep and the ModuleGraph] for when this is constructed.
-
hsc_IC :: InteractiveContext,
-- ^ The context for evaluating interactive statements
@@ -113,3 +108,4 @@ data HscEnv
, hsc_llvm_config :: !LlvmConfigCache
-- ^ LLVM configuration cache.
}
+
=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -332,7 +332,6 @@ newHscEnvWithHUG top_dir top_dynflags cur_unit home_unit_graph = do
return HscEnv { hsc_dflags = top_dynflags
, hsc_logger = setLogFlags logger (initLogFlags top_dynflags)
, hsc_targets = []
- , hsc_mod_graph = emptyMG
, hsc_IC = emptyInteractiveContext dflags
, hsc_NC = nc_var
, hsc_FC = fc_var
=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -190,12 +190,12 @@ depanalE diag_wrapper msg excluded_mods allow_dup_roots = do
all_errs <- liftIO $ HUG.unitEnv_foldWithKey one_unit_messages (return emptyMessages) (hsc_HUG hsc_env)
logDiagnostics (GhcDriverMessage <$> all_errs)
- setSession hsc_env { hsc_mod_graph = mod_graph }
+ setSession (setModuleGraph mod_graph hsc_env)
pure (emptyMessages, mod_graph)
else do
-- We don't have a complete module dependency graph,
-- The graph may be disconnected and is unusable.
- setSession hsc_env { hsc_mod_graph = emptyMG }
+ setSession (setModuleGraph emptyMG hsc_env)
pure (errs, emptyMG)
@@ -616,7 +616,7 @@ load' mhmi_cache how_much diag_wrapper mHscMessage mod_graph = do
-- for any client who might interact with GHC via load'.
-- See Note [Timing of plugin initialization]
initializeSessionPlugins
- modifySession $ \hsc_env -> hsc_env { hsc_mod_graph = mod_graph }
+ modifySession (setModuleGraph mod_graph)
guessOutputFile
hsc_env <- getSession
=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -768,8 +768,9 @@ runHscPhase pipe_env hsc_env0 input_fn src_flavour = do
-- files. See GHC.Tc.Utils.TcGblEnv.tcg_type_env_var.
-- See also Note [hsc_type_env_var hack]
type_env_var <- newIORef emptyNameEnv
- let hsc_env' = hsc_env { hsc_type_env_vars = knotVarsFromModuleEnv (mkModuleEnv [(mod, type_env_var)])
- , hsc_mod_graph = mg }
+ let hsc_env' =
+ setModuleGraph mg
+ hsc_env { hsc_type_env_vars = knotVarsFromModuleEnv (mkModuleEnv [(mod, type_env_var)]) }
=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -671,7 +671,7 @@ dontLeakTheHUG thing_inside = do
-- oneshot mode does not support backpack
-- and we want to avoid prodding the hsc_mod_graph thunk
| isOneShot (ghcMode (hsc_dflags hsc_env)) = False
- | mgHasHoles (hsc_mod_graph hsc_env) = True
+ | mgHasHoles (ue_module_graph old_unit_env) = True
| otherwise = False
pruneHomeUnitEnv hme = do
-- NB: These are empty HPTs because Iface/Load first consults the HPT
@@ -683,19 +683,19 @@ dontLeakTheHUG thing_inside = do
| otherwise
= do
hug' <- traverse pruneHomeUnitEnv (ue_home_unit_graph old_unit_env)
+ let !new_mod_graph = emptyMG { mg_mss = panic "cleanTopEnv: mg_mss"
+ , mg_graph = panic "cleanTopEnv: mg_graph"
+ , mg_has_holes = keepFor20509 }
return old_unit_env
{ ue_home_unit_graph = hug'
+ , ue_module_graph = new_mod_graph
}
in do
!unit_env <- unit_env_io
-- mg_has_holes will be checked again, but nothing else about the module graph
- let !new_mod_graph = emptyMG { mg_mss = panic "cleanTopEnv: mg_mss"
- , mg_graph = panic "cleanTopEnv: mg_graph"
- , mg_has_holes = keepFor20509 }
pure $
hsc_env
{ hsc_targets = panic "cleanTopEnv: hsc_targets"
- , hsc_mod_graph = new_mod_graph
, hsc_IC = panic "cleanTopEnv: hsc_IC"
, hsc_type_env_vars = case maybe_type_vars of
Just vars -> vars
=====================================
compiler/GHC/Tc/Module.hs
=====================================
@@ -2109,7 +2109,7 @@ for the unit portion of the graph, if it's not already been performed.
withInteractiveModuleNode :: HscEnv -> TcM a -> TcM a
withInteractiveModuleNode hsc_env thing_inside = do
mg <- liftIO $ downsweepInteractiveImports hsc_env (hsc_IC hsc_env)
- updTopEnv (\env -> env { hsc_mod_graph = mg }) thing_inside
+ updTopEnv (setModuleGraph mg) thing_inside
runTcInteractive :: HscEnv -> TcRn a -> IO (Messages TcRnMessage, Maybe a)
=====================================
compiler/GHC/Unit/Env.hs
=====================================
@@ -23,21 +23,22 @@
-- ┌▽────────────┐ │ │
-- │HomeUnitGraph│ │ │
-- └┬────────────┘ │ │
--- ┌▽─────────────────▽┐ │
--- │UnitEnv │ │
--- └┬──────────────────┘ │
--- ┌▽───────────────────────────────────────▽┐
--- │HscEnv │
--- └─────────────────────────────────────────┘
+-- ┌▽─────────────────▽─────────────────────▽┐
+-- │UnitEnv │
+-- └┬─────────────-──────────────────────────┘
+-- │
+-- │
+-- ┌▽──────────────────────────────────────▽┐
+-- │HscEnv │
+-- └────────────────────────────────────────┘
-- @
--
--- The 'UnitEnv' references both the 'HomeUnitGraph' (with all the home unit
--- modules) and the 'ExternalPackageState' (information about all
--- non-home/external units). The 'HscEnv' references this 'UnitEnv' and the
--- 'ModuleGraph' (which describes the relationship between the modules being
--- compiled). The 'HomeUnitGraph' has one 'HomePackageTable' for every unit.
---
--- TODO: Arguably, the 'ModuleGraph' should be part of 'UnitEnv' rather than being in the 'HscEnv'.
+-- The 'UnitEnv' references the 'HomeUnitGraph' (with all the home unit
+-- modules), the 'ExternalPackageState' (information about all
+-- non-home/external units), and the 'ModuleGraph' (which describes the
+-- relationship between the modules being compiled).
+-- The 'HscEnv' references this 'UnitEnv'.
+-- The 'HomeUnitGraph' has one 'HomePackageTable' for every unit.
module GHC.Unit.Env
( UnitEnv (..)
, initUnitEnv
@@ -119,6 +120,7 @@ import GHC.Unit.Home.ModInfo
import GHC.Unit.Home.PackageTable
import GHC.Unit.Home.Graph (HomeUnitGraph, HomeUnitEnv)
import qualified GHC.Unit.Home.Graph as HUG
+import GHC.Unit.Module.Graph
import GHC.Platform
import GHC.Settings
@@ -163,6 +165,10 @@ data UnitEnv = UnitEnv
, ue_current_unit :: UnitId
+ , ue_module_graph :: !ModuleGraph
+ -- ^ The module graph of the current session
+ -- See Note [Downsweep and the ModuleGraph] for when this is constructed.
+
, ue_home_unit_graph :: !HomeUnitGraph
-- See Note [Multiple Home Units]
@@ -182,6 +188,7 @@ initUnitEnv cur_unit hug namever platform = do
return $ UnitEnv
{ ue_eps = eps
, ue_home_unit_graph = hug
+ , ue_module_graph = emptyMG
, ue_current_unit = cur_unit
, ue_platform = platform
, ue_namever = namever
=====================================
ghc/GHCi/UI.hs
=====================================
@@ -4680,7 +4680,7 @@ clearHPTs = do
let pruneHomeUnitEnv hme = liftIO $ do
emptyHpt <- emptyHomePackageTable
pure hme{ homeUnitEnv_hpt = emptyHpt }
- discardMG hsc = hsc { hsc_mod_graph = GHC.emptyMG }
+ discardMG hsc = setModuleGraph GHC.emptyMG hsc
modifySessionM $ \hsc_env -> do
hug' <- traverse pruneHomeUnitEnv $ hsc_HUG hsc_env
pure $ discardMG $ discardIC $ hscUpdateHUG (const hug') hsc_env
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0f7cdd19e4404be66b92c338cbd9b39…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0f7cdd19e4404be66b92c338cbd9b39…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/torsten.schmits/worker-debug] Link package DB bytecode in make mode
by Torsten Schmits (@torsten.schmits) 13 Jun '25
by Torsten Schmits (@torsten.schmits) 13 Jun '25
13 Jun '25
Torsten Schmits pushed to branch wip/torsten.schmits/worker-debug at Glasgow Haskell Compiler / GHC
Commits:
66de4a3a by Torsten Schmits at 2025-06-13T16:11:51+02:00
Link package DB bytecode in make mode
- - - - -
1 changed file:
- compiler/GHC/Linker/Deps.hs
Changes:
=====================================
compiler/GHC/Linker/Deps.hs
=====================================
@@ -156,9 +156,10 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
listToUDFM [(moduleName (mi_module (hm_iface m)), m) | m <- mmods]
link_libs =
uniqDSetToList (unionManyUniqDSets (init_pkg_set : pkgs))
+ deps <- oneshot_deps opts link_libs
pure $
LinkModules (LinkHomeModule <$> link_mods) :
- (LinkLibrary <$> link_libs)
+ deps
-- This code is used in `--make` mode to calculate the home package and unit dependencies
-- for a set of modules.
@@ -168,15 +169,15 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
-- It is also a matter of correctness to use the module graph so that dependencies between home units
-- is resolved correctly.
- make_deps_loop :: (UniqDSet UnitId, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set.Set NodeKey)
+ make_deps_loop :: (UniqDSet Module, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet Module, Set.Set NodeKey)
make_deps_loop found [] = found
make_deps_loop found@(found_units, found_mods) (nk:nexts)
| NodeKey_Module nk `Set.member` found_mods = make_deps_loop found nexts
| otherwise =
case fmap mkNodeKey <$> mgReachable mod_graph (NodeKey_Module nk) of
Nothing ->
- let (ModNodeKeyWithUid _ uid) = nk
- in make_deps_loop (addOneToUniqDSet found_units uid, found_mods) nexts
+ let (ModNodeKeyWithUid GWIB {gwib_mod} uid) = nk
+ in make_deps_loop (addOneToUniqDSet found_units (Module (RealUnit (Definite uid)) gwib_mod), found_mods) nexts
Just trans_deps ->
let deps = Set.insert (NodeKey_Module nk) (Set.fromList trans_deps)
-- See #936 and the ghci.prog007 test for why we have to continue traversing through
@@ -195,7 +196,7 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
let iface = hm_iface hmi
case mi_hsc_src iface of
HsBootFile -> throwProgramError opts $ link_boot_mod_error (mi_module iface)
- _ -> pure (mkUniqDSet $ Set.toList $ dep_direct_pkgs (mi_deps iface), hmi)
+ _ -> pure ( mkUniqDSet $ [usg_mod | UsagePackageModule {usg_mod} <- mi_usages iface], hmi)
Nothing -> throwProgramError opts $
text "getLinkDeps: Home module not loaded" <+> ppr (gwib_mod gwib) <+> ppr uid
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/66de4a3ad9b15d48c86c69269ba2796…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/66de4a3ad9b15d48c86c69269ba2796…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/torsten.schmits/worker-debug] Deleted 1 commit: debug retainers
by Torsten Schmits (@torsten.schmits) 13 Jun '25
by Torsten Schmits (@torsten.schmits) 13 Jun '25
13 Jun '25
Torsten Schmits pushed to branch wip/torsten.schmits/worker-debug at Glasgow Haskell Compiler / GHC
WARNING: The push did not contain any new commits, but force pushed to delete the commits and changes below.
Deleted commits:
6d8c65a7 by Torsten Schmits at 2025-05-16T18:47:18+02:00
debug retainers
- - - - -
1 changed file:
- compiler/GHC.hs
Changes:
=====================================
compiler/GHC.hs
=====================================
@@ -625,7 +625,9 @@ setUnitDynFlagsNoCheck uid dflags1 = do
let old_hue = ue_findHomeUnitEnv uid (hsc_unit_env hsc_env)
let cached_unit_dbs = homeUnitEnv_unit_dbs old_hue
- (dbs,unit_state,home_unit,mconstants) <- liftIO $ initUnits logger dflags1 cached_unit_dbs (hsc_all_home_unit_ids hsc_env)
+ !all_ids = hsc_all_home_unit_ids hsc_env
+ !all_ids' = seq (ppr all_ids) all_ids
+ (dbs,unit_state,home_unit,mconstants) <- liftIO $ initUnits logger dflags1 cached_unit_dbs all_ids'
updated_dflags <- liftIO $ updatePlatformConstants dflags1 mconstants
let upd hue =
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6d8c65a7096bba40ba1ba208e8fbfb0…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6d8c65a7096bba40ba1ba208e8fbfb0…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T130103] rts/linker/LoadArchive: Don't rely on file extensions for identification
by Ben Gamari (@bgamari) 13 Jun '25
by Ben Gamari (@bgamari) 13 Jun '25
13 Jun '25
Ben Gamari pushed to branch wip/T130103 at Glasgow Haskell Compiler / GHC
Commits:
c77b9301 by Ben Gamari at 2025-06-13T09:58:47-04:00
rts/linker/LoadArchive: Don't rely on file extensions for identification
Previously archive members would be identified via their file extension,
as described in #13103. We now instead use a more principled approach,
relying on the magic number in the member's header.
As well, we refactor treatment of archive format detection to improve
code clarity and error handling.
Closes #13103.
- - - - -
1 changed file:
- rts/linker/LoadArchive.c
Changes:
=====================================
rts/linker/LoadArchive.c
=====================================
@@ -33,6 +33,7 @@
#define DEBUG_LOG(...) IF_DEBUG(linker, debugBelch("loadArchive: " __VA_ARGS__))
+
#if defined(darwin_HOST_OS) || defined(ios_HOST_OS)
/* Read 4 bytes and convert to host byte order */
static uint32_t read4Bytes(const char buf[static 4])
@@ -40,7 +41,7 @@ static uint32_t read4Bytes(const char buf[static 4])
return ntohl(*(uint32_t*)buf);
}
-static bool loadFatArchive(char tmp[static 20], FILE* f, pathchar* path)
+static bool loadFatArchive(char input[static 20], FILE* f, pathchar* path)
{
uint32_t nfat_arch, nfat_offset, cputype, cpusubtype;
#if defined(i386_HOST_ARCH)
@@ -58,8 +59,9 @@ static bool loadFatArchive(char tmp[static 20], FILE* f, pathchar* path)
#error Unknown Darwin architecture
#endif
- nfat_arch = read4Bytes(tmp + 4);
+ nfat_arch = read4Bytes(input + 4);
DEBUG_LOG("found a fat archive containing %d architectures\n", nfat_arch);
+ char tmp[20];
nfat_offset = 0;
for (uint32_t i = 0; i < nfat_arch; i++) {
/* search for the right arch */
@@ -108,7 +110,40 @@ static bool loadFatArchive(char tmp[static 20], FILE* f, pathchar* path)
}
#endif
-static StgBool readThinArchiveMember(int n, int memberSize, pathchar* path,
+enum ObjectFileFormat {
+ NotObject,
+ PortableExecutable,
+ ELF,
+ MachO32,
+ MachO64,
+};
+
+static enum ObjectFileFormat identifyObjectFile_(char* buf, size_t sz)
+{
+ if (sz > 4 && ((uint32_t*)buf)[0] == 0x5a4d) {
+ return PortableExecutable;
+ }
+ if (sz > 4 && memcmp(buf, "\x7f" "ELF", 4) == 0) {
+ return ELF;
+ }
+ if (sz > 4 && ((uint32_t*)buf)[0] == 0xfeedface) {
+ return MachO32;
+ }
+ if (sz > 4 && ((uint32_t*)buf)[0] == 0xfeedfacf) {
+ return MachO64;
+ }
+ return NotObject;
+}
+
+static enum ObjectFileFormat identifyObjectFile(FILE *f)
+{
+ char buf[32];
+ ssize_t sz = fread(buf, 1, 32, f);
+ CHECK(fseek(f, -sz, SEEK_CUR) == 0);
+ return identifyObjectFile_(buf, sz);
+}
+
+static bool readThinArchiveMember(int n, int memberSize, pathchar* path,
char* fileName, char* image)
{
bool has_succeeded = false;
@@ -149,7 +184,7 @@ inner_fail:
return has_succeeded;
}
-static bool checkFatArchive(char magic[static 20], FILE* f, pathchar* path)
+static bool checkFatArchive(char magic[static 4], FILE* f, pathchar* path)
{
bool success = false;
#if defined(darwin_HOST_OS) || defined(ios_HOST_OS)
@@ -241,46 +276,21 @@ lookupGNUArchiveIndex(int gnuFileIndexSize, char **fileName_,
return true;
}
-HsInt loadArchive_ (pathchar *path)
-{
- char *image = NULL;
- HsInt retcode = 0;
- int memberSize;
- int memberIdx = 0;
- FILE *f = NULL;
- int n;
- size_t thisFileNameSize = (size_t)-1; /* shut up bogus GCC warning */
- char *fileName;
- size_t fileNameSize;
- bool isGnuIndex, isThin, isImportLib;
- char *gnuFileIndex;
- int gnuFileIndexSize;
- int misalignment = 0;
-
- DEBUG_LOG("start\n");
- DEBUG_LOG("Loading archive `%" PATH_FMT "'\n", path);
+enum ArchiveFormat {
+ StandardArchive,
+ ThinArchive,
+ FatArchive,
+};
- /* Check that we haven't already loaded this archive.
- Ignore requests to load multiple times */
- if (isAlreadyLoaded(path)) {
- IF_DEBUG(linker,
- debugBelch("ignoring repeated load of %" PATH_FMT "\n", path));
- return 1; /* success */
+static bool identifyArchiveFormat(FILE *f, pathchar *path, enum ArchiveFormat *out)
+{
+ char tmp[8];
+ size_t n = fread(tmp, 1, 8, f);
+ if (n != 8) {
+ errorBelch("loadArchive: Failed reading header from `%" PATH_FMT "'", path); \
+ return false;
}
- gnuFileIndex = NULL;
- gnuFileIndexSize = 0;
-
- fileNameSize = 32;
- fileName = stgMallocBytes(fileNameSize, "loadArchive(fileName)");
-
- isThin = false;
- isImportLib = false;
-
- f = pathopen(path, WSTR("rb"));
- if (!f)
- FAIL("loadObj: can't read `%" PATH_FMT "'", path);
-
/* Check if this is an archive by looking for the magic "!<arch>\n"
* string. Usually, if this fails, we belch an error and return. On
* Darwin however, we may have a fat archive, which contains archives for
@@ -299,12 +309,10 @@ HsInt loadArchive_ (pathchar *path)
* its magic "!<arch>\n" string and continue processing just as if
* we had a single architecture archive.
*/
-
- n = fread ( tmp, 1, 8, f );
- if (n != 8) {
- FAIL("Failed reading header from `%" PATH_FMT "'", path);
+ if (strncmp(tmp, "!<arch>\n", 8) == 0) {
+ *out = StandardArchive;
+ return true;
}
- if (strncmp(tmp, "!<arch>\n", 8) == 0) {}
/* Check if this is a thin archive by looking for the magic string "!<thin>\n"
*
* ar thin libraries have the exact same format as normal archives except they
@@ -321,16 +329,59 @@ HsInt loadArchive_ (pathchar *path)
*
*/
else if (strncmp(tmp, "!<thin>\n", 8) == 0) {
- isThin = true;
+ *out = ThinArchive;
+ return true;
}
else {
bool success = checkFatArchive(tmp, f, path);
- if (!success)
- goto fail;
+ if (!success) {
+ return false;
+ }
+ *out = FatArchive;
+ return true;
}
+}
+
+HsInt loadArchive_ (pathchar *path)
+{
+ char *image = NULL;
+ HsInt retcode = 0;
+ int memberIdx = 0;
+ FILE *f = NULL;
+ size_t thisFileNameSize = (size_t) -1; /* shut up bogus GCC warning */
+ int misalignment = 0;
+
+ DEBUG_LOG("start\n");
+ DEBUG_LOG("Loading archive `%" PATH_FMT "'\n", path);
+
+ /* Check that we haven't already loaded this archive.
+ Ignore requests to load multiple times */
+ if (isAlreadyLoaded(path)) {
+ IF_DEBUG(linker,
+ debugBelch("ignoring repeated load of %" PATH_FMT "\n", path));
+ return 1; /* success */
+ }
+
+ char *gnuFileIndex = NULL;
+ int gnuFileIndexSize = 0;
+
+ size_t fileNameSize = 32;
+ char *fileName = stgMallocBytes(fileNameSize, "loadArchive(fileName)");
+
+ f = pathopen(path, WSTR("rb"));
+ if (!f)
+ FAIL("loadObj: can't read `%" PATH_FMT "'", path);
+
+ enum ArchiveFormat archive_fmt;
+ if (!identifyArchiveFormat(f, path, &archive_fmt)) {
+ FAIL("failed to identify archive format of %" PATH_FMT ".", path);
+ }
+ bool isThin = archive_fmt == ThinArchive;
+
DEBUG_LOG("loading archive contents\n");
while (1) {
+ size_t n;
DEBUG_LOG("reading at %ld\n", ftell(f));
n = fread ( fileName, 1, 16, f );
if (n != 16) {
@@ -350,6 +401,7 @@ HsInt loadArchive_ (pathchar *path)
}
#endif
+ char tmp[32];
n = fread ( tmp, 1, 12, f );
if (n != 12)
FAIL("Failed reading mod time from `%" PATH_FMT "'", path);
@@ -368,9 +420,16 @@ HsInt loadArchive_ (pathchar *path)
tmp[10] = '\0';
for (n = 0; isdigit(tmp[n]); n++);
tmp[n] = '\0';
- memberSize = atoi(tmp);
+ size_t memberSize;
+ {
+ char *end;
+ memberSize = strtol(tmp, &end, 10);
+ if (tmp == end) {
+ FAIL("Failed to decode member size");
+ }
+ }
- DEBUG_LOG("size of this archive member is %d\n", memberSize);
+ DEBUG_LOG("size of this archive member is %zd\n", memberSize);
n = fread ( tmp, 1, 2, f );
if (n != 2)
FAIL("Failed reading magic from `%" PATH_FMT "'", path);
@@ -378,7 +437,7 @@ HsInt loadArchive_ (pathchar *path)
FAIL("Failed reading magic from `%" PATH_FMT "' at %ld. Got %c%c",
path, ftell(f), tmp[0], tmp[1]);
- isGnuIndex = false;
+ bool isGnuIndex = false;
/* Check for BSD-variant large filenames */
if (0 == strncmp(fileName, "#1/", 3)) {
size_t n = 0;
@@ -459,12 +518,7 @@ HsInt loadArchive_ (pathchar *path)
DEBUG_LOG("Found member file `%s'\n", fileName);
- /* TODO: Stop relying on file extensions to determine input formats.
- Instead try to match file headers. See #13103. */
- isObject = (thisFileNameSize >= 2 && strncmp(fileName + thisFileNameSize - 2, ".o" , 2) == 0)
- || (thisFileNameSize >= 3 && strncmp(fileName + thisFileNameSize - 3, ".lo" , 3) == 0)
- || (thisFileNameSize >= 4 && strncmp(fileName + thisFileNameSize - 4, ".p_o", 4) == 0)
- || (thisFileNameSize >= 4 && strncmp(fileName + thisFileNameSize - 4, ".obj", 4) == 0);
+ enum ObjectFileFormat object_fmt = identifyObjectFile(f);
#if defined(OBJFORMAT_PEi386)
/*
@@ -478,13 +532,15 @@ HsInt loadArchive_ (pathchar *path)
*
* Linker members (e.g. filename / are skipped since they are not needed)
*/
- isImportLib = thisFileNameSize >= 4 && strncmp(fileName + thisFileNameSize - 4, ".dll", 4) == 0;
+ bool isImportLib = thisFileNameSize >= 4 && strncmp(fileName + thisFileNameSize - 4, ".dll", 4) == 0;
+#else
+ bool isImportLib = false;
#endif // windows
DEBUG_LOG("\tthisFileNameSize = %d\n", (int)thisFileNameSize);
- DEBUG_LOG("\tisObject = %d\n", isObject);
+ DEBUG_LOG("\tisObject = %d\n", object_fmt);
- if (isObject) {
+ if (object_fmt != NotObject) {
DEBUG_LOG("Member is an object file...loading...\n");
#if defined(darwin_HOST_OS) || defined(ios_HOST_OS)
@@ -509,7 +565,7 @@ HsInt loadArchive_ (pathchar *path)
}
else
{
- n = fread ( image, 1, memberSize, f );
+ size_t n = fread ( image, 1, memberSize, f );
if (n != memberSize) {
FAIL("error whilst reading `%" PATH_FMT "'", path);
}
@@ -527,9 +583,11 @@ HsInt loadArchive_ (pathchar *path)
ObjectCode *oc = mkOc(STATIC_OBJECT, path, image, memberSize, false, archiveMemberName,
misalignment);
#if defined(OBJFORMAT_MACHO)
+ ASSERT(object_fmt == MachO32 || object_fmt == MachO64);
ocInit_MachO( oc );
#endif
#if defined(OBJFORMAT_ELF)
+ ASSERT(object_fmt == ELF);
ocInit_ELF( oc );
#endif
@@ -574,7 +632,7 @@ while reading filename from `%" PATH_FMT "'", path);
"Skipping...\n");
n = fseek(f, memberSize, SEEK_CUR);
if (n != 0)
- FAIL("error whilst seeking by %d in `%" PATH_FMT "'",
+ FAIL("error whilst seeking by %zd in `%" PATH_FMT "'",
memberSize, path);
}
#endif
@@ -585,7 +643,7 @@ while reading filename from `%" PATH_FMT "'", path);
if (!isThin || thisFileNameSize == 0) {
n = fseek(f, memberSize, SEEK_CUR);
if (n != 0)
- FAIL("error whilst seeking by %d in `%" PATH_FMT "'",
+ FAIL("error whilst seeking by %zd in `%" PATH_FMT "'",
memberSize, path);
}
}
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c77b93013bcef8098a21f5d830aa4f4…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c77b93013bcef8098a21f5d830aa4f4…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
f93798ba by Cheng Shao at 2025-06-13T09:52:35-04:00
libffi: update to 3.5.1
Bumps libffi submodule.
- - - - -
1 changed file:
- libffi-tarballs
Changes:
=====================================
libffi-tarballs
=====================================
@@ -1 +1 @@
-Subproject commit ac7fa3132d382056837cad297ab4c66418febb69
+Subproject commit a5480d7e7f86a9bb5b44dd1156a92f69f7c185ec
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f93798ba57c4a4a75afe0b6e9ea9811…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f93798ba57c4a4a75afe0b6e9ea9811…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][master] Refactor the treatment of nested Template Haskell splices
by Marge Bot (@marge-bot) 13 Jun '25
by Marge Bot (@marge-bot) 13 Jun '25
13 Jun '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
1d02798e by Matthew Pickering at 2025-06-13T09:51:54-04:00
Refactor the treatment of nested Template Haskell splices
* The difference between a normal splice, a quasiquoter and implicit
splice caused by lifting is stored in the AST after renaming.
* Information that the renamer learns about splices is stored in the
relevant splice extension points (XUntypedSpliceExpr, XQuasiQuote).
* Normal splices and quasi quotes record the flavour of splice
(exp/pat/dec etc)
* Implicit lifting stores information about why the lift was attempted,
so if it fails, that can be reported to the user.
* After renaming, the decision taken to attempt to implicitly lift a
variable is stored in the `XXUntypedSplice` extension field in the
`HsImplicitLiftSplice` constructor.
* Since all the information is stored in the AST, in `HsUntypedSplice`,
the type of `PendingRnSplice` now just stores a `HsUntypedSplice`.
* Error messages since the original program can be easily
printed, this is noticeable in the case of implicit lifting.
* The user-written syntax is directly type-checked. Before, some
desugaring took place in the
* Fixes .hie files to work better with nested splices (nested splices
are not indexed)
* The location of the quoter in a quasiquote is now located, so error
messages will precisely point to it (and again, it is indexed by hie
files)
In the future, the typechecked AST should also retain information about
the splices and the specific desugaring being left to the desugarer.
Also, `runRnSplice` should call `tcUntypedSplice`, otherwise the
typechecking logic is duplicated (see the `QQError` and `QQTopError`
tests for a difference caused by this).
- - - - -
46 changed files:
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Expr.hs-boot
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Gen/Splice.hs-boot
- compiler/GHC/Tc/Types/ErrCtxt.hs
- compiler/GHC/Tc/Types/TH.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/ThLevelIndex.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- testsuite/tests/diagnostic-codes/codes.stdout
- testsuite/tests/linear/should_fail/LinearTHFail.stderr
- testsuite/tests/linters/notes.stdout
- testsuite/tests/perf/compiler/hard_hole_fits.stderr
- testsuite/tests/quasiquotation/T3953.stderr
- + testsuite/tests/quotes/QQError.hs
- + testsuite/tests/quotes/QQError.stderr
- testsuite/tests/quotes/T10384.stderr
- testsuite/tests/quotes/TH_localname.stderr
- testsuite/tests/quotes/all.T
- + testsuite/tests/th/QQInQuote.hs
- + testsuite/tests/th/QQTopError.hs
- + testsuite/tests/th/QQTopError.stderr
- testsuite/tests/th/T10598_TH.stderr
- testsuite/tests/th/T14681.stderr
- testsuite/tests/th/T17804.stderr
- testsuite/tests/th/T5508.stderr
- testsuite/tests/th/TH_Lift.stderr
- testsuite/tests/th/all.T
- testsuite/tests/th/overloaded/TH_overloaded_constraints_fail.stderr
- utils/check-exact/ExactPrint.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1d02798e73e482d300f9f526f0a6094…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1d02798e73e482d300f9f526f0a6094…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][master] Improve redundant constraints for instance decls
by Marge Bot (@marge-bot) 13 Jun '25
by Marge Bot (@marge-bot) 13 Jun '25
13 Jun '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
19f20861 by Simon Peyton Jones at 2025-06-13T09:51:11-04:00
Improve redundant constraints for instance decls
Addresses #25992, which showed that the default methods
of an instance decl could make GHC fail to report redundant
constraints.
Figuring out how to do this led me to refactor the computation
of redundant constraints. See the entirely rewritten
Note [Tracking redundant constraints]
in GHC.Tc.Solver.Solve
- - - - -
14 changed files:
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Instantiate.hs
- testsuite/tests/dependent/should_fail/T13135_simple.stderr
- + testsuite/tests/typecheck/should_compile/T25992.hs
- + testsuite/tests/typecheck/should_compile/T25992.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/tcfail097.stderr
Changes:
=====================================
compiler/GHC/Tc/Errors.hs
=====================================
@@ -399,13 +399,6 @@ warnRedundantConstraints ctxt env info redundant_evs
| null redundant_evs
= return ()
- -- Do not report redundant constraints for quantified constraints
- -- See (RC4) in Note [Tracking redundant constraints]
- -- Fortunately it is easy to spot implications constraints that arise
- -- from quantified constraints, from their SkolInfo
- | InstSkol (IsQC {}) _ <- info
- = return ()
-
| SigSkol user_ctxt _ _ <- info
-- When dealing with a user-written type signature,
-- we want to add "In the type signature for f".
=====================================
compiler/GHC/Tc/Solver/Default.hs
=====================================
@@ -247,11 +247,11 @@ tryUnsatisfiableGivens wc =
; solveAgainIf did_work final_wc }
where
go_wc (WC { wc_simple = wtds, wc_impl = impls, wc_errors = errs })
- = do impls' <- mapMaybeBagM go_impl impls
+ = do impls' <- mapBagM go_impl impls
return $ WC { wc_simple = wtds, wc_impl = impls', wc_errors = errs }
go_impl impl
| isSolvedStatus (ic_status impl)
- = return $ Just impl
+ = return impl
-- Is there a Given with type "Unsatisfiable msg"?
-- If so, use it to solve all other Wanteds.
| unsat_given:_ <- mapMaybe unsatisfiableEv_maybe (ic_given impl)
@@ -271,24 +271,26 @@ unsatisfiableEv_maybe v = (v,) <$> isUnsatisfiableCt_maybe (idType v)
-- | We have an implication with an 'Unsatisfiable' Given; use that Given to
-- solve all the other Wanted constraints, including those nested within
-- deeper implications.
-solveImplicationUsingUnsatGiven :: (EvVar, Type) -> Implication -> TcS (Maybe Implication)
+solveImplicationUsingUnsatGiven :: (EvVar, Type) -> Implication -> TcS Implication
solveImplicationUsingUnsatGiven
unsat_given@(given_ev,_)
- impl@(Implic { ic_wanted = wtd, ic_tclvl = tclvl, ic_binds = ev_binds_var, ic_need_inner = inner })
+ impl@(Implic { ic_wanted = wtd, ic_tclvl = tclvl, ic_binds = ev_binds_var
+ , ic_need_implic = inner })
| isCoEvBindsVar ev_binds_var
-- We can't use Unsatisfiable evidence in kinds.
-- See Note [Coercion evidence only] in GHC.Tc.Types.Evidence.
- = return $ Just impl
+ = return impl
| otherwise
= do { wcs <- nestImplicTcS ev_binds_var tclvl $ go_wc wtd
; setImplicationStatus $
impl { ic_wanted = wcs
- , ic_need_inner = inner `extendVarSet` given_ev } }
+ , ic_need_implic = inner `extendEvNeedSet` given_ev } }
+ -- Record that the Given is needed; I'm not certain why
where
go_wc :: WantedConstraints -> TcS WantedConstraints
go_wc wc@(WC { wc_simple = wtds, wc_impl = impls })
= do { mapBagM_ go_simple wtds
- ; impls <- mapMaybeBagM (solveImplicationUsingUnsatGiven unsat_given) impls
+ ; impls <- mapBagM (solveImplicationUsingUnsatGiven unsat_given) impls
; return $ wc { wc_simple = emptyBag, wc_impl = impls } }
go_simple :: Ct -> TcS ()
go_simple ct = case ctEvidence ct of
@@ -399,21 +401,21 @@ tryConstraintDefaulting wc
where
go_wc :: WantedConstraints -> TcS WantedConstraints
go_wc wc@(WC { wc_simple = simples, wc_impl = implics })
- = do { simples' <- mapMaybeBagM go_simple simples
- ; mb_implics <- mapMaybeBagM go_implic implics
- ; return (wc { wc_simple = simples', wc_impl = mb_implics }) }
+ = do { simples' <- mapMaybeBagM go_simple simples
+ ; implics' <- mapBagM go_implic implics
+ ; return (wc { wc_simple = simples', wc_impl = implics' }) }
go_simple :: Ct -> TcS (Maybe Ct)
go_simple ct = do { solved <- tryCtDefaultingStrategy ct
; if solved then return Nothing
else return (Just ct) }
- go_implic :: Implication -> TcS (Maybe Implication)
+ go_implic :: Implication -> TcS Implication
-- The Maybe is because solving the CallStack constraint
-- may well allow us to discard the implication entirely
go_implic implic
| isSolvedStatus (ic_status implic)
- = return (Just implic) -- Nothing to solve inside here
+ = return implic -- Nothing to solve inside here
| otherwise
= do { wanteds <- setEvBindsTcS (ic_binds implic) $
-- defaultCallStack sets a binding, so
=====================================
compiler/GHC/Tc/Solver/InertSet.hs
=====================================
@@ -2089,18 +2089,8 @@ solveOneFromTheOther.
(a) If both are GivenSCOrigin, choose the one that is unblocked if possible
according to Note [Solving superclass constraints] in GHC.Tc.TyCl.Instance.
- (b) Prefer constraints that are not superclass selections. Example:
-
- f :: (Eq a, Ord a) => a -> Bool
- f x = x == x
-
- Eager superclass expansion gives us two [G] Eq a constraints. We
- want to keep the one from the user-written Eq a, not the superclass
- selection. This means we report the Ord a as redundant with
- -Wredundant-constraints, not the Eq a.
-
- Getting this wrong was #20602. See also
- Note [Tracking redundant constraints] in GHC.Tc.Solver.
+ (b) Prefer constraints that are not superclass selections. See
+ (TRC3) in Note [Tracking redundant constraints] in GHC.Tc.Solver.
(c) If both are GivenSCOrigin, chooose the one with the shallower
superclass-selection depth, in the hope of identifying more correct
=====================================
compiler/GHC/Tc/Solver/Solve.hs
=====================================
@@ -42,6 +42,7 @@ import GHC.Types.Var( EvVar, tyVarKind )
import GHC.Types.Var.Env
import GHC.Types.Var.Set
import GHC.Types.Basic ( IntWithInf, intGtLimit )
+import GHC.Types.Unique.Set( nonDetStrictFoldUniqSet )
import GHC.Data.Bag
@@ -51,9 +52,10 @@ import GHC.Utils.Misc
import GHC.Driver.Session
-import Data.List( deleteFirstsBy )
import Control.Monad
+
+import Data.List( deleteFirstsBy )
import Data.Foldable ( traverse_ )
import Data.Maybe ( mapMaybe )
import qualified Data.Semigroup as S
@@ -277,10 +279,10 @@ solveNestedImplications implics
; traceTcS "solveNestedImplications end }" $
vcat [ text "unsolved_implics =" <+> ppr unsolved_implics ]
- ; return (catBagMaybes unsolved_implics) }
+ ; return unsolved_implics }
-solveImplication :: Implication -- Wanted
- -> TcS (Maybe Implication) -- Simplified implication (empty or singleton)
+solveImplication :: Implication -- Wanted
+ -> TcS Implication -- Simplified implication (empty or singleton)
-- Precondition: The TcS monad contains an empty worklist and given-only inerts
-- which after trying to solve this implication we must restore to their original value
solveImplication imp@(Implic { ic_tclvl = tclvl
@@ -290,7 +292,7 @@ solveImplication imp@(Implic { ic_tclvl = tclvl
, ic_info = info
, ic_status = status })
| isSolvedStatus status
- = return (Just imp) -- Do nothing
+ = return imp -- Do nothing
| otherwise -- Even for IC_Insoluble it is worth doing more work
-- The insoluble stuff might be in one sub-implication
@@ -350,90 +352,63 @@ solveImplication imp@(Implic { ic_tclvl = tclvl
-}
----------------------
-setImplicationStatus :: Implication -> TcS (Maybe Implication)
+setImplicationStatus :: Implication -> TcS Implication
-- Finalise the implication returned from solveImplication,
--- setting the ic_status field
+-- * Set the ic_status field
+-- * Prune unnecessary evidence bindings
+-- * Prune unnecessary child implications
-- Precondition: the ic_status field is not already IC_Solved
--- Return Nothing if we can discard the implication altogether
-setImplicationStatus implic@(Implic { ic_status = old_status
- , ic_info = info
- , ic_wanted = wc
- , ic_given = givens })
- | assertPpr (not (isSolvedStatus old_status)) (ppr info) $
+setImplicationStatus implic@(Implic { ic_status = old_status
+ , ic_info = info
+ , ic_wanted = wc })
+ = assertPpr (not (isSolvedStatus old_status)) (ppr info) $
-- Precondition: we only set the status if it is not already solved
- not (isSolvedWC pruned_wc)
- = do { traceTcS "setImplicationStatus(not-all-solved) {" (ppr implic)
-
- ; implic <- neededEvVars implic
-
- ; let new_status | insolubleWC pruned_wc = IC_Insoluble
- | otherwise = IC_Unsolved
- new_implic = implic { ic_status = new_status
- , ic_wanted = pruned_wc }
-
- ; traceTcS "setImplicationStatus(not-all-solved) }" (ppr new_implic)
-
- ; return $ Just new_implic }
-
- | otherwise -- Everything is solved
- -- Set status to IC_Solved,
- -- and compute the dead givens and outer needs
- -- See Note [Tracking redundant constraints]
- = do { traceTcS "setImplicationStatus(all-solved) {" (ppr implic)
-
- ; implic@(Implic { ic_need_inner = need_inner
- , ic_need_outer = need_outer }) <- neededEvVars implic
-
- ; bad_telescope <- checkBadTelescope implic
-
- ; let warn_givens = findUnnecessaryGivens info need_inner givens
-
- discard_entire_implication -- Can we discard the entire implication?
- = null warn_givens -- No warning from this implication
- && not bad_telescope
- && isEmptyWC pruned_wc -- No live children
- && isEmptyVarSet need_outer -- No needed vars to pass up to parent
-
- final_status
- | bad_telescope = IC_BadTelescope
- | otherwise = IC_Solved { ics_dead = warn_givens }
- final_implic = implic { ic_status = final_status
- , ic_wanted = pruned_wc }
-
- ; traceTcS "setImplicationStatus(all-solved) }" $
- vcat [ text "discard:" <+> ppr discard_entire_implication
- , text "new_implic:" <+> ppr final_implic ]
-
- ; return $ if discard_entire_implication
- then Nothing
- else Just final_implic }
- where
- WC { wc_simple = simples, wc_impl = implics, wc_errors = errs } = wc
-
- pruned_implics = filterBag keep_me implics
- pruned_wc = WC { wc_simple = simples
- , wc_impl = pruned_implics
- , wc_errors = errs } -- do not prune holes; these should be reported
-
- keep_me :: Implication -> Bool
- keep_me ic
- | IC_Solved { ics_dead = dead_givens } <- ic_status ic
- -- Fully solved
- , null dead_givens -- No redundant givens to report
- , isEmptyBag (wc_impl (ic_wanted ic))
- -- And no children that might have things to report
- = False -- Tnen we don't need to keep it
- | otherwise
- = True -- Otherwise, keep it
+ do { traceTcS "setImplicationStatus {" (ppr implic)
+
+ ; let solved = isSolvedWC wc
+ ; new_implic <- neededEvVars implic
+ ; bad_telescope <- if solved then checkBadTelescope implic
+ else return False
+
+ ; let new_status | insolubleWC wc = IC_Insoluble
+ | not solved = IC_Unsolved
+ | bad_telescope = IC_BadTelescope
+ | otherwise = IC_Solved { ics_dead = dead_givens }
+ dead_givens = findRedundantGivens new_implic
+ new_wc = pruneImplications wc
+
+ final_implic = new_implic { ic_status = new_status
+ , ic_wanted = new_wc }
+
+ ; traceTcS "setImplicationStatus }" (ppr final_implic)
+ ; return final_implic }
+
+pruneImplications :: WantedConstraints -> WantedConstraints
+-- We have now recorded the `ic_need` variables of the child
+-- implications (in `ic_need_implics` of the parent) so we can
+-- delete any unnecessary children.
+pruneImplications wc@(WC { wc_impl = implics })
+ = wc { wc_impl = filterBag keep_me implics }
+ -- Do not prune holes; these should be reported
+ where
+ keep_me :: Implication -> Bool
+ keep_me (Implic { ic_status = status, ic_wanted = wanted })
+ | IC_Solved { ics_dead = dead_givens } <- status -- Fully solved
+ , null dead_givens -- No redundant givens to report
+ , isEmptyBag (wc_impl wanted) -- No children that might have things to report
+ = False
+ | otherwise
+ = True -- Otherwise, keep it
-findUnnecessaryGivens :: SkolemInfoAnon -> VarSet -> [EvVar] -> [EvVar]
-findUnnecessaryGivens info need_inner givens
+findRedundantGivens :: Implication -> [EvVar]
+findRedundantGivens (Implic { ic_info = info, ic_need = need, ic_given = givens })
| not (warnRedundantGivens info) -- Don't report redundant constraints at all
- = []
+ = [] -- See (TRC4) of Note [Tracking redundant constraints]
| not (null unused_givens) -- Some givens are literally unused
= unused_givens
+ -- Only try this if unused_givens is empty: see (TRC2a)
| otherwise -- All givens are used, but some might
= redundant_givens -- still be redundant e.g. (Eq a, Ord a)
@@ -443,11 +418,13 @@ findUnnecessaryGivens info need_inner givens
unused_givens = filterOut is_used givens
+ needed_givens_ignoring_default_methods = ens_fvs need
is_used given = is_type_error given
- || given `elemVarSet` need_inner
+ || given `elemVarSet` needed_givens_ignoring_default_methods
|| (in_instance_decl && is_improving (idType given))
- minimal_givens = mkMinimalBySCs evVarPred givens
+ minimal_givens = mkMinimalBySCs evVarPred givens -- See (TRC2)
+
is_minimal = (`elemVarSet` mkVarSet minimal_givens)
redundant_givens
| in_instance_decl = []
@@ -459,6 +436,26 @@ findUnnecessaryGivens info need_inner givens
is_improving pred -- (transSuperClasses p) does not include p
= any isImprovementPred (pred : transSuperClasses pred)
+warnRedundantGivens :: SkolemInfoAnon -> Bool
+warnRedundantGivens (SigSkol ctxt _ _)
+ = case ctxt of
+ FunSigCtxt _ rrc -> reportRedundantConstraints rrc
+ ExprSigCtxt rrc -> reportRedundantConstraints rrc
+ _ -> False
+
+warnRedundantGivens (InstSkol from _)
+ -- Do not report redundant constraints for quantified constraints
+ -- See (TRC4) in Note [Tracking redundant constraints]
+ -- Fortunately it is easy to spot implications constraints that arise
+ -- from quantified constraints, from their SkolInfo
+ = case from of
+ IsQC {} -> False
+ IsClsInst {} -> True
+
+ -- To think about: do we want to report redundant givens for
+ -- pattern synonyms, PatSynSigSkol? c.f #9953, comment:21.
+warnRedundantGivens _ = False
+
{- Note [Redundant constraints in instance decls]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Instance declarations are special in two ways:
@@ -510,21 +507,10 @@ checkBadTelescope (Implic { ic_info = info
| otherwise
= go (later_skols `extendVarSet` one_skol) earlier_skols
-warnRedundantGivens :: SkolemInfoAnon -> Bool
-warnRedundantGivens (SigSkol ctxt _ _)
- = case ctxt of
- FunSigCtxt _ rrc -> reportRedundantConstraints rrc
- ExprSigCtxt rrc -> reportRedundantConstraints rrc
- _ -> False
-
- -- To think about: do we want to report redundant givens for
- -- pattern synonyms, PatSynSigSkol? c.f #9953, comment:21.
-warnRedundantGivens (InstSkol {}) = True
-warnRedundantGivens _ = False
-
neededEvVars :: Implication -> TcS Implication
-- Find all the evidence variables that are "needed",
--- and delete dead evidence bindings
+-- /and/ delete dead evidence bindings
+--
-- See Note [Tracking redundant constraints]
-- See Note [Delete dead Given evidence bindings]
--
@@ -540,52 +526,93 @@ neededEvVars :: Implication -> TcS Implication
-- Then a2 is needed too
--
-- - Prune out all Given bindings that are not needed
---
--- - From the 'needed' set, delete ev_bndrs, the binders of the
--- evidence bindings, to give the final needed variables
---
-neededEvVars implic@(Implic { ic_given = givens
- , ic_binds = ev_binds_var
- , ic_wanted = WC { wc_impl = implics }
- , ic_need_inner = old_needs })
+
+neededEvVars implic@(Implic { ic_info = info
+ , ic_binds = ev_binds_var
+ , ic_wanted = WC { wc_impl = implics }
+ , ic_need_implic = old_need_implic -- See (TRC1)
+ })
= do { ev_binds <- TcS.getTcEvBindsMap ev_binds_var
; tcvs <- TcS.getTcEvTyCoVars ev_binds_var
- ; let seeds1 = foldr add_implic_seeds old_needs implics
- seeds2 = nonDetStrictFoldEvBindMap add_wanted seeds1 ev_binds
- -- It's OK to use a non-deterministic fold here
- -- because add_wanted is commutative
- seeds3 = seeds2 `unionVarSet` tcvs
- need_inner = findNeededEvVars ev_binds seeds3
- live_ev_binds = filterEvBindMap (needed_ev_bind need_inner) ev_binds
- need_outer = varSetMinusEvBindMap need_inner live_ev_binds
- `delVarSetList` givens
-
+ ; let -- Find the variables needed by `implics`
+ new_need_implic@(ENS { ens_dms = dm_seeds, ens_fvs = other_seeds })
+ = foldr add_implic old_need_implic implics
+ -- Start from old_need_implic! See (TRC1)
+
+ -- Get the variables needed by the solved bindings
+ -- (It's OK to use a non-deterministic fold here
+ -- because add_wanted is commutative.)
+ seeds_w = nonDetStrictFoldEvBindMap add_wanted tcvs ev_binds
+
+ need_ignoring_dms = findNeededGivenEvVars ev_binds (other_seeds `unionVarSet` seeds_w)
+ need_from_dms = findNeededGivenEvVars ev_binds dm_seeds
+ need_full = need_ignoring_dms `unionVarSet` need_from_dms
+
+ -- `need`: the Givens from outer scopes that are used in this implication
+ -- is_dm_skol: see (TRC5)
+ need | is_dm_skol info = ENS { ens_dms = trim ev_binds need_full
+ , ens_fvs = emptyVarSet }
+ | otherwise = ENS { ens_dms = trim ev_binds need_from_dms
+ , ens_fvs = trim ev_binds need_ignoring_dms }
+
+ -- Delete dead Given evidence bindings
+ -- See Note [Delete dead Given evidence bindings]
+ ; let live_ev_binds = filterEvBindMap (needed_ev_bind need_full) ev_binds
; TcS.setTcEvBindsMap ev_binds_var live_ev_binds
- -- See Note [Delete dead Given evidence bindings]
; traceTcS "neededEvVars" $
- vcat [ text "old_needs:" <+> ppr old_needs
- , text "seeds3:" <+> ppr seeds3
+ vcat [ text "old_need_implic:" <+> ppr old_need_implic
+ , text "new_need_implic:" <+> ppr new_need_implic
, text "tcvs:" <+> ppr tcvs
+ , text "need_ignoring_dms:" <+> ppr need_ignoring_dms
+ , text "need_from_dms:" <+> ppr need_from_dms
+ , text "need:" <+> ppr need
, text "ev_binds:" <+> ppr ev_binds
, text "live_ev_binds:" <+> ppr live_ev_binds ]
-
- ; return (implic { ic_need_inner = need_inner
- , ic_need_outer = need_outer }) }
+ ; return (implic { ic_need = need
+ , ic_need_implic = new_need_implic }) }
where
- add_implic_seeds (Implic { ic_need_outer = needs }) acc
- = needs `unionVarSet` acc
-
- needed_ev_bind needed (EvBind { eb_lhs = ev_var
- , eb_info = info })
- | EvBindGiven{} <- info = ev_var `elemVarSet` needed
- | otherwise = True -- Keep all wanted bindings
-
- add_wanted :: EvBind -> VarSet -> VarSet
- add_wanted (EvBind { eb_info = info, eb_rhs = rhs }) needs
- | EvBindGiven{} <- info = needs -- Add the rhs vars of the Wanted bindings only
- | otherwise = evVarsOfTerm rhs `unionVarSet` needs
+ trim :: EvBindMap -> VarSet -> VarSet
+ -- Delete variables bound by Givens or bindings
+ trim ev_binds needs = needs `varSetMinusEvBindMap` ev_binds
+
+ add_implic :: Implication -> EvNeedSet -> EvNeedSet
+ add_implic (Implic { ic_given = givens, ic_need = need }) acc
+ = (need `delGivensFromEvNeedSet` givens) `unionEvNeedSet` acc
+
+ needed_ev_bind needed (EvBind { eb_lhs = ev_var, eb_info = info })
+ | EvBindGiven{} <- info = ev_var `elemVarSet` needed
+ | otherwise = True -- Keep all wanted bindings
+
+ add_wanted :: EvBind -> VarSet -> VarSet
+ add_wanted (EvBind { eb_info = info, eb_rhs = rhs }) needs
+ | EvBindGiven{} <- info = needs -- Add the rhs vars of the Wanted bindings only
+ | otherwise = evVarsOfTerm rhs `unionVarSet` needs
+
+ is_dm_skol :: SkolemInfoAnon -> Bool
+ is_dm_skol (MethSkol _ is_dm) = is_dm
+ is_dm_skol _ = False
+
+findNeededGivenEvVars :: EvBindMap -> VarSet -> VarSet
+-- Find all the Given evidence needed by seeds,
+-- looking transitively through bindings for Givens (only)
+findNeededGivenEvVars ev_binds seeds
+ = transCloVarSet also_needs seeds
+ where
+ also_needs :: VarSet -> VarSet
+ also_needs needs = nonDetStrictFoldUniqSet add emptyVarSet needs
+ -- It's OK to use a non-deterministic fold here because we immediately
+ -- forget about the ordering by creating a set
+
+ add :: Var -> VarSet -> VarSet
+ add v needs
+ | Just ev_bind <- lookupEvBind ev_binds v
+ , EvBind { eb_info = EvBindGiven, eb_rhs = rhs } <- ev_bind
+ -- Look at Given bindings only
+ = evVarsOfTerm rhs `unionVarSet` needs
+ | otherwise
+ = needs
-------------------------------------------------
simplifyDelayedErrors :: Bag DelayedError -> TcS (Bag DelayedError)
@@ -707,117 +734,84 @@ in GHC.Tc.Gen.HsType.
Note [Tracking redundant constraints]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-With Opt_WarnRedundantConstraints, GHC can report which
-constraints of a type signature (or instance declaration) are
-redundant, and can be omitted. Here is an overview of how it
-works.
-
-This is all tested in typecheck/should_compile/T20602 (among
-others).
-
------ What is a redundant constraint?
-
-* The things that can be redundant are precisely the Given
- constraints of an implication.
-
-* A constraint can be redundant in two different ways:
- a) It is not needed by the Wanted constraints covered by the
- implication E.g.
- f :: Eq a => a -> Bool
- f x = True -- Equality not used
- b) It is implied by other givens. E.g.
- f :: (Eq a, Ord a) => blah -- Eq a unnecessary
- g :: (Eq a, a~b, Eq b) => blah -- Either Eq a or Eq b unnecessary
-
-* To find (a) we need to know which evidence bindings are 'wanted';
- hence the eb_is_given field on an EvBind.
-
-* To find (b), we use mkMinimalBySCs on the Givens to see if any
- are unnecessary.
-
------ How tracking works
-
-(RC1) When two Givens are the same, we drop the evidence for the one
- that requires more superclass selectors. This is done
- according to 2(c) of Note [Replacement vs keeping] in GHC.Tc.Solver.InertSet.
-
-(RC2) The ic_need fields of an Implic records in-scope (given) evidence
- variables bound by the context, that were needed to solve this
- implication (so far). See the declaration of Implication.
-
-(RC3) setImplicationStatus:
- When the constraint solver finishes solving all the wanteds in
- an implication, it sets its status to IC_Solved
-
- - The ics_dead field, of IC_Solved, records the subset of this
- implication's ic_given that are redundant (not needed).
-
- - We compute which evidence variables are needed by an implication
- in setImplicationStatus. A variable is needed if
- a) it is free in the RHS of a Wanted EvBind,
- b) it is free in the RHS of an EvBind whose LHS is needed, or
- c) it is in the ics_need of a nested implication.
-
- - After computing which variables are needed, we then look at the
- remaining variables for internal redundancies. This is case (b)
- from above. This is also done in setImplicationStatus.
- Note that we only look for case (b) if case (a) shows up empty,
- as exemplified below.
-
- - We need to be careful not to discard an implication
- prematurely, even one that is fully solved, because we might
- thereby forget which variables it needs, and hence wrongly
- report a constraint as redundant. But we can discard it once
- its free vars have been incorporated into its parent; or if it
- simply has no free vars. This careful discarding is also
- handled in setImplicationStatus.
-
-(RC4) We do not want to report redundant constraints for implications
- that come from quantified constraints. Example #23323:
- data T a
- instance Show (T a) where ... -- No context!
- foo :: forall f c. (forall a. c a => Show (f a)) => Proxy c -> f Int -> Int
- bar = foo @T @Eq
-
- The call to `foo` gives us
- [W] d : (forall a. Eq a => Show (T a))
- To solve this, GHC.Tc.Solver.Solve.solveForAll makes an implication constraint:
- forall a. Eq a => [W] ds : Show (T a)
- and because of the degnerate instance for `Show (T a)`, we don't need the `Eq a`
- constraint. But we don't want to report it as redundant!
-
-* Examples:
+With Opt_WarnRedundantConstraints, GHC can report which constraints of a type
+signature (or instance declaration) are redundant, and can be omitted. Here is
+an overview of how it works.
- f, g, h :: (Eq a, Ord a) => a -> Bool
- f x = x == x
- g x = x > x
- h x = x == x && x > x
+This is all tested in typecheck/should_compile/T20602 (among others).
- All three will discover that they have two [G] Eq a constraints:
- one as given and one extracted from the Ord a constraint. They will
- both discard the latter, as noted above and in
- Note [Replacement vs keeping] in GHC.Tc.Solver.InertSet.
+How tracking works:
- The body of f uses the [G] Eq a, but not the [G] Ord a. It will
- report a redundant Ord a using the logic for case (a).
+* We maintain the `ic_need` field in an implication:
+ ic_need: the set of Given evidence variables that are needed somewhere
+ inside this implication; and are bound either by this implication
+ or by an enclosing one.
- The body of g uses the [G] Ord a, but not the [G] Eq a. It will
- report a redundant Eq a using the logic for case (a).
+* `setImplicationStatus` does all the work:
+ - When the constraint solver finishes solving all the wanteds in
+ an implication, it sets its status to IC_Solved
- The body of h uses both [G] Ord a and [G] Eq a. Case (a) will
- thus come up with nothing redundant. But then, the case (b)
- check will discover that Eq a is redundant and report this.
+ - `neededEvVars`: computes which evidence variables are needed by an
+ implication in `setImplicationStatus`. A variable is needed if
- If we did case (b) even when case (a) reports something, then
- we would report both constraints as redundant for f, which is
- terrible.
+ a) It is in the ic_need field of this implication, computed in
+ a previous call to `setImplicationStatus`; see (TRC1)
------ Reporting redundant constraints
+ b) It is in the ics_need of a nested implication; see `add_implic`
+ in `neededEvVars`
+
+ c) It is free in the RHS of any /Wanted/ EvBind; each such binding
+ solves a Wanted, so we want them all. See `add_wanted` in
+ `neededEvVars`
+
+ d) It is free in the RHS of a /Given/ EvBind whose LHS is needed:
+ see `findNeededGivenEvVars` called from `neededEvVars`.
+
+ - Next, if the final status is IC_Solved, `setImplicationStatus` uses
+ `findRedundantGivens` to decide which of this implication's Givens
+ are redundant.
+
+ - It also uses `pruneImplications` to discard any now-unnecessary child
+ implications.
+
+* GHC.Tc.Errors does the actual warning, in `warnRedundantConstraints`.
+
+
+Wrinkles:
+
+(TRC1) `pruneImplications` drops any sub-implications of an Implication
+ that are irrelevant for error reporting:
+ - no unsolved wanteds
+ - no sub-implications
+ - no redundant givens to report
+ But in doing so we must not lose track of the variables that those implications
+ needed! So we track the ic_needs of all child implications in `ic_need_implics`.
+ Crucially, this set includes things need by child implications that have been
+ discarded by `pruneImplications`.
+
+(TRC2) A Given can be redundant because it is implied by other Givens
+ f :: (Eq a, Ord a) => blah -- Eq a unnecessary
+ g :: (Eq a, a~b, Eq b) => blah -- Either Eq a or Eq b unnecessary
+ We nail this by using `mkMinimalBySCs` in `findRedundantGivens`.
+ (TRC2a) But NOTE that we only attempt this mkMinimalBySCs stuff if all Givens
+ used by evidence bindings. Example:
+ f :: (Eq a, Ord a) => a -> Bool
+ f x = x == x
+ We report (Ord a) as unused because it is. But we must not also report (Eq a)
+ as unused because it is a superclass of Ord!
-* GHC.Tc.Errors does the actual warning, in warnRedundantConstraints.
+(TRC3) When two Givens are the same, prefer one that does not involve superclass
+ selection, or more generally has shallower superclass-selection depth:
+ see 2(b,c) in Note [Replacement vs keeping] in GHC.Tc.Solver.InertSet.
+ e.g f :: (Eq a, Ord a) => a -> Bool
+ f x = x == x
+ Eager superclass expansion gives us two [G] Eq a constraints. We want to keep
+ the one from the user-written Eq a, not the superclass selection. This means
+ we report the Ord a as redundant with -Wredundant-constraints, not the Eq a.
+ Getting this wrong was #20602.
-* We don't report redundant givens for *every* implication; only
- for those which reply True to GHC.Tc.Solver.warnRedundantGivens:
+(TRC4) We don't compute redundant givens for *every* implication; only
+ for those which reply True to `warnRedundantGivens`:
- For example, in a class declaration, the default method *can*
use the class constraint, but it certainly doesn't *have* to,
@@ -836,9 +830,68 @@ others).
- GHC.Tc.Gen.Bind.tcSpecPrag
- GHC.Tc.Gen.Bind.tcTySig
- This decision is taken in setImplicationStatus, rather than GHC.Tc.Errors
- so that we can discard implication constraints that we don't need.
- So ics_dead consists only of the *reportable* redundant givens.
+ - We do not want to report redundant constraints for implications
+ that come from quantified constraints. Example #23323:
+ data T a
+ instance Show (T a) where ... -- No context!
+ foo :: forall f c. (forall a. c a => Show (f a)) => Proxy c -> f Int -> Int
+ bar = foo @T @Eq
+
+ The call to `foo` gives us
+ [W] d : (forall a. Eq a => Show (T a))
+ To solve this, GHC.Tc.Solver.Solve.solveForAll makes an implication constraint:
+ forall a. Eq a => [W] ds : Show (T a)
+ and because of the degnerate instance for `Show (T a)`, we don't need the `Eq a`
+ constraint. But we don't want to report it as redundant!
+
+(TRC5) Consider this (#25992), where `op2` has a default method
+ class C a where { op1, op2 :: a -> a
+ ; op2 = op1 . op1 }
+ instance C a => C [a] where
+ op1 x = x
+
+ Plainly the (C a) constraint is unused; but the expanded decl will look like
+ $dmop2 :: C a => a -> a
+ $dmop2 = op1 . op2
+
+ $fCList :: forall a. C a => C [a]
+ $fCList @a (d::C a) = MkC (\(x:a).x) ($dmop2 @a d)
+
+ Notice that `d` gets passed to `$dmop`: it is "needed". But it's only
+ /really/ needed if some /other/ method (in this case `op1`) uses it.
+
+ So, rather than one set of "needed Givens" we use `EvNeedSet` to track
+ a /pair/ of sets:
+ ens_dms: needed /only/ by default-method calls
+ ens_fvs: needed by something other than a default-method call
+ It's a bit of a palaver, but not really difficult.
+ All the logic is localised in `neededEvVars`.
+
+
+
+----- Reporting redundant constraints
+
+
+----- Examples
+
+ f, g, h :: (Eq a, Ord a) => a -> Bool
+ f x = x == x
+ g x = x > x
+ h x = x == x && x > x
+
+ All of f,g,h will discover that they have two [G] Eq a constraints: one as
+ given and one extracted from the Ord a constraint. They will both discard
+ the latter; see (TRC3).
+
+ The body of f uses the [G] Eq a, but not the [G] Ord a. It will report a
+ redundant Ord a.
+
+ The body of g uses the [G] Ord a, but not the [G] Eq a. It will report a
+ redundant Eq a.
+
+ The body of h uses both [G] Ord a and [G] Eq a; each is used in a solved
+ Wanted evidence binding. But (TRC2) kicks in and discovers the Eq a
+ is redundant.
----- Shortcomings
@@ -1732,4 +1785,4 @@ solveCompletelyIfRequired ct (TcS thing_inside)
; return $ Stop (ctEvidence ct) (text "Not fully solved; kept as inert:" <+> ppr ct)
} }
_notFullySolveMode ->
- thing_inside env
\ No newline at end of file
+ thing_inside env
=====================================
compiler/GHC/Tc/TyCl/Instance.hs
=====================================
@@ -495,7 +495,8 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_ext = lwarn
do { dfun_ty <- tcHsClsInstType (InstDeclCtxt False) hs_ty
; let (tyvars, theta, clas, inst_tys) = tcSplitDFunTy dfun_ty
-- NB: tcHsClsInstType does checkValidInstance
- ; skol_info <- mkSkolemInfo (mkClsInstSkol clas inst_tys)
+ ; skol_info <- mkSkolemInfo (InstSkol IsClsInst pSizeZero)
+ -- pSizeZero: here the size part of InstSkol is irrelevant
; (subst, skol_tvs) <- tcInstSkolTyVars skol_info tyvars
; let tv_skol_prs = [ (tyVarName tv, skol_tv)
| (tv, skol_tv) <- tyvars `zip` skol_tvs ]
@@ -1816,7 +1817,7 @@ tcMethods :: SkolemInfoAnon -> DFunId -> Class
-> TcM ([Id], LHsBinds GhcTc, Bag Implication)
-- The returned inst_meth_ids all have types starting
-- forall tvs. theta => ...
-tcMethods skol_info dfun_id clas tyvars dfun_ev_vars inst_tys
+tcMethods _skol_info dfun_id clas tyvars dfun_ev_vars inst_tys
dfun_ev_binds (spec_inst_prags, prag_fn) op_items
(InstBindings { ib_binds = binds
, ib_tyvars = lexical_tvs
@@ -1852,7 +1853,7 @@ tcMethods skol_info dfun_id clas tyvars dfun_ev_vars inst_tys
tc_item :: ClassOpItem -> TcM (Id, LHsBind GhcTc, Maybe Implication)
tc_item (sel_id, dm_info)
| Just (user_bind, bndr_loc, prags) <- findMethodBind (idName sel_id) binds prag_fn
- = tcMethodBody skol_info clas tyvars dfun_ev_vars inst_tys
+ = tcMethodBody False clas tyvars dfun_ev_vars inst_tys
dfun_ev_binds is_derived hs_sig_fn
spec_inst_prags prags
sel_id user_bind bndr_loc
@@ -1888,7 +1889,7 @@ tcMethods skol_info dfun_id clas tyvars dfun_ev_vars inst_tys
Just (dm_name, dm_spec) ->
do { (meth_bind, inline_prags) <- mkDefMethBind inst_loc dfun_id clas sel_id dm_name dm_spec
- ; tcMethodBody skol_info clas tyvars dfun_ev_vars inst_tys
+ ; tcMethodBody True clas tyvars dfun_ev_vars inst_tys
dfun_ev_binds is_derived hs_sig_fn
spec_inst_prags inline_prags
sel_id meth_bind inst_loc }
@@ -2013,25 +2014,26 @@ Instead, we take the following approach:
-}
------------------------
-tcMethodBody :: SkolemInfoAnon
+tcMethodBody :: Bool
-> Class -> [TcTyVar] -> [EvVar] -> [TcType]
-> TcEvBinds -> Bool
-> HsSigFun
-> [LTcSpecPrag] -> [LSig GhcRn]
-> Id -> LHsBind GhcRn -> SrcSpan
-> TcM (TcId, LHsBind GhcTc, Maybe Implication)
-tcMethodBody skol_info clas tyvars dfun_ev_vars inst_tys
+tcMethodBody is_def_meth clas tyvars dfun_ev_vars inst_tys
dfun_ev_binds is_derived
sig_fn spec_inst_prags prags
sel_id (L bind_loc meth_bind) bndr_loc
= add_meth_ctxt $
do { traceTc "tcMethodBody" (ppr sel_id <+> ppr (idType sel_id) $$ ppr bndr_loc)
+ ; let skol_info = MethSkol meth_name is_def_meth
; (global_meth_id, local_meth_id) <- setSrcSpan bndr_loc $
mkMethIds clas tyvars dfun_ev_vars
inst_tys sel_id
; let lm_bind = meth_bind { fun_id = L (noAnnSrcSpan bndr_loc)
- (idName local_meth_id) }
+ (idName local_meth_id) }
-- Substitute the local_meth_name for the binder
-- NB: the binding is always a FunBind
@@ -2042,7 +2044,7 @@ tcMethodBody skol_info clas tyvars dfun_ev_vars inst_tys
tcMethodBodyHelp sig_fn sel_id local_meth_id (L bind_loc lm_bind)
; global_meth_id <- addInlinePrags global_meth_id prags
- ; spec_prags <- tcExtendIdEnv1 (idName sel_id) global_meth_id $
+ ; spec_prags <- tcExtendIdEnv1 meth_name global_meth_id $
-- tcExtendIdEnv1: tricky point: a SPECIALISE pragma in prags
-- mentions sel_name but the pragma is really for global_meth_id.
-- So we bind sel_name to global_meth_id, just in the pragmas.
@@ -2071,6 +2073,8 @@ tcMethodBody skol_info clas tyvars dfun_ev_vars inst_tys
; return (global_meth_id, L bind_loc full_bind, Just meth_implic) }
where
+ meth_name = idName sel_id
+
-- For instance decls that come from deriving clauses
-- we want to print out the full source code if there's an error
-- because otherwise the user won't see the code at all
=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -67,6 +67,7 @@ module GHC.Tc.Types.Constraint (
ImplicStatus(..), isInsolubleStatus, isSolvedStatus,
UserGiven, getUserGivensFromImplics,
HasGivenEqs(..), checkImplicationInvariants,
+ EvNeedSet(..), emptyEvNeedSet, unionEvNeedSet, extendEvNeedSet, delGivensFromEvNeedSet,
-- CtLocEnv
CtLocEnv(..), setCtLocEnvLoc, setCtLocEnvLvl, getCtLocEnvLoc, getCtLocEnvLvl, ctLocEnvInGeneratedCode,
@@ -1458,18 +1459,43 @@ data Implication
-- The ic_need fields keep track of which Given evidence
-- is used by this implication or its children
- -- NB: including stuff used by nested implications that have since
- -- been discarded
- -- See Note [Needed evidence variables]
- -- and (RC2) in Note [Tracking redundant constraints]a
- ic_need_inner :: VarSet, -- Includes all used Given evidence
- ic_need_outer :: VarSet, -- Includes only the free Given evidence
- -- i.e. ic_need_inner after deleting
- -- (a) givens (b) binders of ic_binds
+ -- See Note [Tracking redundant constraints]
+ -- NB: these sets include stuff used by fully-solved nested implications
+ -- that have since been discarded
+ ic_need :: EvNeedSet, -- All needed Given evidence, from this implication
+ -- or outer ones
+ -- That is, /after/ deleting the binders of ic_binds,
+ -- but /before/ deleting ic_givens
+
+ ic_need_implic :: EvNeedSet, -- Union of of the ic_need of all implications in ic_wanted
+ -- /including/ any fully-solved implications that have been
+ -- discarded by `pruneImplications`. This discarding is why
+ -- we need to keep this field in the first place.
ic_status :: ImplicStatus
}
+data EvNeedSet = ENS { ens_dms :: VarSet -- Needed only by default methods
+ , ens_fvs :: VarSet -- Needed by things /other than/ default methods
+ -- See (TRC5) in Note [Tracking redundant constraints]
+ }
+
+emptyEvNeedSet :: EvNeedSet
+emptyEvNeedSet = ENS { ens_dms = emptyVarSet, ens_fvs = emptyVarSet }
+
+unionEvNeedSet :: EvNeedSet -> EvNeedSet -> EvNeedSet
+unionEvNeedSet (ENS { ens_dms = dm1, ens_fvs = fv1 })
+ (ENS { ens_dms = dm2, ens_fvs = fv2 })
+ = ENS { ens_dms = dm1 `unionVarSet` dm2, ens_fvs = fv1 `unionVarSet` fv2 }
+
+extendEvNeedSet :: EvNeedSet -> Var -> EvNeedSet
+extendEvNeedSet ens@(ENS { ens_fvs = fvs }) v = ens { ens_fvs = fvs `extendVarSet` v }
+
+delGivensFromEvNeedSet :: EvNeedSet -> [Var] -> EvNeedSet
+delGivensFromEvNeedSet (ENS { ens_dms = dms, ens_fvs = fvs }) givens
+ = ENS { ens_dms = dms `delVarSetList` givens
+ , ens_fvs = fvs `delVarSetList` givens }
+
implicationPrototype :: CtLocEnv -> Implication
implicationPrototype ct_loc_env
= Implic { -- These fields must be initialised
@@ -1478,15 +1504,17 @@ implicationPrototype ct_loc_env
, ic_info = panic "newImplic:info"
, ic_warn_inaccessible = panic "newImplic:warn_inaccessible"
- , ic_env = ct_loc_env
+ -- Given by caller
+ , ic_env = ct_loc_env
+
-- The rest have sensible default values
- , ic_skols = []
- , ic_given = []
- , ic_wanted = emptyWC
- , ic_given_eqs = MaybeGivenEqs
- , ic_status = IC_Unsolved
- , ic_need_inner = emptyVarSet
- , ic_need_outer = emptyVarSet }
+ , ic_skols = []
+ , ic_given = []
+ , ic_wanted = emptyWC
+ , ic_given_eqs = MaybeGivenEqs
+ , ic_status = IC_Unsolved
+ , ic_need = emptyEvNeedSet
+ , ic_need_implic = emptyEvNeedSet }
data ImplicStatus
= IC_Solved -- All wanteds in the tree are solved, all the way down
@@ -1562,7 +1590,7 @@ instance Outputable Implication where
, ic_given = given, ic_given_eqs = given_eqs
, ic_wanted = wanted, ic_status = status
, ic_binds = binds
- , ic_need_inner = need_in, ic_need_outer = need_out
+ , ic_need = need, ic_need_implic = need_implic
, ic_info = info })
= hang (text "Implic" <+> lbrace)
2 (sep [ text "TcLevel =" <+> ppr tclvl
@@ -1572,10 +1600,15 @@ instance Outputable Implication where
, hang (text "Given =") 2 (pprEvVars given)
, hang (text "Wanted =") 2 (ppr wanted)
, text "Binds =" <+> ppr binds
- , whenPprDebug (text "Needed inner =" <+> ppr need_in)
- , whenPprDebug (text "Needed outer =" <+> ppr need_out)
+ , text "need =" <+> ppr need
+ , text "need_implic =" <+> ppr need_implic
, pprSkolInfo info ] <+> rbrace)
+instance Outputable EvNeedSet where
+ ppr (ENS { ens_dms = dms, ens_fvs = fvs })
+ = text "ENS" <> braces (sep [text "ens_dms =" <+> ppr dms
+ , text "ens_fvs =" <+> ppr fvs])
+
instance Outputable ImplicStatus where
ppr IC_Insoluble = text "Insoluble"
ppr IC_BadTelescope = text "Bad telescope"
@@ -1663,18 +1696,6 @@ all at once, creating one implication constraint for the lot:
implication. TL;DR: an explicit forall should generate an implication
quantified only over those explicitly quantified variables.
-Note [Needed evidence variables]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Th ic_need_evs field holds the free vars of ic_binds, and all the
-ic_binds in nested implications.
-
- * Main purpose: if one of the ic_givens is not mentioned in here, it
- is redundant.
-
- * solveImplication may drop an implication altogether if it has no
- remaining 'wanteds'. But we still track the free vars of its
- evidence binds, even though it has now disappeared.
-
Note [Shadowing in a constraint]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
We assume NO SHADOWING in a constraint. Specifically
@@ -2012,6 +2033,7 @@ checkSkolInfoAnon sk1 sk2 = go sk1 sk2
go (TyConSkol f1 n1) (TyConSkol f2 n2) = f1==f2 && n1==n2
go (DataConSkol n1) (DataConSkol n2) = n1==n2
go (InstSkol {}) (InstSkol {}) = True
+ go (MethSkol n1 d1) (MethSkol n2 d2) = n1==n2 && d1==d2
go FamInstSkol FamInstSkol = True
go BracketSkol BracketSkol = True
go (RuleSkol n1) (RuleSkol n2) = n1==n2
=====================================
compiler/GHC/Tc/Types/Evidence.hs
=====================================
@@ -28,7 +28,7 @@ module GHC.Tc.Types.Evidence (
-- * EvTerm (already a CoreExpr)
EvTerm(..), EvExpr,
evId, evCoercion, evCast, evDFunApp, evDataConApp, evSelector,
- mkEvCast, evVarsOfTerm, mkEvScSelectors, evTypeable, findNeededEvVars,
+ mkEvCast, evVarsOfTerm, mkEvScSelectors, evTypeable,
evTermCoercion, evTermCoercion_maybe,
EvCallStack(..),
@@ -50,27 +50,30 @@ module GHC.Tc.Types.Evidence (
import GHC.Prelude
-import GHC.Types.Unique.DFM
-import GHC.Types.Unique.FM
-import GHC.Types.Var
-import GHC.Types.Id( idScaledType )
+import GHC.Tc.Utils.TcType
+
+import GHC.Core
import GHC.Core.Coercion.Axiom
import GHC.Core.Coercion
import GHC.Core.Ppr () -- Instance OutputableBndr TyVar
-import GHC.Tc.Utils.TcType
+import GHC.Core.Predicate
import GHC.Core.Type
import GHC.Core.TyCon
import GHC.Core.DataCon ( DataCon, dataConWrapId )
-import GHC.Builtin.Names
+import GHC.Core.Class (Class, classSCSelId )
+import GHC.Core.FVs ( exprSomeFreeVars )
+import GHC.Core.InstEnv ( CanonicalEvidence(..) )
+
+import GHC.Types.Unique.DFM
+import GHC.Types.Unique.FM
+import GHC.Types.Var
+import GHC.Types.Name( isInternalName )
+import GHC.Types.Id( idScaledType )
import GHC.Types.Var.Env
import GHC.Types.Var.Set
-import GHC.Core.Predicate
import GHC.Types.Basic
-import GHC.Core
-import GHC.Core.Class (Class, classSCSelId )
-import GHC.Core.FVs ( exprSomeFreeVars )
-import GHC.Core.InstEnv ( CanonicalEvidence(..) )
+import GHC.Builtin.Names
import GHC.Utils.Misc
import GHC.Utils.Panic
@@ -865,27 +868,13 @@ evTermCoercion tm = case evTermCoercion_maybe tm of
* *
********************************************************************* -}
-findNeededEvVars :: EvBindMap -> VarSet -> VarSet
--- Find all the Given evidence needed by seeds,
--- looking transitively through binds
-findNeededEvVars ev_binds seeds
- = transCloVarSet also_needs seeds
- where
- also_needs :: VarSet -> VarSet
- also_needs needs = nonDetStrictFoldUniqSet add emptyVarSet needs
- -- It's OK to use a non-deterministic fold here because we immediately
- -- forget about the ordering by creating a set
-
- add :: Var -> VarSet -> VarSet
- add v needs
- | Just ev_bind <- lookupEvBind ev_binds v
- , EvBind { eb_info = EvBindGiven, eb_rhs = rhs } <- ev_bind
- = evVarsOfTerm rhs `unionVarSet` needs
- | otherwise
- = needs
+relevantEvVar :: Var -> Bool
+-- Just returns /local/ free evidence variables; i.e ones with Internal Names
+-- Top-level ones (DFuns, dictionary selectors and the like) don't count
+relevantEvVar v = isInternalName (varName v)
evVarsOfTerm :: EvTerm -> VarSet
-evVarsOfTerm (EvExpr e) = exprSomeFreeVars isEvVar e
+evVarsOfTerm (EvExpr e) = exprSomeFreeVars relevantEvVar e
evVarsOfTerm (EvTypeable _ ev) = evVarsOfTypeable ev
evVarsOfTerm (EvFun {}) = emptyVarSet -- See Note [Free vars of EvFun]
=====================================
compiler/GHC/Tc/Types/Origin.hs
=====================================
@@ -15,7 +15,7 @@ module GHC.Tc.Types.Origin (
-- * SkolemInfo
SkolemInfo(..), SkolemInfoAnon(..), mkSkolemInfo, getSkolemInfo, pprSigSkolInfo, pprSkolInfo,
- unkSkol, unkSkolAnon, mkClsInstSkol,
+ unkSkol, unkSkolAnon,
-- * CtOrigin
CtOrigin(..), exprCtOrigin, lexprCtOrigin, matchesCtOrigin, grhssCtOrigin,
@@ -58,7 +58,6 @@ import GHC.Hs
import GHC.Core.DataCon
import GHC.Core.ConLike
import GHC.Core.TyCon
-import GHC.Core.Class
import GHC.Core.InstEnv
import GHC.Core.PatSyn
import GHC.Core.Multiplicity ( scaledThing )
@@ -288,6 +287,10 @@ data SkolemInfoAnon
ClsInstOrQC -- Whether class instance or quantified constraint
PatersonSize -- Head has the given PatersonSize
+ | MethSkol Name Bool -- Bound by the type of class method op
+ -- True <=> it's a default method
+ -- False <=> it's a user-written method
+
| FamInstSkol -- Bound at a family instance decl
| PatSkol -- An existential type variable bound by a pattern for
ConLike -- a data constructor with an existential type.
@@ -348,9 +351,6 @@ mkSkolemInfo sk_anon = do
getSkolemInfo :: SkolemInfo -> SkolemInfoAnon
getSkolemInfo (SkolemInfo _ skol_anon) = skol_anon
-mkClsInstSkol :: Class -> [Type] -> SkolemInfoAnon
-mkClsInstSkol cls tys = InstSkol IsClsInst (pSizeClassPred cls tys)
-
instance Outputable SkolemInfo where
ppr (SkolemInfo _ sk_info ) = ppr sk_info
@@ -369,6 +369,8 @@ pprSkolInfo (InstSkol IsClsInst sz) = vcat [ text "the instance declaration"
, whenPprDebug (braces (ppr sz)) ]
pprSkolInfo (InstSkol (IsQC {}) sz) = vcat [ text "a quantified context"
, whenPprDebug (braces (ppr sz)) ]
+pprSkolInfo (MethSkol name d) = text "the" <+> ppWhen d (text "default")
+ <+> text "method declaration for" <+> ppr name
pprSkolInfo FamInstSkol = text "a family instance declaration"
pprSkolInfo BracketSkol = text "a Template Haskell bracket"
pprSkolInfo (RuleSkol name) = text "the RULE" <+> pprRuleName name
=====================================
compiler/GHC/Tc/Utils/Instantiate.hs
=====================================
@@ -582,8 +582,11 @@ tcSkolDFunType dfun_ty
-- We instantiate the dfun_tyd with superSkolems.
-- See Note [Subtle interaction of recursion and overlap]
-- and Note [Super skolems: binding when looking up instances]
- ; let inst_tys = substTys subst tys
- skol_info_anon = mkClsInstSkol cls inst_tys }
+ ; let inst_tys = substTys subst tys
+ skol_info_anon = InstSkol IsClsInst (pSizeClassPred cls inst_tys)
+ -- We need to take the size of `inst_tys` (not `tys`) because
+ -- Paterson sizes mention the free type variables
+ }
; let inst_theta = substTheta subst theta
; return (skol_info_anon, inst_tvs, inst_theta, cls, inst_tys) }
=====================================
testsuite/tests/dependent/should_fail/T13135_simple.stderr
=====================================
@@ -1,8 +1,8 @@
-
T13135_simple.hs:34:11: error: [GHC-83865]
- • Couldn't match type ‘SmartFun sig’ with ‘Bool’
+ • Couldn't match type ‘SmartFun sig1’ with ‘Bool’
Expected: Int -> Bool
- Actual: SmartFun (SigFun Int sig)
- The type variable ‘sig’ is ambiguous
+ Actual: SmartFun (SigFun Int sig1)
+ The type variable ‘sig1’ is ambiguous
• In the expression: smartSym
In an equation for ‘problem’: problem = smartSym
+
=====================================
testsuite/tests/typecheck/should_compile/T25992.hs
=====================================
@@ -0,0 +1,8 @@
+{-# OPTIONS_GHC -Wredundant-constraints #-}
+
+module T25992 where
+
+data P a = P
+
+instance Eq a => Semigroup (P a) where
+ P <> P = P
=====================================
testsuite/tests/typecheck/should_compile/T25992.stderr
=====================================
@@ -0,0 +1,4 @@
+T25992.hs:7:10: warning: [GHC-30606] [-Wredundant-constraints]
+ • Redundant constraint: Eq a
+ • In the instance declaration for ‘Semigroup (P a)’
+
=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -941,3 +941,4 @@ test('T25597', normal, compile, [''])
test('T25960', normal, compile, [''])
test('T26020', normal, compile, [''])
test('T26020a', [extra_files(['T26020a_help.hs'])], multimod_compile, ['T26020a', '-v0'])
+test('T25992', normal, compile, [''])
=====================================
testsuite/tests/typecheck/should_fail/tcfail097.stderr
=====================================
@@ -7,8 +7,8 @@ tcfail097.hs:5:6: error: [GHC-39999]
The type variable ‘a0’ is ambiguous
Potentially matching instances:
instance Eq Ordering -- Defined in ‘GHC.Internal.Classes’
- instance Eq a => Eq (Solo a) -- Defined in ‘GHC.Internal.Classes’
- ...plus 22 others
+ instance Eq Integer -- Defined in ‘GHC.Internal.Bignum.Integer’
+ ...plus 23 others
...plus five instances involving out-of-scope types
(use -fprint-potential-instances to see them all)
• In the ambiguity check for ‘f’
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/19f20861b7462c6224d4ebdaeaa5d1e…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/19f20861b7462c6224d4ebdaeaa5d1e…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/andreask/spec-float-again] 19 commits: Refactor handling of imported COMPLETE pragmas
by Andreas Klebinger (@AndreasK) 13 Jun '25
by Andreas Klebinger (@AndreasK) 13 Jun '25
13 Jun '25
Andreas Klebinger pushed to branch wip/andreask/spec-float-again at Glasgow Haskell Compiler / GHC
Commits:
b08c08ae by soulomoon at 2025-05-28T01:57:23+08:00
Refactor handling of imported COMPLETE pragmas
from the HPT
Previously, we imported COMPLETE pragmas from all modules in the Home
Package Table (HPT) during type checking. However, since !13675, there
may be non-below modules in the HPT from the dependency tree that we do
not want to import COMPLETE pragmas from. This refactor changes the way
we handle COMPLETE pragmas from the HPT to only import them from modules
that are "below" the current module in the HPT.
- Add hugCompleteSigsBelow to filter COMPLETE pragmas from "below"
modules in the HPT, mirroring hugRulesBelow.
- Move responsibility for calling hugCompleteSigsBelow to tcRnImports,
storing the result in the new tcg_complete_match_env field of TcGblEnv.
- Update getCompleteMatchesTcM to use tcg_complete_match_env.
This refactor only affects how COMPLETE pragmas are imported from the
HPT, imports from external packages are unchanged.
- - - - -
16014bf8 by Hécate Kleidukos at 2025-05-28T20:09:34-04:00
Expose all of Backtraces' internals for ghc-internal
Closes #26049
- - - - -
a0adc30d by Ryan Hendrickson at 2025-05-30T14:12:52-04:00
haddock: Fix links to type operators
- - - - -
7b64697c by Mario Blažević at 2025-05-30T14:13:41-04:00
Introduce parenBreakableList and use it in ppHsContext
- - - - -
5f213bff by fendor at 2025-06-02T09:16:24+02:00
Make GHCi commands compatible with multiple home units
=== Design
We enable all GHCi features that were previously guarded by the `inMulti`
option.
GHCi supported multiple home units up to a certain degree for quite a while now.
The supported feature set was limited, due to a design impasse:
One of the home units must be "active", e.g., there must be one `HomeUnit`
whose `UnitId` is "active" which is returned when calling
```haskell
do
hscActiveUnitId <$> getSession
```
This makes sense in a GHC session, since you are always compiling a particular
Module, but it makes less intuitive sense in an interactive session.
Given an expression to evaluate, we can't easily tell in which "context" the expression
should be parsed, typechecked and evaluated.
That's why initially, most of GHCi features, except for `:reload`ing were disabled
if the GHCi session had more than one `HomeUnitEnv`.
We lift this restriction, enabling all features of GHCi for the multiple home unit case.
To do this, we fundamentally change the `HomeUnitEnv` graph to be multiple home unit first.
Instead of differentiating the case were we have a single home unit and multiple,
we now always set up a multiple home unit session that scales seamlessly to an arbitrary
amount of home units.
We introduce two new `HomeUnitEnv`s that are always added to the `HomeUnitGraph`.
They are:
The "interactive-ghci", called the `interactiveGhciUnit`, contains the same
`DynFlags` that are used by the `InteractiveContext` for interactive evaluation
of expressions.
This `HomeUnitEnv` is only used on the prompt of GHCi, so we may refer to it as
"interactive-prompt" unit.
See Note [Relation between the `InteractiveContext` and `interactiveGhciUnitId`]
for discussing its role.
And the "interactive-session"", called `interactiveSessionUnit` or
`interactiveSessionUnitId`, which is used for loading Scripts into
GHCi that are not `Target`s of any home unit, via `:load` or `:add`.
Both of these "interactive" home units depend on all other `HomeUnitEnv`s that
are passed as arguments on the cli.
Additionally, the "interactive-ghci" unit depends on `interactive-session`.
We always evaluate expressions in the context of the
"interactive-ghci" session.
Since "interactive-ghci" depends on all home units, we can import any `Module`
from the other home units with ease.
As we have a clear `HomeUnitGraph` hierarchy, we can set `interactiveGhciUnitId`
as the active home unit for the full duration of the GHCi session.
In GHCi, we always set `interactiveGhciUnitId` to be the currently active home unit.
=== Implementation Details
Given this design idea, the implementation is relatively straight
forward.
The core insight is that a `ModuleName` is not sufficient to identify a
`Module` in the `HomeUnitGraph`. Thus, large parts of the PR is simply
about refactoring usages of `ModuleName` to prefer `Module`, which has a
`Unit` attached and is unique over the `HomeUnitGraph`.
Consequentially, most usages of `lookupHPT` are likely to be incorrect and have
been replaced by `lookupHugByModule` which is keyed by a `Module`.
In `GHCi/UI.hs`, we make sure there is only one location where we are
actually translating `ModuleName` to a `Module`:
* `lookupQualifiedModuleName`
If a `ModuleName` is ambiguous, we detect this and report it to the
user.
To avoid repeated lookups of `ModuleName`s, we store the `Module` in the
`InteractiveImport`, which additionally simplifies the interface
loading.
A subtle detail is that the `DynFlags` of the `InteractiveContext` are
now stored both in the `HomeUnitGraph` and in the `InteractiveContext`.
In UI.hs, there are multiple code paths where we are careful to update
the `DynFlags` in both locations.
Most importantly in `addToProgramDynFlags`.
---
There is one metric increase in this commit:
-------------------------
Metric Increase:
T4029
-------------------------
It is an increase from 14.4 MB to 16.1 MB (+11.8%) which sounds like a
pretty big regression at first.
However, we argue this increase is solely caused by using more data
structures for managing multiple home units in the GHCi session.
In particular, due to the design decision of using three home units, the
base memory usage increases... but by how much?
A big contributor is the `UnitState`, of which we have three now, which
on its own 260 KB per instance. That makes an additional memory usage of
520 KB, already explaining a third of the overall memory usage increase.
Then we store more elements in the `HomeUnitGraph`, we have more
`HomeUnitEnv` entries, etc...
While we didn't chase down each byte, we looked at the memory usage over time
for both `-hi` and `-hT` profiles and can say with confidence while the memory
usage increased slightly, we did not introduce any space leak, as
the graph looks almost identical as the memory usage graph of GHC HEAD.
---
Adds testcases for GHCi multiple home units session
* Test truly multiple home unit sessions, testing reload logic and code evaluation.
* Test that GHCi commands such as `:all-types`, `:browse`, etc., work
* Object code reloading for home modules
* GHCi debugger multiple home units session
- - - - -
de603d01 by fendor at 2025-06-02T09:16:24+02:00
Update "loading compiled code" GHCi documentation
To use object code in GHCi, the module needs to be compiled for use in
GHCi. To do that, users need to compile their modules with:
* `-dynamic`
* `-this-unit-id interactive-session`
Otherwise, the interface files will not match.
- - - - -
b255a8ca by Vladislav Zavialov at 2025-06-02T16:00:12-04:00
docs: Fix code example for NoListTuplePuns
Without the fix, the example produces an error:
Test.hs:11:3: error: [GHC-45219]
• Data constructor ‘Tuple’ returns type ‘Tuple2 a b’
instead of an instance of its parent type ‘Tuple a’
• In the definition of data constructor ‘Tuple’
In the data type declaration for ‘Tuple’
Fortunately, a one line change makes it compile.
- - - - -
6558467c by Ryan Hendrickson at 2025-06-06T05:46:58-04:00
haddock: Parse math even after ordinary characters
Fixes a bug where math sections were not recognized if preceded by a
character that isn't special (like space or a markup character).
- - - - -
265d0024 by ARATA Mizuki at 2025-06-06T05:47:48-04:00
AArch64 NCG: Fix sub-word arithmetic right shift
As noted in Note [Signed arithmetic on AArch64], we should zero-extend sub-word values.
Fixes #26061
- - - - -
05e9be18 by Simon Hengel at 2025-06-06T05:48:35-04:00
Allow Unicode in "message" and "hints" with -fdiagnostics-as-json
(fixes #26075)
- - - - -
bfa6b70f by ARATA Mizuki at 2025-06-06T05:49:24-04:00
x86 NCG: Fix code generation of bswap64 on i386
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
Fix #25601
- - - - -
35826d8b by Matthew Pickering at 2025-06-08T22:00:41+01:00
Hadrian: Add option to generate .hie files for stage1 libraries
The +hie_files flavour transformer can be enabled to produce hie files
for stage1 libraries. The hie files are produced in the
"extra-compilation-artifacts" folder and copied into the resulting
bindist.
At the moment the hie files are not produced for the release flavour,
they add about 170M to the final bindist.
Towards #16901
- - - - -
e2467dbd by Ryan Hendrickson at 2025-06-09T13:07:05-04:00
Fix various failures to -fprint-unicode-syntax
- - - - -
1d99d3e4 by maralorn at 2025-06-12T03:47:39-04:00
Add necessary flag for js linking
- - - - -
974d5734 by maralorn at 2025-06-12T03:47:39-04:00
Don’t use additional linker flags to detect presence of -fno-pie in configure.ac
This mirrors the behavior of ghc-toolchain
- - - - -
1e9eb118 by Andrew Lelechenko at 2025-06-12T03:48:21-04:00
Add HasCallStack to Control.Monad.Fail.fail
CLC proposal https://github.com/haskell/core-libraries-committee/issues/327
2% compile-time allocations increase in T3064, likely because `fail`
is now marginally more expensive to compile.
Metric Increase:
T3064
- - - - -
6d12060f by meooow25 at 2025-06-12T14:26:07-04:00
Bump containers submodule to 0.8
Also
* Disable -Wunused-imports for containers
* Allow containers-0.8 for in-tree packages
* Bump some submodules so that they allow containers-0.8. These are not
at any particular versions.
* Remove unused deps containers and split from ucd2haskell
* Fix tests affected by the new containers and hpc-bin
- - - - -
537bd233 by Peng Fan at 2025-06-12T14:27:02-04:00
NCG/LA64: Optimize code generation and reduce build-directory size.
1. makeFarBranches: Prioritize fewer instruction sequences.
2. Prefer instructions with immediate numbers to reduce register moves,
e.g. andi,ori,xori,addi.
3. Ppr: Remove unnecessary judgments.
4. genJump: Avoid "ld+jr" as much as possible.
5. BCOND and BCOND1: Implement conditional jumps with two jump ranges,
with limited choice of the shortest.
6. Implement FSQRT, CLT, CTZ.
7. Remove unnecessary code.
- - - - -
8fa6f191 by Andreas Klebinger at 2025-06-13T13:38:47+00:00
Revert "Specialise: Don't float out constraint components."
This reverts commit c9abb87ccc0c91cd94f42b3e36270158398326ef.
Turns out two benchmarks from #19747 regresses by a factor of 7-8x if
we do not float those out.
- - - - -
235 changed files:
- compiler/GHC.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/LA64.hs
- compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- compiler/GHC/CmmToAsm/LA64/Instr.hs
- compiler/GHC/CmmToAsm/LA64/Ppr.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Unbound.hs
- compiler/GHC/Runtime/Context.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Types/Error.hs
- compiler/GHC/Types/Name/Ppr.hs
- compiler/GHC/Unit/Env.hs
- compiler/GHC/Unit/Home/Graph.hs
- compiler/GHC/Unit/Types.hs
- compiler/ghc.cabal.in
- docs/users_guide/exts/data_kinds.rst
- docs/users_guide/ghci.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Info.hs
- ghc/GHCi/UI/Monad.hs
- ghc/Main.hs
- ghc/ghc-bin.cabal.in
- hadrian/doc/flavours.md
- hadrian/doc/user-settings.md
- hadrian/hadrian.cabal
- hadrian/src/Context.hs
- hadrian/src/Context/Path.hs
- hadrian/src/Flavour.hs
- hadrian/src/Flavour/Type.hs
- hadrian/src/Settings/Builders/Ghc.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Flavours/Release.hs
- hadrian/src/Settings/Warnings.hs
- libraries/base/changelog.md
- libraries/base/tests/IO/withBinaryFile002.stderr
- libraries/base/tests/IO/withFile002.stderr
- libraries/base/tests/IO/withFileBlocking002.stderr
- libraries/containers
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-heap/ghc-heap.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs-boot
- libraries/ghc-internal/src/GHC/Internal/IO.hs-boot
- libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs-boot
- libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal
- libraries/ghci/ghci.cabal.in
- libraries/haskeline
- libraries/hpc
- m4/fp_gcc_supports_no_pie.m4
- m4/fptools_set_c_ld_flags.m4
- testsuite/driver/testlib.py
- + testsuite/tests/cmm/should_run/T25601.hs
- + testsuite/tests/cmm/should_run/T25601.stdout
- + testsuite/tests/cmm/should_run/T25601a.cmm
- testsuite/tests/cmm/should_run/all.T
- + testsuite/tests/codeGen/should_run/T26061.hs
- + testsuite/tests/codeGen/should_run/T26061.stdout
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/deSugar/should_run/DsDoExprFailMsg.stderr
- testsuite/tests/deSugar/should_run/DsMonadCompFailMsg.stderr
- testsuite/tests/driver/T8526/T8526.stdout
- testsuite/tests/driver/fat-iface/fat014.stdout
- testsuite/tests/driver/json.stderr
- testsuite/tests/driver/json_warn.stderr
- testsuite/tests/driver/multipleHomeUnits/multiGHCi.stderr
- testsuite/tests/ghc-api/T6145.hs
- testsuite/tests/ghc-api/annotations-literals/literals.hs
- testsuite/tests/ghc-api/annotations-literals/parsed.hs
- testsuite/tests/ghc-api/apirecomp001/myghc.hs
- testsuite/tests/ghc-api/fixed-nodes/T1.hs
- + testsuite/tests/ghci.debugger/scripts/break031/Makefile
- + testsuite/tests/ghci.debugger/scripts/break031/a/A.hs
- + testsuite/tests/ghci.debugger/scripts/break031/all.T
- + testsuite/tests/ghci.debugger/scripts/break031/b/B.hs
- + testsuite/tests/ghci.debugger/scripts/break031/break031a.script
- + testsuite/tests/ghci.debugger/scripts/break031/break031a.stdout
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.script
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.stderr
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.stdout
- + testsuite/tests/ghci.debugger/scripts/break031/unitA
- + testsuite/tests/ghci.debugger/scripts/break031/unitB
- testsuite/tests/ghci/linking/dyn/T3372.hs
- + testsuite/tests/ghci/prog-mhu001/Makefile
- + testsuite/tests/ghci/prog-mhu001/all.T
- + testsuite/tests/ghci/prog-mhu001/e/E.hs
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001a.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001a.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001b.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001b.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001c.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001c.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001d.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001d.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001e.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001e.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001f.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001f.stdout
- + testsuite/tests/ghci/prog-mhu001/unitE
- + testsuite/tests/ghci/prog-mhu001/unitE-main-is
- + testsuite/tests/ghci/prog-mhu002/Makefile
- + testsuite/tests/ghci/prog-mhu002/a/A.hs
- + testsuite/tests/ghci/prog-mhu002/all.T
- + testsuite/tests/ghci/prog-mhu002/b/B.hs
- + testsuite/tests/ghci/prog-mhu002/c/C.hs
- + testsuite/tests/ghci/prog-mhu002/d/Main.hs
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.stderr
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.stderr
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002c.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002c.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002d.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002d.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002e.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002e.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002f.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002f.stdout
- + testsuite/tests/ghci/prog-mhu002/unitA
- + testsuite/tests/ghci/prog-mhu002/unitB
- + testsuite/tests/ghci/prog-mhu002/unitC
- + testsuite/tests/ghci/prog-mhu002/unitD
- + testsuite/tests/ghci/prog-mhu003/Makefile
- + testsuite/tests/ghci/prog-mhu003/a/A.hs
- + testsuite/tests/ghci/prog-mhu003/all.T
- + testsuite/tests/ghci/prog-mhu003/b/Foo.hs
- + testsuite/tests/ghci/prog-mhu003/c/C.hs
- + testsuite/tests/ghci/prog-mhu003/d/Foo.hs
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.script
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.stderr
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.stdout
- + testsuite/tests/ghci/prog-mhu003/unitA
- + testsuite/tests/ghci/prog-mhu003/unitB
- + testsuite/tests/ghci/prog-mhu003/unitC
- + testsuite/tests/ghci/prog-mhu003/unitD
- + testsuite/tests/ghci/prog-mhu004/Makefile
- + testsuite/tests/ghci/prog-mhu004/a/Foo.hs
- + testsuite/tests/ghci/prog-mhu004/all.T
- + testsuite/tests/ghci/prog-mhu004/b/Foo.hs
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.script
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stderr
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stdout
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004b.script
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004b.stdout
- + testsuite/tests/ghci/prog-mhu004/unitA
- + testsuite/tests/ghci/prog-mhu004/unitB
- testsuite/tests/ghci/prog010/ghci.prog010.script
- testsuite/tests/ghci/prog018/prog018.stdout
- + testsuite/tests/ghci/prog020/A.hs
- + testsuite/tests/ghci/prog020/B.hs
- + testsuite/tests/ghci/prog020/Makefile
- + testsuite/tests/ghci/prog020/all.T
- + testsuite/tests/ghci/prog020/ghci.prog020.script
- + testsuite/tests/ghci/prog020/ghci.prog020.stderr
- + testsuite/tests/ghci/prog020/ghci.prog020.stdout
- testsuite/tests/ghci/scripts/T12550.stdout
- testsuite/tests/ghci/scripts/T13869.stdout
- testsuite/tests/ghci/scripts/T13997.stdout
- testsuite/tests/ghci/scripts/T17669.stdout
- testsuite/tests/ghci/scripts/T18330.stdout
- testsuite/tests/ghci/scripts/T1914.stdout
- testsuite/tests/ghci/scripts/T20217.stdout
- testsuite/tests/ghci/scripts/T20587.stdout
- testsuite/tests/ghci/scripts/T21110.stderr
- testsuite/tests/ghci/scripts/T6105.stdout
- testsuite/tests/ghci/scripts/T8042.stdout
- testsuite/tests/ghci/scripts/T8042recomp.stdout
- testsuite/tests/ghci/scripts/T8959b.stderr
- testsuite/tests/ghci/scripts/all.T
- testsuite/tests/ghci/scripts/ghci024.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
- testsuite/tests/ghci/scripts/ghci058.script
- + testsuite/tests/ghci/scripts/print-unicode-syntax.script
- + testsuite/tests/ghci/scripts/print-unicode-syntax.stderr
- + testsuite/tests/ghci/scripts/print-unicode-syntax.stdout
- testsuite/tests/ghci/should_run/T11825.stdout
- testsuite/tests/ghci/should_run/TopEnvIface.stdout
- testsuite/tests/hpc/fork/hpc_fork.stdout
- testsuite/tests/hpc/function/tough.stdout
- testsuite/tests/hpc/function2/tough2.stdout
- testsuite/tests/hpc/simple/hpc001.stdout
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/partial-sigs/should_fail/T10999.stderr
- testsuite/tests/quasiquotation/T7918.hs
- testsuite/tests/rebindable/DoRestrictedM.hs
- testsuite/tests/th/T15321.stderr
- testsuite/tests/typecheck/should_compile/subsumption_sort_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
- utils/haddock/haddock-api/resources/html/Linuwial.std-theme/linuwial.css
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Utils.hs
- utils/haddock/haddock-api/src/Haddock/Interface/LexParseRn.hs
- utils/haddock/haddock-library/haddock-library.cabal
- utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs
- utils/haddock/haddock-library/test/Documentation/Haddock/ParserSpec.hs
- utils/haddock/html-test/ref/Bug1004.html
- utils/haddock/html-test/ref/Bug548.html
- utils/haddock/html-test/ref/Bug973.html
- utils/haddock/html-test/ref/Hash.html
- utils/haddock/html-test/ref/ImplicitParams.html
- utils/haddock/html-test/ref/Instances.html
- utils/haddock/html-test/ref/PatternSyns.html
- utils/haddock/html-test/ref/TypeOperators.html
- utils/haddock/html-test/src/TypeOperators.hs
- utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
- utils/hpc
- utils/hsc2hs
- utils/iserv/iserv.cabal.in
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d6fb9c27e5ff2649feda31c11f8e24…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d6fb9c27e5ff2649feda31c11f8e24…
You're receiving this email because of your account on gitlab.haskell.org.
1
0