
[Git][ghc/ghc][wip/romes/step-out-5] 31 commits: haddock: Parse math even after ordinary characters
by Rodrigo Mesquita (@alt-romes) 23 Jun '25
by Rodrigo Mesquita (@alt-romes) 23 Jun '25
23 Jun '25
Rodrigo Mesquita pushed to branch wip/romes/step-out-5 at Glasgow Haskell Compiler / GHC
Commits:
6558467c by Ryan Hendrickson at 2025-06-06T05:46:58-04:00
haddock: Parse math even after ordinary characters
Fixes a bug where math sections were not recognized if preceded by a
character that isn't special (like space or a markup character).
- - - - -
265d0024 by ARATA Mizuki at 2025-06-06T05:47:48-04:00
AArch64 NCG: Fix sub-word arithmetic right shift
As noted in Note [Signed arithmetic on AArch64], we should zero-extend sub-word values.
Fixes #26061
- - - - -
05e9be18 by Simon Hengel at 2025-06-06T05:48:35-04:00
Allow Unicode in "message" and "hints" with -fdiagnostics-as-json
(fixes #26075)
- - - - -
bfa6b70f by ARATA Mizuki at 2025-06-06T05:49:24-04:00
x86 NCG: Fix code generation of bswap64 on i386
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
Fix #25601
- - - - -
35826d8b by Matthew Pickering at 2025-06-08T22:00:41+01:00
Hadrian: Add option to generate .hie files for stage1 libraries
The +hie_files flavour transformer can be enabled to produce hie files
for stage1 libraries. The hie files are produced in the
"extra-compilation-artifacts" folder and copied into the resulting
bindist.
At the moment the hie files are not produced for the release flavour,
they add about 170M to the final bindist.
Towards #16901
- - - - -
e2467dbd by Ryan Hendrickson at 2025-06-09T13:07:05-04:00
Fix various failures to -fprint-unicode-syntax
- - - - -
1d99d3e4 by maralorn at 2025-06-12T03:47:39-04:00
Add necessary flag for js linking
- - - - -
974d5734 by maralorn at 2025-06-12T03:47:39-04:00
Don’t use additional linker flags to detect presence of -fno-pie in configure.ac
This mirrors the behavior of ghc-toolchain
- - - - -
1e9eb118 by Andrew Lelechenko at 2025-06-12T03:48:21-04:00
Add HasCallStack to Control.Monad.Fail.fail
CLC proposal https://github.com/haskell/core-libraries-committee/issues/327
2% compile-time allocations increase in T3064, likely because `fail`
is now marginally more expensive to compile.
Metric Increase:
T3064
- - - - -
6d12060f by meooow25 at 2025-06-12T14:26:07-04:00
Bump containers submodule to 0.8
Also
* Disable -Wunused-imports for containers
* Allow containers-0.8 for in-tree packages
* Bump some submodules so that they allow containers-0.8. These are not
at any particular versions.
* Remove unused deps containers and split from ucd2haskell
* Fix tests affected by the new containers and hpc-bin
- - - - -
537bd233 by Peng Fan at 2025-06-12T14:27:02-04:00
NCG/LA64: Optimize code generation and reduce build-directory size.
1. makeFarBranches: Prioritize fewer instruction sequences.
2. Prefer instructions with immediate numbers to reduce register moves,
e.g. andi,ori,xori,addi.
3. Ppr: Remove unnecessary judgments.
4. genJump: Avoid "ld+jr" as much as possible.
5. BCOND and BCOND1: Implement conditional jumps with two jump ranges,
with limited choice of the shortest.
6. Implement FSQRT, CLT, CTZ.
7. Remove unnecessary code.
- - - - -
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
- - - - -
0ded57aa by Rodrigo Mesquita at 2025-06-23T14:59:50+01:00
debugger/rts: Allow toggling step-in per thread
The RTS global flag `rts_stop_next_breakpoint` globally sets the
interpreter to stop at the immediate next breakpoint.
With this commit, single step mode can additionally be set per thread in
the TSO flag (TSO_STOP_NEXT_BREAKPOINT).
Being able to toggle "stop at next breakpoint" per thread is an
important requirement for implementing "stepping out" of a function in a
multi-threaded context.
And, more generally, having a per-thread flag for single-stepping paves the
way for multi-threaded debugging.
That said, when we want to enable "single step" mode for the whole
interpreted program we still want to stop at the immediate next
breakpoint, whichever thread it belongs to.
That's why we also keep the global `rts_stop_next_breakpoint` flag, with
`rts_enableStopNextBreakpointAll` and `rts_disableStopNextBreakpointAll` helpers.
Preparation for #26042
- - - - -
1c611c21 by Rodrigo Mesquita at 2025-06-23T14:59:51+01:00
docs: Case continuation BCOs
This commit documents a subtle interaction between frames for case BCOs
and their parents frames. Namely, case continuation BCOs may refer to
(non-local) variables that are part of the parent's frame.
The note expanding a bit on these details is called [Case continuation BCOs]
- - - - -
7ee82353 by Rodrigo Mesquita at 2025-06-23T14:59:51+01:00
debugger: Implement step-out feature
Implements support for stepping-out of a function (aka breaking right after
returning from a function) in the interactive debugger.
It also introduces a GHCi command :stepout to step-out of a function
being debugged in the interpreter. The feature is described as:
Stop at the first breakpoint immediately after returning from the current
function scope.
Known limitations: because a function tail-call does not push a stack
frame, if step-out is used inside of a function that was tail-called,
execution will not be returned to its caller, but rather its caller's
first non-tail caller. On the other hand, it means the debugger
follows the more realistic execution of the program.
In the following example:
.. code-block:: none
f = do
a
b <--- (1) set breakpoint then step in here
c
b = do
...
d <--- (2) step-into this tail call
d = do
...
something <--- (3) step-out here
...
Stepping-out will stop execution at the `c` invokation in `f`, rather than
stopping at `b`.
The key idea is simple: When step-out is enabled, traverse the runtime
stack until a continuation BCO is found -- and enable the breakpoint
heading that BCO explicitly using its tick-index.
The details are specified in `Note [Debugger: Step-out]` in `rts/Interpreter.c`.
Since PUSH_ALTS BCOs (representing case continuations) were never headed
by a breakpoint (unlike the case alternatives they push), we introduced
the BRK_ALTS instruction to allow the debugger to set a case
continuation to stop at the breakpoint heading the alternative that is
taken. This is further described in `Note [Debugger: BRK_ALTS]`.
Fixes #26042
- - - - -
3c784fa2 by Rodrigo Mesquita at 2025-06-23T14:59:51+01:00
debugger: Filter step-out stops by SrcSpan
To implement step-out, the RTS looks for the first continuation frame on
the stack and explicitly enables its entry breakpoint. However, some
continuations will be contained in the function from which step-out was
initiated (trivial example is a case expression).
Similarly to steplocal, we will filter the breakpoints at which the RTS
yields to the debugger based on the SrcSpan. When doing step-out, only
stop if the breakpoint is /not/ contained in the function from which we
initiated it.
This is especially relevant in monadic statements such as IO which is
compiled to a long chain of case expressions.
See Note [Debugger: Filtering step-out stops]
- - - - -
338 changed files:
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/LA64.hs
- compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- compiler/GHC/CmmToAsm/LA64/Instr.hs
- compiler/GHC/CmmToAsm/LA64/Ppr.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/Core/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/Specialise.hs
- compiler/GHC/Core/PatSyn.hs
- compiler/GHC/Core/TyCo/Ppr.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Driver/Config.hs
- compiler/GHC/Driver/Flags.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/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Eval/Types.hs
- compiler/GHC/Stg/EnforceEpt/Types.hs
- compiler/GHC/StgToByteCode.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/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.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/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/ghc.cabal.in
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/exts/gadt_syntax.rst
- docs/users_guide/exts/required_type_arguments.rst
- docs/users_guide/ghci.rst
- docs/users_guide/using-warnings.rst
- docs/users_guide/using.rst
- ghc/GHCi/UI.hs
- ghc/ghc-bin.cabal.in
- hadrian/doc/flavours.md
- hadrian/doc/user-settings.md
- hadrian/hadrian.cabal
- hadrian/src/Context.hs
- hadrian/src/Context/Path.hs
- hadrian/src/Flavour.hs
- hadrian/src/Flavour/Type.hs
- hadrian/src/Settings/Builders/Ghc.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Flavours/Release.hs
- hadrian/src/Settings/Warnings.hs
- 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/Exts/Heap/Closures.hs
- libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc
- libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc
- libraries/ghc-heap/ghc-heap.cabal.in
- libraries/ghc-heap/tests/parse_tso_flags.hs
- 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/Debugger.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- libraries/ghci/ghci.cabal.in
- libraries/haskeline
- libraries/hpc
- linters/lint-whitespace/lint-whitespace.cabal
- m4/fp_gcc_supports_no_pie.m4
- m4/fptools_set_c_ld_flags.m4
- rts/Disassembler.c
- rts/Interpreter.c
- rts/Interpreter.h
- rts/RtsSymbols.c
- rts/StgMiscClosures.cmm
- rts/include/rts/Bytecodes.h
- rts/include/rts/Constants.h
- rts/include/rts/storage/Closures.h
- rts/include/stg/MachRegs.h
- testsuite/tests/annotations/should_fail/annfail03.stderr
- testsuite/tests/annotations/should_fail/annfail09.stderr
- + testsuite/tests/cmm/should_run/T25601.hs
- + testsuite/tests/cmm/should_run/T25601.stdout
- + testsuite/tests/cmm/should_run/T25601a.cmm
- testsuite/tests/cmm/should_run/all.T
- + testsuite/tests/codeGen/should_run/T26061.hs
- + testsuite/tests/codeGen/should_run/T26061.stdout
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/deSugar/should_run/DsDoExprFailMsg.stderr
- testsuite/tests/deSugar/should_run/DsMonadCompFailMsg.stderr
- testsuite/tests/dependent/should_fail/T13135_simple.stderr
- testsuite/tests/dependent/should_fail/T16326_Fail6.stderr
- testsuite/tests/diagnostic-codes/codes.stdout
- testsuite/tests/driver/json.stderr
- testsuite/tests/driver/json_warn.stderr
- + testsuite/tests/ghc-api/T26120.hs
- + testsuite/tests/ghc-api/T26120.stdout
- testsuite/tests/ghc-api/all.T
- + testsuite/tests/ghci.debugger/scripts/T26042b.hs
- + testsuite/tests/ghci.debugger/scripts/T26042b.script
- + testsuite/tests/ghci.debugger/scripts/T26042b.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042c.hs
- + testsuite/tests/ghci.debugger/scripts/T26042c.script
- + testsuite/tests/ghci.debugger/scripts/T26042c.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042d.hs
- + testsuite/tests/ghci.debugger/scripts/T26042d.script
- + testsuite/tests/ghci.debugger/scripts/T26042d.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042e.hs
- + testsuite/tests/ghci.debugger/scripts/T26042e.script
- + testsuite/tests/ghci.debugger/scripts/T26042e.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042f.hs
- + testsuite/tests/ghci.debugger/scripts/T26042f.script
- + testsuite/tests/ghci.debugger/scripts/T26042f1.stderr
- + testsuite/tests/ghci.debugger/scripts/T26042f1.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042f2.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042g.hs
- + testsuite/tests/ghci.debugger/scripts/T26042g.script
- + testsuite/tests/ghci.debugger/scripts/T26042g.stdout
- testsuite/tests/ghci.debugger/scripts/all.T
- testsuite/tests/ghci/scripts/T12550.stdout
- testsuite/tests/ghci/scripts/T8959b.stderr
- testsuite/tests/ghci/scripts/all.T
- + testsuite/tests/ghci/scripts/print-unicode-syntax.script
- + testsuite/tests/ghci/scripts/print-unicode-syntax.stderr
- + testsuite/tests/ghci/scripts/print-unicode-syntax.stdout
- testsuite/tests/ghci/should_run/T11825.stdout
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- + testsuite/tests/hiefile/should_run/HieGadtConSigs.hs
- + testsuite/tests/hiefile/should_run/HieGadtConSigs.stdout
- testsuite/tests/hiefile/should_run/all.T
- testsuite/tests/hpc/fork/hpc_fork.stdout
- testsuite/tests/hpc/function/tough.stdout
- testsuite/tests/hpc/function2/tough2.stdout
- testsuite/tests/hpc/simple/hpc001.stdout
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/linear/should_fail/LinearTHFail.stderr
- testsuite/tests/linters/notes.stdout
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/partial-sigs/should_fail/T10999.stderr
- testsuite/tests/perf/compiler/hard_hole_fits.stderr
- testsuite/tests/printer/T18791.stderr
- testsuite/tests/quasiquotation/T3953.stderr
- testsuite/tests/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/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/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/haddock-library/src/Documentation/Haddock/Parser.hs
- utils/haddock/haddock-library/test/Documentation/Haddock/ParserSpec.hs
- + 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/81bee76dde05a2c3e99371dc1a1505…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/81bee76dde05a2c3e99371dc1a1505…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/fix-reload-targets] Teach `:reload` about multiple home units
by Hannes Siebenhandl (@fendor) 23 Jun '25
by Hannes Siebenhandl (@fendor) 23 Jun '25
23 Jun '25
Hannes Siebenhandl pushed to branch wip/fendor/fix-reload-targets at Glasgow Haskell Compiler / GHC
Commits:
d794cf84 by fendor at 2025-06-23T15:52:14+02: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.
- - - - -
13 changed files:
- compiler/GHC/Driver/Make.hs
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Print.hs
- testsuite/tests/ghc-e/should_fail/T18441fail5.stderr
- + testsuite/tests/ghci/prog021/A.hs
- + testsuite/tests/ghci/prog021/B.hs
- + testsuite/tests/ghci/prog021/Makefile
- + testsuite/tests/ghci/prog021/prog021.T
- + testsuite/tests/ghci/prog021/prog021.script
- + testsuite/tests/ghci/prog021/prog021.stderr
- + testsuite/tests/ghci/prog021/prog021.stdout
- testsuite/tests/ghci/scripts/ghci021.stderr
Changes:
=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -135,6 +135,7 @@ import qualified GHC.Data.Maybe as M
import GHC.Data.Graph.Directed.Reachability
import qualified GHC.Unit.Home.Graph as HUG
import GHC.Unit.Home.PackageTable
+import qualified Data.List as List
-- -----------------------------------------------------------------------------
-- Loading the program
@@ -601,11 +602,13 @@ createBuildPlan mod_graph maybe_top_mod =
in
-
- assertPpr (sum (map countMods build_plan) == lengthMG mod_graph)
- (vcat [text "Build plan missing nodes:", (text "PLAN:" <+> ppr (sum (map countMods build_plan))), (text "GRAPH:" <+> ppr (lengthMG mod_graph))])
+ -- The assertion needs to operate on 'cycle_mod_graph' as we prune the module graph during 'topSortModuleGraph'.
+ assertPpr (sum (map countMods build_plan) == lengthMGWithSCC cycle_mod_graph)
+ (vcat [text "Build plan missing nodes:", (text "PLAN:" <+> ppr (sum (map countMods build_plan))), (text "GRAPH:" <+> ppr (lengthMGWithSCC cycle_mod_graph))])
build_plan
-
+ where
+ lengthMGWithSCC :: [SCC a] -> Int
+ lengthMGWithSCC = List.foldl' (\acc scc -> length scc + acc) 0
-- | Generalized version of 'load' which also supports a custom
-- 'Messager' (for reporting progress) and 'ModuleGraph' (generally
=====================================
ghc/GHCi/UI.hs
=====================================
@@ -1302,7 +1302,8 @@ runOneCommand eh gCmd = do
st <- getGHCiState
ghciHandle (\e -> lift $ eh e >>= return . Just) $
handleSourceError printErrorAndFail $
- cmd_wrapper st $ doCommand c
+ handleGhciCommandError printErrorAndContinue $
+ cmd_wrapper st $ doCommand c
-- source error's are handled by runStmt
-- is the handler necessary here?
where
@@ -1310,6 +1311,10 @@ runOneCommand eh gCmd = do
printGhciException err
return $ Just False -- Exit ghc -e, but not GHCi
+ printErrorAndContinue err = do
+ printGhciCommandException err
+ return $ Just False -- Exit ghc -e, but not GHCi
+
noSpace q = q >>= maybe (return Nothing)
(\c -> case removeSpaces c of
"" -> noSpace q
@@ -2286,13 +2291,16 @@ unAddModule files = do
-- | @:reload@ command
reloadModule :: GhciMonad m => String -> m ()
reloadModule m = do
- session <- GHC.getSession
- let home_unit = homeUnitId (hsc_home_unit session)
- ok <- doLoadAndCollectInfo Reload (loadTargets home_unit)
+ loadTarget <- findLoadTarget
+ ok <- doLoadAndCollectInfo Reload loadTarget
when (failed ok) failIfExprEvalMode
where
- loadTargets hu | null m = LoadAllTargets
- | otherwise = LoadUpTo (mkModule hu (GHC.mkModuleName m))
+ findLoadTarget
+ | null m =
+ pure LoadAllTargets
+ | otherwise = do
+ mod' <- lookupHomeUnitModuleName (GHC.mkModuleName m)
+ pure $ LoadUpTo mod'
reloadModuleDefer :: GhciMonad m => String -> m ()
reloadModuleDefer = wrapDeferTypeErrors . reloadModule
@@ -4747,8 +4755,11 @@ showException se =
Just other_ghc_ex -> putException (show other_ghc_ex)
Nothing ->
case fromException se of
- Just UserInterrupt -> putException "Interrupted."
- _ -> putException ("*** Exception: " ++ show se)
+ Just (GhciCommandError s) -> putException (show (GhciCommandError s))
+ Nothing ->
+ case fromException se of
+ Just UserInterrupt -> putException "Interrupted."
+ _ -> putException ("*** Exception: " ++ show se)
where
putException = hPutStrLn stderr
@@ -4798,15 +4809,22 @@ lookupModuleName mName = lookupQualifiedModuleName NoPkgQual mName
lookupQualifiedModuleName :: GHC.GhcMonad m => PkgQual -> ModuleName -> m Module
lookupQualifiedModuleName qual modl = do
GHC.lookupAllQualifiedModuleNames qual modl >>= \case
- [] -> throwGhcException (CmdLineError ("module '" ++ str ++ "' could not be found."))
+ [] -> throwGhciCommandError (GhciModuleError $ GhciModuleNameNotFound modl)
[m] -> pure m
- ms -> throwGhcException (CmdLineError ("module name '" ++ str ++ "' is ambiguous:\n" ++ errorMsg ms))
+ ms -> throwGhciCommandError (GhciModuleError $ GhciAmbiguousModuleName modl ms)
+
+lookupHomeUnitModuleName :: GHC.GhcMonad m => ModuleName -> m HomeUnitModule
+lookupHomeUnitModuleName modl = do
+ m <- GHC.lookupLoadedHomeModuleByModuleName modl >>= \case
+ Nothing -> throwGhciCommandError (GhciModuleError $ GhciNoLocalModuleName modl)
+ Just [m] -> pure m
+ Just ms -> throwGhciCommandError (GhciModuleError $ GhciAmbiguousModuleName modl ms)
+
+ if unitIsDefinite (moduleUnit m)
+ then pure (fmap toUnitId m)
+ else throwGhcException (CmdLineError ("module '" ++ str ++ "' is not from a definite unit"))
where
str = moduleNameString modl
- errorMsg ms = intercalate "\n"
- [ "- " ++ unitIdString (toUnitId (moduleUnit m)) ++ ":" ++ moduleNameString (moduleName m)
- | m <- ms
- ]
showModule :: Module -> String
showModule = moduleNameString . moduleName
=====================================
ghc/GHCi/UI/Exception.hs
=====================================
@@ -5,7 +5,10 @@
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE LambdaCase #-}
module GHCi.UI.Exception
- ( GhciMessage(..)
+ ( GhciCommandError(..)
+ , throwGhciCommandError
+ , handleGhciCommandError
+ , GhciMessage(..)
, GhciMessageOpts(..)
, fromGhcOpts
, toGhcHint
@@ -29,19 +32,57 @@ import GHC.Tc.Errors.Ppr
import GHC.Tc.Errors.Types
import GHC.Types.Error.Codes
+import GHC.Types.SrcLoc (interactiveSrcSpan)
import GHC.TypeLits
import GHC.Unit.State
import GHC.Utils.Outputable
+import GHC.Utils.Error
import GHC.Generics
import GHC.Types.Error
import GHC.Types
import qualified GHC
+import Control.Exception
+import Control.Monad.Catch as MC (MonadCatch, catch)
+import Control.Monad.IO.Class
import Data.List.NonEmpty (NonEmpty(..))
+-- | A 'GhciCommandError' are messages that caused the abortion of a GHCi command.
+newtype GhciCommandError = GhciCommandError (Messages GhciMessage)
+
+instance Exception GhciCommandError
+
+instance Show GhciCommandError where
+ -- We implement 'Show' because it's required by the 'Exception' instance, but diagnostics
+ -- shouldn't be shown via the 'Show' typeclass, but rather rendered using the ppr functions.
+ -- This also explains why there is no 'Show' instance for a 'MsgEnvelope'.
+ show (GhciCommandError msgs) =
+ renderWithContext defaultSDocContext
+ . vcat
+ . pprMsgEnvelopeBagWithLocDefault
+ . getMessages
+ $ msgs
+
+-- | Perform the given action and call the exception handler if the action
+-- throws a 'SourceError'. See 'SourceError' for more information.
+handleGhciCommandError :: (MonadCatch m) =>
+ (GhciCommandError -> m a) -- ^ exception handler
+ -> m a -- ^ action to perform
+ -> m a
+handleGhciCommandError handler act =
+ MC.catch act (\(e :: GhciCommandError) -> handler e)
+
+throwGhciCommandError :: MonadIO m => GhciCommandMessage -> m a
+throwGhciCommandError errorMessage =
+ liftIO
+ . throwIO
+ . GhciCommandError
+ . singleMessage
+ $ mkPlainErrorMsgEnvelope interactiveSrcSpan (GhciCommandMessage errorMessage)
+
-- | The Options passed to 'diagnosticMessage'
-- in the 'Diagnostic' instance of 'GhciMessage'.
data GhciMessageOpts = GhciMessageOpts
@@ -257,6 +298,9 @@ data GhciModuleError
| GhciNoResolvedModules
| GhciNoModuleForName GHC.Name
| GhciNoMatchingModuleExport
+ | GhciNoLocalModuleName !GHC.ModuleName
+ | GhciModuleNameNotFound !GHC.ModuleName
+ | GhciAmbiguousModuleName !GHC.ModuleName ![GHC.Module]
deriving Generic
instance Diagnostic GhciModuleError where
@@ -278,6 +322,16 @@ instance Diagnostic GhciModuleError where
-> "No module for" <+> ppr name
GhciNoMatchingModuleExport
-> "No matching export in any local modules."
+ GhciNoLocalModuleName modl
+ -> "Module" <+> quotes (ppr modl) <+> "cannot be found locally"
+ GhciModuleNameNotFound modl
+ -> "module" <+> quotes (ppr modl) <+> "could not be found."
+ GhciAmbiguousModuleName modl candidates
+ -> "Module name" <+> quotes (ppr modl) <+> "is ambiguous" <>
+ vcat
+ [ text "-" <+> ppr (GHC.moduleName m) <> colon <> ppr (GHC.moduleUnit m)
+ | m <- candidates
+ ]
diagnosticReason = \case
GhciModuleNotFound{} ->
@@ -294,6 +348,12 @@ instance Diagnostic GhciModuleError where
ErrorWithoutFlag
GhciNoMatchingModuleExport{} ->
ErrorWithoutFlag
+ GhciNoLocalModuleName{} ->
+ ErrorWithoutFlag
+ GhciModuleNameNotFound{} ->
+ ErrorWithoutFlag
+ GhciAmbiguousModuleName{} ->
+ ErrorWithoutFlag
diagnosticHints = \case
GhciModuleNotFound{} ->
@@ -310,7 +370,12 @@ instance Diagnostic GhciModuleError where
[]
GhciNoMatchingModuleExport{} ->
[]
-
+ GhciNoLocalModuleName{} ->
+ []
+ GhciModuleNameNotFound{} ->
+ []
+ GhciAmbiguousModuleName{} ->
+ []
diagnosticCode = constructorCode @GHCi
-- | A Diagnostic emitted by GHCi while executing a command
@@ -487,6 +552,9 @@ type family GhciDiagnosticCode c = n | n -> c where
GhciDiagnosticCode "GhciNoModuleForName" = 21847
GhciDiagnosticCode "GhciNoMatchingModuleExport" = 59723
GhciDiagnosticCode "GhciArgumentParseError" = 35671
+ GhciDiagnosticCode "GhciNoLocalModuleName" = 81235
+ GhciDiagnosticCode "GhciModuleNameNotFound" = 40475
+ GhciDiagnosticCode "GhciAmbiguousModuleName" = 59019
type GhciConRecursInto :: Symbol -> Maybe Type
type family GhciConRecursInto con where
=====================================
ghc/GHCi/UI/Print.hs
=====================================
@@ -5,6 +5,7 @@ module GHCi.UI.Print
, printForUserPartWay
, printError
, printGhciException
+ , printGhciCommandException
) where
import qualified GHC
@@ -64,7 +65,7 @@ printForUserPartWay doc = do
-- | pretty-print a 'GhciCommandMessage'
printError :: GhcMonad m => GhciCommandMessage -> m ()
printError err =
- let errEnvelope = mkPlainErrorMsgEnvelope (UnhelpfulSpan UnhelpfulInteractive) err
+ let errEnvelope = mkPlainErrorMsgEnvelope interactiveSrcSpan err
in printError' (const NoDiagnosticOpts) (singleMessage errEnvelope)
-- | Print the all diagnostics in a 'SourceError'. Specialised for GHCi error reporting
@@ -72,6 +73,9 @@ printError err =
printGhciException :: GhcMonad m => SourceError -> m ()
printGhciException err = printError' initGhciPrintConfig (GhciGhcMessage <$> (srcErrorMessages err))
+printGhciCommandException :: GhcMonad m => GhciCommandError -> m ()
+printGhciCommandException (GhciCommandError errs) = printError' initGhciPrintConfig errs
+
printError' :: (GhcMonad m, Diagnostic a) => (DynFlags -> DiagnosticOpts a) -> Messages a -> m ()
printError' get_config err = do
dflags <- getDynFlags
=====================================
testsuite/tests/ghc-e/should_fail/T18441fail5.stderr
=====================================
@@ -1,4 +1,4 @@
-<no location info>: error: [GHC-82272]
- module ‘Abcde’ cannot be found locally
+<interactive>: error: [GHCi-81235]
+ Module ‘Abcde’ cannot be found locally
1
=====================================
testsuite/tests/ghci/prog021/A.hs
=====================================
@@ -0,0 +1,5 @@
+module A (f) where
+
+f x = [x]
+
+g x = Just x
=====================================
testsuite/tests/ghci/prog021/B.hs
=====================================
@@ -0,0 +1,5 @@
+module B where
+
+import A
+
+h = f
=====================================
testsuite/tests/ghci/prog021/Makefile
=====================================
@@ -0,0 +1,3 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
=====================================
testsuite/tests/ghci/prog021/prog021.T
=====================================
@@ -0,0 +1,6 @@
+test('prog021',
+ [req_interp,
+ cmd_prefix('ghciWayFlags=' + config.ghci_way_flags),
+ extra_files(['A.hs', 'B.hs', 'prog021.script'])
+ ],
+ ghci_script, ['prog021.script'])
=====================================
testsuite/tests/ghci/prog021/prog021.script
=====================================
@@ -0,0 +1,15 @@
+-- Loads all targets
+:load A B
+:m + A B
+f 5
+g 5
+h 5
+-- Load only one target
+:reload A
+:m A
+putStrLn "B is not loaded, we can't add it to the context"
+:m + B
+f 5
+putStrLn "`g` and `h` are not in scope"
+g 5
+h 5
=====================================
testsuite/tests/ghci/prog021/prog021.stderr
=====================================
@@ -0,0 +1,10 @@
+<no location info>: error: [GHC-35235]
+ Could not find module ‘B’.
+ It is not a module in the current program, or in any known package.
+
+<interactive>:14:1: error: [GHC-88464]
+ Variable not in scope: g :: t0 -> t
+
+<interactive>:15:1: error: [GHC-88464]
+ Variable not in scope: h :: t0 -> t
+
=====================================
testsuite/tests/ghci/prog021/prog021.stdout
=====================================
@@ -0,0 +1,6 @@
+[5]
+Just 5
+[5]
+B is not loaded, we can't add it to the context
+[5]
+`g` and `h` are not in scope
=====================================
testsuite/tests/ghci/scripts/ghci021.stderr
=====================================
@@ -1,3 +1,3 @@
-<no location info>: error: [GHC-82272]
- module ‘ThisDoesNotExist’ cannot be found locally
+<interactive>: error: [GHCi-81235]
+ Module ‘ThisDoesNotExist’ cannot be found locally
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d794cf84edd310cd538c194df81176e…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d794cf84edd310cd538c194df81176e…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/fix-reload-targets] Teach `:reload` about multiple home units
by Hannes Siebenhandl (@fendor) 23 Jun '25
by Hannes Siebenhandl (@fendor) 23 Jun '25
23 Jun '25
Hannes Siebenhandl pushed to branch wip/fendor/fix-reload-targets at Glasgow Haskell Compiler / GHC
Commits:
ccdab30e by fendor at 2025-06-23T15:46:28+02: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.
- - - - -
13 changed files:
- compiler/GHC/Driver/Make.hs
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Print.hs
- testsuite/tests/ghc-e/should_fail/T18441fail5.stderr
- + testsuite/tests/ghci/prog021/A.hs
- + testsuite/tests/ghci/prog021/B.hs
- + testsuite/tests/ghci/prog021/Makefile
- + testsuite/tests/ghci/prog021/prog021.T
- + testsuite/tests/ghci/prog021/prog021.script
- + testsuite/tests/ghci/prog021/prog021.stderr
- + testsuite/tests/ghci/prog021/prog021.stdout
- testsuite/tests/ghci/scripts/ghci021.stderr
Changes:
=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -135,6 +135,7 @@ import qualified GHC.Data.Maybe as M
import GHC.Data.Graph.Directed.Reachability
import qualified GHC.Unit.Home.Graph as HUG
import GHC.Unit.Home.PackageTable
+import qualified Data.List as List
-- -----------------------------------------------------------------------------
-- Loading the program
@@ -601,11 +602,13 @@ createBuildPlan mod_graph maybe_top_mod =
in
-
- assertPpr (sum (map countMods build_plan) == lengthMG mod_graph)
- (vcat [text "Build plan missing nodes:", (text "PLAN:" <+> ppr (sum (map countMods build_plan))), (text "GRAPH:" <+> ppr (lengthMG mod_graph))])
+ -- The assertion needs to operate on 'cycle_mod_graph' as we prune the module graph during 'topSortModuleGraph'.
+ assertPpr (sum (map countMods build_plan) == lengthMGWithSCC cycle_mod_graph)
+ (vcat [text "Build plan missing nodes:", (text "PLAN:" <+> ppr (sum (map countMods build_plan))), (text "GRAPH:" <+> ppr (lengthMGWithSCC cycle_mod_graph))])
build_plan
-
+ where
+ lengthMGWithSCC :: [SCC a] -> Int
+ lengthMGWithSCC = List.foldl' (\acc scc -> length scc + acc) 0
-- | Generalized version of 'load' which also supports a custom
-- 'Messager' (for reporting progress) and 'ModuleGraph' (generally
=====================================
ghc/GHCi/UI.hs
=====================================
@@ -1302,7 +1302,8 @@ runOneCommand eh gCmd = do
st <- getGHCiState
ghciHandle (\e -> lift $ eh e >>= return . Just) $
handleSourceError printErrorAndFail $
- cmd_wrapper st $ doCommand c
+ handleGhciCommandError printErrorAndContinue $
+ cmd_wrapper st $ doCommand c
-- source error's are handled by runStmt
-- is the handler necessary here?
where
@@ -1310,6 +1311,10 @@ runOneCommand eh gCmd = do
printGhciException err
return $ Just False -- Exit ghc -e, but not GHCi
+ printErrorAndContinue err = do
+ printGhciCommandException err
+ return $ Just False -- Exit ghc -e, but not GHCi
+
noSpace q = q >>= maybe (return Nothing)
(\c -> case removeSpaces c of
"" -> noSpace q
@@ -2286,13 +2291,16 @@ unAddModule files = do
-- | @:reload@ command
reloadModule :: GhciMonad m => String -> m ()
reloadModule m = do
- session <- GHC.getSession
- let home_unit = homeUnitId (hsc_home_unit session)
- ok <- doLoadAndCollectInfo Reload (loadTargets home_unit)
+ loadTarget <- findLoadTarget
+ ok <- doLoadAndCollectInfo Reload loadTarget
when (failed ok) failIfExprEvalMode
where
- loadTargets hu | null m = LoadAllTargets
- | otherwise = LoadUpTo (mkModule hu (GHC.mkModuleName m))
+ findLoadTarget
+ | null m =
+ pure LoadAllTargets
+ | otherwise = do
+ mod' <- lookupHomeUnitModuleName (GHC.mkModuleName m)
+ pure $ LoadUpTo mod'
reloadModuleDefer :: GhciMonad m => String -> m ()
reloadModuleDefer = wrapDeferTypeErrors . reloadModule
@@ -4747,8 +4755,11 @@ showException se =
Just other_ghc_ex -> putException (show other_ghc_ex)
Nothing ->
case fromException se of
- Just UserInterrupt -> putException "Interrupted."
- _ -> putException ("*** Exception: " ++ show se)
+ Just (GhciCommandError s) -> putException (show (GhciCommandError s))
+ Nothing ->
+ case fromException se of
+ Just UserInterrupt -> putException "Interrupted."
+ _ -> putException ("*** Exception: " ++ show se)
where
putException = hPutStrLn stderr
@@ -4798,15 +4809,22 @@ lookupModuleName mName = lookupQualifiedModuleName NoPkgQual mName
lookupQualifiedModuleName :: GHC.GhcMonad m => PkgQual -> ModuleName -> m Module
lookupQualifiedModuleName qual modl = do
GHC.lookupAllQualifiedModuleNames qual modl >>= \case
- [] -> throwGhcException (CmdLineError ("module '" ++ str ++ "' could not be found."))
+ [] -> throwGhciCommandError (GhciModuleError $ GhciModuleNameNotFound modl)
[m] -> pure m
- ms -> throwGhcException (CmdLineError ("module name '" ++ str ++ "' is ambiguous:\n" ++ errorMsg ms))
+ ms -> throwGhciCommandError (GhciModuleError $ GhciAmbiguousModuleName modl ms)
+
+lookupHomeUnitModuleName :: GHC.GhcMonad m => ModuleName -> m HomeUnitModule
+lookupHomeUnitModuleName modl = do
+ m <- GHC.lookupLoadedHomeModuleByModuleName modl >>= \case
+ Nothing -> throwGhciCommandError (GhciModuleError $ GhciNoLocalModuleName modl)
+ Just [m] -> pure m
+ Just ms -> throwGhciCommandError (GhciModuleError $ GhciAmbiguousModuleName modl ms)
+
+ if unitIsDefinite (moduleUnit m)
+ then pure (fmap toUnitId m)
+ else throwGhcException (CmdLineError ("module '" ++ str ++ "' is not from a definite unit"))
where
str = moduleNameString modl
- errorMsg ms = intercalate "\n"
- [ "- " ++ unitIdString (toUnitId (moduleUnit m)) ++ ":" ++ moduleNameString (moduleName m)
- | m <- ms
- ]
showModule :: Module -> String
showModule = moduleNameString . moduleName
=====================================
ghc/GHCi/UI/Exception.hs
=====================================
@@ -5,7 +5,10 @@
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE LambdaCase #-}
module GHCi.UI.Exception
- ( GhciMessage(..)
+ ( GhciCommandError(..)
+ , throwGhciCommandError
+ , handleGhciCommandError
+ , GhciMessage(..)
, GhciMessageOpts(..)
, fromGhcOpts
, toGhcHint
@@ -29,19 +32,57 @@ import GHC.Tc.Errors.Ppr
import GHC.Tc.Errors.Types
import GHC.Types.Error.Codes
+import GHC.Types.SrcLoc (interactiveSrcSpan)
import GHC.TypeLits
import GHC.Unit.State
import GHC.Utils.Outputable
+import GHC.Utils.Error
import GHC.Generics
import GHC.Types.Error
import GHC.Types
import qualified GHC
+import Control.Exception
+import Control.Monad.Catch as MC (MonadCatch, catch)
+import Control.Monad.IO.Class
import Data.List.NonEmpty (NonEmpty(..))
+-- | A 'GhciCommandError' are messages that caused the abortion of a GHCi command.
+newtype GhciCommandError = GhciCommandError (Messages GhciMessage)
+
+instance Exception GhciCommandError
+
+instance Show GhciCommandError where
+ -- We implement 'Show' because it's required by the 'Exception' instance, but diagnostics
+ -- shouldn't be shown via the 'Show' typeclass, but rather rendered using the ppr functions.
+ -- This also explains why there is no 'Show' instance for a 'MsgEnvelope'.
+ show (GhciCommandError msgs) =
+ renderWithContext defaultSDocContext
+ . vcat
+ . pprMsgEnvelopeBagWithLocDefault
+ . getMessages
+ $ msgs
+
+-- | Perform the given action and call the exception handler if the action
+-- throws a 'SourceError'. See 'SourceError' for more information.
+handleGhciCommandError :: (MonadCatch m) =>
+ (GhciCommandError -> m a) -- ^ exception handler
+ -> m a -- ^ action to perform
+ -> m a
+handleGhciCommandError handler act =
+ MC.catch act (\(e :: GhciCommandError) -> handler e)
+
+throwGhciCommandError :: MonadIO m => GhciCommandMessage -> m a
+throwGhciCommandError errorMessage =
+ liftIO
+ . throwIO
+ . GhciCommandError
+ . singleMessage
+ $ mkPlainErrorMsgEnvelope interactiveSrcSpan (GhciCommandMessage errorMessage)
+
-- | The Options passed to 'diagnosticMessage'
-- in the 'Diagnostic' instance of 'GhciMessage'.
data GhciMessageOpts = GhciMessageOpts
@@ -57,6 +98,16 @@ data GhciMessage where
GhciGhcMessage :: GhcMessage -> GhciMessage
GhciUnknownMessage :: UnknownDiagnosticFor GhciMessage -> GhciMessage
+-- instance Show GhciMessage where
+-- show = \case
+-- GhciCommandMessage msg -> show msg
+-- GhciGhcMessage msg -> show msg
+-- GhciUnknownMessage msg -> show msg
+
+-- instance Exception GhciMessage where
+-- fromException (SomeException e) = undefined
+-- displayException exc = showSDocUnsafe (pprDiagnostic exc)
+
-- | A 'GhciHint' may either be a hint that GHC emitted ('GhciGhcHint')
-- or one that is specific to GHCi ('GhciCommandHint').
data GhciHint where
@@ -257,6 +308,9 @@ data GhciModuleError
| GhciNoResolvedModules
| GhciNoModuleForName GHC.Name
| GhciNoMatchingModuleExport
+ | GhciNoLocalModuleName !GHC.ModuleName
+ | GhciModuleNameNotFound !GHC.ModuleName
+ | GhciAmbiguousModuleName !GHC.ModuleName ![GHC.Module]
deriving Generic
instance Diagnostic GhciModuleError where
@@ -278,6 +332,16 @@ instance Diagnostic GhciModuleError where
-> "No module for" <+> ppr name
GhciNoMatchingModuleExport
-> "No matching export in any local modules."
+ GhciNoLocalModuleName modl
+ -> "Module" <+> quotes (ppr modl) <+> "cannot be found locally"
+ GhciModuleNameNotFound modl
+ -> "module" <+> quotes (ppr modl) <+> "could not be found."
+ GhciAmbiguousModuleName modl candidates
+ -> "Module name" <+> quotes (ppr modl) <+> "is ambiguous" <>
+ vcat
+ [ text "-" <+> ppr (GHC.moduleName m) <> colon <> ppr (GHC.moduleUnit m)
+ | m <- candidates
+ ]
diagnosticReason = \case
GhciModuleNotFound{} ->
@@ -294,6 +358,12 @@ instance Diagnostic GhciModuleError where
ErrorWithoutFlag
GhciNoMatchingModuleExport{} ->
ErrorWithoutFlag
+ GhciNoLocalModuleName{} ->
+ ErrorWithoutFlag
+ GhciModuleNameNotFound{} ->
+ ErrorWithoutFlag
+ GhciAmbiguousModuleName{} ->
+ ErrorWithoutFlag
diagnosticHints = \case
GhciModuleNotFound{} ->
@@ -310,7 +380,12 @@ instance Diagnostic GhciModuleError where
[]
GhciNoMatchingModuleExport{} ->
[]
-
+ GhciNoLocalModuleName{} ->
+ []
+ GhciModuleNameNotFound{} ->
+ []
+ GhciAmbiguousModuleName{} ->
+ []
diagnosticCode = constructorCode @GHCi
-- | A Diagnostic emitted by GHCi while executing a command
@@ -487,6 +562,9 @@ type family GhciDiagnosticCode c = n | n -> c where
GhciDiagnosticCode "GhciNoModuleForName" = 21847
GhciDiagnosticCode "GhciNoMatchingModuleExport" = 59723
GhciDiagnosticCode "GhciArgumentParseError" = 35671
+ GhciDiagnosticCode "GhciNoLocalModuleName" = 81235
+ GhciDiagnosticCode "GhciModuleNameNotFound" = 40475
+ GhciDiagnosticCode "GhciAmbiguousModuleName" = 59019
type GhciConRecursInto :: Symbol -> Maybe Type
type family GhciConRecursInto con where
=====================================
ghc/GHCi/UI/Print.hs
=====================================
@@ -5,6 +5,7 @@ module GHCi.UI.Print
, printForUserPartWay
, printError
, printGhciException
+ , printGhciCommandException
) where
import qualified GHC
@@ -64,7 +65,7 @@ printForUserPartWay doc = do
-- | pretty-print a 'GhciCommandMessage'
printError :: GhcMonad m => GhciCommandMessage -> m ()
printError err =
- let errEnvelope = mkPlainErrorMsgEnvelope (UnhelpfulSpan UnhelpfulInteractive) err
+ let errEnvelope = mkPlainErrorMsgEnvelope interactiveSrcSpan err
in printError' (const NoDiagnosticOpts) (singleMessage errEnvelope)
-- | Print the all diagnostics in a 'SourceError'. Specialised for GHCi error reporting
@@ -72,6 +73,9 @@ printError err =
printGhciException :: GhcMonad m => SourceError -> m ()
printGhciException err = printError' initGhciPrintConfig (GhciGhcMessage <$> (srcErrorMessages err))
+printGhciCommandException :: GhcMonad m => GhciCommandError -> m ()
+printGhciCommandException (GhciCommandError errs) = printError' initGhciPrintConfig errs
+
printError' :: (GhcMonad m, Diagnostic a) => (DynFlags -> DiagnosticOpts a) -> Messages a -> m ()
printError' get_config err = do
dflags <- getDynFlags
=====================================
testsuite/tests/ghc-e/should_fail/T18441fail5.stderr
=====================================
@@ -1,4 +1,4 @@
-<no location info>: error: [GHC-82272]
- module ‘Abcde’ cannot be found locally
+<interactive>: error: [GHCi-81235]
+ Module ‘Abcde’ cannot be found locally
1
=====================================
testsuite/tests/ghci/prog021/A.hs
=====================================
@@ -0,0 +1,5 @@
+module A (f) where
+
+f x = [x]
+
+g x = Just x
=====================================
testsuite/tests/ghci/prog021/B.hs
=====================================
@@ -0,0 +1,5 @@
+module B where
+
+import A
+
+h = f
=====================================
testsuite/tests/ghci/prog021/Makefile
=====================================
@@ -0,0 +1,3 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
=====================================
testsuite/tests/ghci/prog021/prog021.T
=====================================
@@ -0,0 +1,6 @@
+test('prog021',
+ [req_interp,
+ cmd_prefix('ghciWayFlags=' + config.ghci_way_flags),
+ extra_files(['A.hs', 'B.hs', 'prog021.script'])
+ ],
+ ghci_script, ['prog021.script'])
=====================================
testsuite/tests/ghci/prog021/prog021.script
=====================================
@@ -0,0 +1,15 @@
+-- Loads all targets
+:load A B
+:m + A B
+f 5
+g 5
+h 5
+-- Load only one target
+:reload A
+:m A
+putStrLn "B is not loaded, we can't add it to the context"
+:m + B
+f 5
+putStrLn "`g` and `h` are not in scope"
+g 5
+h 5
=====================================
testsuite/tests/ghci/prog021/prog021.stderr
=====================================
@@ -0,0 +1,10 @@
+<no location info>: error: [GHC-35235]
+ Could not find module ‘B’.
+ It is not a module in the current program, or in any known package.
+
+<interactive>:14:1: error: [GHC-88464]
+ Variable not in scope: g :: t0 -> t
+
+<interactive>:15:1: error: [GHC-88464]
+ Variable not in scope: h :: t0 -> t
+
=====================================
testsuite/tests/ghci/prog021/prog021.stdout
=====================================
@@ -0,0 +1,6 @@
+[5]
+Just 5
+[5]
+B is not loaded, we can't add it to the context
+[5]
+`g` and `h` are not in scope
=====================================
testsuite/tests/ghci/scripts/ghci021.stderr
=====================================
@@ -1,3 +1,3 @@
-<no location info>: error: [GHC-82272]
- module ‘ThisDoesNotExist’ cannot be found locally
+<interactive>: error: [GHCi-81235]
+ Module ‘ThisDoesNotExist’ cannot be found locally
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ccdab30ef743dcec5b76e4a8a56164f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ccdab30ef743dcec5b76e4a8a56164f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/fix-reload-targets] Teach `:reload` about multiple home units
by Hannes Siebenhandl (@fendor) 23 Jun '25
by Hannes Siebenhandl (@fendor) 23 Jun '25
23 Jun '25
Hannes Siebenhandl pushed to branch wip/fendor/fix-reload-targets at Glasgow Haskell Compiler / GHC
Commits:
1e31b3d7 by fendor at 2025-06-23T15:46:21+02: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`.
- - - - -
13 changed files:
- compiler/GHC/Driver/Make.hs
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Print.hs
- testsuite/tests/ghc-e/should_fail/T18441fail5.stderr
- + testsuite/tests/ghci/prog021/A.hs
- + testsuite/tests/ghci/prog021/B.hs
- + testsuite/tests/ghci/prog021/Makefile
- + testsuite/tests/ghci/prog021/prog021.T
- + testsuite/tests/ghci/prog021/prog021.script
- + testsuite/tests/ghci/prog021/prog021.stderr
- + testsuite/tests/ghci/prog021/prog021.stdout
- testsuite/tests/ghci/scripts/ghci021.stderr
Changes:
=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -135,6 +135,7 @@ import qualified GHC.Data.Maybe as M
import GHC.Data.Graph.Directed.Reachability
import qualified GHC.Unit.Home.Graph as HUG
import GHC.Unit.Home.PackageTable
+import qualified Data.List as List
-- -----------------------------------------------------------------------------
-- Loading the program
@@ -601,11 +602,13 @@ createBuildPlan mod_graph maybe_top_mod =
in
-
- assertPpr (sum (map countMods build_plan) == lengthMG mod_graph)
- (vcat [text "Build plan missing nodes:", (text "PLAN:" <+> ppr (sum (map countMods build_plan))), (text "GRAPH:" <+> ppr (lengthMG mod_graph))])
+ -- The assertion needs to operate on 'cycle_mod_graph' as we prune the module graph during 'topSortModuleGraph'.
+ assertPpr (sum (map countMods build_plan) == lengthMGWithSCC cycle_mod_graph)
+ (vcat [text "Build plan missing nodes:", (text "PLAN:" <+> ppr (sum (map countMods build_plan))), (text "GRAPH:" <+> ppr (lengthMGWithSCC cycle_mod_graph))])
build_plan
-
+ where
+ lengthMGWithSCC :: [SCC a] -> Int
+ lengthMGWithSCC = List.foldl' (\acc scc -> length scc + acc) 0
-- | Generalized version of 'load' which also supports a custom
-- 'Messager' (for reporting progress) and 'ModuleGraph' (generally
=====================================
ghc/GHCi/UI.hs
=====================================
@@ -1302,7 +1302,8 @@ runOneCommand eh gCmd = do
st <- getGHCiState
ghciHandle (\e -> lift $ eh e >>= return . Just) $
handleSourceError printErrorAndFail $
- cmd_wrapper st $ doCommand c
+ handleGhciCommandError printErrorAndContinue $
+ cmd_wrapper st $ doCommand c
-- source error's are handled by runStmt
-- is the handler necessary here?
where
@@ -1310,6 +1311,10 @@ runOneCommand eh gCmd = do
printGhciException err
return $ Just False -- Exit ghc -e, but not GHCi
+ printErrorAndContinue err = do
+ printGhciCommandException err
+ return $ Just False -- Exit ghc -e, but not GHCi
+
noSpace q = q >>= maybe (return Nothing)
(\c -> case removeSpaces c of
"" -> noSpace q
@@ -2286,13 +2291,16 @@ unAddModule files = do
-- | @:reload@ command
reloadModule :: GhciMonad m => String -> m ()
reloadModule m = do
- session <- GHC.getSession
- let home_unit = homeUnitId (hsc_home_unit session)
- ok <- doLoadAndCollectInfo Reload (loadTargets home_unit)
+ loadTarget <- findLoadTarget
+ ok <- doLoadAndCollectInfo Reload loadTarget
when (failed ok) failIfExprEvalMode
where
- loadTargets hu | null m = LoadAllTargets
- | otherwise = LoadUpTo (mkModule hu (GHC.mkModuleName m))
+ findLoadTarget
+ | null m =
+ pure LoadAllTargets
+ | otherwise = do
+ mod' <- lookupHomeUnitModuleName (GHC.mkModuleName m)
+ pure $ LoadUpTo mod'
reloadModuleDefer :: GhciMonad m => String -> m ()
reloadModuleDefer = wrapDeferTypeErrors . reloadModule
@@ -4747,8 +4755,11 @@ showException se =
Just other_ghc_ex -> putException (show other_ghc_ex)
Nothing ->
case fromException se of
- Just UserInterrupt -> putException "Interrupted."
- _ -> putException ("*** Exception: " ++ show se)
+ Just (GhciCommandError s) -> putException (show (GhciCommandError s))
+ Nothing ->
+ case fromException se of
+ Just UserInterrupt -> putException "Interrupted."
+ _ -> putException ("*** Exception: " ++ show se)
where
putException = hPutStrLn stderr
@@ -4798,15 +4809,22 @@ lookupModuleName mName = lookupQualifiedModuleName NoPkgQual mName
lookupQualifiedModuleName :: GHC.GhcMonad m => PkgQual -> ModuleName -> m Module
lookupQualifiedModuleName qual modl = do
GHC.lookupAllQualifiedModuleNames qual modl >>= \case
- [] -> throwGhcException (CmdLineError ("module '" ++ str ++ "' could not be found."))
+ [] -> throwGhciCommandError (GhciModuleError $ GhciModuleNameNotFound modl)
[m] -> pure m
- ms -> throwGhcException (CmdLineError ("module name '" ++ str ++ "' is ambiguous:\n" ++ errorMsg ms))
+ ms -> throwGhciCommandError (GhciModuleError $ GhciAmbiguousModuleName modl ms)
+
+lookupHomeUnitModuleName :: GHC.GhcMonad m => ModuleName -> m HomeUnitModule
+lookupHomeUnitModuleName modl = do
+ m <- GHC.lookupLoadedHomeModuleByModuleName modl >>= \case
+ Nothing -> throwGhciCommandError (GhciModuleError $ GhciNoLocalModuleName modl)
+ Just [m] -> pure m
+ Just ms -> throwGhciCommandError (GhciModuleError $ GhciAmbiguousModuleName modl ms)
+
+ if unitIsDefinite (moduleUnit m)
+ then pure (fmap toUnitId m)
+ else throwGhcException (CmdLineError ("module '" ++ str ++ "' is not from a definite unit"))
where
str = moduleNameString modl
- errorMsg ms = intercalate "\n"
- [ "- " ++ unitIdString (toUnitId (moduleUnit m)) ++ ":" ++ moduleNameString (moduleName m)
- | m <- ms
- ]
showModule :: Module -> String
showModule = moduleNameString . moduleName
=====================================
ghc/GHCi/UI/Exception.hs
=====================================
@@ -5,7 +5,10 @@
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE LambdaCase #-}
module GHCi.UI.Exception
- ( GhciMessage(..)
+ ( GhciCommandError(..)
+ , throwGhciCommandError
+ , handleGhciCommandError
+ , GhciMessage(..)
, GhciMessageOpts(..)
, fromGhcOpts
, toGhcHint
@@ -29,19 +32,57 @@ import GHC.Tc.Errors.Ppr
import GHC.Tc.Errors.Types
import GHC.Types.Error.Codes
+import GHC.Types.SrcLoc (interactiveSrcSpan)
import GHC.TypeLits
import GHC.Unit.State
import GHC.Utils.Outputable
+import GHC.Utils.Error
import GHC.Generics
import GHC.Types.Error
import GHC.Types
import qualified GHC
+import Control.Exception
+import Control.Monad.Catch as MC (MonadCatch, catch)
+import Control.Monad.IO.Class
import Data.List.NonEmpty (NonEmpty(..))
+-- | A 'GhciCommandError' are messages that caused the abortion of a GHCi command.
+newtype GhciCommandError = GhciCommandError (Messages GhciMessage)
+
+instance Exception GhciCommandError
+
+instance Show GhciCommandError where
+ -- We implement 'Show' because it's required by the 'Exception' instance, but diagnostics
+ -- shouldn't be shown via the 'Show' typeclass, but rather rendered using the ppr functions.
+ -- This also explains why there is no 'Show' instance for a 'MsgEnvelope'.
+ show (GhciCommandError msgs) =
+ renderWithContext defaultSDocContext
+ . vcat
+ . pprMsgEnvelopeBagWithLocDefault
+ . getMessages
+ $ msgs
+
+-- | Perform the given action and call the exception handler if the action
+-- throws a 'SourceError'. See 'SourceError' for more information.
+handleGhciCommandError :: (MonadCatch m) =>
+ (GhciCommandError -> m a) -- ^ exception handler
+ -> m a -- ^ action to perform
+ -> m a
+handleGhciCommandError handler act =
+ MC.catch act (\(e :: GhciCommandError) -> handler e)
+
+throwGhciCommandError :: MonadIO m => GhciCommandMessage -> m a
+throwGhciCommandError errorMessage =
+ liftIO
+ . throwIO
+ . GhciCommandError
+ . singleMessage
+ $ mkPlainErrorMsgEnvelope interactiveSrcSpan (GhciCommandMessage errorMessage)
+
-- | The Options passed to 'diagnosticMessage'
-- in the 'Diagnostic' instance of 'GhciMessage'.
data GhciMessageOpts = GhciMessageOpts
@@ -57,6 +98,16 @@ data GhciMessage where
GhciGhcMessage :: GhcMessage -> GhciMessage
GhciUnknownMessage :: UnknownDiagnosticFor GhciMessage -> GhciMessage
+-- instance Show GhciMessage where
+-- show = \case
+-- GhciCommandMessage msg -> show msg
+-- GhciGhcMessage msg -> show msg
+-- GhciUnknownMessage msg -> show msg
+
+-- instance Exception GhciMessage where
+-- fromException (SomeException e) = undefined
+-- displayException exc = showSDocUnsafe (pprDiagnostic exc)
+
-- | A 'GhciHint' may either be a hint that GHC emitted ('GhciGhcHint')
-- or one that is specific to GHCi ('GhciCommandHint').
data GhciHint where
@@ -257,6 +308,9 @@ data GhciModuleError
| GhciNoResolvedModules
| GhciNoModuleForName GHC.Name
| GhciNoMatchingModuleExport
+ | GhciNoLocalModuleName !GHC.ModuleName
+ | GhciModuleNameNotFound !GHC.ModuleName
+ | GhciAmbiguousModuleName !GHC.ModuleName ![GHC.Module]
deriving Generic
instance Diagnostic GhciModuleError where
@@ -278,6 +332,16 @@ instance Diagnostic GhciModuleError where
-> "No module for" <+> ppr name
GhciNoMatchingModuleExport
-> "No matching export in any local modules."
+ GhciNoLocalModuleName modl
+ -> "Module" <+> quotes (ppr modl) <+> "cannot be found locally"
+ GhciModuleNameNotFound modl
+ -> "module" <+> quotes (ppr modl) <+> "could not be found."
+ GhciAmbiguousModuleName modl candidates
+ -> "Module name" <+> quotes (ppr modl) <+> "is ambiguous" <>
+ vcat
+ [ text "-" <+> ppr (GHC.moduleName m) <> colon <> ppr (GHC.moduleUnit m)
+ | m <- candidates
+ ]
diagnosticReason = \case
GhciModuleNotFound{} ->
@@ -294,6 +358,12 @@ instance Diagnostic GhciModuleError where
ErrorWithoutFlag
GhciNoMatchingModuleExport{} ->
ErrorWithoutFlag
+ GhciNoLocalModuleName{} ->
+ ErrorWithoutFlag
+ GhciModuleNameNotFound{} ->
+ ErrorWithoutFlag
+ GhciAmbiguousModuleName{} ->
+ ErrorWithoutFlag
diagnosticHints = \case
GhciModuleNotFound{} ->
@@ -310,7 +380,12 @@ instance Diagnostic GhciModuleError where
[]
GhciNoMatchingModuleExport{} ->
[]
-
+ GhciNoLocalModuleName{} ->
+ []
+ GhciModuleNameNotFound{} ->
+ []
+ GhciAmbiguousModuleName{} ->
+ []
diagnosticCode = constructorCode @GHCi
-- | A Diagnostic emitted by GHCi while executing a command
@@ -487,6 +562,9 @@ type family GhciDiagnosticCode c = n | n -> c where
GhciDiagnosticCode "GhciNoModuleForName" = 21847
GhciDiagnosticCode "GhciNoMatchingModuleExport" = 59723
GhciDiagnosticCode "GhciArgumentParseError" = 35671
+ GhciDiagnosticCode "GhciNoLocalModuleName" = 81235
+ GhciDiagnosticCode "GhciModuleNameNotFound" = 40475
+ GhciDiagnosticCode "GhciAmbiguousModuleName" = 59019
type GhciConRecursInto :: Symbol -> Maybe Type
type family GhciConRecursInto con where
=====================================
ghc/GHCi/UI/Print.hs
=====================================
@@ -5,6 +5,7 @@ module GHCi.UI.Print
, printForUserPartWay
, printError
, printGhciException
+ , printGhciCommandException
) where
import qualified GHC
@@ -64,7 +65,7 @@ printForUserPartWay doc = do
-- | pretty-print a 'GhciCommandMessage'
printError :: GhcMonad m => GhciCommandMessage -> m ()
printError err =
- let errEnvelope = mkPlainErrorMsgEnvelope (UnhelpfulSpan UnhelpfulInteractive) err
+ let errEnvelope = mkPlainErrorMsgEnvelope interactiveSrcSpan err
in printError' (const NoDiagnosticOpts) (singleMessage errEnvelope)
-- | Print the all diagnostics in a 'SourceError'. Specialised for GHCi error reporting
@@ -72,6 +73,9 @@ printError err =
printGhciException :: GhcMonad m => SourceError -> m ()
printGhciException err = printError' initGhciPrintConfig (GhciGhcMessage <$> (srcErrorMessages err))
+printGhciCommandException :: GhcMonad m => GhciCommandError -> m ()
+printGhciCommandException (GhciCommandError errs) = printError' initGhciPrintConfig errs
+
printError' :: (GhcMonad m, Diagnostic a) => (DynFlags -> DiagnosticOpts a) -> Messages a -> m ()
printError' get_config err = do
dflags <- getDynFlags
=====================================
testsuite/tests/ghc-e/should_fail/T18441fail5.stderr
=====================================
@@ -1,4 +1,4 @@
-<no location info>: error: [GHC-82272]
- module ‘Abcde’ cannot be found locally
+<interactive>: error: [GHCi-81235]
+ Module ‘Abcde’ cannot be found locally
1
=====================================
testsuite/tests/ghci/prog021/A.hs
=====================================
@@ -0,0 +1,5 @@
+module A (f) where
+
+f x = [x]
+
+g x = Just x
=====================================
testsuite/tests/ghci/prog021/B.hs
=====================================
@@ -0,0 +1,5 @@
+module B where
+
+import A
+
+h = f
=====================================
testsuite/tests/ghci/prog021/Makefile
=====================================
@@ -0,0 +1,3 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
=====================================
testsuite/tests/ghci/prog021/prog021.T
=====================================
@@ -0,0 +1,6 @@
+test('prog021',
+ [req_interp,
+ cmd_prefix('ghciWayFlags=' + config.ghci_way_flags),
+ extra_files(['A.hs', 'B.hs', 'prog021.script'])
+ ],
+ ghci_script, ['prog021.script'])
=====================================
testsuite/tests/ghci/prog021/prog021.script
=====================================
@@ -0,0 +1,15 @@
+-- Loads all targets
+:load A B
+:m + A B
+f 5
+g 5
+h 5
+-- Load only one target
+:reload A
+:m A
+putStrLn "B is not loaded, we can't add it to the context"
+:m + B
+f 5
+putStrLn "`g` and `h` are not in scope"
+g 5
+h 5
=====================================
testsuite/tests/ghci/prog021/prog021.stderr
=====================================
@@ -0,0 +1,10 @@
+<no location info>: error: [GHC-35235]
+ Could not find module ‘B’.
+ It is not a module in the current program, or in any known package.
+
+<interactive>:14:1: error: [GHC-88464]
+ Variable not in scope: g :: t0 -> t
+
+<interactive>:15:1: error: [GHC-88464]
+ Variable not in scope: h :: t0 -> t
+
=====================================
testsuite/tests/ghci/prog021/prog021.stdout
=====================================
@@ -0,0 +1,6 @@
+[5]
+Just 5
+[5]
+B is not loaded, we can't add it to the context
+[5]
+`g` and `h` are not in scope
=====================================
testsuite/tests/ghci/scripts/ghci021.stderr
=====================================
@@ -1,3 +1,3 @@
-<no location info>: error: [GHC-82272]
- module ‘ThisDoesNotExist’ cannot be found locally
+<interactive>: error: [GHCi-81235]
+ Module ‘ThisDoesNotExist’ cannot be found locally
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1e31b3d7621161d3883f8316b6a5bd5…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1e31b3d7621161d3883f8316b6a5bd5…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/fix-reload-targets] Teach `:reload` about multiple home units
by Hannes Siebenhandl (@fendor) 23 Jun '25
by Hannes Siebenhandl (@fendor) 23 Jun '25
23 Jun '25
Hannes Siebenhandl pushed to branch wip/fendor/fix-reload-targets at Glasgow Haskell Compiler / GHC
Commits:
f02c9d6f by fendor at 2025-06-23T15:43:57+02: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`.
- - - - -
13 changed files:
- compiler/GHC/Driver/Make.hs
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Print.hs
- testsuite/tests/ghc-e/should_fail/T18441fail5.stderr
- + testsuite/tests/ghci/prog021/A.hs
- + testsuite/tests/ghci/prog021/B.hs
- + testsuite/tests/ghci/prog021/Makefile
- + testsuite/tests/ghci/prog021/prog021.T
- + testsuite/tests/ghci/prog021/prog021.script
- + testsuite/tests/ghci/prog021/prog021.stderr
- + testsuite/tests/ghci/prog021/prog021.stdout
- testsuite/tests/ghci/scripts/ghci021.stderr
Changes:
=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -135,6 +135,7 @@ import qualified GHC.Data.Maybe as M
import GHC.Data.Graph.Directed.Reachability
import qualified GHC.Unit.Home.Graph as HUG
import GHC.Unit.Home.PackageTable
+import qualified Data.List as List
-- -----------------------------------------------------------------------------
-- Loading the program
@@ -601,11 +602,13 @@ createBuildPlan mod_graph maybe_top_mod =
in
-
- assertPpr (sum (map countMods build_plan) == lengthMG mod_graph)
- (vcat [text "Build plan missing nodes:", (text "PLAN:" <+> ppr (sum (map countMods build_plan))), (text "GRAPH:" <+> ppr (lengthMG mod_graph))])
+ -- The assertion needs to operate on 'cycle_mod_graph' as we prune the module graph during 'topSortModuleGraph'.
+ assertPpr (sum (map countMods build_plan) == lengthMGWithSCC cycle_mod_graph)
+ (vcat [text "Build plan missing nodes:", (text "PLAN:" <+> ppr (sum (map countMods build_plan))), (text "GRAPH:" <+> ppr (lengthMGWithSCC cycle_mod_graph))])
build_plan
-
+ where
+ lengthMGWithSCC :: [SCC a] -> Int
+ lengthMGWithSCC = List.foldl' (\acc scc -> length scc + acc) 0
-- | Generalized version of 'load' which also supports a custom
-- 'Messager' (for reporting progress) and 'ModuleGraph' (generally
=====================================
ghc/GHCi/UI.hs
=====================================
@@ -178,6 +178,7 @@ import GHC.IO.Handle ( hFlushAll )
import GHC.TopHandler ( topHandler )
import qualified GHC.Unit.Module.Graph as GHC
+import Debug.Trace
-----------------------------------------------------------------------------
@@ -1302,7 +1303,8 @@ runOneCommand eh gCmd = do
st <- getGHCiState
ghciHandle (\e -> lift $ eh e >>= return . Just) $
handleSourceError printErrorAndFail $
- cmd_wrapper st $ doCommand c
+ handleGhciCommandError printErrorAndContinue $
+ cmd_wrapper st $ doCommand c
-- source error's are handled by runStmt
-- is the handler necessary here?
where
@@ -1310,6 +1312,10 @@ runOneCommand eh gCmd = do
printGhciException err
return $ Just False -- Exit ghc -e, but not GHCi
+ printErrorAndContinue err = do
+ printGhciCommandException err
+ return $ Just False -- Exit ghc -e, but not GHCi
+
noSpace q = q >>= maybe (return Nothing)
(\c -> case removeSpaces c of
"" -> noSpace q
@@ -2286,13 +2292,16 @@ unAddModule files = do
-- | @:reload@ command
reloadModule :: GhciMonad m => String -> m ()
reloadModule m = do
- session <- GHC.getSession
- let home_unit = homeUnitId (hsc_home_unit session)
- ok <- doLoadAndCollectInfo Reload (loadTargets home_unit)
+ loadTarget <- findLoadTarget
+ ok <- doLoadAndCollectInfo Reload loadTarget
when (failed ok) failIfExprEvalMode
where
- loadTargets hu | null m = LoadAllTargets
- | otherwise = LoadUpTo (mkModule hu (GHC.mkModuleName m))
+ findLoadTarget
+ | null m =
+ pure LoadAllTargets
+ | otherwise = do
+ mod' <- lookupHomeUnitModuleName (GHC.mkModuleName m)
+ pure $ LoadUpTo mod'
reloadModuleDefer :: GhciMonad m => String -> m ()
reloadModuleDefer = wrapDeferTypeErrors . reloadModule
@@ -4739,7 +4748,8 @@ handler exception = do
ghciHandle handler (showException exception >> return False)
showException :: MonadIO m => SomeException -> m ()
-showException se =
+showException se = do
+ traceM "showException called"
liftIO $ case fromException se of
-- omit the location for CmdLineError:
Just (CmdLineError s) -> putException s
@@ -4747,8 +4757,11 @@ showException se =
Just other_ghc_ex -> putException (show other_ghc_ex)
Nothing ->
case fromException se of
- Just UserInterrupt -> putException "Interrupted."
- _ -> putException ("*** Exception: " ++ show se)
+ Just (GhciCommandError s) -> putException (show (GhciCommandError s))
+ Nothing ->
+ case fromException se of
+ Just UserInterrupt -> putException "Interrupted."
+ _ -> putException ("*** Exception: " ++ show se)
where
putException = hPutStrLn stderr
@@ -4798,15 +4811,22 @@ lookupModuleName mName = lookupQualifiedModuleName NoPkgQual mName
lookupQualifiedModuleName :: GHC.GhcMonad m => PkgQual -> ModuleName -> m Module
lookupQualifiedModuleName qual modl = do
GHC.lookupAllQualifiedModuleNames qual modl >>= \case
- [] -> throwGhcException (CmdLineError ("module '" ++ str ++ "' could not be found."))
+ [] -> throwGhciCommandError (GhciModuleError $ GhciModuleNameNotFound modl)
[m] -> pure m
- ms -> throwGhcException (CmdLineError ("module name '" ++ str ++ "' is ambiguous:\n" ++ errorMsg ms))
+ ms -> throwGhciCommandError (GhciModuleError $ GhciAmbiguousModuleName modl ms)
+
+lookupHomeUnitModuleName :: GHC.GhcMonad m => ModuleName -> m HomeUnitModule
+lookupHomeUnitModuleName modl = do
+ m <- GHC.lookupLoadedHomeModuleByModuleName modl >>= \case
+ Nothing -> throwGhciCommandError (GhciModuleError $ GhciNoLocalModuleName modl)
+ Just [m] -> pure m
+ Just ms -> throwGhciCommandError (GhciModuleError $ GhciAmbiguousModuleName modl ms)
+
+ if unitIsDefinite (moduleUnit m)
+ then pure (fmap toUnitId m)
+ else throwGhcException (CmdLineError ("module '" ++ str ++ "' is not from a definite unit"))
where
str = moduleNameString modl
- errorMsg ms = intercalate "\n"
- [ "- " ++ unitIdString (toUnitId (moduleUnit m)) ++ ":" ++ moduleNameString (moduleName m)
- | m <- ms
- ]
showModule :: Module -> String
showModule = moduleNameString . moduleName
=====================================
ghc/GHCi/UI/Exception.hs
=====================================
@@ -5,7 +5,10 @@
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE LambdaCase #-}
module GHCi.UI.Exception
- ( GhciMessage(..)
+ ( GhciCommandError(..)
+ , throwGhciCommandError
+ , handleGhciCommandError
+ , GhciMessage(..)
, GhciMessageOpts(..)
, fromGhcOpts
, toGhcHint
@@ -29,19 +32,57 @@ import GHC.Tc.Errors.Ppr
import GHC.Tc.Errors.Types
import GHC.Types.Error.Codes
+import GHC.Types.SrcLoc (interactiveSrcSpan)
import GHC.TypeLits
import GHC.Unit.State
import GHC.Utils.Outputable
+import GHC.Utils.Error
import GHC.Generics
import GHC.Types.Error
import GHC.Types
import qualified GHC
+import Control.Exception
+import Control.Monad.Catch as MC (MonadCatch, catch)
+import Control.Monad.IO.Class
import Data.List.NonEmpty (NonEmpty(..))
+-- | A 'GhciCommandError' are messages that caused the abortion of a GHCi command.
+newtype GhciCommandError = GhciCommandError (Messages GhciMessage)
+
+instance Exception GhciCommandError
+
+instance Show GhciCommandError where
+ -- We implement 'Show' because it's required by the 'Exception' instance, but diagnostics
+ -- shouldn't be shown via the 'Show' typeclass, but rather rendered using the ppr functions.
+ -- This also explains why there is no 'Show' instance for a 'MsgEnvelope'.
+ show (GhciCommandError msgs) =
+ renderWithContext defaultSDocContext
+ . vcat
+ . pprMsgEnvelopeBagWithLocDefault
+ . getMessages
+ $ msgs
+
+-- | Perform the given action and call the exception handler if the action
+-- throws a 'SourceError'. See 'SourceError' for more information.
+handleGhciCommandError :: (MonadCatch m) =>
+ (GhciCommandError -> m a) -- ^ exception handler
+ -> m a -- ^ action to perform
+ -> m a
+handleGhciCommandError handler act =
+ MC.catch act (\(e :: GhciCommandError) -> handler e)
+
+throwGhciCommandError :: MonadIO m => GhciCommandMessage -> m a
+throwGhciCommandError errorMessage =
+ liftIO
+ . throwIO
+ . GhciCommandError
+ . singleMessage
+ $ mkPlainErrorMsgEnvelope interactiveSrcSpan (GhciCommandMessage errorMessage)
+
-- | The Options passed to 'diagnosticMessage'
-- in the 'Diagnostic' instance of 'GhciMessage'.
data GhciMessageOpts = GhciMessageOpts
@@ -57,6 +98,16 @@ data GhciMessage where
GhciGhcMessage :: GhcMessage -> GhciMessage
GhciUnknownMessage :: UnknownDiagnosticFor GhciMessage -> GhciMessage
+-- instance Show GhciMessage where
+-- show = \case
+-- GhciCommandMessage msg -> show msg
+-- GhciGhcMessage msg -> show msg
+-- GhciUnknownMessage msg -> show msg
+
+-- instance Exception GhciMessage where
+-- fromException (SomeException e) = undefined
+-- displayException exc = showSDocUnsafe (pprDiagnostic exc)
+
-- | A 'GhciHint' may either be a hint that GHC emitted ('GhciGhcHint')
-- or one that is specific to GHCi ('GhciCommandHint').
data GhciHint where
@@ -257,6 +308,9 @@ data GhciModuleError
| GhciNoResolvedModules
| GhciNoModuleForName GHC.Name
| GhciNoMatchingModuleExport
+ | GhciNoLocalModuleName !GHC.ModuleName
+ | GhciModuleNameNotFound !GHC.ModuleName
+ | GhciAmbiguousModuleName !GHC.ModuleName ![GHC.Module]
deriving Generic
instance Diagnostic GhciModuleError where
@@ -278,6 +332,16 @@ instance Diagnostic GhciModuleError where
-> "No module for" <+> ppr name
GhciNoMatchingModuleExport
-> "No matching export in any local modules."
+ GhciNoLocalModuleName modl
+ -> "Module" <+> quotes (ppr modl) <+> "cannot be found locally"
+ GhciModuleNameNotFound modl
+ -> "module" <+> quotes (ppr modl) <+> "could not be found."
+ GhciAmbiguousModuleName modl candidates
+ -> "Module name" <+> quotes (ppr modl) <+> "is ambiguous" <>
+ vcat
+ [ text "-" <+> ppr (GHC.moduleName m) <> colon <> ppr (GHC.moduleUnit m)
+ | m <- candidates
+ ]
diagnosticReason = \case
GhciModuleNotFound{} ->
@@ -294,6 +358,12 @@ instance Diagnostic GhciModuleError where
ErrorWithoutFlag
GhciNoMatchingModuleExport{} ->
ErrorWithoutFlag
+ GhciNoLocalModuleName{} ->
+ ErrorWithoutFlag
+ GhciModuleNameNotFound{} ->
+ ErrorWithoutFlag
+ GhciAmbiguousModuleName{} ->
+ ErrorWithoutFlag
diagnosticHints = \case
GhciModuleNotFound{} ->
@@ -310,7 +380,12 @@ instance Diagnostic GhciModuleError where
[]
GhciNoMatchingModuleExport{} ->
[]
-
+ GhciNoLocalModuleName{} ->
+ []
+ GhciModuleNameNotFound{} ->
+ []
+ GhciAmbiguousModuleName{} ->
+ []
diagnosticCode = constructorCode @GHCi
-- | A Diagnostic emitted by GHCi while executing a command
@@ -487,6 +562,9 @@ type family GhciDiagnosticCode c = n | n -> c where
GhciDiagnosticCode "GhciNoModuleForName" = 21847
GhciDiagnosticCode "GhciNoMatchingModuleExport" = 59723
GhciDiagnosticCode "GhciArgumentParseError" = 35671
+ GhciDiagnosticCode "GhciNoLocalModuleName" = 81235
+ GhciDiagnosticCode "GhciModuleNameNotFound" = 40475
+ GhciDiagnosticCode "GhciAmbiguousModuleName" = 59019
type GhciConRecursInto :: Symbol -> Maybe Type
type family GhciConRecursInto con where
=====================================
ghc/GHCi/UI/Print.hs
=====================================
@@ -5,6 +5,7 @@ module GHCi.UI.Print
, printForUserPartWay
, printError
, printGhciException
+ , printGhciCommandException
) where
import qualified GHC
@@ -64,7 +65,7 @@ printForUserPartWay doc = do
-- | pretty-print a 'GhciCommandMessage'
printError :: GhcMonad m => GhciCommandMessage -> m ()
printError err =
- let errEnvelope = mkPlainErrorMsgEnvelope (UnhelpfulSpan UnhelpfulInteractive) err
+ let errEnvelope = mkPlainErrorMsgEnvelope interactiveSrcSpan err
in printError' (const NoDiagnosticOpts) (singleMessage errEnvelope)
-- | Print the all diagnostics in a 'SourceError'. Specialised for GHCi error reporting
@@ -72,6 +73,9 @@ printError err =
printGhciException :: GhcMonad m => SourceError -> m ()
printGhciException err = printError' initGhciPrintConfig (GhciGhcMessage <$> (srcErrorMessages err))
+printGhciCommandException :: GhcMonad m => GhciCommandError -> m ()
+printGhciCommandException (GhciCommandError errs) = printError' initGhciPrintConfig errs
+
printError' :: (GhcMonad m, Diagnostic a) => (DynFlags -> DiagnosticOpts a) -> Messages a -> m ()
printError' get_config err = do
dflags <- getDynFlags
=====================================
testsuite/tests/ghc-e/should_fail/T18441fail5.stderr
=====================================
@@ -1,4 +1,4 @@
-<no location info>: error: [GHC-82272]
- module ‘Abcde’ cannot be found locally
+<interactive>: error: [GHCi-81235]
+ Module ‘Abcde’ cannot be found locally
1
=====================================
testsuite/tests/ghci/prog021/A.hs
=====================================
@@ -0,0 +1,5 @@
+module A (f) where
+
+f x = [x]
+
+g x = Just x
=====================================
testsuite/tests/ghci/prog021/B.hs
=====================================
@@ -0,0 +1,5 @@
+module B where
+
+import A
+
+h = f
=====================================
testsuite/tests/ghci/prog021/Makefile
=====================================
@@ -0,0 +1,3 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
=====================================
testsuite/tests/ghci/prog021/prog021.T
=====================================
@@ -0,0 +1,6 @@
+test('prog021',
+ [req_interp,
+ cmd_prefix('ghciWayFlags=' + config.ghci_way_flags),
+ extra_files(['A.hs', 'B.hs', 'prog021.script'])
+ ],
+ ghci_script, ['prog021.script'])
=====================================
testsuite/tests/ghci/prog021/prog021.script
=====================================
@@ -0,0 +1,15 @@
+-- Loads all targets
+:load A B
+:m + A B
+f 5
+g 5
+h 5
+-- Load only one target
+:reload A
+:m A
+putStrLn "B is not loaded, we can't add it to the context"
+:m + B
+f 5
+putStrLn "`g` and `h` are not in scope"
+g 5
+h 5
=====================================
testsuite/tests/ghci/prog021/prog021.stderr
=====================================
@@ -0,0 +1,10 @@
+<no location info>: error: [GHC-35235]
+ Could not find module ‘B’.
+ It is not a module in the current program, or in any known package.
+
+<interactive>:14:1: error: [GHC-88464]
+ Variable not in scope: g :: t0 -> t
+
+<interactive>:15:1: error: [GHC-88464]
+ Variable not in scope: h :: t0 -> t
+
=====================================
testsuite/tests/ghci/prog021/prog021.stdout
=====================================
@@ -0,0 +1,6 @@
+[5]
+Just 5
+[5]
+B is not loaded, we can't add it to the context
+[5]
+`g` and `h` are not in scope
=====================================
testsuite/tests/ghci/scripts/ghci021.stderr
=====================================
@@ -1,3 +1,3 @@
-<no location info>: error: [GHC-82272]
- module ‘ThisDoesNotExist’ cannot be found locally
+<interactive>: error: [GHCi-81235]
+ Module ‘ThisDoesNotExist’ cannot be found locally
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f02c9d6f6364bd0039af0fe23d1a68f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f02c9d6f6364bd0039af0fe23d1a68f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/fix-reload-targets] Teach `:reload` about multiple home units
by Hannes Siebenhandl (@fendor) 23 Jun '25
by Hannes Siebenhandl (@fendor) 23 Jun '25
23 Jun '25
Hannes Siebenhandl pushed to branch wip/fendor/fix-reload-targets at Glasgow Haskell Compiler / GHC
Commits:
01e62ede by fendor at 2025-06-23T15:37:27+02: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`.
- - - - -
13 changed files:
- compiler/GHC/Driver/Make.hs
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Print.hs
- testsuite/tests/ghc-e/should_fail/T18441fail5.stderr
- + testsuite/tests/ghci/prog021/A.hs
- + testsuite/tests/ghci/prog021/B.hs
- + testsuite/tests/ghci/prog021/Makefile
- + testsuite/tests/ghci/prog021/prog021.T
- + testsuite/tests/ghci/prog021/prog021.script
- + testsuite/tests/ghci/prog021/prog021.stderr
- + testsuite/tests/ghci/prog021/prog021.stdout
- testsuite/tests/ghci/scripts/ghci021.stderr
Changes:
=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -135,6 +135,7 @@ import qualified GHC.Data.Maybe as M
import GHC.Data.Graph.Directed.Reachability
import qualified GHC.Unit.Home.Graph as HUG
import GHC.Unit.Home.PackageTable
+import qualified Data.List as List
-- -----------------------------------------------------------------------------
-- Loading the program
@@ -601,11 +602,13 @@ createBuildPlan mod_graph maybe_top_mod =
in
-
- assertPpr (sum (map countMods build_plan) == lengthMG mod_graph)
- (vcat [text "Build plan missing nodes:", (text "PLAN:" <+> ppr (sum (map countMods build_plan))), (text "GRAPH:" <+> ppr (lengthMG mod_graph))])
+ -- The assertion needs to operate on 'cycle_mod_graph' as we prune the module graph during 'topSortModuleGraph'.
+ assertPpr (sum (map countMods build_plan) == lengthMGWithSCC cycle_mod_graph)
+ (vcat [text "Build plan missing nodes:", (text "PLAN:" <+> ppr (sum (map countMods build_plan))), (text "GRAPH:" <+> ppr (lengthMGWithSCC cycle_mod_graph))])
build_plan
-
+ where
+ lengthMGWithSCC :: [SCC a] -> Int
+ lengthMGWithSCC = List.foldl' (\acc scc -> length scc + acc) 0
-- | Generalized version of 'load' which also supports a custom
-- 'Messager' (for reporting progress) and 'ModuleGraph' (generally
=====================================
ghc/GHCi/UI.hs
=====================================
@@ -178,6 +178,7 @@ import GHC.IO.Handle ( hFlushAll )
import GHC.TopHandler ( topHandler )
import qualified GHC.Unit.Module.Graph as GHC
+import Debug.Trace
-----------------------------------------------------------------------------
@@ -1302,7 +1303,8 @@ runOneCommand eh gCmd = do
st <- getGHCiState
ghciHandle (\e -> lift $ eh e >>= return . Just) $
handleSourceError printErrorAndFail $
- cmd_wrapper st $ doCommand c
+ handleGhciCommandError printErrorAndContinue $
+ cmd_wrapper st $ doCommand c
-- source error's are handled by runStmt
-- is the handler necessary here?
where
@@ -1310,6 +1312,10 @@ runOneCommand eh gCmd = do
printGhciException err
return $ Just False -- Exit ghc -e, but not GHCi
+ printErrorAndContinue err = do
+ printGhciCommandException err
+ return $ Just False -- Exit ghc -e, but not GHCi
+
noSpace q = q >>= maybe (return Nothing)
(\c -> case removeSpaces c of
"" -> noSpace q
@@ -2286,13 +2292,16 @@ unAddModule files = do
-- | @:reload@ command
reloadModule :: GhciMonad m => String -> m ()
reloadModule m = do
- session <- GHC.getSession
- let home_unit = homeUnitId (hsc_home_unit session)
- ok <- doLoadAndCollectInfo Reload (loadTargets home_unit)
+ loadTarget <- findLoadTarget
+ ok <- doLoadAndCollectInfo Reload loadTarget
when (failed ok) failIfExprEvalMode
where
- loadTargets hu | null m = LoadAllTargets
- | otherwise = LoadUpTo (mkModule hu (GHC.mkModuleName m))
+ findLoadTarget
+ | null m =
+ pure LoadAllTargets
+ | otherwise = do
+ mod' <- lookupHomeUnitModuleName (GHC.mkModuleName m)
+ pure $ LoadUpTo mod'
reloadModuleDefer :: GhciMonad m => String -> m ()
reloadModuleDefer = wrapDeferTypeErrors . reloadModule
@@ -4739,7 +4748,8 @@ handler exception = do
ghciHandle handler (showException exception >> return False)
showException :: MonadIO m => SomeException -> m ()
-showException se =
+showException se = do
+ traceM "showException called"
liftIO $ case fromException se of
-- omit the location for CmdLineError:
Just (CmdLineError s) -> putException s
@@ -4747,8 +4757,11 @@ showException se =
Just other_ghc_ex -> putException (show other_ghc_ex)
Nothing ->
case fromException se of
- Just UserInterrupt -> putException "Interrupted."
- _ -> putException ("*** Exception: " ++ show se)
+ Just (GhciCommandError s) -> putException (show (GhciCommandError s))
+ Nothing ->
+ case fromException se of
+ Just UserInterrupt -> putException "Interrupted."
+ _ -> putException ("*** Exception: " ++ show se)
where
putException = hPutStrLn stderr
@@ -4798,15 +4811,22 @@ lookupModuleName mName = lookupQualifiedModuleName NoPkgQual mName
lookupQualifiedModuleName :: GHC.GhcMonad m => PkgQual -> ModuleName -> m Module
lookupQualifiedModuleName qual modl = do
GHC.lookupAllQualifiedModuleNames qual modl >>= \case
- [] -> throwGhcException (CmdLineError ("module '" ++ str ++ "' could not be found."))
+ [] -> throwGhciCommandError (GhciModuleError $ GhciModuleNameNotFound modl)
[m] -> pure m
- ms -> throwGhcException (CmdLineError ("module name '" ++ str ++ "' is ambiguous:\n" ++ errorMsg ms))
+ ms -> throwGhciCommandError (GhciModuleError $ GhciAmbiguousModuleName modl ms)
+
+lookupHomeUnitModuleName :: GHC.GhcMonad m => ModuleName -> m HomeUnitModule
+lookupHomeUnitModuleName modl = do
+ m <- GHC.lookupLoadedHomeModuleByModuleName modl >>= \case
+ Nothing -> throwGhciCommandError (GhciModuleError $ GhciNoLocalModuleName modl)
+ Just [m] -> pure m
+ Just ms -> throwGhciCommandError (GhciModuleError $ GhciAmbiguousModuleName modl ms)
+
+ if unitIsDefinite (moduleUnit m)
+ then pure (fmap toUnitId m)
+ else throwGhcException (CmdLineError ("module '" ++ str ++ "' is not from a definite unit"))
where
str = moduleNameString modl
- errorMsg ms = intercalate "\n"
- [ "- " ++ unitIdString (toUnitId (moduleUnit m)) ++ ":" ++ moduleNameString (moduleName m)
- | m <- ms
- ]
showModule :: Module -> String
showModule = moduleNameString . moduleName
=====================================
ghc/GHCi/UI/Exception.hs
=====================================
@@ -5,7 +5,10 @@
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE LambdaCase #-}
module GHCi.UI.Exception
- ( GhciMessage(..)
+ ( GhciCommandError(..)
+ , throwGhciCommandError
+ , handleGhciCommandError
+ , GhciMessage(..)
, GhciMessageOpts(..)
, fromGhcOpts
, toGhcHint
@@ -29,19 +32,57 @@ import GHC.Tc.Errors.Ppr
import GHC.Tc.Errors.Types
import GHC.Types.Error.Codes
+import GHC.Types.SrcLoc (interactiveSrcSpan)
import GHC.TypeLits
import GHC.Unit.State
import GHC.Utils.Outputable
+import GHC.Utils.Error
import GHC.Generics
import GHC.Types.Error
import GHC.Types
import qualified GHC
+import Control.Exception
+import Control.Monad.Catch as MC (MonadCatch, catch)
+import Control.Monad.IO.Class
import Data.List.NonEmpty (NonEmpty(..))
+-- | A 'GhciCommandError' are messages that caused the abortion of a GHCi command.
+newtype GhciCommandError = GhciCommandError (Messages GhciMessage)
+
+instance Exception GhciCommandError
+
+instance Show GhciCommandError where
+ -- We implement 'Show' because it's required by the 'Exception' instance, but diagnostics
+ -- shouldn't be shown via the 'Show' typeclass, but rather rendered using the ppr functions.
+ -- This also explains why there is no 'Show' instance for a 'MsgEnvelope'.
+ show (GhciCommandError msgs) =
+ renderWithContext defaultSDocContext
+ . vcat
+ . pprMsgEnvelopeBagWithLocDefault
+ . getMessages
+ $ msgs
+
+-- | Perform the given action and call the exception handler if the action
+-- throws a 'SourceError'. See 'SourceError' for more information.
+handleGhciCommandError :: (MonadCatch m) =>
+ (GhciCommandError -> m a) -- ^ exception handler
+ -> m a -- ^ action to perform
+ -> m a
+handleGhciCommandError handler act =
+ MC.catch act (\(e :: GhciCommandError) -> handler e)
+
+throwGhciCommandError :: MonadIO m => GhciCommandMessage -> m a
+throwGhciCommandError errorMessage =
+ liftIO
+ . throwIO
+ . GhciCommandError
+ . singleMessage
+ $ mkPlainErrorMsgEnvelope interactiveSrcSpan (GhciCommandMessage errorMessage)
+
-- | The Options passed to 'diagnosticMessage'
-- in the 'Diagnostic' instance of 'GhciMessage'.
data GhciMessageOpts = GhciMessageOpts
@@ -57,6 +98,16 @@ data GhciMessage where
GhciGhcMessage :: GhcMessage -> GhciMessage
GhciUnknownMessage :: UnknownDiagnosticFor GhciMessage -> GhciMessage
+-- instance Show GhciMessage where
+-- show = \case
+-- GhciCommandMessage msg -> show msg
+-- GhciGhcMessage msg -> show msg
+-- GhciUnknownMessage msg -> show msg
+
+-- instance Exception GhciMessage where
+-- fromException (SomeException e) = undefined
+-- displayException exc = showSDocUnsafe (pprDiagnostic exc)
+
-- | A 'GhciHint' may either be a hint that GHC emitted ('GhciGhcHint')
-- or one that is specific to GHCi ('GhciCommandHint').
data GhciHint where
@@ -257,6 +308,9 @@ data GhciModuleError
| GhciNoResolvedModules
| GhciNoModuleForName GHC.Name
| GhciNoMatchingModuleExport
+ | GhciNoLocalModuleName !GHC.ModuleName
+ | GhciModuleNameNotFound !GHC.ModuleName
+ | GhciAmbiguousModuleName !GHC.ModuleName ![GHC.Module]
deriving Generic
instance Diagnostic GhciModuleError where
@@ -278,6 +332,16 @@ instance Diagnostic GhciModuleError where
-> "No module for" <+> ppr name
GhciNoMatchingModuleExport
-> "No matching export in any local modules."
+ GhciNoLocalModuleName modl
+ -> "Module" <+> quote (ppr modl) <+> "cannot be found locally"
+ GhciModuleNameNotFound modl
+ -> "module" <+> quote (ppr modl) <+> "could not be found."
+ GhciAmbiguousModuleName modl candidates
+ -> "Module name" <+> quote (ppr modl) <+> "is ambiguous" <>
+ vcat
+ [ text "-" <+> ppr (GHC.moduleName m) <> colon <> ppr (GHC.moduleUnit m)
+ | m <- candidates
+ ]
diagnosticReason = \case
GhciModuleNotFound{} ->
@@ -294,6 +358,12 @@ instance Diagnostic GhciModuleError where
ErrorWithoutFlag
GhciNoMatchingModuleExport{} ->
ErrorWithoutFlag
+ GhciNoLocalModuleName{} ->
+ ErrorWithoutFlag
+ GhciModuleNameNotFound{} ->
+ ErrorWithoutFlag
+ GhciAmbiguousModuleName{} ->
+ ErrorWithoutFlag
diagnosticHints = \case
GhciModuleNotFound{} ->
@@ -310,7 +380,12 @@ instance Diagnostic GhciModuleError where
[]
GhciNoMatchingModuleExport{} ->
[]
-
+ GhciNoLocalModuleName{} ->
+ []
+ GhciModuleNameNotFound{} ->
+ []
+ GhciAmbiguousModuleName{} ->
+ []
diagnosticCode = constructorCode @GHCi
-- | A Diagnostic emitted by GHCi while executing a command
@@ -487,6 +562,9 @@ type family GhciDiagnosticCode c = n | n -> c where
GhciDiagnosticCode "GhciNoModuleForName" = 21847
GhciDiagnosticCode "GhciNoMatchingModuleExport" = 59723
GhciDiagnosticCode "GhciArgumentParseError" = 35671
+ GhciDiagnosticCode "GhciNoLocalModuleName" = 81235
+ GhciDiagnosticCode "GhciModuleNameNotFound" = 40475
+ GhciDiagnosticCode "GhciAmbiguousModuleName" = 59019
type GhciConRecursInto :: Symbol -> Maybe Type
type family GhciConRecursInto con where
=====================================
ghc/GHCi/UI/Print.hs
=====================================
@@ -5,6 +5,7 @@ module GHCi.UI.Print
, printForUserPartWay
, printError
, printGhciException
+ , printGhciCommandException
) where
import qualified GHC
@@ -64,7 +65,7 @@ printForUserPartWay doc = do
-- | pretty-print a 'GhciCommandMessage'
printError :: GhcMonad m => GhciCommandMessage -> m ()
printError err =
- let errEnvelope = mkPlainErrorMsgEnvelope (UnhelpfulSpan UnhelpfulInteractive) err
+ let errEnvelope = mkPlainErrorMsgEnvelope interactiveSrcSpan err
in printError' (const NoDiagnosticOpts) (singleMessage errEnvelope)
-- | Print the all diagnostics in a 'SourceError'. Specialised for GHCi error reporting
@@ -72,6 +73,9 @@ printError err =
printGhciException :: GhcMonad m => SourceError -> m ()
printGhciException err = printError' initGhciPrintConfig (GhciGhcMessage <$> (srcErrorMessages err))
+printGhciCommandException :: GhcMonad m => GhciCommandError -> m ()
+printGhciCommandException (GhciCommandError errs) = printError' initGhciPrintConfig errs
+
printError' :: (GhcMonad m, Diagnostic a) => (DynFlags -> DiagnosticOpts a) -> Messages a -> m ()
printError' get_config err = do
dflags <- getDynFlags
=====================================
testsuite/tests/ghc-e/should_fail/T18441fail5.stderr
=====================================
@@ -1,4 +1,4 @@
-<no location info>: error: [GHC-82272]
- module ‘Abcde’ cannot be found locally
+<interactive>: error: [GHCi-81235]
+ Module 'Abcde cannot be found locally
1
=====================================
testsuite/tests/ghci/prog021/A.hs
=====================================
@@ -0,0 +1,5 @@
+module A (f) where
+
+f x = [x]
+
+g x = Just x
=====================================
testsuite/tests/ghci/prog021/B.hs
=====================================
@@ -0,0 +1,5 @@
+module B where
+
+import A
+
+h = f
=====================================
testsuite/tests/ghci/prog021/Makefile
=====================================
@@ -0,0 +1,3 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
=====================================
testsuite/tests/ghci/prog021/prog021.T
=====================================
@@ -0,0 +1,6 @@
+test('prog021',
+ [req_interp,
+ cmd_prefix('ghciWayFlags=' + config.ghci_way_flags),
+ extra_files(['A.hs', 'B.hs', 'prog021.script'])
+ ],
+ ghci_script, ['prog021.script'])
=====================================
testsuite/tests/ghci/prog021/prog021.script
=====================================
@@ -0,0 +1,15 @@
+-- Loads all targets
+:load A B
+:m + A B
+f 5
+g 5
+h 5
+-- Load only one target
+:reload A
+:m A
+putStrLn "B is not loaded, we can't add it to the context"
+:m + B
+f 5
+putStrLn "`g` and `h` are not in scope"
+g 5
+h 5
=====================================
testsuite/tests/ghci/prog021/prog021.stderr
=====================================
@@ -0,0 +1,10 @@
+<no location info>: error: [GHC-35235]
+ Could not find module ‘B’.
+ It is not a module in the current program, or in any known package.
+
+<interactive>:14:1: error: [GHC-88464]
+ Variable not in scope: g :: t0 -> t
+
+<interactive>:15:1: error: [GHC-88464]
+ Variable not in scope: h :: t0 -> t
+
=====================================
testsuite/tests/ghci/prog021/prog021.stdout
=====================================
@@ -0,0 +1,6 @@
+[5]
+Just 5
+[5]
+B is not loaded, we can't add it to the context
+[5]
+`g` and `h` are not in scope
=====================================
testsuite/tests/ghci/scripts/ghci021.stderr
=====================================
@@ -1,3 +1,3 @@
-<no location info>: error: [GHC-82272]
- module ‘ThisDoesNotExist’ cannot be found locally
+<interactive>: error: [GHCi-81235]
+ Module 'ThisDoesNotExist cannot be found locally
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/01e62ede136b6b24dc8fd47d5d3615b…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/01e62ede136b6b24dc8fd47d5d3615b…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/romes/step-out-5] Apply 1 suggestion(s) to 1 file(s)
by Rodrigo Mesquita (@alt-romes) 23 Jun '25
by Rodrigo Mesquita (@alt-romes) 23 Jun '25
23 Jun '25
Rodrigo Mesquita pushed to branch wip/romes/step-out-5 at Glasgow Haskell Compiler / GHC
Commits:
81bee76d by Rodrigo Mesquita at 2025-06-23T13:28:49+00:00
Apply 1 suggestion(s) to 1 file(s)
Co-authored-by: Ben Gamari <ben(a)well-typed.com>
- - - - -
1 changed file:
- compiler/GHC/Runtime/Eval/Types.hs
Changes:
=====================================
compiler/GHC/Runtime/Eval/Types.hs
=====================================
@@ -105,7 +105,7 @@ from which step-out was initiated. A trivial example is a case expression:
f x = case <brk>g x of ...
-If we're stopped in <brk>, the continuation will be case alternatives rather
+If we're stopped in <brk>, the continuation will be in the case alternatives rather
than in the function which called `f`. This is especially relevant for monadic
do-blocks which may end up being compiled to long chains of case expressions,
such as IO, and we don't want to stop at every line in the block while stepping out!
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/81bee76dde05a2c3e99371dc1a15053…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/81bee76dde05a2c3e99371dc1a15053…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T18570] 25 commits: Hadrian: Add option to generate .hie files for stage1 libraries
by Sjoerd Visscher (@trac-sjoerd_visscher) 23 Jun '25
by Sjoerd Visscher (@trac-sjoerd_visscher) 23 Jun '25
23 Jun '25
Sjoerd Visscher pushed to branch wip/T18570 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
- - - - -
58405fa9 by Sjoerd Visscher at 2025-06-23T14:27:36+02:00
Calculate multiplicity for record selector functions
Until now record selector functions always had multiplicity Many, but when all the other fields have been declared with multiplicity Many (including the case when there are no other fields), then the selector function is allowed to be used linearly too, as it is allowed to discard all the other fields. Since in that case the multiplicity can be both One and Many, the selector function is made multiplicity-polymorphic.
- - - - -
430288ea by Sjoerd Visscher at 2025-06-23T14:28:41+02:00
test
- - - - -
287 changed files:
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/CmmToAsm/LA64.hs
- compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- compiler/GHC/CmmToAsm/LA64/Instr.hs
- compiler/GHC/CmmToAsm/LA64/Ppr.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/DataCon.hs-boot
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/PatSyn.hs
- compiler/GHC/Core/TyCo/Ppr.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Driver/Flags.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/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/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/Splice.hs
- compiler/GHC/Tc/Gen/Splice.hs-boot
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/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/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/ghc.cabal.in
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/bugs.rst
- docs/users_guide/exts/gadt_syntax.rst
- docs/users_guide/exts/linear_types.rst
- docs/users_guide/exts/required_type_arguments.rst
- docs/users_guide/using-warnings.rst
- docs/users_guide/using.rst
- ghc/ghc-bin.cabal.in
- hadrian/doc/flavours.md
- hadrian/doc/user-settings.md
- hadrian/hadrian.cabal
- hadrian/src/Context.hs
- hadrian/src/Context/Path.hs
- hadrian/src/Flavour.hs
- hadrian/src/Flavour/Type.hs
- hadrian/src/Settings/Builders/Ghc.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Flavours/Release.hs
- hadrian/src/Settings/Warnings.hs
- libffi-tarballs
- libraries/base/changelog.md
- libraries/base/tests/IO/withBinaryFile002.stderr
- libraries/base/tests/IO/withFile002.stderr
- libraries/base/tests/IO/withFileBlocking002.stderr
- libraries/containers
- libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-heap/ghc-heap.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs-boot
- libraries/ghc-internal/src/GHC/Internal/IO.hs-boot
- libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs-boot
- libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal
- libraries/ghci/ghci.cabal.in
- libraries/haskeline
- libraries/hpc
- linters/lint-whitespace/lint-whitespace.cabal
- m4/fp_gcc_supports_no_pie.m4
- m4/fptools_set_c_ld_flags.m4
- rts/include/stg/MachRegs.h
- 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/ghci/scripts/T12550.stdout
- testsuite/tests/ghci/scripts/T8959b.stderr
- testsuite/tests/ghci/scripts/all.T
- + testsuite/tests/ghci/scripts/print-unicode-syntax.script
- + testsuite/tests/ghci/scripts/print-unicode-syntax.stderr
- + testsuite/tests/ghci/scripts/print-unicode-syntax.stdout
- testsuite/tests/ghci/should_run/T11825.stdout
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- + testsuite/tests/hiefile/should_run/HieGadtConSigs.hs
- + testsuite/tests/hiefile/should_run/HieGadtConSigs.stdout
- testsuite/tests/hiefile/should_run/all.T
- testsuite/tests/hpc/fork/hpc_fork.stdout
- testsuite/tests/hpc/function/tough.stdout
- testsuite/tests/hpc/function2/tough2.stdout
- testsuite/tests/hpc/simple/hpc001.stdout
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- + testsuite/tests/linear/should_compile/LinearRecordSelector.hs
- testsuite/tests/linear/should_compile/all.T
- + testsuite/tests/linear/should_fail/LinearRecordSelectorFail.hs
- + testsuite/tests/linear/should_fail/LinearRecordSelectorFail.stderr
- testsuite/tests/linear/should_fail/LinearTHFail.stderr
- testsuite/tests/linear/should_fail/all.T
- testsuite/tests/linters/notes.stdout
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/partial-sigs/should_fail/T10999.stderr
- testsuite/tests/perf/compiler/hard_hole_fits.stderr
- testsuite/tests/printer/T18791.stderr
- testsuite/tests/quasiquotation/T3953.stderr
- testsuite/tests/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/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/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/ce06db6666461a9d9dfa6a7da5a603…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ce06db6666461a9d9dfa6a7da5a603…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T25282] Deleted 1 commit: cabal.project-reinstall: allow newer ghc-paths:Cabal
by Teo Camarasu (@teo) 23 Jun '25
by Teo Camarasu (@teo) 23 Jun '25
23 Jun '25
Teo Camarasu pushed to branch wip/T25282 at Glasgow Haskell Compiler / GHC
WARNING: The push did not contain any new commits, but force pushed to delete the commits and changes below.
Deleted commits:
a584acd3 by Teo Camarasu at 2025-06-23T12:35:52+01:00
cabal.project-reinstall: allow newer ghc-paths:Cabal
This upper bound will be wrong whenever we are using a development version of Cabal in-tree, so let's just add an allow-newer here
- - - - -
1 changed file:
- cabal.project-reinstall
Changes:
=====================================
cabal.project-reinstall
=====================================
@@ -68,6 +68,9 @@ constraints: ghc +internal-interpreter +dynamic-system-linke,
any.pretty installed,
any.template-haskell installed
+allow-newer:
+ ghc-paths:Cabal
+
benchmarks: False
tests: False
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a584acd3a46940cf19421670913ee0f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a584acd3a46940cf19421670913ee0f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T25282] 4 commits: Visible forall in GADTs (#25127)
by Teo Camarasu (@teo) 23 Jun '25
by Teo Camarasu (@teo) 23 Jun '25
23 Jun '25
Teo Camarasu pushed to branch wip/T25282 at Glasgow Haskell Compiler / GHC
Commits:
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
- - - - -
aab8f59a by Teo Camarasu at 2025-06-23T12:35:52+01: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
- - - - -
a584acd3 by Teo Camarasu at 2025-06-23T12:35:52+01:00
cabal.project-reinstall: allow newer ghc-paths:Cabal
This upper bound will be wrong whenever we are using a development version of Cabal in-tree, so let's just add an allow-newer here
- - - - -
86 changed files:
- cabal.project-reinstall
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/DataCon.hs-boot
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/PatSyn.hs
- compiler/GHC/Core/TyCo/Ppr.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/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/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.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/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/Var.hs-boot
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/Language/Haskell/Syntax/Pat.hs
- compiler/Setup.hs
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/exts/gadt_syntax.rst
- docs/users_guide/exts/required_type_arguments.rst
- hadrian/src/Rules/Generate.hs
- libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
- linters/lint-whitespace/lint-whitespace.cabal
- testsuite/tests/dependent/should_fail/T16326_Fail6.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/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/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/T20868.stdout
- testsuite/tests/th/all.T
- 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/TyAppPat_TooMany.stderr
- + testsuite/tests/vdq-rta/should_compile/T25127_data.hs
- + testsuite/tests/vdq-rta/should_compile/T25127_data_inst.hs
- + testsuite/tests/vdq-rta/should_compile/T25127_infix.hs
- + testsuite/tests/vdq-rta/should_compile/T25127_newtype.hs
- testsuite/tests/vdq-rta/should_compile/all.T
- testsuite/tests/vdq-rta/should_fail/T24159_type_syntax_th_fail.script
- + testsuite/tests/vdq-rta/should_fail/T25127_fail_arity.hs
- + testsuite/tests/vdq-rta/should_fail/T25127_fail_arity.stderr
- + testsuite/tests/vdq-rta/should_fail/T25127_fail_th_quote.hs
- + testsuite/tests/vdq-rta/should_fail/T25127_fail_th_quote.stderr
- testsuite/tests/vdq-rta/should_fail/all.T
- utils/check-exact/ExactPrint.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/GhcUtils.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ae14bd72dcbada01363dcf847dacd1…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ae14bd72dcbada01363dcf847dacd1…
You're receiving this email because of your account on gitlab.haskell.org.
1
0