
[Git][ghc/ghc][wip/T26115] 37 commits: Revert "Specialise: Don't float out constraint components."
by Simon Peyton Jones (@simonpj) 29 Jun '25
by Simon Peyton Jones (@simonpj) 29 Jun '25
29 Jun '25
Simon Peyton Jones pushed to branch wip/T26115 at Glasgow Haskell Compiler / GHC
Commits:
c7aa0c10 by Andreas Klebinger at 2025-06-15T05:47:24-04: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.
- - - - -
fd998679 by Krzysztof Gogolewski at 2025-06-15T05:48:06-04:00
Fix EPT enforcement when mixing unboxed tuples and non-tuples
The code was assuming that an alternative cannot be returning a normal
datacon and an unboxed tuple at the same time. However, as seen in #26107,
this can happen when using a GADT to refine the representation type.
The solution is just to conservatively return TagDunno.
- - - - -
e64b3f16 by ARATA Mizuki at 2025-06-17T10:13:42+09:00
MachRegs.h: Don't define NO_ARG_REGS when a XMM register is defined
On i386, MAX_REAL_VANILLA_REG is 1, but MAX_REAL_XMM_REG is 4.
If we define NO_ARG_REGS on i386, programs that use SIMD vectors may segfault.
Closes #25985
A couple of notes on the BROKEN_TESTS field:
* This fixes the segfault from T25062_V16.
* The failure from T22187_run was fixed in an earlier commit (see #25561),
but BROKEN_TESTS was missed at that time. Now should be a good time to
mark it fixed.
- - - - -
3e7c6b4d by Matthew Pickering at 2025-06-18T15:34:04-04:00
Improve error messages when implicit lifting fails
This patch concerns programs which automatically try to fix level errors
by inserting `Lift`. For example:
```
foo x = [| x |]
~>
foo x = [| $(lift x) |]
```
Before, there were two problems with the message.
1. (#26031), the location of the error was reported as the whole
quotation.
2. (#26035), the message just mentions there is no Lift instance, but
gives no indicate why the user program needed a Lift instance in the
first place.
This problem is especially bad when you disable
`ImplicitStagePersistence`, so you just end up with a confusing "No
instance for" message rather than an error message about levels
This patch fixes both these issues.
Firstly, `PendingRnSplice` differentiates between a user-written splice
and an implicit lift. Then, the Lift instance is precisely requested
with a specific origin in the typechecker. If the instance fails to be
solved, the message is reported using the `TcRnBadlyLevelled`
constructor (like a normal level error).
Fixes #26031, #26035
- - - - -
44b8cee2 by Cheng Shao at 2025-06-18T15:34:46-04:00
testsuite: add T26120 marked as broken
- - - - -
894a04f3 by Cheng Shao at 2025-06-18T15:34:46-04:00
compiler: fix GHC.SysTools.Ar archive member size writing logic
This patch fixes a long-standing bug in `GHC.SysTools.Ar` that emits
the wrong archive member size in each archive header. It should encode
the exact length of the member payload, excluding any padding byte,
otherwise malformed archive that extracts a broken object with an
extra trailing byte could be created.
Apart from the in-tree `T26120` test, I've also created an out-of-tree
testsuite at https://github.com/TerrorJack/ghc-ar-quickcheck that
contains QuickCheck roundtrip tests for `GHC.SysTools.Ar`. With this
fix, simple roundtrip tests and `writeGNUAr`/GNU `ar` roundtrip test
passes. There might be more bugs lurking in here, but this patch is
still a critical bugfix already.
Fixes #26120 #22586.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
f677ab5f by Lauren Yim at 2025-06-18T15:35:37-04:00
fix some typos in the warnings page in the user guide
- - - - -
b968e1c1 by Rodrigo Mesquita at 2025-06-18T15:36:18-04:00
Add a frozen callstack to throwGhcException
Fixes #25956
- - - - -
a5e0c3a3 by fendor at 2025-06-18T15:36:59-04:00
Update using.rst to advertise full mhu support for GHCi
- - - - -
d3e60e97 by Ryan Scott at 2025-06-18T22:29:21-04:00
Deprecate -Wdata-kinds-tc, make DataKinds issues in typechecker become errors
!11314 introduced the `-Wdata-kinds-tc` warning as part of a fix for #22141.
This was a temporary stopgap measure to allow users who were accidentally
relying on code which needed the `DataKinds` extension in order to typecheck
without having to explicitly enable the extension.
Now that some amount of time has passed, this patch deprecates
`-Wdata-kinds-tc` and upgrades any `DataKinds`-related issues in the
typechecker (which were previously warnings) into errors.
- - - - -
fd5b5177 by Ryan Hendrickson at 2025-06-18T22:30:06-04:00
haddock: Add redact-type-synonyms pragma
`{-# OPTIONS_HADDOCK redact-type-synonyms #-}` pragma will hide the RHS
of type synonyms, and display the result kind instead, if the RHS
contains any unexported types.
- - - - -
fbc0b92a by Vladislav Zavialov at 2025-06-22T04:25:16+03:00
Visible forall in GADTs (#25127)
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>
- - - - -
ae003a3a by Teo Camarasu at 2025-06-23T05:21:48-04:00
linters: lint-whitespace: bump upper-bound for containers
The version of containers was bumped in https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13989
- - - - -
0fb37893 by Matthew Pickering at 2025-06-23T13:55:10-04: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.
- - - - -
3bf6720e by soulomoon at 2025-06-23T13:55:52-04:00
Remove hptAllFamInstances usage during upsweep
Fixes #26118
This change eliminates the use of hptAllFamInstances during the upsweep phase,
as it could access non-below modules from the home package table.
The following updates were made:
* Updated checkFamInstConsistency to accept an explicit ModuleEnv FamInstEnv
parameter and removed the call to hptAllFamInstances.
* Adjusted hugInstancesBelow so we can construct ModuleEnv FamInstEnv
from its result,
* hptAllFamInstances and allFamInstances functions are removed.
- - - - -
83ee7b78 by Ben Gamari at 2025-06-24T05:02:07-04:00
configure: Don't force value of OTOOL, etc. if not present
Previously if `otool` and `install_name_tool` were not present they
would be overridden by `fp_settings.m4`. This logic was introduced in
4ff93292243888545da452ea4d4c1987f2343591 without explanation.
- - - - -
9329c9e1 by Ben Gamari at 2025-06-24T05:02:07-04:00
ghc-toolchain: Add support for otool, install_name_tool
Fixes part of ghc#23675.
- - - - -
25f5c998 by Ben Gamari at 2025-06-24T05:02:08-04:00
ghc-toolchain: Add support for llc, opt, llvm-as
Fixes #23675.
- - - - -
51d150dd by Rodrigo Mesquita at 2025-06-24T05:02:08-04:00
hadrian: Use settings-use-distro-mingw directly
The type `ToolchainSetting` only made sense when we had more settings to
fetch from the system config file. Even then "settings-use-distro-mingw"
is arguably not a toolchain setting.
With the fix for #23675, all toolchain tools were moved to the
`ghc-toolchain` `Toolchain` format. Therefore, we can inline
`settings-use-distro-mingw` accesses and delete `ToolchainSetting`.
- - - - -
dcf68a83 by Rodrigo Mesquita at 2025-06-24T05:02:08-04:00
configure: Check LlvmTarget exists for LlvmAsFlags
If LlvmTarget was empty, LlvmAsFlags would be just "--target=".
If it is empty now, simply keep LlvmAsFlags empty.
ghc-toolchain already does this right. This fix makes the two
configurations match up.
- - - - -
580a3353 by Ben Gamari at 2025-06-24T05:02:51-04:00
rts/linker/LoadArchive: Use bool
Improve type precision by using `bool` instead of `int` and `StgBool`.
- - - - -
76d1041d by Ben Gamari at 2025-06-24T05:02:51-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.
- - - - -
4b748a99 by Teo Camarasu at 2025-06-24T15:31:07-04:00
template-haskell: improve changelog
stable -> more stable, just to clarify that this interface isn't fully stable.
errornously -> mistakenly: I typod this and also let's go for a simpler word
- - - - -
e358e477 by Sylvain Henry at 2025-06-24T15:31:58-04:00
Bump stack resolver to use GHC 9.6.7
Cf #26139
- - - - -
4bf5eb63 by fendor at 2025-06-25T17:05:43-04:00
Teach `:reload` about multiple home units
`:reload` needs to lookup the `ModuleName` and must not assume the given
`ModuleName` is in the current `HomeUnit`.
We add a new utility function which allows us to find a `HomeUnitModule`
instead of a `Module`.
Further, we introduce the `GhciCommandError` type which can be used to
abort the execution of a GHCi command.
This error is caught and printed in a human readable fashion.
- - - - -
b3d97bb3 by fendor at 2025-06-25T17:06:25-04:00
Implement `-fno-load-initial-targets` flag
We add the new flag `-fno-load-initial-targets` which doesn't load all `Target`s
immediately but only computes the module graph for all `Target`s.
The user can then decide to load modules from that module graph using
the syntax:
ghci> :reload <Mod>
This will load everything in the module graph up to `Mod`.
The user can return to the initial state by using the builtin target
`none` to unload all modules.
ghci> :reload none
Is in principle identical to starting a new session with the
`-fno-load-initial-targets` flag.
The `-fno-load-initial-targets` flag allows for faster startup time of GHCi when a
user has lots of `Target`s.
We additionally extend the `:reload` command to accept multiple
`ModuleName`s. For example:
ghci> :reload <Mod1> <Mod2>
Loads all modules up to the modules `Mod1` and `Mod2`.
- - - - -
49f44e52 by Teo Camarasu at 2025-06-26T04:19:51-04:00
Expose ghc-internal unit id through the settings file
This in combination with the unit id of the compiler library allows
cabal to know of the two unit ids that should not be reinstalled (in
specific circumstances) as:
- when using plugins, we want to link against exactly the compiler unit
id
- when using TemplateHaskell we want to link against exactly the package
that contains the TemplateHaskell interfaces, which is `ghc-internal`
See: <https://github.com/haskell/cabal/issues/10087>
Resolves #25282
- - - - -
499c4efe by Bryan Richter at 2025-06-26T04:20:33-04:00
CI: Fix and clean up capture of timings
* Fixes the typo that caused 'cat ci-timings' to report "no such file or
directory"
* Gave ci_timings.txt a file extension so it may play better with other
systems
* Fixed the use of time_it so all times are recorded
* Fixed time_it to print name along with timing
- - - - -
86c90c9e by Bryan Richter at 2025-06-26T04:20:33-04:00
CI: Update collapsible section usage
The syntax apparently changed at some point.
- - - - -
04308ee4 by Bryan Richter at 2025-06-26T04:20:33-04:00
CI: Add more collapsible sections
- - - - -
43b606bb by Florian Ragwitz at 2025-06-27T16:31:26-04:00
Tick uses of wildcard/pun field binds as if using the record selector function
Fixes #17834.
See Note [Record-selector ticks] for additional reasoning behind this as well
as an overview of the implementation details and future improvements.
- - - - -
d4952549 by Ben Gamari at 2025-06-27T16:32:08-04:00
testsuite/caller-cc: Make CallerCc[123] less sensitive
These were previously sensitive to irrelevant changes in program
structure. To avoid this we filter out all by lines emitted by the
-fcaller-cc from the profile.
- - - - -
cb4fbbcc by Simon Peyton Jones at 2025-06-29T17:10:21+01:00
Renaming around predicate types
.. we were (as it turned out) abstracting over
type-class selectors in SPECIALISATION rules!
Wibble isEqPred
- - - - -
3c38ecc8 by Simon Peyton Jones at 2025-06-29T17:10:21+01:00
Refactor of Specialise.hs
This is a bit experimental. The original aim was to simplify
specUnfolding by getting rid of the dx_binds returned by specHeader;
but I'm worried about duplicating work so it's not finished.
Generally, though, `specHeader` is simpler and clearer which is good.
Alos add a few more `HasDebugCallStack` contexts.
- - - - -
40e7890a by Simon Peyton Jones at 2025-06-29T17:10:39+01:00
Improve treatment of SPECIALISE pragmas -- again!
This MR does another major refactor of the way that SPECIALISE
pragmas work, to fix #26115, #26116, #26117.
* We now /always/ solve forall-constraints in an all-or-nothing way.
See Note [Solving a Wanted forall-constraint] in GHC.Tc.Solver.Solve
This means we might have unsolved quantified constraints, which need
to be reported. See `inert_insts` in `getUnsolvedInerts`.
* I refactored the short-cut solver for type classes to work by
recursively calling the solver rather than by having a little baby
solver that kept being not clever enough.
See Note [Shortcut solving] in GHC.Tc.Solver.Dict
* When solving a forall-constraint, we now solve it immediately,
rather than emitting an implication constraint to be solved later.
This saves quite a bit of plumbing; e.g
- The `wl_implics` field of `WorkList` is gone,
- The types of `solveSimpleWanteds` and friends are simplified.
- An EvFun contains binding, rather than an EvBindsVar ref-cell that
will in the future contain bindings. That makes `evVarsOfTerm`
simpler
* I totally rewrote the desugaring of SPECIALISE pragmas, again.
The new story is in Note [Desugaring new-form SPECIALISE pragmas]
in GHC.HsToCore.Binds
Both old-form and new-form SPECIALISE pragmas now route through the same
function `dsSpec_help`. The tricky function `decomposeRuleLhs` is now used only
for user-written RULES, not for SPECIALISE pragmas.
* A small refactor: `ebv_tcvs` in `EvBindsBar` now has a list of coercions, rather
than a set of tyvars. We just delay taking the free vars.
- - - - -
17b1a135 by Simon Peyton Jones at 2025-06-29T17:10:39+01:00
Do not look in inert_cans in lookupInInerts
...it bypasses all the shortcut stuff
- - - - -
51acab69 by Simon Peyton Jones at 2025-06-29T23:27:36+01:00
Simplify findDict and friends
- - - - -
286 changed files:
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/common.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Core.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/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/PatSyn.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/TyCo/Ppr.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Env/Types.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Stg/EnforceEpt/Types.hs
- compiler/GHC/SysTools/Ar.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/Sig.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Instance/Family.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Rewrite.hs
- compiler/GHC/Tc/Solver/Solve.hs
- + compiler/GHC/Tc/Solver/Solve.hs-boot
- compiler/GHC/Tc/Solver/Types.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/Var.hs
- compiler/GHC/Types/Var.hs-boot
- compiler/GHC/Unit/Env.hs
- compiler/GHC/Unit/Home/Graph.hs
- compiler/GHC/Unit/Home/PackageTable.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Utils/Panic.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/Language/Haskell/Syntax/Pat.hs
- compiler/Setup.hs
- distrib/configure.ac.in
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/exts/gadt_syntax.rst
- docs/users_guide/exts/required_type_arguments.rst
- docs/users_guide/ghci.rst
- docs/users_guide/using-warnings.rst
- docs/users_guide/using.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Print.hs
- hadrian/cfg/default.host.target.in
- hadrian/cfg/default.target.in
- hadrian/cfg/system.config.in
- hadrian/src/Builder.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Settings/Builders/RunTest.hs
- hadrian/stack.yaml
- hadrian/stack.yaml.lock
- libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
- libraries/template-haskell/changelog.md
- linters/lint-whitespace/lint-whitespace.cabal
- m4/fp_settings.m4
- m4/ghc_toolchain.m4
- m4/prep_target_file.m4
- rts/include/stg/MachRegs.h
- rts/linker/LoadArchive.c
- testsuite/tests/annotations/should_fail/annfail03.stderr
- testsuite/tests/annotations/should_fail/annfail09.stderr
- testsuite/tests/dependent/should_fail/T16326_Fail6.stderr
- + testsuite/tests/ghc-api/T26120.hs
- + testsuite/tests/ghc-api/T26120.stdout
- testsuite/tests/ghc-api/all.T
- testsuite/tests/ghc-e/should_fail/T18441fail5.stderr
- testsuite/tests/ghci/prog-mhu003/prog-mhu003.stderr
- testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stderr
- + testsuite/tests/ghci/prog-mhu005/Makefile
- + testsuite/tests/ghci/prog-mhu005/a/A.hs
- + testsuite/tests/ghci/prog-mhu005/all.T
- + testsuite/tests/ghci/prog-mhu005/b/B.hs
- + testsuite/tests/ghci/prog-mhu005/prog-mhu005a.script
- + testsuite/tests/ghci/prog-mhu005/prog-mhu005a.stderr
- + testsuite/tests/ghci/prog-mhu005/prog-mhu005a.stdout
- + testsuite/tests/ghci/prog-mhu005/unitA
- + testsuite/tests/ghci/prog-mhu005/unitB
- + testsuite/tests/ghci/prog021/A.hs
- + testsuite/tests/ghci/prog021/B.hs
- + testsuite/tests/ghci/prog021/Makefile
- + testsuite/tests/ghci/prog021/all.T
- + testsuite/tests/ghci/prog021/prog021a.script
- + testsuite/tests/ghci/prog021/prog021a.stderr
- + testsuite/tests/ghci/prog021/prog021a.stdout
- + testsuite/tests/ghci/prog021/prog021b.script
- + testsuite/tests/ghci/prog021/prog021b.stderr
- + testsuite/tests/ghci/prog021/prog021b.stdout
- + testsuite/tests/ghci/prog022/A.hs
- + testsuite/tests/ghci/prog022/B.hs
- + testsuite/tests/ghci/prog022/Makefile
- + testsuite/tests/ghci/prog022/all.T
- + testsuite/tests/ghci/prog022/ghci.prog022a.script
- + testsuite/tests/ghci/prog022/ghci.prog022a.stderr
- + testsuite/tests/ghci/prog022/ghci.prog022a.stdout
- + testsuite/tests/ghci/prog022/ghci.prog022b.script
- + testsuite/tests/ghci/prog022/ghci.prog022b.stderr
- + testsuite/tests/ghci/prog022/ghci.prog022b.stdout
- testsuite/tests/ghci/scripts/ghci021.stderr
- 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/recsel/Makefile
- + testsuite/tests/hpc/recsel/recsel.hs
- + testsuite/tests/hpc/recsel/recsel.stdout
- + testsuite/tests/hpc/recsel/test.T
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/printer/T18791.stderr
- testsuite/tests/profiling/should_run/caller-cc/all.T
- testsuite/tests/quasiquotation/qq001/qq001.stderr
- testsuite/tests/quasiquotation/qq002/qq002.stderr
- testsuite/tests/quasiquotation/qq003/qq003.stderr
- testsuite/tests/quasiquotation/qq004/qq004.stderr
- + testsuite/tests/quotes/LiftErrMsg.hs
- + testsuite/tests/quotes/LiftErrMsg.stderr
- + testsuite/tests/quotes/LiftErrMsgDefer.hs
- + testsuite/tests/quotes/LiftErrMsgDefer.stderr
- + testsuite/tests/quotes/LiftErrMsgTyped.hs
- + testsuite/tests/quotes/LiftErrMsgTyped.stderr
- testsuite/tests/quotes/T10384.stderr
- testsuite/tests/quotes/TH_localname.stderr
- testsuite/tests/quotes/all.T
- + testsuite/tests/rep-poly/T26107.hs
- testsuite/tests/rep-poly/all.T
- + testsuite/tests/simplCore/should_compile/T26115.hs
- + testsuite/tests/simplCore/should_compile/T26115.stderr
- + testsuite/tests/simplCore/should_compile/T26116.hs
- + testsuite/tests/simplCore/should_compile/T26116.stderr
- + testsuite/tests/simplCore/should_compile/T26117.hs
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/splice-imports/SI03.stderr
- testsuite/tests/splice-imports/SI05.stderr
- testsuite/tests/splice-imports/SI16.stderr
- testsuite/tests/splice-imports/SI18.stderr
- testsuite/tests/splice-imports/SI20.stderr
- testsuite/tests/splice-imports/SI25.stderr
- testsuite/tests/splice-imports/SI28.stderr
- testsuite/tests/splice-imports/SI31.stderr
- + 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/T16976z.stderr
- testsuite/tests/th/T17820a.stderr
- testsuite/tests/th/T17820b.stderr
- testsuite/tests/th/T17820c.stderr
- testsuite/tests/th/T17820d.stderr
- testsuite/tests/th/T17820e.stderr
- testsuite/tests/th/T20868.stdout
- testsuite/tests/th/T23829_hasty.stderr
- testsuite/tests/th/T23829_hasty_b.stderr
- testsuite/tests/th/T5795.stderr
- testsuite/tests/th/all.T
- + testsuite/tests/typecheck/should_compile/T20873c.hs
- − testsuite/tests/typecheck/should_compile/T22141a.stderr
- − testsuite/tests/typecheck/should_compile/T22141b.stderr
- − testsuite/tests/typecheck/should_compile/T22141c.stderr
- − testsuite/tests/typecheck/should_compile/T22141d.stderr
- − testsuite/tests/typecheck/should_compile/T22141e.stderr
- testsuite/tests/typecheck/should_compile/T23171.hs
- testsuite/tests/typecheck/should_compile/T23739a.hs
- + testsuite/tests/typecheck/should_compile/TyAppPat_Tricky.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/T20443b.stderr
- − testsuite/tests/typecheck/should_fail/T20873c.hs
- − testsuite/tests/typecheck/should_fail/T20873c.stderr
- testsuite/tests/typecheck/should_compile/T22141a.hs → testsuite/tests/typecheck/should_fail/T22141a.hs
- testsuite/tests/typecheck/should_fail/T22141a.stderr
- testsuite/tests/typecheck/should_compile/T22141b.hs → testsuite/tests/typecheck/should_fail/T22141b.hs
- testsuite/tests/typecheck/should_fail/T22141b.stderr
- testsuite/tests/typecheck/should_compile/T22141c.hs → testsuite/tests/typecheck/should_fail/T22141c.hs
- testsuite/tests/typecheck/should_fail/T22141c.stderr
- testsuite/tests/typecheck/should_compile/T22141d.hs → testsuite/tests/typecheck/should_fail/T22141d.hs
- testsuite/tests/typecheck/should_fail/T22141d.stderr
- testsuite/tests/typecheck/should_compile/T22141e.hs → testsuite/tests/typecheck/should_fail/T22141e.hs
- testsuite/tests/typecheck/should_fail/T22141e.stderr
- testsuite/tests/typecheck/should_compile/T22141e_Aux.hs → testsuite/tests/typecheck/should_fail/T22141e_Aux.hs
- testsuite/tests/typecheck/should_fail/TyAppPat_TooMany.stderr
- testsuite/tests/typecheck/should_fail/all.T
- + 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/T23739_fail_case.hs
- testsuite/tests/vdq-rta/should_fail/T23739_fail_case.stderr
- 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/exe/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
- utils/haddock/CHANGES.md
- utils/haddock/doc/cheatsheet/haddocks.md
- utils/haddock/doc/markup.rst
- utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs
- utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/GhcUtils.hs
- utils/haddock/haddock-api/src/Haddock/Interface.hs
- utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
- + utils/haddock/html-test/ref/RedactTypeSynonyms.html
- + utils/haddock/html-test/src/RedactTypeSynonyms.hs
- + utils/haddock/latex-test/ref/RedactTypeSynonyms/RedactTypeSynonyms.tex
- + utils/haddock/latex-test/src/RedactTypeSynonyms/RedactTypeSynonyms.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6611434614feabaef546987da3e9d9…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6611434614feabaef546987da3e9d9…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/bump-win32-tarballs] rts: Mark API set symbols as HIDDEN and correct symbol type
by Tamar Christina (@Phyx) 29 Jun '25
by Tamar Christina (@Phyx) 29 Jun '25
29 Jun '25
Tamar Christina pushed to branch wip/bump-win32-tarballs at Glasgow Haskell Compiler / GHC
Commits:
ac1780b6 by Tamar Christina at 2025-06-29T21:37:39+01:00
rts: Mark API set symbols as HIDDEN and correct symbol type
- - - - -
1 changed file:
- rts/linker/PEi386.c
Changes:
=====================================
rts/linker/PEi386.c
=====================================
@@ -1174,8 +1174,10 @@ bool checkAndLoadImportLibrary( pathchar* arch_name, char* member_name, FILE* f
// Because the symbol has been loaded before we actually need it, if a
// stronger reference wants to add a duplicate we should discard this
// one to preserve link order.
- if (!ghciInsertSymbolTable(dll, symhash, symbol, sym, false,
- SYM_TYPE_CODE | SYM_TYPE_DUP_DISCARD, NULL))
+ SymType symType = SYM_TYPE_DUP_DISCARD | SYM_TYPE_HIDDEN;
+ symType |= hdr.Type == IMPORT_OBJECT_CODE ? SYM_TYPE_CODE : SYM_TYPE_DATA;
+
+ if (!ghciInsertSymbolTable(dll, symhash, symbol, sym, false, symType, NULL))
return false;
return true;
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ac1780b62a270952a983128f385f88f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ac1780b62a270952a983128f385f88f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/bump-win32-tarballs] 2 commits: rts: rename label so name doesn't conflict with param
by Tamar Christina (@Phyx) 29 Jun '25
by Tamar Christina (@Phyx) 29 Jun '25
29 Jun '25
Tamar Christina pushed to branch wip/bump-win32-tarballs at Glasgow Haskell Compiler / GHC
Commits:
a22e5175 by Tamar Christina at 2025-06-29T13:16:11+01:00
rts: rename label so name doesn't conflict with param
- - - - -
8a431bcb by Tamar Christina at 2025-06-29T16:25:41+01:00
rts: Handle API set symbol versioning conflicts
- - - - -
1 changed file:
- rts/linker/PEi386.c
Changes:
=====================================
rts/linker/PEi386.c
=====================================
@@ -342,6 +342,98 @@
Finally, we enter `ocResolve`, where we resolve relocations and and allocate
jump islands (using the m32 allocator for backing storage) as necessary.
+ Note [Windows API Set]
+ ~~~~~~~~~~~~~~~~~~~~~~
+ Windows has a concept called API Sets [1][2] which is intended to be Windows's
+ equivalent to glibc's symbolic versioning. It is also used to handle the API
+ surface difference between different device classes. e.g. the API might be
+ handled differently between a desktop and tablet.
+
+ This is handled through two mechanisms:
+
+ 1. Direct Forward: These use import libraries to manage to first level
+ redirection. So what used to be in ucrt.dll is now redirected based on
+ ucrt.lib. Every API now points to a possible different set of API sets
+ each following the API set contract:
+
+ * The name must begin either with the string api- or ext-.
+ * Names that begin with api- represent APIs that exist on all Windows
+ editions that satisfy the API's version requirements.
+ * Names that begin with ext- represent APIs that may not exist on all
+ Windows editions.
+ * The name must end with the sequence l<n>-<n>-<n>, where n consists of
+ decimal digits.
+ * The body of the name can be alphanumeric characters, or dashes (-).
+ * The name is case insensitive.
+
+ Here are some examples of API set contract names:
+
+ - api-ms-win-core-ums-l1-1-0
+ - ext-ms-win-com-ole32-l1-1-5
+ - ext-ms-win-ntuser-window-l1-1-0
+ - ext-ms-win-ntuser-window-l1-1-1
+
+ Forward references don't require anything special from the calling
+ application in that the Windows loader through "LoadLibrary" will
+ automatically load the right reference for you if given an API set
+ name including the ".dll" suffix. For example:
+
+ INFO: DLL api-ms-win-eventing-provider-l1-1-0.dll was redirected to C:\WINDOWS\SYSTEM32\kernelbase.dll by API set
+ INFO: DLL api-ms-win-core-apiquery-l1-1-0.dll was redirected to C:\WINDOWS\SYSTEM32\ntdll.dll by API set
+ INFO: DLL api-ms-win-core-processthreads-l1-1-3.dll was redirected to C:\WINDOWS\SYSTEM32\kernelbase.dll by API set
+ INFO: DLL api-ms-win-core-processthreads-l1-1-2.dll was redirected to C:\WINDOWS\SYSTEM32\kernelbase.dll by API set
+ INFO: DLL api-ms-win-core-processthreads-l1-1-1.dll was redirected to C:\WINDOWS\SYSTEM32\kernelbase.dll by API set
+ INFO: DLL api-ms-win-core-processthreads-l1-1-0.dll was redirected to C:\WINDOWS\SYSTEM32\kernelbase.dll by API set
+ INFO: DLL api-ms-win-core-registry-l1-1-0.dll was redirected to C:\WINDOWS\SYSTEM32\kernelbase.dll by API set
+ INFO: DLL api-ms-win-core-heap-l1-1-0.dll was redirected to C:\WINDOWS\SYSTEM32\kernelbase.dll by API set
+ INFO: DLL api-ms-win-core-heap-l2-1-0.dll was redirected to C:\WINDOWS\SYSTEM32\kernelbase.dll by API set
+ INFO: DLL api-ms-win-core-memory-l1-1-1.dll was redirected to C:\WINDOWS\SYSTEM32\kernelbase.dll by API set
+ INFO: DLL api-ms-win-core-memory-l1-1-0.dll was redirected to C:\WINDOWS\SYSTEM32\kernelbase.dll by API set
+ INFO: DLL api-ms-win-core-memory-l1-1-2.dll was redirected to C:\WINDOWS\SYSTEM32\kernelbase.dll by API set
+ INFO: DLL api-ms-win-core-handle-l1-1-0.dll was redirected to C:\WINDOWS\SYSTEM32\kernelbase.dll by API set
+
+ Which shows how the loader has redirected some of the references used
+ by ghci.
+
+ Historically though we've treated shared libs lazily. We would load\
+ the shared library, but not resolve the symbol immediately and wait until
+ the symbol is requested to iterate in order through the shared libraries.
+
+ This assumes that you ever only had one version of a symbol. i.e. we had
+ an assumption that all exported symbols in different shared libraries
+ should be the same, because most of the time they come from re-exporting
+ from a base library. This is a bit of a weak assumption and doesn't hold
+ with API Sets.
+
+ For that reason the loader now resolves symbols immediately, and because
+ we now resolve using BIND_NOW we must make sure that a symbol loaded
+ through an OC has precedent because the BIND_NOW refernce was not asked
+ for. For that reason we load the symbols for API sets with the
+ SYM_TYPE_DUP_DISCARD flag set.
+
+ 2. Reverse forwarders: This is when the application has a direct reference
+ to the old name of an API. e.g. if GHC still used "msvcrt.dll" or
+ "ucrt.dll" we would have had to deal with this case. In this case the
+ loader intercepts the call and if it exists the dll is loaded. There is
+ an extra indirection as you go from foo.dll => api-ms-foo-1.dll => foo_imp.dll
+
+ But if the API doesn't exist on the device it's resolved to a stub in the
+ API set that if called will result in an error should it be called [3].
+
+ This means that usages of GetProcAddress and LoadLibrary to check for the
+ existance of a function aren't safe, because they'll always succeed, but may
+ result in a pointer to the stub rather than the actual function.
+
+ WHat does this mean for the RTS linker? Nothing. We don't have a fallback
+ for if the function doesn't exist. The RTS is merely just executing what
+ it was told to run. It's writers of libraries that have to be careful when
+ doing dlopen()/LoadLibrary.
+
+
+ [1] https://learn.microsoft.com/en-us/windows/win32/apiindex/windows-apisets
+ [2] https://mingwpy.github.io/ucrt.html#api-set-implementation
+ [3] https://learn.microsoft.com/en-us/windows/win32/apiindex/detect-api-set-ava…
+
*/
#include "Rts.h"
@@ -882,7 +974,7 @@ addDLL_PEi386( const pathchar *dll_name, HINSTANCE *loaded )
goto error;
}
} else {
- goto loaded; /* We're done. DLL has been loaded. */
+ goto loaded_ok; /* We're done. DLL has been loaded. */
}
}
}
@@ -890,7 +982,7 @@ addDLL_PEi386( const pathchar *dll_name, HINSTANCE *loaded )
// We failed to load
goto error;
-loaded:
+loaded_ok:
addLoadedDll(&loaded_dll_cache, dll_name, instance);
addDLLHandle(buf, instance);
if (loaded) {
@@ -1055,7 +1147,8 @@ bool checkAndLoadImportLibrary( pathchar* arch_name, char* member_name, FILE* f
// We must call `addDLL_PEi386` directly rather than `addDLL` because `addDLL`
// is now a wrapper around `loadNativeObj` which acquires a lock which we
// already have here.
- const char* result = addDLL_PEi386(dll, NULL);
+ HINSTANCE instance;
+ const char* result = addDLL_PEi386(dll, &instance);
stgFree(image);
@@ -1069,6 +1162,22 @@ bool checkAndLoadImportLibrary( pathchar* arch_name, char* member_name, FILE* f
}
stgFree(dll);
+
+ // See Note [Windows API Set]
+ // We must immediately tie the symbol to the shared library. The easiest
+ // way is to load the symbol immediately. We already have all the
+ // information so might as well
+ SymbolAddr* sym = lookupSymbolInDLL_PEi386 (symbol, instance, dll, NULL);
+ ASSERT(sym);
+ // The symbol must have been found, and we can add it to the RTS symbol table
+ IF_DEBUG(linker, debugBelch("checkAndLoadImportLibrary: resolved symbol %s to %p\n", symbol, sym));
+ // Because the symbol has been loaded before we actually need it, if a
+ // stronger reference wants to add a duplicate we should discard this
+ // one to preserve link order.
+ if (!ghciInsertSymbolTable(dll, symhash, symbol, sym, false,
+ SYM_TYPE_CODE | SYM_TYPE_DUP_DISCARD, NULL))
+ return false;
+
return true;
}
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d2c66a91150b49e3969c25af2a9868…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d2c66a91150b49e3969c25af2a9868…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/supersven/riscv-vectors] 49 commits: Hadrian: Add option to generate .hie files for stage1 libraries
by Sven Tennie (@supersven) 29 Jun '25
by Sven Tennie (@supersven) 29 Jun '25
29 Jun '25
Sven Tennie pushed to branch wip/supersven/riscv-vectors 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.
- - - - -
c7aa0c10 by Andreas Klebinger at 2025-06-15T05:47:24-04: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.
- - - - -
fd998679 by Krzysztof Gogolewski at 2025-06-15T05:48:06-04:00
Fix EPT enforcement when mixing unboxed tuples and non-tuples
The code was assuming that an alternative cannot be returning a normal
datacon and an unboxed tuple at the same time. However, as seen in #26107,
this can happen when using a GADT to refine the representation type.
The solution is just to conservatively return TagDunno.
- - - - -
e64b3f16 by ARATA Mizuki at 2025-06-17T10:13:42+09:00
MachRegs.h: Don't define NO_ARG_REGS when a XMM register is defined
On i386, MAX_REAL_VANILLA_REG is 1, but MAX_REAL_XMM_REG is 4.
If we define NO_ARG_REGS on i386, programs that use SIMD vectors may segfault.
Closes #25985
A couple of notes on the BROKEN_TESTS field:
* This fixes the segfault from T25062_V16.
* The failure from T22187_run was fixed in an earlier commit (see #25561),
but BROKEN_TESTS was missed at that time. Now should be a good time to
mark it fixed.
- - - - -
3e7c6b4d by Matthew Pickering at 2025-06-18T15:34:04-04:00
Improve error messages when implicit lifting fails
This patch concerns programs which automatically try to fix level errors
by inserting `Lift`. For example:
```
foo x = [| x |]
~>
foo x = [| $(lift x) |]
```
Before, there were two problems with the message.
1. (#26031), the location of the error was reported as the whole
quotation.
2. (#26035), the message just mentions there is no Lift instance, but
gives no indicate why the user program needed a Lift instance in the
first place.
This problem is especially bad when you disable
`ImplicitStagePersistence`, so you just end up with a confusing "No
instance for" message rather than an error message about levels
This patch fixes both these issues.
Firstly, `PendingRnSplice` differentiates between a user-written splice
and an implicit lift. Then, the Lift instance is precisely requested
with a specific origin in the typechecker. If the instance fails to be
solved, the message is reported using the `TcRnBadlyLevelled`
constructor (like a normal level error).
Fixes #26031, #26035
- - - - -
44b8cee2 by Cheng Shao at 2025-06-18T15:34:46-04:00
testsuite: add T26120 marked as broken
- - - - -
894a04f3 by Cheng Shao at 2025-06-18T15:34:46-04:00
compiler: fix GHC.SysTools.Ar archive member size writing logic
This patch fixes a long-standing bug in `GHC.SysTools.Ar` that emits
the wrong archive member size in each archive header. It should encode
the exact length of the member payload, excluding any padding byte,
otherwise malformed archive that extracts a broken object with an
extra trailing byte could be created.
Apart from the in-tree `T26120` test, I've also created an out-of-tree
testsuite at https://github.com/TerrorJack/ghc-ar-quickcheck that
contains QuickCheck roundtrip tests for `GHC.SysTools.Ar`. With this
fix, simple roundtrip tests and `writeGNUAr`/GNU `ar` roundtrip test
passes. There might be more bugs lurking in here, but this patch is
still a critical bugfix already.
Fixes #26120 #22586.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
f677ab5f by Lauren Yim at 2025-06-18T15:35:37-04:00
fix some typos in the warnings page in the user guide
- - - - -
b968e1c1 by Rodrigo Mesquita at 2025-06-18T15:36:18-04:00
Add a frozen callstack to throwGhcException
Fixes #25956
- - - - -
a5e0c3a3 by fendor at 2025-06-18T15:36:59-04:00
Update using.rst to advertise full mhu support for GHCi
- - - - -
d3e60e97 by Ryan Scott at 2025-06-18T22:29:21-04:00
Deprecate -Wdata-kinds-tc, make DataKinds issues in typechecker become errors
!11314 introduced the `-Wdata-kinds-tc` warning as part of a fix for #22141.
This was a temporary stopgap measure to allow users who were accidentally
relying on code which needed the `DataKinds` extension in order to typecheck
without having to explicitly enable the extension.
Now that some amount of time has passed, this patch deprecates
`-Wdata-kinds-tc` and upgrades any `DataKinds`-related issues in the
typechecker (which were previously warnings) into errors.
- - - - -
fd5b5177 by Ryan Hendrickson at 2025-06-18T22:30:06-04:00
haddock: Add redact-type-synonyms pragma
`{-# OPTIONS_HADDOCK redact-type-synonyms #-}` pragma will hide the RHS
of type synonyms, and display the result kind instead, if the RHS
contains any unexported types.
- - - - -
fbc0b92a by Vladislav Zavialov at 2025-06-22T04:25:16+03:00
Visible forall in GADTs (#25127)
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>
- - - - -
ae003a3a by Teo Camarasu at 2025-06-23T05:21:48-04:00
linters: lint-whitespace: bump upper-bound for containers
The version of containers was bumped in https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13989
- - - - -
0fb37893 by Matthew Pickering at 2025-06-23T13:55:10-04: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.
- - - - -
3bf6720e by soulomoon at 2025-06-23T13:55:52-04:00
Remove hptAllFamInstances usage during upsweep
Fixes #26118
This change eliminates the use of hptAllFamInstances during the upsweep phase,
as it could access non-below modules from the home package table.
The following updates were made:
* Updated checkFamInstConsistency to accept an explicit ModuleEnv FamInstEnv
parameter and removed the call to hptAllFamInstances.
* Adjusted hugInstancesBelow so we can construct ModuleEnv FamInstEnv
from its result,
* hptAllFamInstances and allFamInstances functions are removed.
- - - - -
83ee7b78 by Ben Gamari at 2025-06-24T05:02:07-04:00
configure: Don't force value of OTOOL, etc. if not present
Previously if `otool` and `install_name_tool` were not present they
would be overridden by `fp_settings.m4`. This logic was introduced in
4ff93292243888545da452ea4d4c1987f2343591 without explanation.
- - - - -
9329c9e1 by Ben Gamari at 2025-06-24T05:02:07-04:00
ghc-toolchain: Add support for otool, install_name_tool
Fixes part of ghc#23675.
- - - - -
25f5c998 by Ben Gamari at 2025-06-24T05:02:08-04:00
ghc-toolchain: Add support for llc, opt, llvm-as
Fixes #23675.
- - - - -
51d150dd by Rodrigo Mesquita at 2025-06-24T05:02:08-04:00
hadrian: Use settings-use-distro-mingw directly
The type `ToolchainSetting` only made sense when we had more settings to
fetch from the system config file. Even then "settings-use-distro-mingw"
is arguably not a toolchain setting.
With the fix for #23675, all toolchain tools were moved to the
`ghc-toolchain` `Toolchain` format. Therefore, we can inline
`settings-use-distro-mingw` accesses and delete `ToolchainSetting`.
- - - - -
dcf68a83 by Rodrigo Mesquita at 2025-06-24T05:02:08-04:00
configure: Check LlvmTarget exists for LlvmAsFlags
If LlvmTarget was empty, LlvmAsFlags would be just "--target=".
If it is empty now, simply keep LlvmAsFlags empty.
ghc-toolchain already does this right. This fix makes the two
configurations match up.
- - - - -
580a3353 by Ben Gamari at 2025-06-24T05:02:51-04:00
rts/linker/LoadArchive: Use bool
Improve type precision by using `bool` instead of `int` and `StgBool`.
- - - - -
76d1041d by Ben Gamari at 2025-06-24T05:02:51-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.
- - - - -
4b748a99 by Teo Camarasu at 2025-06-24T15:31:07-04:00
template-haskell: improve changelog
stable -> more stable, just to clarify that this interface isn't fully stable.
errornously -> mistakenly: I typod this and also let's go for a simpler word
- - - - -
e358e477 by Sylvain Henry at 2025-06-24T15:31:58-04:00
Bump stack resolver to use GHC 9.6.7
Cf #26139
- - - - -
4bf5eb63 by fendor at 2025-06-25T17:05:43-04:00
Teach `:reload` about multiple home units
`:reload` needs to lookup the `ModuleName` and must not assume the given
`ModuleName` is in the current `HomeUnit`.
We add a new utility function which allows us to find a `HomeUnitModule`
instead of a `Module`.
Further, we introduce the `GhciCommandError` type which can be used to
abort the execution of a GHCi command.
This error is caught and printed in a human readable fashion.
- - - - -
b3d97bb3 by fendor at 2025-06-25T17:06:25-04:00
Implement `-fno-load-initial-targets` flag
We add the new flag `-fno-load-initial-targets` which doesn't load all `Target`s
immediately but only computes the module graph for all `Target`s.
The user can then decide to load modules from that module graph using
the syntax:
ghci> :reload <Mod>
This will load everything in the module graph up to `Mod`.
The user can return to the initial state by using the builtin target
`none` to unload all modules.
ghci> :reload none
Is in principle identical to starting a new session with the
`-fno-load-initial-targets` flag.
The `-fno-load-initial-targets` flag allows for faster startup time of GHCi when a
user has lots of `Target`s.
We additionally extend the `:reload` command to accept multiple
`ModuleName`s. For example:
ghci> :reload <Mod1> <Mod2>
Loads all modules up to the modules `Mod1` and `Mod2`.
- - - - -
49f44e52 by Teo Camarasu at 2025-06-26T04:19:51-04:00
Expose ghc-internal unit id through the settings file
This in combination with the unit id of the compiler library allows
cabal to know of the two unit ids that should not be reinstalled (in
specific circumstances) as:
- when using plugins, we want to link against exactly the compiler unit
id
- when using TemplateHaskell we want to link against exactly the package
that contains the TemplateHaskell interfaces, which is `ghc-internal`
See: <https://github.com/haskell/cabal/issues/10087>
Resolves #25282
- - - - -
499c4efe by Bryan Richter at 2025-06-26T04:20:33-04:00
CI: Fix and clean up capture of timings
* Fixes the typo that caused 'cat ci-timings' to report "no such file or
directory"
* Gave ci_timings.txt a file extension so it may play better with other
systems
* Fixed the use of time_it so all times are recorded
* Fixed time_it to print name along with timing
- - - - -
86c90c9e by Bryan Richter at 2025-06-26T04:20:33-04:00
CI: Update collapsible section usage
The syntax apparently changed at some point.
- - - - -
04308ee4 by Bryan Richter at 2025-06-26T04:20:33-04:00
CI: Add more collapsible sections
- - - - -
43b606bb by Florian Ragwitz at 2025-06-27T16:31:26-04:00
Tick uses of wildcard/pun field binds as if using the record selector function
Fixes #17834.
See Note [Record-selector ticks] for additional reasoning behind this as well
as an overview of the implementation details and future improvements.
- - - - -
d4952549 by Ben Gamari at 2025-06-27T16:32:08-04:00
testsuite/caller-cc: Make CallerCc[123] less sensitive
These were previously sensitive to irrelevant changes in program
structure. To avoid this we filter out all by lines emitted by the
-fcaller-cc from the profile.
- - - - -
4da00f8a by Sven Tennie at 2025-06-29T12:56:15+02:00
Implement CPU vector support (RVV) detection for RISC-V
- - - - -
7d006673 by Sven Tennie at 2025-06-29T12:56:16+02:00
Introduce -mriscv-vlen driver argument with runtime check
Ensure that the configured vlen fits to the detected one.
- - - - -
d9d3e110 by Sven Tennie at 2025-06-29T12:56:16+02:00
Compile AutoApply_V*.cmm and Jumps_V*.cmm with vector support
If the running CPU does not support RVV, this code will not be executed.
However, at build time, we have to emit (prepare) it.
- - - - -
fe4118dd by Sven Tennie at 2025-06-29T12:56:16+02:00
Emit code for RVV
This includes adding the vector registers to the register allocator and
adding support for the related MachOps to the cod generator.
- - - - -
c0822d62 by Sven Tennie at 2025-06-29T12:56:16+02:00
Detect RVV CPU features and make them configurable for CROSS_EMULATOR
Unfortunately, the cpuinfo Python package is abandonned. Thus, we just
add RVV detection here (and not upstream.)
cpuinfo is not executed on the CROSS_EMULATOR. So, we make supported
features configurable.
- - - - -
afe7a855 by Sven Tennie at 2025-06-29T12:56:16+02:00
Adjust SIMD test to support/use RISC-V
- - - - -
bc674b54 by Sven Tennie at 2025-06-29T12:56:16+02:00
WIP: Test for the RVV c calling convention
- - - - -
392 changed files:
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/common.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/CodeGen.Platform.h
- compiler/GHC.hs
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/CmmToAsm/Config.hs
- compiler/GHC/CmmToAsm/Format.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/RV64.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToAsm/RV64/Regs.hs
- compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Linear/RV64.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/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/PatSyn.hs
- compiler/GHC/Core/TyCo/Ppr.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Config/StgToCmm.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Env/Types.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.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/HsToCore/Ticks.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/Linker/ExtraObj.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Platform/Reg/Class.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Stg/EnforceEpt/Types.hs
- compiler/GHC/StgToCmm/Config.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/SysTools/Ar.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/Instance/Family.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/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/Tc/Validity.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/GHC/Unit/Env.hs
- compiler/GHC/Unit/Home/Graph.hs
- compiler/GHC/Unit/Home/PackageTable.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Utils/Outputable.hs
- compiler/GHC/Utils/Panic.hs
- 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/Setup.hs
- compiler/ghc.cabal.in
- distrib/configure.ac.in
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/exts/gadt_syntax.rst
- docs/users_guide/exts/required_type_arguments.rst
- docs/users_guide/ghci.rst
- docs/users_guide/using-warnings.rst
- docs/users_guide/using.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Print.hs
- ghc/ghc-bin.cabal.in
- hadrian/cfg/default.host.target.in
- hadrian/cfg/default.target.in
- hadrian/cfg/system.config.in
- hadrian/doc/flavours.md
- hadrian/doc/user-settings.md
- hadrian/hadrian.cabal
- hadrian/src/Builder.hs
- hadrian/src/Context.hs
- hadrian/src/Context/Path.hs
- hadrian/src/Flavour.hs
- hadrian/src/Flavour/Type.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Settings/Builders/Ghc.hs
- hadrian/src/Settings/Builders/RunTest.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Flavours/Release.hs
- hadrian/src/Settings/Packages.hs
- hadrian/src/Settings/Warnings.hs
- hadrian/stack.yaml
- hadrian/stack.yaml.lock
- 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
- libraries/template-haskell/changelog.md
- libraries/unix
- linters/lint-whitespace/lint-whitespace.cabal
- m4/fp_gcc_supports_no_pie.m4
- m4/fp_settings.m4
- m4/fptools_set_c_ld_flags.m4
- m4/ghc_toolchain.m4
- m4/prep_target_file.m4
- rts/CheckVectorSupport.c
- rts/RtsStartup.c
- rts/include/stg/MachRegs.h
- rts/include/stg/MachRegs/riscv64.h
- rts/linker/LoadArchive.c
- testsuite/driver/cpu_features.py
- testsuite/driver/cpuinfo.py
- testsuite/driver/testglobals.py
- testsuite/driver/testlib.py
- testsuite/tests/annotations/should_fail/annfail03.stderr
- testsuite/tests/annotations/should_fail/annfail09.stderr
- 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/ghc-api/T26120.hs
- + testsuite/tests/ghc-api/T26120.stdout
- testsuite/tests/ghc-api/all.T
- testsuite/tests/ghc-e/should_fail/T18441fail5.stderr
- testsuite/tests/ghci/prog-mhu003/prog-mhu003.stderr
- testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stderr
- + testsuite/tests/ghci/prog-mhu005/Makefile
- + testsuite/tests/ghci/prog-mhu005/a/A.hs
- + testsuite/tests/ghci/prog-mhu005/all.T
- + testsuite/tests/ghci/prog-mhu005/b/B.hs
- + testsuite/tests/ghci/prog-mhu005/prog-mhu005a.script
- + testsuite/tests/ghci/prog-mhu005/prog-mhu005a.stderr
- + testsuite/tests/ghci/prog-mhu005/prog-mhu005a.stdout
- + testsuite/tests/ghci/prog-mhu005/unitA
- + testsuite/tests/ghci/prog-mhu005/unitB
- + testsuite/tests/ghci/prog021/A.hs
- + testsuite/tests/ghci/prog021/B.hs
- + testsuite/tests/ghci/prog021/Makefile
- + testsuite/tests/ghci/prog021/all.T
- + testsuite/tests/ghci/prog021/prog021a.script
- + testsuite/tests/ghci/prog021/prog021a.stderr
- + testsuite/tests/ghci/prog021/prog021a.stdout
- + testsuite/tests/ghci/prog021/prog021b.script
- + testsuite/tests/ghci/prog021/prog021b.stderr
- + testsuite/tests/ghci/prog021/prog021b.stdout
- + testsuite/tests/ghci/prog022/A.hs
- + testsuite/tests/ghci/prog022/B.hs
- + testsuite/tests/ghci/prog022/Makefile
- + testsuite/tests/ghci/prog022/all.T
- + testsuite/tests/ghci/prog022/ghci.prog022a.script
- + testsuite/tests/ghci/prog022/ghci.prog022a.stderr
- + testsuite/tests/ghci/prog022/ghci.prog022a.stdout
- + testsuite/tests/ghci/prog022/ghci.prog022b.script
- + testsuite/tests/ghci/prog022/ghci.prog022b.stderr
- + testsuite/tests/ghci/prog022/ghci.prog022b.stdout
- testsuite/tests/ghci/scripts/T12550.stdout
- testsuite/tests/ghci/scripts/T8959b.stderr
- testsuite/tests/ghci/scripts/all.T
- testsuite/tests/ghci/scripts/ghci021.stderr
- + 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/recsel/Makefile
- + testsuite/tests/hpc/recsel/recsel.hs
- + testsuite/tests/hpc/recsel/recsel.stdout
- + testsuite/tests/hpc/recsel/test.T
- 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/profiling/should_run/caller-cc/all.T
- testsuite/tests/quasiquotation/T3953.stderr
- testsuite/tests/quasiquotation/qq001/qq001.stderr
- testsuite/tests/quasiquotation/qq002/qq002.stderr
- testsuite/tests/quasiquotation/qq003/qq003.stderr
- testsuite/tests/quasiquotation/qq004/qq004.stderr
- + testsuite/tests/quotes/LiftErrMsg.hs
- + testsuite/tests/quotes/LiftErrMsg.stderr
- + testsuite/tests/quotes/LiftErrMsgDefer.hs
- + testsuite/tests/quotes/LiftErrMsgDefer.stderr
- + testsuite/tests/quotes/LiftErrMsgTyped.hs
- + testsuite/tests/quotes/LiftErrMsgTyped.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/rep-poly/T26107.hs
- testsuite/tests/rep-poly/all.T
- + testsuite/tests/simd/should_run/VectorCCallConv.hs
- + testsuite/tests/simd/should_run/VectorCCallConv.stdout
- + testsuite/tests/simd/should_run/VectorCCallConv_c.c
- testsuite/tests/simd/should_run/all.T
- testsuite/tests/simd/should_run/simd013C.c
- testsuite/tests/splice-imports/SI03.stderr
- testsuite/tests/splice-imports/SI05.stderr
- testsuite/tests/splice-imports/SI16.stderr
- testsuite/tests/splice-imports/SI18.stderr
- testsuite/tests/splice-imports/SI20.stderr
- testsuite/tests/splice-imports/SI25.stderr
- testsuite/tests/splice-imports/SI28.stderr
- testsuite/tests/splice-imports/SI31.stderr
- + 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/T16976z.stderr
- testsuite/tests/th/T17804.stderr
- testsuite/tests/th/T17820a.stderr
- testsuite/tests/th/T17820b.stderr
- testsuite/tests/th/T17820c.stderr
- testsuite/tests/th/T17820d.stderr
- testsuite/tests/th/T17820e.stderr
- testsuite/tests/th/T20868.stdout
- testsuite/tests/th/T23829_hasty.stderr
- testsuite/tests/th/T23829_hasty_b.stderr
- testsuite/tests/th/T5508.stderr
- testsuite/tests/th/T5795.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/T20873c.hs
- − testsuite/tests/typecheck/should_compile/T22141a.stderr
- − testsuite/tests/typecheck/should_compile/T22141b.stderr
- − testsuite/tests/typecheck/should_compile/T22141c.stderr
- − testsuite/tests/typecheck/should_compile/T22141d.stderr
- − testsuite/tests/typecheck/should_compile/T22141e.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/T20873c.hs
- − testsuite/tests/typecheck/should_fail/T20873c.stderr
- testsuite/tests/typecheck/should_compile/T22141a.hs → testsuite/tests/typecheck/should_fail/T22141a.hs
- testsuite/tests/typecheck/should_fail/T22141a.stderr
- testsuite/tests/typecheck/should_compile/T22141b.hs → testsuite/tests/typecheck/should_fail/T22141b.hs
- testsuite/tests/typecheck/should_fail/T22141b.stderr
- testsuite/tests/typecheck/should_compile/T22141c.hs → testsuite/tests/typecheck/should_fail/T22141c.hs
- testsuite/tests/typecheck/should_fail/T22141c.stderr
- testsuite/tests/typecheck/should_compile/T22141d.hs → testsuite/tests/typecheck/should_fail/T22141d.hs
- testsuite/tests/typecheck/should_fail/T22141d.stderr
- testsuite/tests/typecheck/should_compile/T22141e.hs → testsuite/tests/typecheck/should_fail/T22141e.hs
- testsuite/tests/typecheck/should_fail/T22141e.stderr
- testsuite/tests/typecheck/should_compile/T22141e_Aux.hs → testsuite/tests/typecheck/should_fail/T22141e_Aux.hs
- testsuite/tests/typecheck/should_fail/TyAppPat_TooMany.stderr
- testsuite/tests/typecheck/should_fail/all.T
- 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/T23739_fail_case.hs
- testsuite/tests/vdq-rta/should_fail/T23739_fail_case.stderr
- 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/exe/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
- utils/haddock/CHANGES.md
- utils/haddock/doc/cheatsheet/haddocks.md
- utils/haddock/doc/markup.rst
- utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs
- utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/GhcUtils.hs
- utils/haddock/haddock-api/src/Haddock/Interface.hs
- utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
- utils/haddock/haddock-library/haddock-library.cabal
- + utils/haddock/html-test/ref/RedactTypeSynonyms.html
- + utils/haddock/html-test/src/RedactTypeSynonyms.hs
- utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
- + utils/haddock/latex-test/ref/RedactTypeSynonyms/RedactTypeSynonyms.tex
- + utils/haddock/latex-test/src/RedactTypeSynonyms/RedactTypeSynonyms.hs
- 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/b6ea3f6a477885f214c873533a6301…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b6ea3f6a477885f214c873533a6301…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/supersven/riscv-vectors] 7 commits: Implement CPU vector support (RVV) detection for RISC-V
by Sven Tennie (@supersven) 29 Jun '25
by Sven Tennie (@supersven) 29 Jun '25
29 Jun '25
Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC
Commits:
dac9434c by Sven Tennie at 2025-06-29T12:13:42+02:00
Implement CPU vector support (RVV) detection for RISC-V
- - - - -
cfb7da61 by Sven Tennie at 2025-06-29T12:21:03+02:00
Introduce -mriscv-vlen driver argument with runtime check
Ensure that the configured vlen fits to the detected one.
- - - - -
134ffb9f by Sven Tennie at 2025-06-29T12:24:46+02:00
Compile AutoApply_V*.cmm and Jumps_V*.cmm with vector support
If the running CPU does not support RVV, this code will not be executed.
However, at build time, we have to emit (prepare) it.
- - - - -
d56e98f5 by Sven Tennie at 2025-06-29T12:28:10+02:00
Emit code for RVV
This includes adding the vector registers to the register allocator and
adding support for the related MachOps to the cod generator.
- - - - -
5d2c3b26 by Sven Tennie at 2025-06-29T12:31:32+02:00
Detect RVV CPU features and make them configurable for CROSS_EMULATOR
Unfortunately, the cpuinfo Python package is abandonned. Thus, we just
add RVV detection here (and not upstream.)
cpuinfo is not executed on the CROSS_EMULATOR. So, we make supported
features configurable.
- - - - -
d7a7aa64 by Sven Tennie at 2025-06-29T12:33:52+02:00
Adjust SIMD test to support/use RISC-V
- - - - -
b6ea3f6a by Sven Tennie at 2025-06-29T12:34:24+02:00
WIP: Test for the RVV c calling convention
- - - - -
37 changed files:
- compiler/CodeGen.Platform.h
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/CmmToAsm/Config.hs
- compiler/GHC/CmmToAsm/Format.hs
- compiler/GHC/CmmToAsm/RV64.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToAsm/RV64/Regs.hs
- compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Linear/RV64.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Config/StgToCmm.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Linker/ExtraObj.hs
- compiler/GHC/Platform/Reg/Class.hs
- compiler/GHC/StgToCmm/Config.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/Utils/Outputable.hs
- docs/users_guide/using.rst
- hadrian/src/Settings/Packages.hs
- libraries/unix
- rts/CheckVectorSupport.c
- rts/RtsStartup.c
- rts/include/stg/MachRegs.h
- rts/include/stg/MachRegs/riscv64.h
- testsuite/driver/cpu_features.py
- testsuite/driver/cpuinfo.py
- testsuite/driver/testglobals.py
- testsuite/driver/testlib.py
- + testsuite/tests/simd/should_run/VectorCCallConv.hs
- + testsuite/tests/simd/should_run/VectorCCallConv.stdout
- + testsuite/tests/simd/should_run/VectorCCallConv_c.c
- testsuite/tests/simd/should_run/all.T
- testsuite/tests/simd/should_run/simd013C.c
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/463de8893208cdc5a49a42b5de9951…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/463de8893208cdc5a49a42b5de9951…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc] Pushed new branch wip/supersven/riscv-vectors_SAVE
by Sven Tennie (@supersven) 29 Jun '25
by Sven Tennie (@supersven) 29 Jun '25
29 Jun '25
Sven Tennie pushed new branch wip/supersven/riscv-vectors_SAVE at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/supersven/riscv-vectors_SAVE
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/supersven/riscv-vectors] 2 commits: Delete cruft
by Sven Tennie (@supersven) 29 Jun '25
by Sven Tennie (@supersven) 29 Jun '25
29 Jun '25
Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC
Commits:
f6705fd2 by Sven Tennie at 2025-06-28T17:58:23+02:00
Delete cruft
- - - - -
463de889 by Sven Tennie at 2025-06-29T12:04:59+02:00
CheckVectorSupport: Support non-RVV cpus
- - - - -
5 changed files:
- − Makefile.save
- − Notes.md
- − ghc.diff
- − git.diff
- rts/CheckVectorSupport.c
Changes:
=====================================
Makefile.save deleted
=====================================
@@ -1,13 +0,0 @@
-.PHONY: boot configure build test-simd000
-
-boot:
- ./boot
-
-configure: boot
- configure_ghc
-
-build:
- hadrian/build -j --docs=none --flavour=devel2
-
-test-simd000: build
- CROSS_EMULATOR="qemu-riscv64" hadrian/build -j --docs=none --flavour=devel2 test --only=simd000
=====================================
Notes.md deleted
=====================================
@@ -1,7 +0,0 @@
-main.S:
-
-```
-v8 {q = {0xb0000000000000003}, l = {0x3, 0xb}, w = {0x3, 0x0, 0xb, 0x0}, s = {0x3, 0x0, 0x0, 0x0, 0xb, 0x0, 0x0, 0x0}, b = {0x3, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0xb, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0}}
-v10 {q = {0x1}, l = {0x1, 0x0}, w = {0x1, 0x0, 0x0, 0x0}, s = {0x1, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0, 0x0}, b = {0x1, 0x0 <repeats 15 times>}}
-
-```
=====================================
ghc.diff deleted
=====================================
@@ -1,74 +0,0 @@
-diff --git a/compiler/CodeGen.Platform.h b/compiler/CodeGen.Platform.h
-index 6f85686030..f91fee07fe 100644
---- a/compiler/CodeGen.Platform.h
-+++ b/compiler/CodeGen.Platform.h
-@@ -1274,44 +1274,6 @@ freeReg REG_XMM5 = False
- freeReg REG_XMM6 = False
- # endif
-
--# if defined(REG_YMM1)
--freeReg REG_YMM1 = False
--# endif
--# if defined(REG_YMM2)
--freeReg REG_YMM2 = False
--# endif
--# if defined(REG_YMM3)
--freeReg REG_YMM3 = False
--# endif
--# if defined(REG_YMM4)
--freeReg REG_YMM4 = False
--# endif
--# if defined(REG_YMM5)
--freeReg REG_YMM5 = False
--# endif
--# if defined(REG_YMM6)
--freeReg REG_YMM6 = False
--# endif
--
--# if defined(REG_ZMM1)
--freeReg REG_ZMM1 = False
--# endif
--# if defined(REG_ZMM2)
--freeReg REG_ZMM2 = False
--# endif
--# if defined(REG_ZMM3)
--freeReg REG_ZMM3 = False
--# endif
--# if defined(REG_ZMM4)
--freeReg REG_ZMM4 = False
--# endif
--# if defined(REG_ZMM5)
--freeReg REG_ZMM5 = False
--# endif
--# if defined(REG_ZMM6)
--freeReg REG_ZMM6 = False
--# endif
--
- freeReg _ = True
-
- #else
-diff --git a/compiler/GHC/CmmToAsm/RV64/Instr.hs b/compiler/GHC/CmmToAsm/RV64/Instr.hs
-index bb4e0ba61c..ec00d5ef68 100644
---- a/compiler/GHC/CmmToAsm/RV64/Instr.hs
-+++ b/compiler/GHC/CmmToAsm/RV64/Instr.hs
-@@ -20,7 +20,6 @@ import GHC.CmmToAsm.Utils
- import GHC.Data.FastString (LexicalFastString)
- import GHC.Platform
- import GHC.Platform.Reg
--import GHC.Platform.Reg.Class.Separate
- import GHC.Platform.Regs
- import GHC.Prelude
- import GHC.Stack
-diff --git a/compiler/GHC/CmmToAsm/RV64/Ppr.hs b/compiler/GHC/CmmToAsm/RV64/Ppr.hs
-index 75cbcf2da6..2735bb5bef 100644
---- a/compiler/GHC/CmmToAsm/RV64/Ppr.hs
-+++ b/compiler/GHC/CmmToAsm/RV64/Ppr.hs
-@@ -797,7 +797,7 @@ pprInstr platform instr = case instr of
- FNMSub -> text "\tfnmsub" <> dot <> floatPrecission d
- in op4 fma d r1 r2 r3
- VFMA variant o1@(OpReg fmt _reg) o2 o3
-- | VecFormat l fmt' <- fmt ->
-+ | VecFormat _l fmt' <- fmt ->
- let formatString = if (isFloatFormat . scalarFormatFormat) fmt' then text "f" else text ""
- prefix = text "v" <> formatString
- suffix = text "vv"
=====================================
git.diff deleted
=====================================
@@ -1,33 +0,0 @@
-diff --git a/testsuite/driver/cpuinfo.py b/testsuite/driver/cpuinfo.py
-index 4617b04a4c..841ec9dfdc 100644
---- a/testsuite/driver/cpuinfo.py
-+++ b/testsuite/driver/cpuinfo.py
-@@ -2151,6 +2152,10 @@ def _get_cpu_info_from_riscv_isa():
- seen.add(item)
- return unique_list
-
-+ # Big endian is easier to head, but RISC-V is little endian
-+ def bigToLittleEndian(w):
-+ return int.from_bytes(w, byteorder='big').to_bytes(4, byteorder='little')
-+
- g_trace.header('Tying to get info from device-tree ...')
-
- try:
-@@ -2175,16 +2180,17 @@ def _get_cpu_info_from_riscv_isa():
-
- if arch_string.startswith('rv32'):
- vlen = run_asm(
-- b"\xc2\x20\x25\x73", # csrr a0, 0xc22
-- b"\x00\x00\x80\x67" # ret
-+ bigToLittleEndian(b"\xc2\x20\x25\x73"), # csrr a0, 0xc22
-+ bigToLittleEndian(b"\x00\x00\x80\x67") # ret
- )
- elif arch_string.startswith('rv64'):
- vlen = run_asm(
-- b"\xc2\x20\x25\x73", # csrr a0, 0xc22
-- b"\x00\x05\x05\x1b", # sext.w a0, a0
-- b"\x00\x00\x80\x67" # ret
-+ bigToLittleEndian(b"\xc2\x20\x25\x73"), # csrr a0, 0xc22
-+ bigToLittleEndian(b"\x00\x05\x05\x1b"), # sext.w a0, a0
-+ bigToLittleEndian(b"\x00\x00\x80\x67") # ret
- )
=====================================
rts/CheckVectorSupport.c
=====================================
@@ -4,10 +4,17 @@
#if defined(__riscv_v) && defined(__riscv_v_intrinsic)
#include <riscv_vector.h>
#include <stdlib.h>
+#include <signal.h>
+#include <setjmp.h>
-// TODO: Find better file for this.
-void* malloc_vlen_vector() {
- return malloc(__riscv_vlenb());
+static jmp_buf jmpbuf;
+
+// Signal handler for SIGILL (Illegal Instruction)
+static void sigill_handler(int);
+static void sigill_handler(__attribute__((unused)) int sig) {
+ // If we get here, the vector instruction caused an illegal instruction
+ // exception. We just swallow it.
+ longjmp(jmpbuf, 1);
}
#endif
@@ -74,11 +81,29 @@ int checkVectorSupport(void) {
supports_V32 = hwcap & PPC_FEATURE_HAS_VSX;
*/
+ // Detect RISC-V support
#elif defined(__riscv_v) && defined(__riscv_v_intrinsic)
// __riscv_v ensures we only get here when the compiler target (arch)
// supports vectors.
-
- unsigned vlenb = __riscv_vlenb();
+ // Unfortunately, the status registers that could tell about RVV support
+ // are part of the priviledged ISA. So, we try to get VLENB from the `vlenb`
+ // register that only exists with RVV. If this throws an illegal instruction
+ // exception, we know that RVV is not supported by the executing CPU.
+
+ // Set up signal handler to catch illegal instruction
+ struct sigaction sa, old_sa;
+ sa.sa_handler = sigill_handler;
+ sigemptyset(&sa.sa_mask);
+ sa.sa_flags = 0;
+ sigaction(SIGILL, &sa, &old_sa);
+
+ unsigned vlenb = 0;
+ if (setjmp(jmpbuf) == 0) {
+ // Try to execute a vector instruction
+ vlenb = __riscv_vlenb();
+ }
+ // Restore original signal handler
+ sigaction(SIGILL, &old_sa, NULL);
// VLENB gives the length in bytes
supports_V16 = vlenb >= 16;
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7f5ae460efbb8513e80941fdeecea8…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7f5ae460efbb8513e80941fdeecea8…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/bump-win32-tarballs] rts: Fix offset by 1 error and check for both delimiters
by Tamar Christina (@Phyx) 29 Jun '25
by Tamar Christina (@Phyx) 29 Jun '25
29 Jun '25
Tamar Christina pushed to branch wip/bump-win32-tarballs at Glasgow Haskell Compiler / GHC
Commits:
d2c66a91 by Tamar Christina at 2025-06-29T11:00:06+01:00
rts: Fix offset by 1 error and check for both delimiters
- - - - -
1 changed file:
- rts/linker/LoadArchive.c
Changes:
=====================================
rts/linker/LoadArchive.c
=====================================
@@ -250,11 +250,11 @@ lookupGNUArchiveIndex(int gnuFileIndexSize, char **fileName_,
// Check that the previous entry ends with the expected
// end-of-string delimiter.
#if defined(mingw32_HOST_OS)
-#define STRING_TABLE_DELIM '\0'
+#define IS_SYMBOL_DELIMITER(STR) (STR =='\n' || STR == '\0')
#else
-#define STRING_TABLE_DELIM '\n'
+#define IS_SYMBOL_DELIMITER(STR) (STR =='\n')
#endif
- if (n != 0 && gnuFileIndex[n - 1] != STRING_TABLE_DELIM) {
+ if (n != 0 && !IS_SYMBOL_DELIMITER(gnuFileIndex[n - 1])) {
errorBelch("loadArchive: GNU-variant filename offset "
"%d invalid (range [0..%d]) while reading "
"filename from `%" PATH_FMT "'",
@@ -263,10 +263,10 @@ lookupGNUArchiveIndex(int gnuFileIndexSize, char **fileName_,
}
int i;
- for (i = n; gnuFileIndex[i] != '\n'; i++)
+ for (i = n; !IS_SYMBOL_DELIMITER(gnuFileIndex[i]); i++)
;
- size_t FileNameSize = i - n - 1;
+ size_t FileNameSize = i - n;
if (FileNameSize >= *fileNameSize) {
/* Double it to avoid potentially continually
increasing it by 1 */
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d2c66a91150b49e3969c25af2a9868f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d2c66a91150b49e3969c25af2a9868f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

28 Jun '25
Simon Peyton Jones pushed to branch wip/T26115 at Glasgow Haskell Compiler / GHC
Commits:
0d1363c0 by Simon Peyton Jones at 2025-06-28T23:00:40+01:00
Wibbles
- - - - -
66114346 by Simon Peyton Jones at 2025-06-28T23:37:33+01:00
Wibble
- - - - -
6 changed files:
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
Changes:
=====================================
compiler/GHC/Core/Opt/Specialise.hs
=====================================
@@ -3375,7 +3375,7 @@ beats_or_same (CI { ci_key = args1 }) (CI { ci_key = args2 })
go_arg (SpecDict {}) (SpecDict {}) = True
go_arg UnspecType UnspecType = True
go_arg UnspecArg UnspecArg = True
- go_arg _ _ = False
+ go_arg _ _ = False
----------------------
splitDictBinds :: FloatedDictBinds -> IdSet -> (FloatedDictBinds, OrdList DictBind, IdSet)
@@ -3491,7 +3491,6 @@ newSpecIdSM old_name new_ty details info
; return (assert (not (isCoVarType new_ty)) $
mkLocalVar details new_name ManyTy new_ty info) }
-
{-
Old (but interesting) stuff about unboxed bindings
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
=====================================
compiler/GHC/HsToCore/Binds.hs
=====================================
@@ -796,216 +796,6 @@ Note [Desugaring new-form SPECIALISE pragmas]
which is desugared in this module by `dsSpec`. For the context see
Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig
-Suppose we have f :: forall p q. (Ord p, Eq q) => p -> q -> q, and a pragma
-
- {-# SPECIALISE forall x. f @[a] @[Int] x [3,4] #-}
-
-In `dsSpec` the `SpecPragE` will look something like this:
-
- SpecPragE { spe_fn_id = f
- , spe_bndrs = @a (d:Ord a) (x:[a])
- , spe_call = let d2:Ord [a] = $dfOrdList d
- d3:Eq [Int] = $dfEqList $dfEqInt
- in f @[a] @[Int] d2 d3 x [3,4] }
-We want to get
-
- RULE forall a (d2:Ord a) (d3:Eq [Int]) (x:[a]).
- f @[a] @[Int] d2 d3 x [3,4] = $sf d2 x
-
- $sf :: forall a. Ord [a] => a -> Int
- $sf = /\a. \d2 x.
- let d3 = $dfEqList $dfEqInt
- in <f-rhs> @[a] @[Int] d2 d3 x [3,4]
-
-Notice that
-
-(SP1) If the expression in the SPECIALISE pragma had a type signature, such as
- SPECIALISE f :: Eq b => Int -> b -> b
- then the desugared expression may have type abstractions and applications
- "in the way", like this:
- (/\b. (\d:Eq b). let d1 = $dfOrdInt in f @Int @b d1 d) @b (d2:Eq b)
- The lambdas come from the type signature, which is then re-instantiated,
- hence the applications of those lambdas.
-
- We use the simple optimiser to simplify this to
- let { d = d2; d1 = $dfOrdInt } in f @Int @b d1 d
-
- Important: do no inlining in this "simple optimiser" phase:
- use `simpleOptExprNoInline`. E.g. we don't want to turn it into
- f @Int @b $dfOrdInt d2
- because the latter is harder to match.
-
- Similarly if we have
- let { d1=d; d2=d } in f d1 d2
- we don't want to inline d1/d2 to get this
- f d d
-
-(SP2) $sf does not simply quantify over (d:Ord a). Instead, to figure out what
- it should quantify over, and to include the 'd3' binding in the body of $sf,
- we use the function `prepareSpecLHS`. It takes the simplified LHS `core_call`,
- and uses the dictionary bindings to figure out the RULE LHS and RHS.
-
- This is described in Note [prepareSpecLHS].
-
-Note [prepareSpecLHS]
-~~~~~~~~~~~~~~~~~~~~~
-To compute the appropriate RULE LHS and RHS for a new-form specialise pragma,
-as described in Note [Desugaring new-form SPECIALISE pragmas], we use a function
-called prepareSpecLHS.
-It takes as input a list of (type and evidence) binders, and a Core expression.
-For example, suppose its input is of the following form:
-
- spe_bndrs = @a (d:Ord a)
- spe_call =
- let
- -- call these bindings the call_binds
- d1 :: Num Int
- d1 = $dfNumInt
- d2 :: Ord [a]
- d2 = $dfOrdList d
- d3 :: Eq a
- d3 = $p1Ord d3
- d4 :: Ord (F a)
- d4 = d |> co1
- d5 :: Ord (G a)
- d5 = d4 |> co2
- in
- f @[a] @Int d1 d2 d3 d5
-
-The goal of prepareSpecLHS is then to generate the following two things:
-
- - A specialisation, of the form:
-
- $sf <spec_args> =
- let <spec_binds>
- in <f-rhs> @[a] @Int d1 d2 d3 d5
-
- - A rule, of the form:
-
- RULE forall a d1 d2 d3 d5. f @[a] @Int d1 d2 d3 d5 =
- let <rule_binds>
- in $sf <spec_args>
-
-That is, we must compute 'spec_args', 'rule_binds' and 'spec_binds'. A first
-approach might be:
-
- - take spec_args = spe_bndrs,
- - spec_binds = call_binds.
-
-If we did so, the RULE would look like:
-
- RULE forall a d1 d2 d3 d5. f @[a] @Int d1 d2 d3 d5 =
- let d = <???>
- in $sf @a d
-
-The problem is: how do we recover 'd' from 'd1', 'd2', 'd3', 'd5'? Essentially,
-we need to run call_binds in reverse. In this example, we had:
-
- d1 :: Num Int
- d1 = $dfNumInt
- d2 :: Ord [a]
- d2 = $dfOrdList d
- d3 :: Eq a
- d3 = $p1Ord d3
- d4 :: Ord (F a)
- d4 = d |> co1
- d5 :: Ord (G a)
- d5 = d4 |> co2
-
-Let's try to recover (d: Ord a) from 'd1', 'd2', 'd4', 'd5':
-
- - d1 is a constant binding, so it doesn't help us.
- - d2 uses a top-level instance, which we can't run in reverse; we can't
- obtain Ord a from Ord [a].
- - d3 uses a superclass selector which prevents us from making progress.
- - d5 is defined using d4, and both involve a cast.
- In theory we could define d = d5 |> sym (co1 ; co2), but this gets
- pretty complicated.
-
-This demonstrates the following:
-
- 1. The bindings can't necessarily be "run in reverse".
- 2. Even if the bindings theoretically can be "run in reverse", it is not
- straightforward to do so.
-
-Now, we could strive to make the let-bindings reversible. We already do this
-to some extent for quantified constraints, as explained in
-Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig,
-using the TcSSpecPrag solver mode described in Note [TcSSpecPrag] in GHC.Tc.Solver.Monad.
-However, given (2), we don't bother ensuring that e.g. we don't use top-level
-class instances like in d2 above. Instead, we handle these bindings in
-prepareSpecLHS as follows:
-
- (a) Go through the bindings in order.
-
- (1) Bindings like
- d1 = $dfNumInt
- depend only on constants and move to the specialised function body.
- That is crucial -- it makes those specialised methods available in the
- specialised body. These are the `spec_const_binds`.
-
- Note that these binds /can/ depend on locally-quantified /type/ variables.
- For example, if we have
- instance Monad (ST s) where ...
- then the dictionary for (Monad (ST s)) is effectively a constant dictionary.
- This is important to get specialisation for such types. Example in test T8331.
-
- (2) Other bindings, like
- d2:Ord [a] = $dfOrdList d
- d3 = d
- depend on a locally-quantifed evidence variable `d`.
- Surprisingly, /we want to drop these bindings entirely!/
- This is because, as explained above, it is too difficult to run these
- in reverse. Instead, we drop them, and re-compute which dictionaries
- we will quantify over.
-
- (3) Finally, inside those dictionary bindings we should find the call of the
- function itself
- f @[a] @[Int] d2 d3 x [3,4]
- 'prepareSpecLHS' takes the call apart and returns its arguments.
-
- (b) Now, (a)(2) means that the RULE does not quantify over 'd' any more; it
- quantifies over 'd1' 'd2' 'd3' 'd5'. So we recompute the `rule_bndrs`
- from scratch.
-
- Moreover, the specialised function also no longer quantifies over 'd',
- it quantifies over 'd2' 'd3' 'd5'. This set of binders is computed by
- taking the RULE binders and subtracting off the binders from
- the `spec_const_binds`.
-
-[Shortcoming] This whole approach does have one downside, compared to running
-the let-bindings in reverse: it doesn't allow us to common-up dictionaries.
-Consider for example:
-
- g :: forall a b. ( Eq a, Ord b ) => a -> b -> Bool
- {-# SPECIALISE g :: forall c. Ord c => c -> c -> Bool #-}
-
-The input to prepareSpecLHS will be (more or less):
-
- spe_bndrs: @c (d:Ord c)
- spe_call =
- let
- d1 :: Eq c
- d1 = $p1Ord d
- d2 :: Ord c
- d2 = d
- in
- g @c @c d1 d2
-
-The approach described in (2) will thus lead us to generate:
-
- RULE g @c @c d1 d2 = $sg @c d1 d2
- $sg @c d1 d2 = <g-rhs> @c @c d1 d2
-
-when we would rather avoid passing both dictionaries, and instead generate:
-
- RULE g @c @c d1 d2 = let { d = d2 } in $sg @c d
- $sg @c d = let { d1 = $p1Ord d; d2 = d } in <g-rhs> @c @c d1 d2
-
-For now, we accept this infelicity.
-
-Note [Desugaring new-form SPECIALISE pragmas] -- Take 2
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Suppose we have
f :: forall a b c d. (Ord a, Ord b, Eq c, Ix d) => ...
f = rhs
@@ -1027,11 +817,11 @@ We /could/ generate
RULE f d1 d2 d3 d4 e1..en = $sf d1 d2 d3 d4
$sf d1 d2 d3 d4 = <rhs> d1 d2 d3 d4
-But that would do no specialisation! What we want is this:
+But that would do no specialisation at all! What we want is this:
RULE f d1 _d2 _d3 d4 e1..en = $sf d1 d4
$sf d1 d4 = let d7 = d1 -- Renaming
- dx1 = d7 -- Renaming
- d6 = dx1
+ dx1 = d1 -- Renaming
+ d6 = d1 -- Renaming
d2 = $fOrdList d6
d3 = $fEqList $fEqInt
in rhs d1 d2 d3 d4
@@ -1045,46 +835,61 @@ Notice that:
to line things up
The transformation goes in these steps
+
(S1) decomposeCall: decomopose `the_call` into
- - `rev_binds`: the enclosing let-bindings (actually reversed)
+ - `binds`: the enclosing let-bindings
- `rule_lhs_args`: the arguments of the call itself
- We carefully arrange that the dictionary arguments of the actual
- call, `rule_lhs_args` are all distinct dictionary variables,
- not expressions. How? We use `simpleOptExprNoInline` to avoid
- inlining the let-bindings.
+
+ If the expression in the SPECIALISE pragma had a type signature, such as
+ SPECIALISE g :: Eq b => Int -> b -> b
+ then the desugared expression may have type abstractions and applications
+ "in the way", like this:
+ (/\b. (\d:Eq b). let d1 = $dfOrdInt in f @Int @b d1 d) @b (d2:Eq b)
+ The lambdas come from the type signature, which is then re-instantiated,
+ hence the applications of those lambdas.
+
+ so `decomposeCall` uses the simple optimiser to simplify this to
+ let { d = d2; d1 = $dfOrdInt } in f @Int @b d1 d
+
+ Wrinkle (S1a): do no inlining in this "simple optimiser" phase:
+ use `simpleOptExprNoInline`. E.g. we don't want to turn it into
+ f @Int @b $dfOrdInt d2
+ because the latter is harder to match. Similarly if we have
+ let { d1=d; d2=d } in f d1 d2
+ we don't want to inline d1/d2 to get this
+ f d d
+
+ TL;DR: as a result the dictionary arguments of the actual call,
+ `rule_lhs_args` are all distinct dictionary variables, not
+ expressions.
(S2) Compute `rule_bndrs`: the free vars of `rule_lhs_args`, which
will be the forall'd template variables of the RULE. In the example,
rule_bndrs = d1,d2,d3,d4
-
-(S3) grabSpecBinds: transform `rev_binds` into `spec_binds`: the
- bindings we will wrap around the call in the RHS of `$sf`
-
-(S4) Find `spec_bndrs`, the subset of `rule_bndrs` that we actually
- need to pass to `$sf`, simply by filtering out those that are
- bound by `spec_binds`. In the example
- spec_bndrs = d1,d4
-
-
- Working inner
-* Grab any bindings we can that will "shadow" the forall'd
- rule-bndrs, giving specialised bindings for them.
- * We keep a set of known_bndrs starting with {d1,..,dn}
- * We keep a binding iff no free var is
- (a) in orig_bndrs (i.e. not totally free)
- (b) not in known_bndrs
- * If we keep it, add its binder to known_bndrs; if not, don't
-
-To maximise what we can "grab", start by extracting /renamings/ of the
-forall'd rule_bndrs, and bringing them to the top. A renaming is
- rule_bndr = d
-If we see this:
- * Bring d=rule_bndr to the top
- * Add d to the set of variables to look for on the right.
- e.g. rule_bndrs = d1, d2
- Bindings { d7=d9; d1=d7 }
- Bring to the top { d7=d1; d9=d7 }
-
+ These variables will get values from a successful RULE match.
+
+(S3) `getRenamings`: starting from the rule_bndrs, make bindings for
+ all other variables that are equal to them. In the example, we
+ make renaming-bindings for d7, dx1, d6.
+
+ NB1: we don't actually have to remove the original bindings;
+ it's harmless to leave them
+ NB2: We also reverse bindings like d1 = d2 |> co, to get
+ d2 = d1 |> sym co
+ It's easy and may help.
+
+(S4) `pickSpecBinds`: pick the bindings we want to keep in the
+ specialised function. We start from `known_vars`, the variables we
+ know, namely the `rule_bndrs` and the binders from (S3), which are
+ all equal to one of the `rule_bndrs`.
+
+ Then we keep a binding if the free vars of its RHS are all known.
+ In our example, `d2` and `d3` are both picked, but `d4` is not.
+ The non-picked ones won't end up being specialised.
+
+(S5) Finally, work out which of the `rule_bndrs` we must pass on to
+ specialised function. We just filter out ones bound by a renaming
+ or a picked binding.
-}
------------------------
@@ -1155,7 +960,9 @@ dsSpec_help :: Name -> Id -> CoreExpr -- Function to specialise
-> InlinePragma -> [Var] -> CoreExpr
-> DsM (Maybe (OrdList (Id,CoreExpr), CoreRule))
dsSpec_help poly_nm poly_id poly_rhs spec_inl orig_bndrs ds_call
- = do { mb_call_info <- decomposeCall poly_id ds_call
+ = do { -- Decompose the call
+ -- Step (S1) of Note [Desugaring new-form SPECIALISE pragmas]
+ mb_call_info <- decomposeCall poly_id ds_call
; case mb_call_info of {
Nothing -> return Nothing ;
Just (binds, rule_lhs_args) ->
@@ -1167,12 +974,17 @@ dsSpec_help poly_nm poly_id poly_rhs spec_inl orig_bndrs ds_call
is_local :: Var -> Bool
is_local v = v `elemVarSet` locals
+ -- Find `rule_bndrs`: (S2) of Note [Desugaring new-form SPECIALISE pragmas]
rule_bndrs = scopedSort (exprsSomeFreeVarsList is_local rule_lhs_args)
+ -- getRenamings: (S3) of Note [Desugaring new-form SPECIALISE pragmas]
rn_binds = getRenamings orig_bndrs binds rule_bndrs
+
+ -- pickSpecBinds: (S4) of Note [Desugaring new-form SPECIALISE pragmas]
known_vars = mkVarSet rule_bndrs `extendVarSetList` bindersOfBinds rn_binds
picked_binds = pickSpecBinds is_local known_vars binds
+ -- Fins `spec_bndrs`: (S5) of Note [Desugaring new-form SPECIALISE pragmas]
-- Make spec_bndrs, the variables to pass to the specialised
-- function, by filtering out the rule_bndrs that aren't needed
spec_binds_bndr_set = mkVarSet (bindersOfBinds picked_binds)
@@ -1262,12 +1074,12 @@ dsSpec_help poly_nm poly_id poly_rhs spec_inl orig_bndrs ds_call
decomposeCall :: Id -> CoreExpr
-> DsM (Maybe ([CoreBind], [CoreExpr] ))
-- Decompose the call into (let <binds> in f <args>)
+-- See (S1) in Note [Desugaring new-form SPECIALISE pragmas]
decomposeCall poly_id ds_call
- = do { -- Simplify the (desugared) call; see wrinkle (SP1)
- -- in Note [Desugaring new-form SPECIALISE pragmas]
- ; dflags <- getDynFlags
+ = do { dflags <- getDynFlags
; let simpl_opts = initSimpleOpts dflags
core_call = simpleOptExprNoInline simpl_opts ds_call
+ -- simpleOpeExprNoInlint: see Wrinkle (S1a)!
; case go [] core_call of {
Nothing -> do { diagnosticDs (DsRuleLhsTooComplicated ds_call core_call)
=====================================
compiler/GHC/Tc/Gen/Sig.hs
=====================================
@@ -759,9 +759,7 @@ This is done in three parts.
(1) Typecheck the expression, capturing its constraints
- (2) Solve these constraints, but in special TcSSpecPrag mode which ensures
- each original Wanted is either fully solved or left untouched.
- See Note [Fully solving constraints for specialisation].
+ (2) Solve these constraints
(3) Compute the constraints to quantify over, using `getRuleQuantCts` on
the unsolved constraints returned by (2).
@@ -797,68 +795,6 @@ This is done in three parts.
of the form:
forall @a @b d1 d2 d3. f d1 d2 d3 = $sf d1 d2 d3
-Note [Fully solving constraints for specialisation]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-As far as specialisation is concerned, it is actively harmful to simplify
-constraints without /fully/ solving them.
-
-Example:
-
- f :: ∀ a t. (Eq a, ∀x. Eq x => Eq (t x)). t a -> Char
- {-# SPECIALISE f @Int #-}
-
- Typechecking 'f' will result in [W] Eq Int, [W] ∀x. Eq x => Eq (t x).
- We absolutely MUST leave the quantified constraint alone, because we want to
- quantify over it. If we were to try to simplify it, we would emit an
- implication and would thereafter never be able to quantify over the original
- quantified constraint.
-
- However, we still need to simplify quantified constraints that can be
- /fully solved/ from instances, otherwise we would never be able to
- specialise them away. Example: {-# SPECIALISE f @a @[] #-}.
-
-The conclusion is this:
-
- when solving the constraints that arise from a specialise pragma, following
- the recipe described in Note [Handling new-form SPECIALISE pragmas], all
- Wanted quantified constraints should either be:
- - fully solved (no free evidence variables), or
- - left untouched.
-
-To achieve this, we run the solver in a special "all-or-nothing" solving mode,
-described in Note [TcSSpecPrag] in GHC.Tc.Solver.Monad.
-
-Note that a similar problem arises in other situations in which the solver takes
-an irreversible step, such as using a top-level class instance. This is currently
-less important, as the desugarer can handle these cases. To explain, consider:
-
- g :: ∀ a. Eq a => a -> Bool
- {-# SPECIALISE g @[e] #-}
-
- Typechecking 'g' will result in [W] Eq [e]. Were we to simplify this to
- [W] Eq e, we would have difficulty generating a RULE for the specialisation:
-
- $sg :: Eq e => [e] -> Bool
-
- RULE ∀ e (d :: Eq [e]). g @[e] d = $sg @e (??? :: Eq e)
- -- Can't fill in ??? because we can't run instances in reverse.
-
- RULE ∀ e (d :: Eq e). g @[e] ($fEqList @e d) = $sg @e d
- -- Bad RULE matching template: matches on the structure of a dictionary
-
- Moreover, there is no real benefit to any of this, because the specialiser
- can't do anything useful from the knowledge that a dictionary for 'Eq [e]' is
- constructed from a dictionary for 'Eq e' using the 'Eq' instance for lists.
-
-Here, it would make sense to also use the "solve completely" mechanism in the
-typechecker to avoid producing evidence terms that we can't "run in reverse".
-However, the current implementation tackles this issue in the desugarer, as is
-explained in Note [prepareSpecLHS] in GHC.HsToCore.Binds.
-So, for the time being at least, in TcSSpecPrag mode, we don't attempt to "fully solve"
-constraints when we use a top-level instance. This might change in the future,
-were we to decide to attempt to address [Shortcoming] in Note [prepareSpecLHS]
-in GHC.HsToCore.Binds.
-
Note [Handling old-form SPECIALISE pragmas]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
NB: this code path is deprecated, and is scheduled to be removed in GHC 9.18, as per #25440.
@@ -1039,7 +975,7 @@ tcSpecPrag poly_id (SpecSigE nm rule_bndrs spec_e inl)
<- tcRuleBndrs skol_info rule_bndrs $
tcInferRho spec_e
- -- (2) Solve the resulting wanteds in TcSSpecPrag mode.
+ -- (2) Solve the resulting wanteds
; ev_binds_var <- newTcEvBinds
; spec_e_wanted <- setTcLevel rhs_tclvl $
runTcSWithEvBinds ev_binds_var $
=====================================
compiler/GHC/Tc/Solver/Dict.hs
=====================================
@@ -462,30 +462,20 @@ from the instance that we have in scope:
case x of { GHC.Types.I# x1 -> GHC.Types.I# (GHC.Prim.+# x1 1#) }
** NB: It is important to emphasize that all this is purely an optimization:
-** exactly the same programs should typecheck with or without this
-** procedure.
-
-Solving fully
-~~~~~~~~~~~~~
-There is a reason why the solver does not simply try to solve such
-constraints with top-level instances. If the solver finds a relevant
-instance declaration in scope, that instance may require a context
-that can't be solved for. A good example of this is:
-
- f :: Ord [a] => ...
- f x = ..Need Eq [a]...
-
-If we have instance `Eq a => Eq [a]` in scope and we tried to use it, we would
-be left with the obligation to solve the constraint Eq a, which we cannot. So we
-must be conservative in our attempt to use an instance declaration to solve the
-[W] constraint we're interested in.
-
-Our rule is that we try to solve all of the instance's subgoals
-recursively all at once. Precisely: We only attempt to solve
-constraints of the form `C1, ... Cm => C t1 ... t n`, where all the Ci
-are themselves class constraints of the form `C1', ... Cm' => C' t1'
-... tn'` and we only succeed if the entire tree of constraints is
-solvable from instances.
+** exactly the same programs should typecheck with or without this procedure.
+
+Consider
+ f :: Ord [a] => ...
+ f x = ..Need Eq [a]...
+We could use the Eq [a] superclass of the Ord [a], or we could use the top-level
+instance `Eq a => Eq [a]`. But if we did the latter we'd be stuck with an
+insoluble constraint (Eq a).
+
+So the ShortCutSolving rule is this:
+ If we could solve a constraint from a local Given,
+ try first to /completely/ solve the constraint using only top-level instances.
+ - If that succeeds, use it
+ - If not, use the local Given
An example that succeeds:
@@ -511,7 +501,8 @@ An example that fails:
f :: C [a] b => b -> Bool
f x = m x == []
-Which, because solving `Eq [a]` demands `Eq a` which we cannot solve, produces:
+Which, because solving `Eq [a]` demands `Eq a` which we cannot solve. so short-cut
+solving fails and we use the superclass of C:
f :: forall a b. C [a] b => b -> Bool
f = \ (@ a) (@ b) ($dC :: C [a] b) (eta :: b) ->
@@ -521,23 +512,49 @@ Which, because solving `Eq [a]` demands `Eq a` which we cannot solve, produces:
(m @ [a] @ b $dC eta)
(GHC.Types.[] @ a)
-Note [Shortcut solving: type families]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Suppose we have (#13943)
- class Take (n :: Nat) where ...
- instance {-# OVERLAPPING #-} Take 0 where ..
- instance {-# OVERLAPPABLE #-} (Take (n - 1)) => Take n where ..
-
-And we have [W] Take 3. That only matches one instance so we get
-[W] Take (3-1). Really we should now rewrite to reduce the (3-1) to 2, and
-so on -- but that is reproducing yet more of the solver. Sigh. For now,
-we just give up (remember all this is just an optimisation).
-
-But we must not just naively try to lookup (Take (3-1)) in the
-InstEnv, or it'll (wrongly) appear not to match (Take 0) and get a
-unique match on the (Take n) instance. That leads immediately to an
-infinite loop. Hence the check that 'preds' have no type families
-(isTyFamFree).
+The moving parts are relatively simple:
+
+* To attempt to solve the constraint completely, we just recursively
+ call the constraint solver. See the use of `tryTcS` in
+ `tcShortCutSolver`.
+
+* When this attempted recursive solving, we set a special mode
+ `TcSShortCut`, which signals that we are trying to solve using only
+ top-level instances. We switch on `TcSShortCut` mode in
+ `tryShortCutSolver`.
+
+* When in TcSShortCut mode, we behave specially in a few places:
+ - `tryInertDicts`, where we would otherwise look for a Given to solve our Wantee
+ - `noMatchableGivenDicts`, which also consults the Givens
+ - `matchLocalInst`, which would otherwise consult Given quantified constraints
+ - `GHC.Tc.Solver.Instance.Class.matchInstEnv`: when short-cut solving, don't
+ pick overlappable top-level instances
+
+
+Some wrinkles:
+
+(SCS1) Note [Shortcut solving: incoherence]
+
+(SCS2) The short-cut solver just uses the solver recursively, so we get its
+ full power:
+
+ * We need to be able to handle recursive super classes. The
+ solved_dicts state ensures that we remember what we have already
+ tried to solve to avoid looping.
+
+ * As #15164 showed, it can be important to exploit sharing between
+ goals. E.g. To solve G we may need G1 and G2. To solve G1 we may need H;
+ and to solve G2 we may need H. If we don't spot this sharing we may
+ solve H twice; and if this pattern repeats we may get exponentially bad
+ behaviour.
+
+ * Suppose we have (#13943)
+ class Take (n :: Nat) where ...
+ instance {-# OVERLAPPING #-} Take 0 where ..
+ instance {-# OVERLAPPABLE #-} (Take (n - 1)) => Take n where ..
+
+ And we have [W] Take 3. That only matches one instance so we get
+ [W] Take (3-1). Then we should reduce the (3-1) to 2, and continue.
Note [Shortcut solving: incoherence]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -603,37 +620,6 @@ The output of `main` if we avoid the optimization under the effect of
IncoherentInstances is `1`. If we were to do the optimization, the output of
`main` would be `2`.
-Note [Shortcut try_solve_from_instance]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-The workhorse of the short-cut solver is
- try_solve_from_instance :: (EvBindMap, DictMap CtEvidence)
- -> CtEvidence -- Solve this
- -> MaybeT TcS (EvBindMap, DictMap CtEvidence)
-Note that:
-
-* The CtEvidence is the goal to be solved
-
-* The MaybeT manages early failure if we find a subgoal that
- cannot be solved from instances.
-
-* The (EvBindMap, DictMap CtEvidence) is an accumulating purely-functional
- state that allows try_solve_from_instance to augment the evidence
- bindings and inert_solved_dicts as it goes.
-
- If it succeeds, we commit all these bindings and solved dicts to the
- main TcS InertSet. If not, we abandon it all entirely.
-
-Passing along the solved_dicts important for two reasons:
-
-* We need to be able to handle recursive super classes. The
- solved_dicts state ensures that we remember what we have already
- tried to solve to avoid looping.
-
-* As #15164 showed, it can be important to exploit sharing between
- goals. E.g. To solve G we may need G1 and G2. To solve G1 we may need H;
- and to solve G2 we may need H. If we don't spot this sharing we may
- solve H twice; and if this pattern repeats we may get exponentially bad
- behaviour.
Note [No Given/Given fundeps]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
=====================================
compiler/GHC/Tc/Solver/Monad.hs
=====================================
@@ -942,20 +942,16 @@ The constraint solver can operate in different modes:
* TcSVanilla: Normal constraint solving mode. This is the default.
* TcSPMCheck: Used by the pattern match overlap checker.
- Like TcSVanilla, but the idea is that the returned InertSet will
- later be resumed, so we do not want to restore type-equality cycles
- See also Note [Type equality cycles] in GHC.Tc.Solver.Equality
+ Like TcSVanilla, but the idea is that the returned InertSet will
+ later be resumed, so we do not want to restore type-equality cycles
+ See also Note [Type equality cycles] in GHC.Tc.Solver.Equality
* TcSEarlyAbort: Abort (fail in the monad) as soon as we come across an
insoluble constraint. This is used to fail-fast when checking for hole-fits.
See Note [Speeding up valid hole-fits].
-* TcSSpecPrag: Solve constraints fully or not at all. This is described in
- Note [TcSSpecPrag].
-
- This mode is currently used in one place only: when solving constraints
- arising from specialise pragmas.
- See Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig.
+* TcSShortCut: Solve constraints fully or not at all. This is described in
+ Note [Shortcut solving] in GHC.Tc.Solver.Dict
-}
data TcSEnv
@@ -1126,54 +1122,6 @@ runTcSEarlyAbort tcs
= do { ev_binds_var <- TcM.newTcEvBinds
; runTcSWithEvBinds' TcSEarlyAbort ev_binds_var tcs }
--- | Run the 'TcS' monad in 'TcSSpecPrag' mode, which either fully solves
--- individual Wanted quantified constraints or leaves them alone.
---
-
-{- Note [TcSSpecPrag]
-~~~~~~~~~~~~~~~~~~~~~
-The TcSSpecPrag mode is a specialized constraint solving mode that guarantees
-that Wanted quantified constraints are either:
- - Fully solved with no free evidence variables, or
- - Left completely untouched (no simplification at all)
-
-Examples:
-
- * [W] forall x. Eq x => Eq (f x).
-
- In TcSSpecPrag mode, we **do not** process this quantified constraint by
- creating a new implication constraint; we leave it alone instead.
-
- * [W] Eq (Maybe Int).
-
- This constraint is solved fully, using two top-level Eq instances.
-
- * [W] forall x. Eq x => Eq [x].
-
- This constraint is solved fully as well, using the Eq instance for lists.
-
-This functionality is crucially used by the specialiser, for which taking an
-irreversible constraint solving steps is actively harmful, as described in
-Note [Fully solving constraints for specialisation] in GHC.Tc.Gen.Sig.
-
-Note that currently we **do not** refrain from using top-level instances,
-even though we also can't run them in reverse; this isn't a problem for the
-specialiser (which is currently the sole consumer of this functionality).
-
-The implementation is as follows: in TcSSpecPrag mode, when we are about to
-solve a Wanted quantified constraint by emitting an implication, we call the
-special function `solveCompletelyIfRequired`. This function recursively calls
-the solver but in TcSVanilla mode (i.e. full-blown solving, with no restrictions).
-If this recursive call manages to solve all the remaining constraints fully,
-then we proceed with that outcome (i.e. we continue with that inert set, etc).
-Otherwise, we discard everything that happened in the recursive call, and
-continue with the original quantified constraint unchanged.
-
-In the future, we could consider re-using this functionality for the short-cut
-solver (see Note [Shortcut solving] in GHC.Tc.Solver.Dict), but we would have to
-be wary of the performance implications.
--}
-
-- | This can deal only with equality constraints.
runTcSEqualities :: TcS a -> TcM a
runTcSEqualities thing_inside
@@ -1282,20 +1230,21 @@ setTcLevelTcS lvl (TcS thing_inside)
nestImplicTcS :: EvBindsVar
-> TcLevel -> TcS a
-> TcS a
-nestImplicTcS ref inner_tclvl (TcS thing_inside)
+nestImplicTcS ev_binds_var inner_tclvl (TcS thing_inside)
= TcS $ \ env@(TcSEnv { tcs_inerts = old_inert_var }) ->
do { inerts <- TcM.readTcRef old_inert_var
-- Initialise the inert_cans from the inert_givens of the parent
-- so that the child is not polluted with the parent's inert Wanteds
+ -- See Note [trySolveImplication] in GHC.Tc.Solver.Solve
+ -- All other InertSet fields are inherited
; let nest_inert = inerts { inert_cycle_breakers = pushCycleBreakerVarStack
(inert_cycle_breakers inerts)
, inert_cans = (inert_givens inerts)
{ inert_given_eqs = False } }
- -- All other InertSet fields are inherited
; new_inert_var <- TcM.newTcRef nest_inert
; new_wl_var <- TcM.newTcRef emptyWorkList
- ; let nest_env = env { tcs_ev_binds = ref
+ ; let nest_env = env { tcs_ev_binds = ev_binds_var
, tcs_inerts = new_inert_var
, tcs_worklist = new_wl_var }
; res <- TcM.setTcLevel inner_tclvl $
@@ -1306,7 +1255,7 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside)
#if defined(DEBUG)
-- Perform a check that the thing_inside did not cause cycles
- ; ev_binds <- TcM.getTcEvBindsMap ref
+ ; ev_binds <- TcM.getTcEvBindsMap ev_binds_var
; checkForCyclicBinds ev_binds
#endif
; return res }
=====================================
compiler/GHC/Tc/Solver/Solve.hs
=====================================
@@ -260,6 +260,11 @@ more meaningful error message (see T19627)
This also applies for quantified constraints; see `-fqcs-fuel` compiler flag and `QCI.qci_pend_sc` field.
-}
+{- ********************************************************************************
+* *
+* Solving implication constraints *
+* *
+******************************************************************************** -}
solveNestedImplications :: Bag Implication
-> TcS (Bag Implication)
@@ -280,7 +285,22 @@ solveNestedImplications implics
; return unsolved_implics }
+{- Note [trySolveImplication]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+`trySolveImplication` may be invoked while solving simple wanteds, notably from
+`solveWantedForAll`. It returns a Bool to say if solving succeeded or failed.
+
+It used `nestImplicTcS` to build a nested scope. One subtle point is that
+`nestImplicTcS` uses the `inert_givens` (not the `inert_cans`) of the current
+inert set to initialse the `InertSet` of the nested scope. It super-important not
+to pollute the sub-solving problem with the unsolved Wanteds of the current scope.
+
+Whenever we do `solveSimpleGivens`, we snapshot the `inert_cans` into `inert_givens`.
+(At that moment there should be no Wanteds.)
+-}
+
trySolveImplication :: Implication -> TcS Bool
+-- See Note [trySolveImplication]
trySolveImplication (Implic { ic_tclvl = tclvl
, ic_binds = ev_binds_var
, ic_given = given_ids
@@ -977,6 +997,7 @@ solveSimpleGivens givens
-- Capture the Givens in the inert_givens of the inert set
-- for use by subsequent calls of nestImplicTcS
+ -- See Note [trySolveImplication]
; updInertSet (\is -> is { inert_givens = inert_cans is })
; cans <- getInertCans
@@ -1368,6 +1389,8 @@ solveWantedForAll qci tvs theta body_pred
, unitBag (mkNonCanonical $ CtWanted wanted_ev)) }
; traceTcS "solveForAll {" (ppr skol_tvs $$ ppr given_ev_vars $$ ppr wanteds $$ ppr w_id)
+
+ -- Try to solve the constraint completely
; ev_binds_var <- TcS.newTcEvBinds
; solved <- trySolveImplication $
(implicationPrototype loc_env)
@@ -1381,9 +1404,13 @@ solveWantedForAll qci tvs theta body_pred
; traceTcS "solveForAll }" (ppr solved)
; evbs <- TcS.getTcEvBindsMap ev_binds_var
; if not solved
- then do { addInertForAll qci
+ then do { -- Not completely solved; abandon that attempt and add the
+ -- original constraint to the inert set
+ addInertForAll qci
; stopWith (CtWanted wtd) "Wanted forall-constraint:unsolved" }
- else do { setWantedEvTerm dest EvCanonical $
+
+ else do { -- Completely solved; build an evidence terms
+ setWantedEvTerm dest EvCanonical $
EvFun { et_tvs = skol_tvs, et_given = given_ev_vars
, et_binds = evBindMapBinds evbs, et_body = w_id }
; stopWith (CtWanted wtd) "Wanted forall-constraint:solved" } }
@@ -1404,36 +1431,68 @@ solveWantedForAll qci tvs theta body_pred
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Solving a wanted forall (quantified) constraint
[W] df :: forall a b. (Eq a, Ord b) => C x a b
-is delightfully easy. Just build an implication constraint
+is delightfully easy in principle. Just build an implication constraint
forall ab. (g1::Eq a, g2::Ord b) => [W] d :: C x a
and discharge df thus:
df = /\ab. \g1 g2. let <binds> in d
where <binds> is filled in by solving the implication constraint.
All the machinery is to hand; there is little to do.
-We can take a more straightforward parth when there is a matching Given, e.g.
- [W] dg :: forall c d. (Eq c, Ord d) => C x c d
-In this case, it's better to directly solve the Wanted from the Given, instead
-of building an implication. This is more than a simple optimisation; see
-Note [Solving Wanted QCs from Given QCs].
+There are some tricky corners though:
+
+(WFA1) We can take a more straightforward parth when there is a matching Given, e.g.
+ [W] dg :: forall c d. (Eq c, Ord d) => C x c d
+ In this case, it's better to directly solve the Wanted from the Given, instead
+ of building an implication. This is more than a simple optimisation; see
+ Note [Solving Wanted QCs from Given QCs].
+
+(WFA2) Termination: see #19690. We want to maintain the invariant (QC-INV):
+
+ (QC-INV) Every quantified constraint returns a non-bottom dictionary
+
+ just as every top-level instance declaration guarantees to return a non-bottom
+ dictionary. But as #19690 shows, it is possible to get a bottom dicionary
+ by superclass selection if we aren't careful. The situation is very similar
+ to that described in Note [Recursive superclasses] in GHC.Tc.TyCl.Instance;
+ and we use the same solution:
+
+ * Give the Givens a CtOrigin of (GivenOrigin (InstSkol IsQC head_size))
+ * Give the Wanted a CtOrigin of (ScOrigin IsQC NakedSc)
+
+ Both of these things are done in solveForAll. Now the mechanism described
+ in Note [Solving superclass constraints] in GHC.Tc.TyCl.Instance takes over.
+
+(WFA3) We do not actually emit an implication to solve later. Rather we
+ try to solve it completely immediately using `trySolveImplication`
+ - If successful, we can build evidence
+ - If unsuccessful, we abandon the attempt and add the unsolved
+ forall-constraint to the inert set.
+ Several reasons for this "solve immediately" approach
-The tricky point is about termination: see #19690. We want to maintain
-the invariant (QC-INV):
+ - It saves quite a bit of plumbing, tracking the emitted implications for
+ later solving; and the evidence would have to contain as-yet-incomplte
+ bindings which complicates tracking of unused Givens.
- (QC-INV) Every quantified constraint returns a non-bottom dictionary
+ - We get better error messages, about failing to solve, say
+ (forall a. a->a) ~ (forall b. b->Int)
-just as every top-level instance declaration guarantees to return a non-bottom
-dictionary. But as #19690 shows, it is possible to get a bottom dicionary
-by superclass selection if we aren't careful. The situation is very similar
-to that described in Note [Recursive superclasses] in GHC.Tc.TyCl.Instance;
-and we use the same solution:
+ - Consider
+ f :: forall f a. (Ix a, forall x. Eq x => Eq (f x)) => a -> f a
+ {-# SPECIALISE f :: forall f. (forall x. Eq x => Eq (f x)) => Int -> f Int #-}
+ This SPECIALISE is treated like an expression with a type signature, so
+ we instantiate the constraints, simplify them and re-generalise. From the
+ instantaiation we get [W] d :: (forall x. Eq a => Eq (f x))
+ and we want to generalise over that. We do not want to attempt to solve it
+ and them get stuck, and emit an error message. If we can't solve it, better
+ to leave it alone
-* Give the Givens a CtOrigin of (GivenOrigin (InstSkol IsQC head_size))
-* Give the Wanted a CtOrigin of (ScOrigin IsQC NakedSc)
+ We still need to simplify quantified constraints that can be
+ /fully solved/ from instances, otherwise we would never be able to
+ specialise them away. Example: {-# SPECIALISE f @[] @a #-}.
-Both of these things are done in solveForAll. Now the mechanism described
-in Note [Solving superclass constraints] in GHC.Tc.TyCl.Instance takes over.
+ You might worry about the wasted work, but it is seldom repeated (because the
+ constraint solver seldom iterates much).
Note [Solving a Given forall-constraint]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a729a7c6e96bd24724f3605adb96fb…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a729a7c6e96bd24724f3605adb96fb…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T23109] 5 commits: Implement unary classes
by Simon Peyton Jones (@simonpj) 28 Jun '25
by Simon Peyton Jones (@simonpj) 28 Jun '25
28 Jun '25
Simon Peyton Jones pushed to branch wip/T23109 at Glasgow Haskell Compiler / GHC
Commits:
39f6451f by Simon Peyton Jones at 2025-06-28T15:36:09+01:00
Implement unary classes
The big change is described exhaustively in
Note [Unary class magic] in GHC.Core.TyCon
Other changes
* We never unbox class dictionaries in worker/wrapper. This has been true for some
time now, but the logic is now centralised in functions in
GHC.Core.Opt.WorkWrap.Utils, namely `canUnboxTyCon`, and `canUnboxArg`
See Note [Do not unbox class dictionaries] in GHC.Core.Opt.WorkWrap.Utils.
* Refactored the `notWorthFloating` logic in GHc.Core.Opt.SetLevels.
I can't remember if I actually changed any behaviour here, but if so it's
only in a corner cases.
* Fixed a bug in `GHC.Core.TyCon.isEnumerationTyCon`, which was wrongly returning
True for (##).
* Remove redundant Role argument to `liftCoSubstWithEx`. It was always
Representational.
* I refactored evidence generation in the constraint solver:
* Made GHC.Tc.Types.Evidence contain better abstactions for evidence
generation.
* I deleted the file `GHC.Tc.Types.EvTerm` and merged its (small) contents
elsewhere. It wasn't paying its way.
* Made evidence for implicit parameters go via a proper abstraction.
Smaller things
* Rename `isDataTyCon` to `isBoxedDataTyCon`.
* GHC.Core.Corecion.liftCoSubstWithEx was only called with Representational role,
so I baked that into the function and removed the argument.
* Get rid of `GHC.Core.TyCon.tyConSingleAlgDataCon_maybe` in favour of calling
`not isNewTyCon` at the call sites; more explicit.
* Refatored `GHC.Core.TyCon.isInjectiveTyCon`; but I don't think I changed its
behaviour
* Moved `decomposeIPPred` to GHC.Core.Predicate
Compile time performance changes:
geo. mean +0.1%
minimum -6.8%
maximum +14.4%
The +14% one is in T21839c, where it seems that a bit more inlining
is taking place. That seems acceptable; and the average change is small
Metric Decrease:
LargeRecord
T12227
T16577
T21839r
T5642
Metric Increase:
T15164
T21839c
T5321FD
T5321Fun
WWRec
- - - - -
ea6a8dda by Simon Peyton Jones at 2025-06-28T15:36:43+01:00
Renaming around predicate types
.. we were (as it turned out) abstracting over
type-class selectors in SPECIALISATION rules!
- - - - -
1cd6455d by Simon Peyton Jones at 2025-06-28T15:36:43+01:00
Small hacky fix to specUnfolding
...just using mkApps instead of mkCoreApps
(This part is likely to change again in a
future commit.)
- - - - -
5f4d1bbe by Simon Peyton Jones at 2025-06-28T15:36:43+01:00
Slight improvement to pre/postInlineUnconditionally
Avoids an extra simplifier iteration
- - - - -
8e9b33f1 by Simon Peyton Jones at 2025-06-28T15:36:43+01:00
Accept GHCi debugger output change
@alt-romes says this is fine
- - - - -
90 changed files:
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Opt/Arity.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/DmdAnal.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Unfold.hs
- compiler/GHC/Core/Unfold/Make.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToStg.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/Call.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Instance/Family.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Rewrite.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- − compiler/GHC/Tc/Types/EvTerm.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Types/Demand.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/RepType.hs
- compiler/GHC/Types/Var.hs
- compiler/ghc.cabal.in
- testsuite/tests/core-to-stg/T24124.stderr
- testsuite/tests/deSugar/should_compile/T2431.stderr
- testsuite/tests/dmdanal/should_compile/T16029.stdout
- testsuite/tests/dmdanal/sigs/T21119.stderr
- testsuite/tests/dmdanal/sigs/T21888.stderr
- testsuite/tests/ghci.debugger/scripts/break011.stdout
- testsuite/tests/ghci.debugger/scripts/break024.stdout
- testsuite/tests/indexed-types/should_compile/T2238.hs
- testsuite/tests/numeric/should_compile/T15547.stderr
- testsuite/tests/numeric/should_compile/T23907.stderr
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/simplCore/should_compile/DataToTagFamilyScrut.stderr
- testsuite/tests/simplCore/should_compile/T15205.stderr
- testsuite/tests/simplCore/should_compile/T17366.stderr
- testsuite/tests/simplCore/should_compile/T17966.stderr
- testsuite/tests/simplCore/should_compile/T22309.stderr
- testsuite/tests/simplCore/should_compile/T22375DataFamily.stderr
- testsuite/tests/simplCore/should_compile/T23307.stderr
- testsuite/tests/simplCore/should_compile/T23307a.stderr
- testsuite/tests/simplCore/should_compile/T25389.stderr
- testsuite/tests/simplCore/should_compile/T25713.stderr
- testsuite/tests/simplCore/should_compile/T7360.stderr
- testsuite/tests/simplStg/should_compile/T15226b.stderr
- testsuite/tests/tcplugins/CtIdPlugin.hs
- testsuite/tests/typecheck/should_compile/Makefile
- testsuite/tests/typecheck/should_compile/T12763.stderr
- testsuite/tests/typecheck/should_compile/T14774.stdout
- testsuite/tests/typecheck/should_compile/T18406b.stderr
- testsuite/tests/typecheck/should_compile/T18529.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/unboxedsums/unpack_sums_7.stdout
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9589a3a6d13f63a4c87a6accee3ab1…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9589a3a6d13f63a4c87a6accee3ab1…
You're receiving this email because of your account on gitlab.haskell.org.
1
0