
[Git][ghc/ghc][wip/supersven/riscv-vectors] 135 commits: Refine `noGivenNewtypeReprEqs` to account for quantified constraints
by Sven Tennie (@supersven) 21 Jun '25
by Sven Tennie (@supersven) 21 Jun '25
21 Jun '25
Sven Tennie pushed to branch wip/supersven/riscv-vectors at Glasgow Haskell Compiler / GHC
Commits:
7b2d1e6d by Simon Peyton Jones at 2025-05-11T03:24:47-04:00
Refine `noGivenNewtypeReprEqs` to account for quantified constraints
This little MR fixes #26020. We are on the edge of completeness
for newtype equalities (that doesn't change) but this MR makes GHC
a bit more consistent -- and fixes the bug reported.
- - - - -
eaa8093b by Cheng Shao at 2025-05-11T03:25:28-04:00
wasm: mark freeJSVal as INLINE
This patch marks `freeJSVal` as `INLINE` for the wasm backend. I
noticed that the `freeJSVal` invocations are not inlined when
inspecting STG/Cmm dumps of downstream libraries that use release
build of the wasm backend. The performance benefit of inlining here is
very modest, but so is the cost anyway; if you are using `freeJSVal`
at all then you care about every potential chance to improve
performance :)
- - - - -
eac196df by Cheng Shao at 2025-05-11T03:25:28-04:00
wasm: add zero length fast path for fromJSString
This patch adds a zero length fast path for `fromJSString`; when
marshaling a zero-length `JSString` we don't need to allocate an empty
`ByteArray#` at all.
- - - - -
652cba7e by Peng Fan at 2025-05-14T04:24:35-04:00
Add LoongArch NCG support
Not supported before.
- - - - -
c01f4374 by Lin Runze at 2025-05-14T04:24:35-04:00
ci: Add LoongArch64 cross-compile CI for testing
- - - - -
ce6cf240 by Ben Gamari at 2025-05-14T04:25:18-04:00
rts/linker: Don't fail due to RTLD_NOW
In !12264 we started using the NativeObj machinery introduced some time
ago for loading of shared objects. One of the side-effects of this
change is shared objects are now loaded eagerly (i.e. with `RTLD_NOW`).
This is needed by NativeObj to ensure full visibility of the mappings of
the loaded object, which is in turn needed for safe shared object
unloading.
Unfortunately, this change subtly regressed, causing compilation
failures in some programs. Specifically, shared objects which refer to
undefined symbols (e.g. which may be usually provided by either the
executable image or libraries loaded via `dlopen`) will fail to load
with eager binding. This is problematic as GHC loads all package
dependencies while, e.g., evaluating TemplateHaskell splices. This
results in compilation failures in programs depending upon (but not
using at compile-time) packages with undefined symbol references.
To mitigate this NativeObj now first attempts to load an object via
eager binding, reverting to lazy binding (and disabling unloading) on
failure.
See Note [Don't fail due to RTLD_NOW].
Fixes #25943.
- - - - -
88ee8bb5 by Sylvain Henry at 2025-05-14T04:26:15-04:00
Deprecate GHC.JS.Prim.Internal.Build (#23432)
Deprecated as per CLC proposal 329 (https://github.com/haskell/core-libraries-committee/issues/329)
- - - - -
b4ed465b by Cheng Shao at 2025-05-14T04:26:57-04:00
libffi: update to 3.4.8
Bumps libffi submodule.
- - - - -
a3e71296 by Matthew Pickering at 2025-05-14T04:27:38-04:00
Remove leftover trace
- - - - -
2d0ecdc6 by Cheng Shao at 2025-05-14T04:28:19-04:00
Revert "ci: re-enable chrome for wasm ghci browser tests"
This reverts commit fee9b351fa5a35d5778d1252789eacaaf5663ae8.
Unfortunately the chrome test jobs may still timeout on certain
runners (e.g. OpenCape) for unknown reasons.
- - - - -
3b3a5dec by Ben Gamari at 2025-05-15T16:10:01-04:00
Don't emit unprintable characters when printing Uniques
When faced with an unprintable tag we now instead print the codepoint
number.
Fixes #25989.
(cherry picked from commit e832b1fadee66e8d6dd7b019368974756f8f8c46)
- - - - -
e1ef8974 by Mike Pilgrem at 2025-05-16T16:09:14-04:00
Translate iff in Haddock documentation into everyday English
- - - - -
fd64667d by Vladislav Zavialov at 2025-05-20T03:25:08-04:00
Allow the 'data' keyword in import/export lists (#25899)
This patch introduces the 'data' namespace specifier in import and
export lists. The intended use is to import data constructors without
their parent type constructors, e.g.
import Data.Proxy as D (data Proxy)
type DP = D.Proxy -- promoted data constructor
Additionally, it is possible to use 'data' to explicitly qualify any
data constructors or terms, incl. operators and field selectors
import Prelude (Semigroup(data (<>)))
import Data.Function (data (&))
import Data.Monoid (data Dual, data getDual)
x = Dual "Hello" <> Dual "World" & getDual
The implementation mostly builds on top of the existing logic for the
'type' and 'pattern' namespace specifiers, plus there are a few tweaks
to how we generate suggestions in error messages.
- - - - -
acc86753 by Ben Gamari at 2025-05-20T03:25:51-04:00
compiler: Use field selectors when creating BCOs
This makes it easier to grep for these fields.
- - - - -
60a55fd7 by Ben Gamari at 2025-05-20T03:25:51-04:00
compiler: Clarify BCO size
Previously the semantics and size of StgBCO was a bit unclear.
Specifically, the `size` field was documented to contain the size of the
bitmap whereas it was actually the size of the closure *and* bitmap.
Additionally, it was not as clear as it could be that the bitmap was a
full StgLargeBitmap with its own `size` field.
- - - - -
ac9fb269 by Simon Peyton Jones at 2025-05-20T09:19:04-04:00
Track rewriter sets more accurately in constraint solving
This MR addresses #26003, by refactoring the arcane
intricacies of Note [Equalities with incompatible kinds].
NB: now retitled to
Note [Equalities with heterogeneous kinds].
and the main Note for this MR.
In particular:
* Abandon invariant (COERCION-HOLE) in Note [Unification preconditions] in
GHC.Tc.Utils.Unify.
* Abandon invariant (TyEq:CH)) in Note [Canonical equalities] in
GHC.Tc.Types.Constraint.
* Instead: add invariant (REWRITERS) to Note [Unification preconditions]:
unify only if the constraint has an empty rewriter set.
Implementation:
* In canEqCanLHSFinish_try_unification, skip trying unification if there is a
non-empty rewriter set.
* To do this, make sure the rewriter set is zonked; do so in selectNextWorkItem,
which also deals with prioritisation.
* When a coercion hole is filled, kick out inert equalities that have that hole
as a rewriter. It might now be unlocked and available to unify.
* Remove the ad-hoc `ch_hetero_kind` field of `CoercionHole`.
* In `selectNextWorkItem`, priorities equalities withan empty rewriter set.
* Defaulting: see (DE6) in Note [Defaulting equalities]
and Note [Limited defaulting in the ambiguity check]
* Concreteness checks: there is some extra faff to try to get decent
error messages when the FRR (representation-polymorphism) checks
fail. In partiular, add a "When unifying..." explanation when the
representation-polymorphism check arose from another constraint.
- - - - -
86406f48 by Cheng Shao at 2025-05-20T09:19:47-04:00
rts: fix rts_clearMemory logic when sanity checks are enabled
This commit fixes an RTS assertion failure when invoking
rts_clearMemory with +RTS -DS. -DS implies -DZ which asserts that free
blocks contain 0xaa as the designated garbage value. Also adds the
sanity way to rts_clearMemory test to prevent future regression.
Closes #26011.
ChatGPT Codex automatically diagnosed the issue and proposed the
initial patch in a single shot, given a GHC checkout and the following
prompt:
---
Someone is reporting the following error when attempting to use `rts_clearMemory` with the RTS option `-DS`:
```
test.wasm: internal error: ASSERTION FAILED: file rts/sm/Storage.c, line 1216
(GHC version 9.12.2.20250327 for wasm32_unknown_wasi)
Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug
```
What's the culprit? How do I look into this issue?
---
I manually reviewed & revised the patch, tested and submitted it.
- - - - -
7147370b by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: do not allocate strings in bytecode assembler
This patch refactors the compiler to avoid allocating iserv buffers
for BCONPtrStr at assemble-time. Now BCONPtrStr ByteStrings are
recorded as a part of CompiledByteCode, and actual allocation only
happens at link-time. This refactoring is necessary for adding
bytecode serialization functionality, as explained by the revised
comments in this commit.
- - - - -
a67db612 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: make bc_strs serializable
This commit makes the bc_strs field in CompiledByteCode serializable;
similar to previous commit, we preserve the ByteString directly and
defer the actual allocation to link-time, as mentioned in updated
comment.
- - - - -
5faf34ef by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: make bc_itbls serializable
This commit makes bc_itbls in CompiledByteCode serializable. A
dedicated ConInfoTable datatype has been added in ghci which is the
recipe for dynamically making a datacon's info table, containing the
payload of the MkConInfoTable iserv message.
- - - - -
2abaf8c1 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: remove FFIInfo bookkeeping in BCO
This commit removes the bc_ffis field from CompiledByteCode
completely, as well as all the related bookkeeping logic in
GHC.StgToByteCode. bc_ffis is actually *unused* in the rest of GHC
codebase! It is merely a list of FFIInfo, which is just a remote
pointer of the libffi ffi_cif struct; once we allocate the ffi_cif
struct and put its pointer in a CCALL instruction, we'll never free it
anyway. So there is no point of bookkeeping.
- - - - -
adb9e4d2 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: make FFIInfo serializable in BCO
This commit makes all the FFIInfo needed in CCALL instructions
serializable. Previously, when doing STG to BCO lowering, we would
allocate a libffi ffi_cif struct and keep its remote pointer as
FFIInfo; but actually we can just keep the type signature as FFIInfo
and defer the actual allocation to link-time.
- - - - -
200f401b by Cheng Shao at 2025-05-20T17:22:19-04:00
ghci: remove redundant NewBreakModule message
This commit removes the redundant NewBreakModule message from ghci: it
just allocates two strings! This functionality can be implemented with
existing MallocStrings in one iserv call.
- - - - -
ddaadca6 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: make breakpoint module name and unit id serializable
This commit makes breakpoint module name and unit id serializable, in
BRK_FUN instructions as well as ModBreaks. We can simply keep the
module name and unit ids, and defer the buffer allocation to link
time.
- - - - -
a0fde202 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: remove unused newModule
This commit removes the now unused newModule function from GHC.
- - - - -
68c8f140 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: add BCONPtrFS for interned top level string literals in BCO
This commit adds BCONPtrFS as a BCO non-pointer literal kind, which
has the same semantics of BCONPtrStr, except it contains a FastString
instead of a ByteString. By using BCONPtrFS to represent top level
string literals that are already FastString in the compilation
pipeline, we enjoy the FastString interning logic and avoid allocating
a bunch of redundant ByteStrings for the same FastStrings, especially
when we lower the BRK_FUN instruction.
- - - - -
f2b532bc by Peng Fan at 2025-05-20T17:23:15-04:00
hadrian: enable GHCi for loongarch64
- - - - -
8ded2330 by kwxm at 2025-05-20T17:24:07-04:00
Fix bugs in `integerRecipMod` and `integerPowMod`
This fixes #26017.
* `integerRecipMod x 1` now returns `(# 1 | #)` for all x; previously it
incorrectly returned `(# | () #)`, indicating failure.
* `integerPowMod 0 e m` now returns `(# | () #)` for e<0 and m>1, indicating
failure; previously it incorrectly returned `(# 0 | #)`.
- - - - -
c9abb87c by Andreas Klebinger at 2025-05-20T17:24:50-04:00
Specialise: Don't float out constraint components.
It was fairly complex to do so and it doesn't seem to improve anything.
Nofib allocations were unaffected as well.
See also Historical Note [Floating dictionaries out of cases]
- - - - -
202b201c by Andreas Klebinger at 2025-05-21T10:16:14-04:00
Interpreter: Add limited support for direct primop evaluation.
This commit adds support for a number of primops directly
to the interpreter. This avoids the indirection of going
through the primop wrapper for those primops speeding interpretation
of optimized code up massively.
Code involving IntSet runs about 25% faster with optimized core and these
changes. For core without breakpoints it's even more pronouced and I
saw reductions in runtime by up to 50%.
Running GHC itself in the interpreter was sped up by ~15% through this
change.
Additionally this comment does a few other related changes:
testsuite:
* Run foundation test in ghci and ghci-opt ways to test these
primops.
* Vastly expand the foundation test to cover all basic primops
by comparing result with the result of calling the wrapper.
Interpreter:
* When pushing arguments for interpreted primops extend each argument to
at least word with when pushing. This avoids some issues with big
endian. We can revisit this if it causes performance issues.
* Restructure the stack chunk check logic. There are now macros for
read accesses which might cross stack chunk boundries and macros which
omit the checks which are used when we statically know we access an
address in the current stack chunk.
- - - - -
67a177b4 by sheaf at 2025-05-21T10:17:04-04:00
QuickLook: do a shape test before unifying
This commit ensures we do a shape test before unifying. This ensures
we don't try to unify a TyVarTv with a non-tyvar, e.g.
alpha[tyv] := Int
On the way, we refactor simpleUnifyCheck:
1. Move the checkTopShape check into simpleUnifyCheck
2. Refactors simpleUnifyCheck to return a value of the new type
SimpleUnifyResult type. Now, simpleUnifyCheck returns "can unify",
"cannot unify" or "dunno" (with "cannot unify" being the new result
it can return). Now:
- touchabilityTest is included; it it fails we return "cannot unify"
- checkTopShape now returns "cannot unify" instead of "dunno" upon failure
3. Move the call to simpleUnifyCheck out of checkTouchableTyVarEq.
After that, checkTouchableTyVarEq becames a simple call to
checkTyEqRhs, so we inline it.
This allows the logic in canEqCanLHSFinish_try_unification to be simplified.
In particular, we now avoid calling 'checkTopShape' twice.
Two further changes suggested by Simon were also implemented:
- In canEqCanLHSFinish, if checkTyEqRhs returns PuFail with
'do_not_prevent_rewriting', we now **continue with this constraint**.
This allows us to use the constraint for rewriting.
- checkTyEqRhs now has a top-level check to avoid flattening a tyfam app
in a top-level equality of the form alpha ~ F tys, as this is
going around in circles. This simplifies the implementation without
any change in behaviour.
Fixes #25950
Fixes #26030
- - - - -
4020972c by sheaf at 2025-05-21T10:17:04-04:00
FixedRuntimeRepError: omit unhelpful explanation
This commit tweaks the FixedRuntimeRepError case of pprTcSolverReportMsg,
to avoid including an explanation which refers to a type variable that
appears nowhere else.
For example, the old error message could look like the following:
The pattern binding does not have a fixed runtime representation.
Its type is:
T :: TYPE R
Cannot unify ‘R’ with the type variable ‘c0’
because the former is not a concrete ‘RuntimeRep’.
With this commit, we now omit the last two lines, because the concrete
type variable (here 'c0') does not appear in the type displayed to the
user (here 'T :: TYPE R').
- - - - -
6d058a69 by Andrea Bedini at 2025-05-21T16:00:51-04:00
Don't fail when ghcversion.h can't be found (#26018)
If ghcversion.h can't be found, don't try to include it. This happens
when there is no rts package in the package db and when -ghcversion-file
argument isn't passed.
Co-authored-by: Syvlain Henry <sylvain(a)haskus.fr>
- - - - -
b1212fbf by Vladislav Zavialov at 2025-05-21T16:01:33-04:00
Implement -Wpattern-namespace-specifier (#25900)
In accordance with GHC Proposal #581 "Namespace-specified imports",
section 2.3 "Deprecate use of pattern in import/export lists", the
`pattern` namespace specifier is now deprecated.
Test cases: T25900 T25900_noext
- - - - -
e650ec3e by Ben Gamari at 2025-05-23T03:42:46-04:00
base: Forward port changelog language from 9.12
- - - - -
94cd9ca4 by Ben Gamari at 2025-05-23T03:42:46-04:00
base: Fix RestructuredText-isms in changelog
- - - - -
7722232c by Ben Gamari at 2025-05-23T03:42:46-04:00
base: Note strictness changes made in 4.16.0.0
Addresses #25886.
- - - - -
3f4b823c by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker: Factor out ProddableBlocks machinery
- - - - -
6e23fef2 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker: Improve efficiency of proddable blocks structure
Previously the linker's "proddable blocks" check relied on a simple
linked list of spans. This resulted in extremely poor complexity while
linking objects with lots of small sections (e.g. objects built with
split sections).
Rework the mechanism to instead use a simple interval set implemented
via binary search.
Fixes #26009.
- - - - -
ea74860c by Ben Gamari at 2025-05-23T03:43:28-04:00
testsuite: Add simple functional test for ProddableBlockSet
- - - - -
74c4db46 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Drop check for LOAD_LIBRARY_SEARCH_*_DIRS
The `LOAD_LIBRARY_SEARCH_USER_DIRS` and
`LOAD_LIBRARY_SEARCH_DEFAULT_DIRS` were introduced in Windows Vista and
have been available every since. As we no longer support Windows XP we
can drop this check.
Addresses #26009.
- - - - -
972d81d6 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Clean up code style
- - - - -
8a1073a5 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/Hash: Factor out hashBuffer
This is a useful helper which can be used for non-strings as well.
- - - - -
44f509f2 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Fix incorrect use of break in nested for
Previously the happy path of PEi386 used `break` in a double-`for` loop
resulting in redundant calls to `LoadLibraryEx`.
Fixes #26052.
- - - - -
bfb12783 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts: Correctly mark const arguments
- - - - -
08469ff8 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Don't repeatedly load DLLs
Previously every DLL-imported symbol would result in a call to
`LoadLibraryEx`. This ended up constituting over 40% of the runtime of
`ghc --interactive -e 42` on Windows. Avoid this by maintaining a
hash-set of loaded DLL names, skipping the call if we have already
loaded the requested DLL.
Addresses #26009.
- - - - -
823d1ccf by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker: Expand comment describing ProddableBlockSet
- - - - -
e9de9e0b by Sylvain Henry at 2025-05-23T15:12:34-04:00
Remove emptyModBreaks
Remove emptyModBreaks and track the absence of ModBreaks with `Maybe
ModBreaks`. It avoids testing for null pointers...
- - - - -
17db44c5 by Ben Gamari at 2025-05-23T15:13:16-04:00
base: Expose Backtraces constructor and fields
This was specified in the proposal (CLC #199) yet somehow didn't make it
into the implementation.
Fixes #26049.
- - - - -
b08c08ae by soulomoon at 2025-05-28T01:57:23+08:00
Refactor handling of imported COMPLETE pragmas
from the HPT
Previously, we imported COMPLETE pragmas from all modules in the Home
Package Table (HPT) during type checking. However, since !13675, there
may be non-below modules in the HPT from the dependency tree that we do
not want to import COMPLETE pragmas from. This refactor changes the way
we handle COMPLETE pragmas from the HPT to only import them from modules
that are "below" the current module in the HPT.
- Add hugCompleteSigsBelow to filter COMPLETE pragmas from "below"
modules in the HPT, mirroring hugRulesBelow.
- Move responsibility for calling hugCompleteSigsBelow to tcRnImports,
storing the result in the new tcg_complete_match_env field of TcGblEnv.
- Update getCompleteMatchesTcM to use tcg_complete_match_env.
This refactor only affects how COMPLETE pragmas are imported from the
HPT, imports from external packages are unchanged.
- - - - -
16014bf8 by Hécate Kleidukos at 2025-05-28T20:09:34-04:00
Expose all of Backtraces' internals for ghc-internal
Closes #26049
- - - - -
a0adc30d by Ryan Hendrickson at 2025-05-30T14:12:52-04:00
haddock: Fix links to type operators
- - - - -
7b64697c by Mario Blažević at 2025-05-30T14:13:41-04:00
Introduce parenBreakableList and use it in ppHsContext
- - - - -
5f213bff by fendor at 2025-06-02T09:16:24+02:00
Make GHCi commands compatible with multiple home units
=== Design
We enable all GHCi features that were previously guarded by the `inMulti`
option.
GHCi supported multiple home units up to a certain degree for quite a while now.
The supported feature set was limited, due to a design impasse:
One of the home units must be "active", e.g., there must be one `HomeUnit`
whose `UnitId` is "active" which is returned when calling
```haskell
do
hscActiveUnitId <$> getSession
```
This makes sense in a GHC session, since you are always compiling a particular
Module, but it makes less intuitive sense in an interactive session.
Given an expression to evaluate, we can't easily tell in which "context" the expression
should be parsed, typechecked and evaluated.
That's why initially, most of GHCi features, except for `:reload`ing were disabled
if the GHCi session had more than one `HomeUnitEnv`.
We lift this restriction, enabling all features of GHCi for the multiple home unit case.
To do this, we fundamentally change the `HomeUnitEnv` graph to be multiple home unit first.
Instead of differentiating the case were we have a single home unit and multiple,
we now always set up a multiple home unit session that scales seamlessly to an arbitrary
amount of home units.
We introduce two new `HomeUnitEnv`s that are always added to the `HomeUnitGraph`.
They are:
The "interactive-ghci", called the `interactiveGhciUnit`, contains the same
`DynFlags` that are used by the `InteractiveContext` for interactive evaluation
of expressions.
This `HomeUnitEnv` is only used on the prompt of GHCi, so we may refer to it as
"interactive-prompt" unit.
See Note [Relation between the `InteractiveContext` and `interactiveGhciUnitId`]
for discussing its role.
And the "interactive-session"", called `interactiveSessionUnit` or
`interactiveSessionUnitId`, which is used for loading Scripts into
GHCi that are not `Target`s of any home unit, via `:load` or `:add`.
Both of these "interactive" home units depend on all other `HomeUnitEnv`s that
are passed as arguments on the cli.
Additionally, the "interactive-ghci" unit depends on `interactive-session`.
We always evaluate expressions in the context of the
"interactive-ghci" session.
Since "interactive-ghci" depends on all home units, we can import any `Module`
from the other home units with ease.
As we have a clear `HomeUnitGraph` hierarchy, we can set `interactiveGhciUnitId`
as the active home unit for the full duration of the GHCi session.
In GHCi, we always set `interactiveGhciUnitId` to be the currently active home unit.
=== Implementation Details
Given this design idea, the implementation is relatively straight
forward.
The core insight is that a `ModuleName` is not sufficient to identify a
`Module` in the `HomeUnitGraph`. Thus, large parts of the PR is simply
about refactoring usages of `ModuleName` to prefer `Module`, which has a
`Unit` attached and is unique over the `HomeUnitGraph`.
Consequentially, most usages of `lookupHPT` are likely to be incorrect and have
been replaced by `lookupHugByModule` which is keyed by a `Module`.
In `GHCi/UI.hs`, we make sure there is only one location where we are
actually translating `ModuleName` to a `Module`:
* `lookupQualifiedModuleName`
If a `ModuleName` is ambiguous, we detect this and report it to the
user.
To avoid repeated lookups of `ModuleName`s, we store the `Module` in the
`InteractiveImport`, which additionally simplifies the interface
loading.
A subtle detail is that the `DynFlags` of the `InteractiveContext` are
now stored both in the `HomeUnitGraph` and in the `InteractiveContext`.
In UI.hs, there are multiple code paths where we are careful to update
the `DynFlags` in both locations.
Most importantly in `addToProgramDynFlags`.
---
There is one metric increase in this commit:
-------------------------
Metric Increase:
T4029
-------------------------
It is an increase from 14.4 MB to 16.1 MB (+11.8%) which sounds like a
pretty big regression at first.
However, we argue this increase is solely caused by using more data
structures for managing multiple home units in the GHCi session.
In particular, due to the design decision of using three home units, the
base memory usage increases... but by how much?
A big contributor is the `UnitState`, of which we have three now, which
on its own 260 KB per instance. That makes an additional memory usage of
520 KB, already explaining a third of the overall memory usage increase.
Then we store more elements in the `HomeUnitGraph`, we have more
`HomeUnitEnv` entries, etc...
While we didn't chase down each byte, we looked at the memory usage over time
for both `-hi` and `-hT` profiles and can say with confidence while the memory
usage increased slightly, we did not introduce any space leak, as
the graph looks almost identical as the memory usage graph of GHC HEAD.
---
Adds testcases for GHCi multiple home units session
* Test truly multiple home unit sessions, testing reload logic and code evaluation.
* Test that GHCi commands such as `:all-types`, `:browse`, etc., work
* Object code reloading for home modules
* GHCi debugger multiple home units session
- - - - -
de603d01 by fendor at 2025-06-02T09:16:24+02:00
Update "loading compiled code" GHCi documentation
To use object code in GHCi, the module needs to be compiled for use in
GHCi. To do that, users need to compile their modules with:
* `-dynamic`
* `-this-unit-id interactive-session`
Otherwise, the interface files will not match.
- - - - -
b255a8ca by Vladislav Zavialov at 2025-06-02T16:00:12-04:00
docs: Fix code example for NoListTuplePuns
Without the fix, the example produces an error:
Test.hs:11:3: error: [GHC-45219]
• Data constructor ‘Tuple’ returns type ‘Tuple2 a b’
instead of an instance of its parent type ‘Tuple a’
• In the definition of data constructor ‘Tuple’
In the data type declaration for ‘Tuple’
Fortunately, a one line change makes it compile.
- - - - -
6558467c by Ryan Hendrickson at 2025-06-06T05:46:58-04:00
haddock: Parse math even after ordinary characters
Fixes a bug where math sections were not recognized if preceded by a
character that isn't special (like space or a markup character).
- - - - -
265d0024 by ARATA Mizuki at 2025-06-06T05:47:48-04:00
AArch64 NCG: Fix sub-word arithmetic right shift
As noted in Note [Signed arithmetic on AArch64], we should zero-extend sub-word values.
Fixes #26061
- - - - -
05e9be18 by Simon Hengel at 2025-06-06T05:48:35-04:00
Allow Unicode in "message" and "hints" with -fdiagnostics-as-json
(fixes #26075)
- - - - -
bfa6b70f by ARATA Mizuki at 2025-06-06T05:49:24-04:00
x86 NCG: Fix code generation of bswap64 on i386
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
Fix #25601
- - - - -
dff648ab by Sven Tennie at 2025-06-07T13:51:41+00:00
WIP: Trying to get simd000 test green
- - - - -
fa3ed3e6 by Sven Tennie at 2025-06-07T13:51:41+00:00
WIP: simd000 - hacked further
- - - - -
86b8d508 by Sven Tennie at 2025-06-07T13:51:41+00:00
WIP
- - - - -
4366a7f4 by Sven Tennie at 2025-06-07T13:51:41+00:00
simd000 green
- - - - -
f925b30e by Sven Tennie at 2025-06-07T13:51:41+00:00
simd001 green
- - - - -
5968f528 by Sven Tennie at 2025-06-07T13:51:41+00:00
simd003 green
- - - - -
708181ff by Sven Tennie at 2025-06-07T13:51:41+00:00
simd006 green
- - - - -
6b1813cb by Sven Tennie at 2025-06-07T13:51:41+00:00
simd007 green
- - - - -
0c7a4457 by Sven Tennie at 2025-06-07T13:51:41+00:00
simd008 && simd009 green
- - - - -
62becc31 by Sven Tennie at 2025-06-07T13:51:42+00:00
Fix int expr cases
- - - - -
60b67392 by Sven Tennie at 2025-06-07T13:51:42+00:00
Vector FMA
- - - - -
800cd71a by Sven Tennie at 2025-06-07T13:51:42+00:00
Add TAB char operator
- - - - -
7401dd54 by Sven Tennie at 2025-06-07T13:51:42+00:00
Fix vector ccalls
- - - - -
f43de17b by Sven Tennie at 2025-06-07T13:51:42+00:00
Define YMM* and ZMM*
- - - - -
64f4ed4f by Sven Tennie at 2025-06-07T13:51:42+00:00
Add TODO
- - - - -
c11056df by Sven Tennie at 2025-06-07T14:00:00+00:00
Define registers for TrivColorable
- - - - -
fd32abfc by Sven Tennie at 2025-06-07T14:00:01+00:00
Add TODOs
- - - - -
8b46cd45 by Sven Tennie at 2025-06-07T14:00:01+00:00
Configure vector register width
- - - - -
1dbefc43 by Sven Tennie at 2025-06-07T14:00:01+00:00
Configure vector register width
- - - - -
10b2c9ae by Sven Tennie at 2025-06-07T14:00:01+00:00
Add documentation
- - - - -
66a4297d by Sven Tennie at 2025-06-07T14:00:01+00:00
Cleanup CodeGen
- - - - -
1e17c10f by Sven Tennie at 2025-06-07T14:00:01+00:00
Add TODOs
- - - - -
4a96b524 by Sven Tennie at 2025-06-07T14:00:01+00:00
Add comment about freeReg for [X,Y,Z]MM
- - - - -
3f0f5ddd by Sven Tennie at 2025-06-07T14:00:01+00:00
Define MAX_REAL_YMM_REG and MAX_REAL_ZMM_REG
- - - - -
8a32dbe8 by Sven Tennie at 2025-06-07T14:00:01+00:00
VID needs only one register; fix MO_V_Broadcast; refactor MO_V_Insert
and MO_V_Insert
- - - - -
d1e19179 by Sven Tennie at 2025-06-07T14:00:01+00:00
Add comment about vector registers in allocatableRegs
- - - - -
204b634c by Sven Tennie at 2025-06-07T14:00:01+00:00
Formatting
- - - - -
04932252 by Sven Tennie at 2025-06-07T14:00:01+00:00
Adjust TODO
- - - - -
2d8a8a44 by Sven Tennie at 2025-06-07T14:00:01+00:00
Delete unused function
- - - - -
d527e82b by Sven Tennie at 2025-06-07T14:00:01+00:00
WIP: Use Format instead of Width in OpReg Operand
Ints, floats and vectors are very different things. So, it is very
helpful to know to which of this three an OpReg Operand relates.
- - - - -
2f49fb41 by Sven Tennie at 2025-06-07T14:00:01+00:00
Simplify VID
- - - - -
6e571fca by Sven Tennie at 2025-06-07T14:00:01+00:00
Simplify VMV
- - - - -
9c2c3e80 by Sven Tennie at 2025-06-07T14:00:01+00:00
Simplify VMERGE
- - - - -
3c46a337 by Sven Tennie at 2025-06-07T14:00:01+00:00
Simplify VSLIDEDOWN
- - - - -
fd49fa2c by Sven Tennie at 2025-06-07T14:00:01+00:00
Simplify other vector instructions
- - - - -
518faf95 by Sven Tennie at 2025-06-07T14:00:01+00:00
Simplify VFMA
- - - - -
f2eb27de by Sven Tennie at 2025-06-07T14:00:01+00:00
regUsageOfInstr with correct format
- - - - -
b1227f1e by Sven Tennie at 2025-06-07T14:00:01+00:00
Assert vector register width
- - - - -
21debd6e by Sven Tennie at 2025-06-07T14:00:01+00:00
Combine float lit cases
- - - - -
788d8c48 by Sven Tennie at 2025-06-07T14:00:01+00:00
Tighten Vector Ppr constraints
- - - - -
6149b205 by Sven Tennie at 2025-06-07T14:00:01+00:00
Compile vector helper files with vector support
- - - - -
74910b29 by Sven Tennie at 2025-06-07T14:00:01+00:00
-mriscv-vlen makes more sense to RISC-V people
VLEN is a well defined term.
- - - - -
3c5e8098 by Sven Tennie at 2025-06-07T14:00:01+00:00
Simplify expressions
- - - - -
a072d43c by Sven Tennie at 2025-06-07T14:00:01+00:00
Fix MO_V_Extract and MO_VF_Extract
- - - - -
4988b9cd by Sven Tennie at 2025-06-07T14:00:01+00:00
Assert register format in more places
Also, fix it.
- - - - -
08b244bc by Sven Tennie at 2025-06-07T14:00:01+00:00
mkSpillInstr: Refactor assertion
- - - - -
8a468ec0 by Sven Tennie at 2025-06-07T14:00:01+00:00
Better algorithm to inject vector config
- - - - -
ffed6e82 by Sven Tennie at 2025-06-07T14:00:01+00:00
cpuinfo.py: Provide RISC-V features
- - - - -
04c6da4a by Sven Tennie at 2025-06-07T14:00:01+00:00
Add TODOs
- - - - -
25b37522 by Sven Tennie at 2025-06-07T14:00:01+00:00
Set and check vector support in Haskell entry code
We have to check this on the executing CPU (target) with access to
DynFlags.
- - - - -
5547801c by Sven Tennie at 2025-06-07T14:00:01+00:00
Allow cpu_features for CROSS_EMULATR to be set
- - - - -
3da5afff by Sven Tennie at 2025-06-07T14:00:01+00:00
Configure simd tests for RISC-V
- - - - -
cbc36ec6 by Sven Tennie at 2025-06-07T14:00:01+00:00
simd013 test for RISC-V
- - - - -
53331bc0 by Sven Tennie at 2025-06-07T14:00:01+00:00
Cleanup warnings
- - - - -
10bc537d by Sven Tennie at 2025-06-07T14:00:01+00:00
WIP: cpuinfo Zvl* extensions
- - - - -
9a207a9b by Sven Tennie at 2025-06-07T14:00:01+00:00
Delete obsolete TODO
- - - - -
78f27768 by Sven Tennie at 2025-06-07T14:00:01+00:00
Document assertVectorRegWidth
- - - - -
53caf2fc by Sven Tennie at 2025-06-07T14:00:02+00:00
Cleanup assignReg
- - - - -
8541498f by Sven Tennie at 2025-06-07T14:00:02+00:00
Cleanup assignMem
- - - - -
c3d2b9af by Sven Tennie at 2025-06-07T14:00:02+00:00
Add TODO
- - - - -
1a9eb7cf by Sven Tennie at 2025-06-07T14:00:02+00:00
Align code with similar occurences
- - - - -
44c21ec8 by Sven Tennie at 2025-06-07T14:00:02+00:00
Broadcast with VMV.V.I
- - - - -
281248de by Sven Tennie at 2025-06-07T14:00:02+00:00
Implement MO_VS_Neg
- - - - -
e7ce596f by Sven Tennie at 2025-06-07T14:00:02+00:00
Cleanup old TODO
- - - - -
1a98b495 by Sven Tennie at 2025-06-07T14:00:02+00:00
Cleanup
- - - - -
35df7cd7 by Sven Tennie at 2025-06-07T14:00:02+00:00
Implement more MachOps
- - - - -
7c859dfc by Sven Tennie at 2025-06-07T14:00:02+00:00
Implement VREM
- - - - -
8161157a by Sven Tennie at 2025-06-07T14:00:02+00:00
Implement MO_VS_Quot and MO_VU_Quot
- - - - -
de45c6f2 by Sven Tennie at 2025-06-07T14:00:02+00:00
Implement MO_X64 and MO_W64 CallishOps
- - - - -
c80dad33 by Sven Tennie at 2025-06-07T14:00:02+00:00
Vector shuffle
- - - - -
e91c5127 by Sven Tennie at 2025-06-07T14:00:02+00:00
Fix
- - - - -
68eda11a by Sven Tennie at 2025-06-07T14:00:02+00:00
Implement MO_VF_Shuffle
- - - - -
3dcd5491 by Sven Tennie at 2025-06-07T14:00:02+00:00
WIP: Vector CCallConv
- - - - -
981c3688 by Sven Tennie at 2025-06-08T14:36:10+00:00
VectorCCallConv_c.c: Add function prototype to suppress warning
- - - - -
c8497fb6 by Sven Tennie at 2025-06-21T14:20:12+00:00
WIP: Vector CCallConv - vectors on heap
- - - - -
470 changed files:
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- + Makefile
- + Makefile.save
- + Notes.md
- + cabal.project
- compiler/CodeGen.Platform.h
- compiler/GHC.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/CmmToAsm.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/Config.hs
- compiler/GHC/CmmToAsm/Dwarf/Constants.hs
- compiler/GHC/CmmToAsm/Format.hs
- + compiler/GHC/CmmToAsm/LA64.hs
- + compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- + compiler/GHC/CmmToAsm/LA64/Cond.hs
- + compiler/GHC/CmmToAsm/LA64/Instr.hs
- + compiler/GHC/CmmToAsm/LA64/Ppr.hs
- + compiler/GHC/CmmToAsm/LA64/RegInfo.hs
- + compiler/GHC/CmmToAsm/LA64/Regs.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/RV64.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToAsm/RV64/Regs.hs
- compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs
- + compiler/GHC/CmmToAsm/Reg/Linear/LA64.hs
- compiler/GHC/CmmToAsm/Reg/Linear/RV64.hs
- compiler/GHC/CmmToAsm/Reg/Target.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCo/Tidy.hs
- compiler/GHC/Driver/Backend.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Config/StgToCmm.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Linker/ExtraObj.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Platform/LoongArch64.hs → compiler/GHC/Platform/LA64.hs
- compiler/GHC/Platform/Reg/Class.hs
- compiler/GHC/Platform/Regs.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Unbound.hs
- compiler/GHC/Runtime/Context.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm/Config.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/SysTools/Cpp.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/Export.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Plugin.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Zonk/TcType.hs
- compiler/GHC/Types/Error.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Hint/Ppr.hs
- compiler/GHC/Types/Name/Ppr.hs
- compiler/GHC/Types/Unique.hs
- compiler/GHC/Unit/Env.hs
- compiler/GHC/Unit/Home/Graph.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Unit/Types.hs
- compiler/GHC/Utils/Outputable.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- compiler/ghc.cabal.in
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/exts/data_kinds.rst
- docs/users_guide/exts/explicit_namespaces.rst
- docs/users_guide/exts/pattern_synonyms.rst
- docs/users_guide/ghci.rst
- docs/users_guide/using-warnings.rst
- docs/users_guide/using.rst
- + ghc.diff
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Info.hs
- ghc/GHCi/UI/Monad.hs
- ghc/Main.hs
- + git.diff
- hadrian/bindist/config.mk.in
- hadrian/src/Flavour.hs
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Settings/Builders/RunTest.hs
- hadrian/src/Settings/Packages.hs
- + hls.json
- libraries/Cabal
- libraries/Win32
- libraries/array
- libraries/base/changelog.md
- libraries/base/src/Control/Exception/Backtrace.hs
- libraries/base/src/GHC/JS/Prim/Internal/Build.hs
- libraries/directory
- + libraries/ghc-bignum/gmp/gmp-tarballs
- libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs
- libraries/ghc-internal/src/GHC/Internal/Data/Maybe.hs
- libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Type/Reflection.hs
- libraries/ghc-internal/src/GHC/Internal/TypeLits.hs
- libraries/ghc-internal/src/GHC/Internal/TypeNats.hs
- libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- libraries/haskeline
- libraries/process
- libraries/unix
- nofib
- rts/CheckVectorSupport.c
- rts/Disassembler.c
- rts/Hash.c
- rts/Hash.h
- rts/Interpreter.c
- rts/Linker.c
- rts/LinkerInternals.h
- rts/PathUtils.c
- rts/PathUtils.h
- rts/PrimOps.cmm
- rts/RtsStartup.c
- rts/RtsSymbols.c
- rts/include/rts/Bytecodes.h
- rts/include/rts/storage/Closures.h
- rts/include/stg/MachRegs.h
- rts/include/stg/MachRegs/riscv64.h
- rts/linker/Elf.c
- rts/linker/LoadNativeObjPosix.c
- rts/linker/MachO.c
- rts/linker/PEi386.c
- rts/linker/PEi386.h
- + rts/linker/ProddableBlocks.c
- + rts/linker/ProddableBlocks.h
- rts/rts.cabal
- rts/sm/Storage.h
- testsuite/driver/cpu_features.py
- testsuite/driver/cpuinfo.py
- testsuite/driver/testglobals.py
- testsuite/driver/testlib.py
- testsuite/tests/bytecode/T22376/all.T
- testsuite/tests/callarity/unittest/CallArity1.hs
- + 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/dependent/should_fail/T11471.stderr
- testsuite/tests/diagnostic-codes/codes.stdout
- testsuite/tests/driver/Makefile
- testsuite/tests/driver/T8526/T8526.stdout
- testsuite/tests/driver/all.T
- testsuite/tests/driver/fat-iface/fat014.stdout
- testsuite/tests/driver/json.stderr
- testsuite/tests/driver/json_warn.stderr
- testsuite/tests/driver/multipleHomeUnits/multiGHCi.stderr
- testsuite/tests/ffi/should_run/all.T
- testsuite/tests/ghc-api/T6145.hs
- testsuite/tests/ghc-api/annotations-literals/literals.hs
- testsuite/tests/ghc-api/annotations-literals/parsed.hs
- testsuite/tests/ghc-api/apirecomp001/myghc.hs
- testsuite/tests/ghc-api/fixed-nodes/T1.hs
- + testsuite/tests/ghci.debugger/scripts/break031/Makefile
- + testsuite/tests/ghci.debugger/scripts/break031/a/A.hs
- + testsuite/tests/ghci.debugger/scripts/break031/all.T
- + testsuite/tests/ghci.debugger/scripts/break031/b/B.hs
- + testsuite/tests/ghci.debugger/scripts/break031/break031a.script
- + testsuite/tests/ghci.debugger/scripts/break031/break031a.stdout
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.script
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.stderr
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.stdout
- + testsuite/tests/ghci.debugger/scripts/break031/unitA
- + testsuite/tests/ghci.debugger/scripts/break031/unitB
- + testsuite/tests/ghci/all.T
- + testsuite/tests/ghci/ghci-mem-primops.hs
- + testsuite/tests/ghci/ghci-mem-primops.script
- + testsuite/tests/ghci/ghci-mem-primops.stdout
- testsuite/tests/ghci/linking/dyn/T3372.hs
- + testsuite/tests/ghci/prog-mhu001/Makefile
- + testsuite/tests/ghci/prog-mhu001/all.T
- + testsuite/tests/ghci/prog-mhu001/e/E.hs
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001a.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001a.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001b.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001b.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001c.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001c.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001d.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001d.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001e.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001e.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001f.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001f.stdout
- + testsuite/tests/ghci/prog-mhu001/unitE
- + testsuite/tests/ghci/prog-mhu001/unitE-main-is
- + testsuite/tests/ghci/prog-mhu002/Makefile
- + testsuite/tests/ghci/prog-mhu002/a/A.hs
- + testsuite/tests/ghci/prog-mhu002/all.T
- + testsuite/tests/ghci/prog-mhu002/b/B.hs
- + testsuite/tests/ghci/prog-mhu002/c/C.hs
- + testsuite/tests/ghci/prog-mhu002/d/Main.hs
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.stderr
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.stderr
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002c.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002c.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002d.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002d.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002e.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002e.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002f.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002f.stdout
- + testsuite/tests/ghci/prog-mhu002/unitA
- + testsuite/tests/ghci/prog-mhu002/unitB
- + testsuite/tests/ghci/prog-mhu002/unitC
- + testsuite/tests/ghci/prog-mhu002/unitD
- + testsuite/tests/ghci/prog-mhu003/Makefile
- + testsuite/tests/ghci/prog-mhu003/a/A.hs
- + testsuite/tests/ghci/prog-mhu003/all.T
- + testsuite/tests/ghci/prog-mhu003/b/Foo.hs
- + testsuite/tests/ghci/prog-mhu003/c/C.hs
- + testsuite/tests/ghci/prog-mhu003/d/Foo.hs
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.script
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.stderr
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.stdout
- + testsuite/tests/ghci/prog-mhu003/unitA
- + testsuite/tests/ghci/prog-mhu003/unitB
- + testsuite/tests/ghci/prog-mhu003/unitC
- + testsuite/tests/ghci/prog-mhu003/unitD
- + testsuite/tests/ghci/prog-mhu004/Makefile
- + testsuite/tests/ghci/prog-mhu004/a/Foo.hs
- + testsuite/tests/ghci/prog-mhu004/all.T
- + testsuite/tests/ghci/prog-mhu004/b/Foo.hs
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.script
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stderr
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stdout
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004b.script
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004b.stdout
- + testsuite/tests/ghci/prog-mhu004/unitA
- + testsuite/tests/ghci/prog-mhu004/unitB
- testsuite/tests/ghci/prog010/ghci.prog010.script
- testsuite/tests/ghci/prog018/prog018.stdout
- + testsuite/tests/ghci/prog020/A.hs
- + testsuite/tests/ghci/prog020/B.hs
- + testsuite/tests/ghci/prog020/Makefile
- + testsuite/tests/ghci/prog020/all.T
- + testsuite/tests/ghci/prog020/ghci.prog020.script
- + testsuite/tests/ghci/prog020/ghci.prog020.stderr
- + testsuite/tests/ghci/prog020/ghci.prog020.stdout
- testsuite/tests/ghci/scripts/T13869.stdout
- testsuite/tests/ghci/scripts/T13997.stdout
- testsuite/tests/ghci/scripts/T17669.stdout
- testsuite/tests/ghci/scripts/T18330.stdout
- testsuite/tests/ghci/scripts/T1914.stdout
- testsuite/tests/ghci/scripts/T20217.stdout
- testsuite/tests/ghci/scripts/T20587.stdout
- testsuite/tests/ghci/scripts/T21110.stderr
- testsuite/tests/ghci/scripts/T6105.stdout
- testsuite/tests/ghci/scripts/T8042.stdout
- testsuite/tests/ghci/scripts/T8042recomp.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
- testsuite/tests/ghci/scripts/ghci058.script
- testsuite/tests/ghci/should_run/TopEnvIface.stdout
- testsuite/tests/indexed-types/should_fail/T8227.stderr
- testsuite/tests/indexed-types/should_fail/T9662.stderr
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- + testsuite/tests/lib/integer/T26017.hs
- + testsuite/tests/lib/integer/T26017.stdout
- testsuite/tests/lib/integer/all.T
- testsuite/tests/lib/integer/integerRecipMod.hs
- testsuite/tests/lib/integer/integerRecipMod.stdout
- testsuite/tests/module/T21826.stderr
- testsuite/tests/numeric/should_run/all.T
- testsuite/tests/numeric/should_run/foundation.hs
- testsuite/tests/numeric/should_run/foundation.stdout
- + testsuite/tests/parser/should_compile/T25900.hs
- + testsuite/tests/parser/should_compile/T25900.stderr
- + testsuite/tests/parser/should_compile/T25900_noext.hs
- + testsuite/tests/parser/should_compile/T25900_noext.stderr
- testsuite/tests/parser/should_compile/all.T
- testsuite/tests/partial-sigs/should_fail/T14040a.stderr
- testsuite/tests/partial-sigs/should_fail/T14584.stderr
- testsuite/tests/patsyn/should_compile/ImpExp_Exp.hs
- testsuite/tests/patsyn/should_compile/T11959.hs
- testsuite/tests/patsyn/should_compile/T11959.stderr
- testsuite/tests/patsyn/should_compile/T11959Lib.hs
- testsuite/tests/patsyn/should_compile/T13350/boolean/Boolean.hs
- testsuite/tests/patsyn/should_compile/T22521.hs
- testsuite/tests/patsyn/should_compile/T9857.hs
- testsuite/tests/patsyn/should_compile/export.hs
- testsuite/tests/perf/should_run/ByteCodeAsm.hs
- testsuite/tests/pmcheck/complete_sigs/T25115a.hs
- testsuite/tests/pmcheck/should_compile/T11822.hs
- testsuite/tests/polykinds/T14172.stderr
- testsuite/tests/polykinds/T14270.hs
- testsuite/tests/polykinds/T14846.stderr
- testsuite/tests/quasiquotation/T7918.hs
- testsuite/tests/rename/should_compile/T12548.hs
- testsuite/tests/rename/should_compile/T22581d.stdout
- + testsuite/tests/rename/should_compile/T25899a.hs
- + testsuite/tests/rename/should_compile/T25899b.hs
- + testsuite/tests/rename/should_compile/T25899c.hs
- + testsuite/tests/rename/should_compile/T25899c_helper.hs
- + testsuite/tests/rename/should_compile/T25899d.script
- + testsuite/tests/rename/should_compile/T25899d.stdout
- testsuite/tests/rename/should_compile/all.T
- testsuite/tests/rename/should_fail/T22581a.stderr
- testsuite/tests/rename/should_fail/T22581b.stderr
- testsuite/tests/rename/should_fail/T25056.stderr
- testsuite/tests/rename/should_fail/T25056a.hs
- + testsuite/tests/rename/should_fail/T25899e1.hs
- + testsuite/tests/rename/should_fail/T25899e1.stderr
- + testsuite/tests/rename/should_fail/T25899e2.hs
- + testsuite/tests/rename/should_fail/T25899e2.stderr
- + testsuite/tests/rename/should_fail/T25899e3.hs
- + testsuite/tests/rename/should_fail/T25899e3.stderr
- + testsuite/tests/rename/should_fail/T25899e_helper.hs
- + testsuite/tests/rename/should_fail/T25899f.hs
- + testsuite/tests/rename/should_fail/T25899f.stderr
- + testsuite/tests/rename/should_fail/T25899f_helper.hs
- testsuite/tests/rename/should_fail/all.T
- testsuite/tests/rep-poly/RepPolyArgument.stderr
- testsuite/tests/rep-poly/RepPolyBackpack1.stderr
- testsuite/tests/rep-poly/RepPolyBinder.stderr
- testsuite/tests/rep-poly/RepPolyDoBind.stderr
- testsuite/tests/rep-poly/RepPolyDoBody1.stderr
- testsuite/tests/rep-poly/RepPolyDoBody2.stderr
- testsuite/tests/rep-poly/RepPolyLeftSection2.stderr
- testsuite/tests/rep-poly/RepPolyMagic.stderr
- testsuite/tests/rep-poly/RepPolyMcBind.stderr
- testsuite/tests/rep-poly/RepPolyMcBody.stderr
- testsuite/tests/rep-poly/RepPolyMcGuard.stderr
- testsuite/tests/rep-poly/RepPolyNPlusK.stderr
- testsuite/tests/rep-poly/RepPolyPatBind.stderr
- testsuite/tests/rep-poly/RepPolyRecordUpdate.stderr
- testsuite/tests/rep-poly/RepPolyRightSection.stderr
- testsuite/tests/rep-poly/RepPolyRule1.stderr
- testsuite/tests/rep-poly/RepPolyTuple.stderr
- testsuite/tests/rep-poly/RepPolyTuple4.stderr
- testsuite/tests/rep-poly/RepPolyTupleSection.stderr
- testsuite/tests/rep-poly/RepPolyWrappedVar.stderr
- testsuite/tests/rep-poly/T11473.stderr
- testsuite/tests/rep-poly/T12709.stderr
- testsuite/tests/rep-poly/T12973.stderr
- testsuite/tests/rep-poly/T13233.stderr
- testsuite/tests/rep-poly/T13929.stderr
- testsuite/tests/rep-poly/T14561.stderr
- testsuite/tests/rep-poly/T14561b.stderr
- testsuite/tests/rep-poly/T17817.stderr
- testsuite/tests/rep-poly/T19615.stderr
- testsuite/tests/rep-poly/T19709b.stderr
- testsuite/tests/rep-poly/T21906.stderr
- testsuite/tests/rep-poly/T23903.stderr
- testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr
- + testsuite/tests/rts/TestProddableBlockSet.c
- testsuite/tests/rts/all.T
- + testsuite/tests/simd/should_run/VectorCCallConv.hs
- + testsuite/tests/simd/should_run/VectorCCallConv_c.c
- testsuite/tests/simd/should_run/all.T
- testsuite/tests/simd/should_run/simd013C.c
- testsuite/tests/simplCore/should_compile/T15186.hs
- testsuite/tests/simplCore/should_compile/T15186A.hs
- testsuite/tests/simplCore/should_compile/simpl017.stderr
- testsuite/tests/typecheck/no_skolem_info/T14040.stderr
- testsuite/tests/typecheck/should_compile/T25266a.stderr
- + testsuite/tests/typecheck/should_compile/T26020.hs
- + testsuite/tests/typecheck/should_compile/T26020a.hs
- + testsuite/tests/typecheck/should_compile/T26020a_help.hs
- + testsuite/tests/typecheck/should_compile/T26030.hs
- testsuite/tests/typecheck/should_compile/TypeRepCon.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/T16204c.stderr
- + testsuite/tests/typecheck/should_fail/T25950.hs
- + testsuite/tests/typecheck/should_fail/T25950.stderr
- testsuite/tests/typecheck/should_fail/T7696.stderr
- testsuite/tests/typecheck/should_fail/T8603.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/warnings/should_compile/DataToTagWarnings.hs
- testsuite/tests/warnings/should_compile/T14794a.hs
- testsuite/tests/warnings/should_compile/T14794a.stderr
- testsuite/tests/warnings/should_compile/T14794b.hs
- testsuite/tests/warnings/should_compile/T14794b.stderr
- testsuite/tests/warnings/should_compile/T14794c.hs
- testsuite/tests/warnings/should_compile/T14794c.stderr
- testsuite/tests/warnings/should_compile/T14794d.hs
- testsuite/tests/warnings/should_compile/T14794d.stderr
- testsuite/tests/warnings/should_compile/T14794e.hs
- testsuite/tests/warnings/should_compile/T14794e.stderr
- testsuite/tests/warnings/should_compile/T14794f.hs
- testsuite/tests/warnings/should_compile/T14794f.stderr
- testsuite/tests/wcompat-warnings/Template.hs
- + testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr
- + tmp/main.S
- utils/check-exact/ExactPrint.hs
- utils/genprimopcode/Main.hs
- utils/genprimopcode/Syntax.hs
- utils/ghc-toolchain/exe/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
- utils/haddock/haddock-api/resources/html/Linuwial.std-theme/linuwial.css
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Utils.hs
- utils/haddock/haddock-api/src/Haddock/Interface/LexParseRn.hs
- utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs
- utils/haddock/haddock-library/test/Documentation/Haddock/ParserSpec.hs
- utils/haddock/html-test/ref/Bug1004.html
- utils/haddock/html-test/ref/Bug548.html
- utils/haddock/html-test/ref/Bug973.html
- utils/haddock/html-test/ref/Hash.html
- utils/haddock/html-test/ref/ImplicitParams.html
- utils/haddock/html-test/ref/Instances.html
- utils/haddock/html-test/ref/PatternSyns.html
- utils/haddock/html-test/ref/TypeOperators.html
- utils/haddock/html-test/src/TypeOperators.hs
- utils/hsc2hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1f65b1e93c981afc56cd4a7cb3f7cb…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1f65b1e93c981afc56cd4a7cb3f7cb…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/int-index/visible-forall-gadts] Visible forall in GADTs (#25127)
by Vladislav Zavialov (@int-index) 21 Jun '25
by Vladislav Zavialov (@int-index) 21 Jun '25
21 Jun '25
Vladislav Zavialov pushed to branch wip/int-index/visible-forall-gadts at Glasgow Haskell Compiler / GHC
Commits:
4951a1da by Vladislav Zavialov at 2025-06-21T15:51:14+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>
- - - - -
81 changed files:
- 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/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
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/exts/gadt_syntax.rst
- docs/users_guide/exts/required_type_arguments.rst
- libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
- 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/-/commit/4951a1dae3ef176310039e724537aff…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4951a1dae3ef176310039e724537aff…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Alan Zimmerman pushed to branch wip/az/ghc-cpp at Glasgow Haskell Compiler / GHC
Commits:
9f4b5aab by Alan Zimmerman at 2025-06-21T13:20:54+01:00
Some cleanup
- - - - -
4 changed files:
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PreProcess.hs
- compiler/GHC/Parser/PreProcess/State.hs
- utils/check-cpp/PreProcess.hs
Changes:
=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -59,7 +59,6 @@ module GHC.Parser.Lexer (
Token(..), lexer, lexerDbg,
ParserOpts(..), mkParserOpts,
PState (..), initParserState, initPragState,
- PSavedAlrState(..), getAlrState, setAlrState,
startSkipping, stopSkipping,
P(..), ParseResult(POk, PFailed),
allocateComments, allocatePriorComments, allocateFinalComments,
@@ -273,7 +272,6 @@ $tab { warnTab }
-- set.
"{-" / { isNormalComment } { nested_comment }
--- "/*" / { ifExtension GhcCppBit } { cpp_comment }
-- Single-line comments are a bit tricky. Haskell 98 says that two or
-- more dashes followed by a symbol should be parsed as a varsym, so we
@@ -1351,6 +1349,7 @@ hopefully_open_brace :: Action p
hopefully_open_brace span buf len buf2
= do relaxed <- getBit RelaxedLayoutBit
ctx <- getContext
+ -- See Note [GHC_CPP saved offset]
offset <- getOffset
let
isOK = relaxed ||
@@ -1592,15 +1591,6 @@ nested_doc_comment span buf _len _buf2 = {-# SCC "nested_doc_comment" #-} withLe
dropTrailingDec "-}" = ""
dropTrailingDec (x:xs) = x:dropTrailingDec xs
-cpp_comment :: Action p
-cpp_comment span buf len _buf2 = {-# SCC "cpp_comment" #-} do
- l <- getLastLocIncludingComments
- let endComment input (L _ comment) = commentEnd lexToken input (Nothing, ITblockComment comment l) buf span
- input <- getInput
- -- Include decorator in comment
- let start_decorator = reverse $ lexemeToString buf len
- cpp_comment_logic endComment start_decorator input span
-
{-# INLINE nested_comment_logic #-}
-- | Includes the trailing '-}' decorators
-- drop the last two elements with the callback if you don't want them to be included
@@ -1635,31 +1625,6 @@ nested_comment_logic endComment commentAcc input span = go commentAcc (1::Int) i
Just (_,_) -> go ('\n':commentAcc) n input
Just (c,input) -> go (c:commentAcc) n input
-{-# INLINE cpp_comment_logic #-}
--- | Includes the trailing '*/' decorators
--- drop the last two elements with the callback if you don't want them to be included
-cpp_comment_logic
- :: (AlexInput -> Located String -> P p (PsLocated Token)) -- ^ Continuation that gets the rest of the input and the lexed comment
- -> String -- ^ starting value for accumulator (reversed) - When we want to include a decorator '/*' in the comment
- -> AlexInput
- -> PsSpan
- -> P p (PsLocated Token)
-cpp_comment_logic endComment commentAcc input span = go commentAcc (1::Int) input
- where
- go commentAcc 0 input@(AI end_loc _) = do
- let comment = reverse commentAcc
- cspan = mkSrcSpanPs $ mkPsSpan (psSpanStart span) end_loc
- lcomment = L cspan comment
- endComment input lcomment
- go commentAcc n input = case alexGetChar' input of
- Nothing -> errBrace input (psRealSpan span)
- Just ('*',input) -> case alexGetChar' input of
- Nothing -> errBrace input (psRealSpan span)
- Just ('/',input) -> go ('/':'*':commentAcc) (n-1) input -- '/'
- Just (_,_) -> go ('*':commentAcc) n input
- Just (c,input) -> go (c:commentAcc) n input
-
-
ghcCppSet :: P p Bool
ghcCppSet = do
exts <- getExts
@@ -1775,6 +1740,7 @@ linePrag span buf len buf2 = do
usePosPrags <- getBit UsePosPragsBit
if usePosPrags
then begin line_prag2 span buf len buf2
+ -- TODO:AZ: should we make this test if GhcCpp is active, and maybe do the old
-- else let !src = lexemeToFastString buf len
-- in return (L span (ITline_prag (SourceText src)))
else nested_comment span buf len buf2
@@ -2166,6 +2132,7 @@ do_bol span _str _len _buf2 = do
-- See Note [Nested comment line pragmas]
b <- getBit InNestedCommentBit
if b then return (L span ITcomment_line_prag) else do
+ -- See Note [GHC_CPP saved offset]
resetOffset
(pos, gen_semic) <- getOffside
case pos of
@@ -2216,6 +2183,7 @@ maybe_layout t = do -- If the alternative layout rule is enabled then
new_layout_context :: Bool -> Bool -> Token -> Action p
new_layout_context strict gen_semic tok span _buf len _buf2 = do
_ <- popLexState
+ -- See Note [GHC_CPP saved offset]
current_col <- getOffset
let offset = current_col - len
ctx <- getContext
@@ -2670,6 +2638,7 @@ data PState a = PState {
pp :: !a,
-- If a CPP directive occurs in the layout context, we need to
-- store the prior column so any alr processing can continue.
+ -- See Note [GHC_CPP saved offset]
pp_last_col :: !(Maybe Int)
}
-- last_loc and last_len are used when generating error messages,
@@ -2684,32 +2653,6 @@ data PState a = PState {
-- of the action, it is the *current* token. Do I understand
-- correctly?
-data PSavedAlrState = PSavedAlrState {
- -- s_warnings :: Messages PsMessage,
- -- s_errors :: Messages PsMessage,
- s_lex_state :: [Int],
- s_context :: [LayoutContext],
- s_alr_pending_implicit_tokens :: [PsLocated Token],
- s_alr_next_token :: Maybe (PsLocated Token),
- s_alr_last_loc :: PsSpan,
- s_alr_context :: [ALRContext],
- s_alr_expecting_ocurly :: Maybe ALRLayout,
- s_alr_justClosedExplicitLetBlock :: Bool,
- s_last_col :: Int
- }
-
-
--- -- | Use for emulating (limited) CPP preprocessing in GHC.
--- -- TODO: move this into PreProcess, and make a param on PState
--- data PpState = PpState {
--- pp_defines :: !(Map String [String]),
--- pp_continuation :: ![Located Token],
--- -- pp_context :: ![PpContext],
--- pp_context :: ![Token], -- What preprocessor directive we are currently processing
--- pp_accepting :: !Bool
--- }
--- deriving (Show)
-
data PpContext = PpContextIf [Located Token]
deriving (Show)
@@ -2825,7 +2768,7 @@ getLastBufCur = P $ \s@(PState { last_buf_cur = last_buf_cur }) -> POk s last_bu
getLastLen :: P p Int
getLastLen = P $ \s@(PState { last_len = last_len }) -> POk s last_len
--- see Note [TBD]
+-- See Note [GHC_CPP saved offset]
getOffset :: P p Int
getOffset = P $ \s@(PState { pp_last_col = last_col,
loc = l}) ->
@@ -2835,74 +2778,55 @@ getOffset = P $ \s@(PState { pp_last_col = last_col,
-- (fromMaybe (srcLocCol (psRealLoc l)) last_col)
in POk s { pp_last_col = Nothing} offset
+-- See Note [GHC_CPP saved offset]
resetOffset :: P p ()
resetOffset = P $ \s -> POk s { pp_last_col = Nothing} ()
+{- Note [GHC_CPP saved offset]
+ ~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+The layout processing machinery examines the offset of the previous
+line when doing its calculations.
+
+When GHC_CPP is used, a set of CPP directives may ignore some number
+of preceding lines, each of which has a different offset.
+
+We deal with this as follows
+
+- When we start skipping lines due to CPP we store the offset of the
+ line before the CPP directive
+- We explicitly ask for the offset using `getOffset` when doing layout
+ calculations
+- If there is a stored offset, we use that instead of the prior line
+ offset
+
+-}
+
startSkipping :: P p ()
startSkipping = do
pushLexState skipping
-- pushLexState (trace ("startSkipping:" ++ show skipping) skipping)
-stopSkipping :: P p Int
+stopSkipping :: P p ()
stopSkipping = do
- -- popLexState
- ret <- popLexState
+ _ <- popLexState
-- We just processed a CPP directive, which included a trailing newline.
-- To properly sync up, we now need to ensure that `do_bol` processing occurs.
- -- But this call does not emit a token.
- -- Maybe it should be an argument to lexToken instead?
- -- Alternatively, push the input location to the previous char.
- AI ps buf <- getInput
- last_buf_cur <- getLastBufCur
- last_loc <- getLastLoc
+ -- But this call does not emit a token, so we instead
+ -- change the input location to the previous char, the newline
+ AI _ps buf <- getInput
last_tk <- getLastTk
case last_tk of
Strict.Just (L l _) -> do
let ps' = PsLoc (realSrcSpanEnd (psRealSpan l)) (bufSpanEnd (psBufSpan l))
let cur' = (cur buf) - 1
- -- let cur' = trace ("stopSkipping:(cur',ps'):" ++ show (cur'',ps')) cur''
setInput (AI ps' (buf { cur = cur'}))
_ -> return ()
- -- return $ trace ("stopSkipping: (ps, cur buf, last_loc, last_buf_cur, last_tk):" ++ show (ps, cur buf, last_loc, last_buf_cur, last_tk)) ret
- return ret
-- old <- popLexState
-- return (trace ("stopSkipping:" ++ show old) old)
-getAlrState :: P p PSavedAlrState
-getAlrState = P $ \s@(PState {loc=l}) -> POk s
- PSavedAlrState {
- -- s_warnings = warnings s,
- -- s_errors = errors s,
- -- s_lex_state = lex_state s,
- s_lex_state = lex_state s,
- s_context = context s,
- s_alr_pending_implicit_tokens = alr_pending_implicit_tokens s,
- s_alr_next_token = alr_next_token s,
- s_alr_last_loc = alr_last_loc s,
- s_alr_context = alr_context s,
- s_alr_expecting_ocurly = alr_expecting_ocurly s,
- s_alr_justClosedExplicitLetBlock = alr_justClosedExplicitLetBlock s,
- s_last_col = srcLocCol (psRealLoc l)
- }
-
-setAlrState :: PSavedAlrState -> P p ()
-setAlrState ss = P $ \s -> POk s {
- -- errors = s_errors ss,
- -- warnings = s_warnings ss,
- lex_state = s_lex_state ss,
- context = s_context ss,
- alr_pending_implicit_tokens = s_alr_pending_implicit_tokens ss,
- alr_next_token = s_alr_next_token ss,
- alr_last_loc = s_alr_last_loc ss,
- alr_context = s_alr_context ss,
- alr_expecting_ocurly = s_alr_expecting_ocurly ss,
- alr_justClosedExplicitLetBlock = s_alr_justClosedExplicitLetBlock ss,
- pp_last_col = Just (s_last_col ss)
- } ()
-
-
{-# INLINE alexGetChar' #-}
-- This version does not squash unicode characters, it is used when
@@ -3199,6 +3123,7 @@ disableHaddock opts = upd_bitmap (xunset HaddockBit)
where
upd_bitmap f = opts { pExtsBitmap = f (pExtsBitmap opts) }
+-- TODO:AZ check which of these are actually needed,
enableGhcCpp :: ParserOpts -> ParserOpts
enableGhcCpp = enableExtBit GhcCppBit
@@ -3881,8 +3806,6 @@ warn_unknown_prag prags span buf len buf2 = do
%************************************************************************
-}
--- TODO:AZ: we should have only mkParensEpToks. Delete mkParensEpAnn, mkParensLocs
-
-- |Given a 'RealSrcSpan' that surrounds a 'HsPar' or 'HsParTy', generate
-- 'EpToken' values for the opening and closing bordering on the start
-- and end of the span
=====================================
compiler/GHC/Parser/PreProcess.hs
=====================================
@@ -14,8 +14,8 @@ module GHC.Parser.PreProcess (
) where
import Data.List (intercalate, sortBy)
-import Data.Maybe (fromMaybe, listToMaybe)
import Data.Map qualified as Map
+import Data.Maybe (fromMaybe, listToMaybe)
import Debug.Trace (trace)
import GHC.Data.FastString
import GHC.Data.Strict qualified as Strict
@@ -23,6 +23,7 @@ import GHC.Data.StringBuffer
import GHC.Driver.DynFlags (DynFlags, xopt)
import GHC.LanguageExtensions qualified as LangExt
import GHC.Parser.Errors.Ppr ()
+import GHC.Parser.Errors.Types (PsMessage (PsErrGhcCpp))
import GHC.Parser.Lexer (P (..), PState (..), ParseResult (..), Token (..))
import GHC.Parser.Lexer qualified as Lexer
import GHC.Parser.PreProcess.Macro
@@ -34,7 +35,6 @@ import GHC.Types.SrcLoc
import GHC.Utils.Error
import GHC.Utils.Outputable (text)
import GHC.Utils.Panic.Plain (panic)
-import GHC.Parser.Errors.Types (PsMessage(PsErrGhcCpp))
-- ---------------------------------------------------------------------
@@ -42,9 +42,10 @@ dumpGhcCpp :: DynFlags -> PState PpState -> SDoc
dumpGhcCpp dflags pst = output
where
ghc_cpp_enabled = xopt LangExt.GhcCpp dflags
- output = if ghc_cpp_enabled
- then text $ sepa ++ defines ++ sepa ++ final ++ sepa
- else text "GHC_CPP not enabled"
+ output =
+ if ghc_cpp_enabled
+ then text $ sepa ++ defines ++ sepa ++ final ++ sepa
+ else text "GHC_CPP not enabled"
-- Note: pst is the state /before/ the parser runs, so we can use it to lex.
(pst_final, bare_toks) = lexAll pst
comments = reverse (Lexer.comment_q pst_final)
@@ -76,6 +77,7 @@ renderCombinedToks toks = showCppTokenStream toks
-- ---------------------------------------------------------------------
-- addSourceToTokens copied here to unbreak an import loop.
-- It should probably move somewhere else
+-- TODO: We should be able to do away with this once #26095 is done
{- | Given a source location and a StringBuffer corresponding to this
location, return a rich token stream with the source associated to the
@@ -105,7 +107,8 @@ addSourceToTokens loc0 buf0 (t@(L sp _) : ts) =
-- ---------------------------------------------------------------------
--- Tweaked from showRichTokenStream
+-- Tweaked from showRichTokenStream, to add markers per line if it is
+-- currently active or not
showCppTokenStream :: [(Located Token, String)] -> String
showCppTokenStream ts0 = go startLoc ts0 ""
where
@@ -196,7 +199,7 @@ ppLexer queueComments cont =
ppLexer queueComments cont
in
case tk of
- -- case (trace ("M.ppLexer:tk=" ++ show (unLoc tk)) tk) of
+ -- case (trace ("M.ppLexer:tk=" ++ show (unLoc tk)) tk) of
L _ ITeof -> do
mInp <- popIncludeLoc
case mInp of
@@ -219,13 +222,11 @@ ppLexer queueComments cont =
case mdump of
Just dump ->
-- We have a dump of the state, put it into an ignored token
+ -- AZ: TODO: is this actually useful?
contIgnoreTok (L l (ITcpp continuation (appendFS s (fsLit dump)) sp))
Nothing -> contIgnoreTok tk
else contInner tk
L _ (ITcppIgnored _ _) -> contIgnoreTok tk
- L _ (ITline_prag _) -> do
- setInLinePragma True
- contIgnoreTok tk
_ -> do
state <- getCppState
inLinePragma <- getInLinePragma
@@ -253,7 +254,7 @@ processCppToks fs = do
-- Combine any prior continuation tokens
cs <- popContinuation
let loc = combineLocs fs (fromMaybe fs (listToMaybe cs))
- processCpp loc (concat $ reverse $ map get (fs:cs))
+ processCpp loc (concat $ reverse $ map get (fs : cs))
processCpp :: SrcSpan -> String -> PP (Maybe String)
processCpp loc s = do
@@ -262,13 +263,11 @@ processCpp loc s = do
then return (Just "\ndumped state\n")
else do
case directive of
- Left err -> Lexer.addError $ mkPlainErrorMsgEnvelope loc $ PsErrGhcCpp (text err)
+ Left err -> Lexer.addError $ mkPlainErrorMsgEnvelope loc $ PsErrGhcCpp (text err)
Right (CppInclude filename) -> do
ppInclude filename
- Right (CppDefine name args def) -> do
- ppDefine (MacroName name args) def
- Right (CppUndef name) -> do
- ppUndef name
+ Right (CppDefine name args def) -> ppDefine (MacroName name args) def
+ Right (CppUndef name) -> ppUndef name
Right (CppIf cond) -> do
val <- cppCond loc cond
ar <- pushAccepting val
=====================================
compiler/GHC/Parser/PreProcess/State.hs
=====================================
@@ -71,7 +71,6 @@ initPpState =
, pp_continuation = []
, pp_defines = Map.empty
, pp_scope = (PpScope True PpNoGroup) :| []
- , pp_alr_state = Nothing
, pp_in_line_pragma = False
}
@@ -81,7 +80,6 @@ data PpState = PpState
, pp_continuation :: ![Located Lexer.Token]
, pp_defines :: !MacroDefines
, pp_scope :: !(NonEmpty PpScope)
- , pp_alr_state :: Maybe Lexer.PSavedAlrState
, pp_in_line_pragma :: !Bool
}
=====================================
utils/check-cpp/PreProcess.hs
=====================================
@@ -329,15 +329,8 @@ processCpp loc s = do
acceptStateChange :: AcceptingResult -> PP ()
acceptStateChange ArNoChange = return ()
acceptStateChange ArNowIgnoring = do
- -- alr <- Lexer.getAlrState
- -- s <- getPpState
- -- let s = trace ("acceptStateChange:ArNowIgnoring") s'
- -- setPpState (s { pp_alr_state = Just alr})
Lexer.startSkipping
acceptStateChange ArNowAccepting = do
- -- s <- getPpState
- -- let s = trace ("acceptStateChange:ArNowAccepting") s'
- -- mapM_ Lexer.setAlrState (pp_alr_state s)
_ <- Lexer.stopSkipping
return ()
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f4b5aabeeeabc3134e5464f8ecb707…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f4b5aabeeeabc3134e5464f8ecb707…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Teo Camarasu pushed new branch wip/teo/th-changelog at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/teo/th-changelog
You're receiving this email because of your account on gitlab.haskell.org.
1
0

21 Jun '25
Teo Camarasu pushed new branch wip/teo/allow-newer-ghc-paths at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/teo/allow-newer-ghc-paths
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/az/ghc-cpp] 134 commits: Deprecate -Wdata-kinds-tc, make DataKinds issues in typechecker become errors
by Alan Zimmerman (@alanz) 21 Jun '25
by Alan Zimmerman (@alanz) 21 Jun '25
21 Jun '25
Alan Zimmerman pushed to branch wip/az/ghc-cpp at Glasgow Haskell Compiler / GHC
Commits:
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.
- - - - -
15b2b2ec by Alan Zimmerman at 2025-06-19T19:35:02+01:00
GHC-CPP: first rough proof of concept
Processes
#define FOO
#ifdef FOO
x = 1
#endif
Into
[ITcppIgnored [L loc ITcppDefine]
,ITcppIgnored [L loc ITcppIfdef]
,ITvarid "x"
,ITequal
,ITinteger (IL {il_text = SourceText "1", il_neg = False, il_value = 1})
,ITcppIgnored [L loc ITcppEndif]
,ITeof]
In time, ITcppIgnored will be pushed into a comment
- - - - -
8a890112 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Tidy up before re-visiting the continuation mechanic
- - - - -
b81a1ae0 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Switch preprocessor to continuation passing style
Proof of concept, needs tidying up
- - - - -
cfe778e2 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Small cleanup
- - - - -
56dde4c8 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Get rid of some cruft
- - - - -
19be2264 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Starting to integrate.
Need to get the pragma recognised and set
- - - - -
9d65fbb9 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Make cppTokens extend to end of line, and process CPP comments
- - - - -
aacef8f5 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Remove unused ITcppDefined
- - - - -
9f54aa10 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Allow spaces between # and keyword for preprocessor directive
- - - - -
841e8b19 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Process CPP continuation lines
They are emited as separate ITcppContinue tokens.
Perhaps the processing should be more like a comment, and keep on
going to the end.
BUT, the last line needs to be slurped as a whole.
- - - - -
d0a141b9 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Accumulate CPP continuations, process when ready
Can be simplified further, we only need one CPP token
- - - - -
12c0689b by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Simplify Lexer interface. Only ITcpp
We transfer directive lines through it, then parse them from scratch
in the preprocessor.
- - - - -
30cd0529 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Deal with directive on last line, with no trailing \n
- - - - -
e2d20617 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Start parsing and processing the directives
- - - - -
74955b8e by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Prepare for processing include files
- - - - -
6c2f7197 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Move PpState into PreProcess
And initParserState, initPragState too
- - - - -
b112d95c by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Process nested include files
Also move PpState out of Lexer.x, so it is easy to evolve it in a ghci
session, loading utils/check-cpp/Main.hs
- - - - -
c62fbc6d by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Split into separate files
- - - - -
5e9b65b6 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Starting on expression parser.
But it hangs. Time for Text.Parsec.Expr
- - - - -
e7233f54 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Start integrating the ghc-cpp work
From https://github.com/alanz/ghc-cpp
- - - - -
d44f73a2 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
WIP
- - - - -
3524ce86 by Alan Zimmerman at 2025-06-19T19:35:02+01:00
Fixup after rebase
- - - - -
7a0bfc0a by Alan Zimmerman at 2025-06-19T19:35:03+01:00
WIP
- - - - -
b247de57 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Fixup after rebase, including all tests pass
- - - - -
186c6054 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Change pragma usage to GHC_CPP from GhcCPP
- - - - -
b7ed58f2 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Some comments
- - - - -
0a7d82d3 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Reformat
- - - - -
0c126cd1 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Delete unused file
- - - - -
741b5935 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Rename module Parse to ParsePP
- - - - -
db9b5584 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Clarify naming in the parser
- - - - -
ed0e5a41 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
WIP. Switching to alex/happy to be able to work in-tree
Since Parsec is not available
- - - - -
e567da0c by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Layering is now correct
- GHC lexer, emits CPP tokens
- accumulated in Preprocessor state
- Lexed by CPP lexer, CPP command extracted, tokens concated with
spaces (to get rid of token pasting via comments)
- if directive lexed and parsed by CPP lexer/parser, and evaluated
- - - - -
468cda2a by Alan Zimmerman at 2025-06-19T19:35:03+01:00
First example working
Loading Example1.hs into ghci, getting the right results
```
{-# LANGUAGE GHC_CPP #-}
module Example1 where
y = 3
x =
"hello"
"bye now"
foo = putStrLn x
```
- - - - -
6bbc63fb by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Rebase, and all tests pass except whitespace for generated parser
- - - - -
a4ec35ca by Alan Zimmerman at 2025-06-19T19:35:03+01:00
More plumbing. Ready for testing tomorrow.
- - - - -
91c2d89f by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Proress. Renamed module State from Types
And at first blush it seems to handle preprocessor scopes properly.
- - - - -
0c944603 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Insert basic GHC version macros into parser
__GLASGOW_HASKELL__
__GLASGOW_HASKELL_FULL_VERSION__
__GLASGOW_HASKELL_PATCHLEVEL1__
__GLASGOW_HASKELL_PATCHLEVEL2__
- - - - -
668d141e by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Re-sync check-cpp for easy ghci work
- - - - -
4f5b0d0b by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Get rid of warnings
- - - - -
7fdc08bd by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Rework macro processing, in check-cpp
Macros kept at the top level, looked up via name, multiple arity
versions per name can be stored
- - - - -
07814b89 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
WIP. Can crack arguments for #define
Next step it to crack out args in an expansion
- - - - -
53e55437 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
WIP on arg parsing.
- - - - -
8c04ddfd by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Progress. Still screwing up nested parens.
- - - - -
8e594a84 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Seems to work, but has redundant code
- - - - -
cc21e1d4 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Remove redundant code
- - - - -
6620f57c by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Reformat
- - - - -
694c05ef by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Expand args, single pass
Still need to repeat until fixpoint
- - - - -
a043620f by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Fixed point expansion
- - - - -
750c694f by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Sync the playground to compiler
- - - - -
6c8750c2 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Working on dumping the GHC_CPP result
But We need to keep the BufSpan in a comment
- - - - -
bdb8adf2 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Keep BufSpan in queued comments in GHC.Parser.Lexer
- - - - -
3ae1d536 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Getting close to being able to print the combined tokens
showing what is in and what is out
- - - - -
accff1b5 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
First implementation of dumpGhcCpp.
Example output
First dumps all macros in the state, then the source, showing which
lines are in and which are out
------------------------------
- |#define FOO(A,B) A + B
- |#define FOO(A,B,C) A + B + C
- |#if FOO(1,FOO(3,4)) == 8
- |-- a comment
|x = 1
- |#else
- |x = 5
- |#endif
- - - - -
8b9bf22a by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Clean up a bit
- - - - -
2f6ecade by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Add -ddump-ghc-cpp option and a test based on it
- - - - -
365aa02d by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Restore Lexer.x rules, we need them for continuation lines
- - - - -
0f6dfae8 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Lexer.x: trying to sort out the span for continuations
- We need to match on \n at the end of the line
- We cannot simply back up for it
- - - - -
9f6aec58 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Inserts predefined macros. But does not dump properly
Because the cpp tokens have a trailing newline
- - - - -
829f75e2 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Remove unnecessary LExer rules
We *need* the ones that explicitly match to the end of the line.
- - - - -
501a2caf by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Generate correct span for ITcpp
Dump now works, except we do not render trailing `\` for continuation
lines. This is good enough for use in test output.
- - - - -
db23d6e9 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Reduce duplication in lexer
- - - - -
047e48f5 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Tweaks
- - - - -
37b47da0 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Insert min_version predefined macros into state
The mechanism now works. Still need to flesh out the full set.
- - - - -
1e045be7 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Trying my alternative pragma syntax.
It works, but dumpGhcCpp is broken, I suspect from the ITcpp token
span update.
- - - - -
9a61360c by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Pragma extraction now works, with both CPP and GHC_CPP
For the following
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 913
{-# LANGUAGE GHC_CPP #-}
#endif
We will enable GHC_CPP only
- - - - -
4f8555c7 by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Remove some tracing
- - - - -
8a68e6dc by Alan Zimmerman at 2025-06-19T19:35:03+01:00
Fix test exes for changes
- - - - -
12177e13 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
For GHC_CPP tests, normalise config-time-based macros
- - - - -
d442984b by Alan Zimmerman at 2025-06-19T19:35:04+01:00
WIP
- - - - -
5cbb9087 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
WIP again. What is wrong?
- - - - -
ff468973 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Revert to dynflags for normal not pragma lexing
- - - - -
00a4da95 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Working on getting check-exact to work properly
- - - - -
04c7e601 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Passes CppCommentPlacement test
- - - - -
0a08e51c by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Starting on exact printing with GHC_CPP
While overriding normal CPP
- - - - -
cebb3403 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Correctly store CPP ignored tokens as comments
By populating the lexeme string in it, based on the bufpos
- - - - -
8aa7e52c by Alan Zimmerman at 2025-06-19T19:35:04+01:00
WIP
- - - - -
373b18ab by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Simplifying
- - - - -
eb25bbc6 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Update the active state logic
- - - - -
0c7a106a by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Work the new logic into the mainline code
- - - - -
22726082 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Process `defined` operator
- - - - -
3725a850 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Manage lexer state while skipping tokens
There is very intricate layout-related state used when lexing. If a
CPP directive blanks out some tokens, store this state when the
blanking starts, and restore it when they are no longer being blanked.
- - - - -
15414093 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Track the last token buffer index, for ITCppIgnored
We need to attach the source being skipped in an ITCppIgnored token.
We cannot simply use its BufSpan as an index into the underlying
StringBuffer as it counts unicode chars, not bytes.
So we update the lexer state to store the starting StringBuffer
location for the last token, and use the already-stored length to
extract the correct portion of the StringBuffer being parsed.
- - - - -
337dbc7a by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Process the ! operator in GHC_CPP expressions
- - - - -
b79f9bea by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Predefine a constant when GHC_CPP is being used.
- - - - -
052e64b3 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
WIP
- - - - -
d996722c by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Skip lines directly in the lexer when required
- - - - -
6d5efd6f by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Properly manage location when accepting tokens again
- - - - -
6edf4195 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Seems to be working now, for Example9
- - - - -
2077e54c by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Remove tracing
- - - - -
83a4d5ab by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Fix parsing '*' in block comments
Instead of replacing them with '-'
- - - - -
097b4235 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Keep the trailing backslash in a ITcpp token
- - - - -
e0e1e90f by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Deal with only enabling one section of a group.
A group is an instance of a conditional introduced by
#if/#ifdef/#ifndef,
and ending at the final #endif, including intermediate #elsif sections
- - - - -
7151fd24 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Replace remaining identifiers with 0 when evaluating
As per the spec
- - - - -
49cfb7a3 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Snapshot before rebase
- - - - -
4cfce858 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Skip non-processed lines starting with #
- - - - -
c706f25d by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Export generateMacros so we can use it in ghc-exactprint
- - - - -
89b39f49 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Fix rebase
- - - - -
2a346936 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Expose initParserStateWithMacrosString
- - - - -
f12c44db by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Fix buggy lexer cppSkip
It was skipping all lines, not just ones prefixed by #
- - - - -
5f84c0db by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Fix evaluation of && to use the correct operator
- - - - -
2d8bedc7 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Deal with closing #-} at the start of a line
- - - - -
555b7a83 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Add the MIN_VERSION_GLASGOW_HASKELL predefined macro
- - - - -
ba80b032 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Include MIN_VERSION_GLASGOW_HASKELL in GhcCpp01.stderr
- - - - -
edf528f7 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Use a strict map for macro defines
- - - - -
c28cd1b7 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Process TIdentifierLParen
Which only matters at the start of #define
- - - - -
0516c631 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Do not provide TIdentifierLParen paren twice
- - - - -
24e4d45d by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Handle whitespace between identifier and '(' for directive only
- - - - -
4de7275c by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Expose some Lexer bitmap manipulation helpers
- - - - -
6d12ec40 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Deal with line pragmas as tokens
Blows up for dumpGhcCpp though
- - - - -
c682be7a by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Allow strings delimited by a single quote too
- - - - -
1a549ee1 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Allow leading whitespace on cpp directives
As per https://timsong-cpp.github.io/cppwp/n4140/cpp#1
- - - - -
4d2d4de1 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Implement GHC_CPP undef
- - - - -
9533c2d7 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Sort out expansion of no-arg macros, in a context with args
And make the expansion bottom out, in the case of recursion
- - - - -
dbcbb002 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Fix GhcCpp01 test
The LINE pragma stuff works in ghc-exactprint when specifically
setting flag to emit ITline_pragma tokens
- - - - -
8e460807 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Process comments in CPP directives
- - - - -
7103a6b2 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Correctly lex pragmas with finel #-} on a newline
- - - - -
830c79e0 by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Do not process CPP-style comments
- - - - -
37a486ec by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Allow cpp-style comments when GHC_CPP enabled
- - - - -
a8a1722b by Alan Zimmerman at 2025-06-19T19:35:04+01:00
Return other pragmas as cpp ignored when GHC_CPP active
- - - - -
789233df by Alan Zimmerman at 2025-06-19T19:35:05+01:00
Fix exactprinting default decl
- - - - -
b3ccee8b by Alan Zimmerman at 2025-06-19T19:35:05+01:00
Reorganise getOptionsFromFile for use in ghc-exactprint
We want to be able to inject predefined macro definitions into the
parser preprocessor state for when we do a hackage roundtrip.
- - - - -
6b84f415 by Alan Zimmerman at 2025-06-19T19:35:05+01:00
Tweak testing
- - - - -
a8fcfa4a by Alan Zimmerman at 2025-06-19T19:35:05+01:00
Only allow unknown cpp pragmas with # in left margin
- - - - -
ac95dd60 by Alan Zimmerman at 2025-06-19T19:35:05+01:00
Require # against left margin for all GHC_CPP directives
- - - - -
8947e929 by Alan Zimmerman at 2025-06-19T19:35:05+01:00
Fix CPP directives appearing in pragmas
And add a test for error reporting for missing `#if`
- - - - -
3c073ceb by Alan Zimmerman at 2025-06-19T19:35:05+01:00
Starting to report GHC_CPP errors using GHC machinery
- - - - -
1ee27ed3 by Alan Zimmerman at 2025-06-19T19:35:05+01:00
More GHC_CPP diagnostic results
- - - - -
f70203f8 by Alan Zimmerman at 2025-06-19T19:35:05+01:00
WIP on converting error calls to GHC diagnostics in GHC_CPP
- - - - -
b3f8401d by Alan Zimmerman at 2025-06-19T19:35:05+01:00
Working on CPP diagnostic reporting
- - - - -
882e38a6 by Alan Zimmerman at 2025-06-19T19:35:05+01:00
Tweak some tests/lint warnings
- - - - -
995e97e4 by Alan Zimmerman at 2025-06-19T19:35:05+01:00
More error reporting in Macro
- - - - -
f0477b99 by Alan Zimmerman at 2025-06-19T19:35:05+01:00
Some cleanups
- - - - -
128 changed files:
- compiler/GHC.hs
- compiler/GHC/Cmm/Lexer.x
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/Cmm/Parser/Monad.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Config/Parser.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Parser.hs-boot
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/HaddockLex.x
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- + compiler/GHC/Parser/PreProcess.hs
- + compiler/GHC/Parser/PreProcess/Eval.hs
- + compiler/GHC/Parser/PreProcess/Lexer.x
- + compiler/GHC/Parser/PreProcess/Macro.hs
- + compiler/GHC/Parser/PreProcess/ParsePP.hs
- + compiler/GHC/Parser/PreProcess/Parser.y
- + compiler/GHC/Parser/PreProcess/ParserM.hs
- + compiler/GHC/Parser/PreProcess/State.hs
- compiler/GHC/Parser/Utils.hs
- compiler/GHC/SysTools/Cpp.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/ghc.cabal.in
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/debugging.rst
- docs/users_guide/using-warnings.rst
- ghc/GHCi/UI.hs
- hadrian/src/Rules/SourceDist.hs
- hadrian/stack.yaml.lock
- libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/driver/T4437.hs
- testsuite/tests/ghc-api/T11579.hs
- + testsuite/tests/ghc-cpp/GhcCpp01.hs
- + testsuite/tests/ghc-cpp/GhcCpp01.stderr
- + testsuite/tests/ghc-cpp/GhcCpp02.hs
- + testsuite/tests/ghc-cpp/GhcCpp02.stderr
- + testsuite/tests/ghc-cpp/all.T
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- + testsuite/tests/printer/CppCommentPlacement.hs
- + 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/all.T
- − 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/all.T
- testsuite/tests/vdq-rta/should_fail/T23739_fail_case.hs
- testsuite/tests/vdq-rta/should_fail/T23739_fail_case.stderr
- + utils/check-cpp/.ghci
- + utils/check-cpp/.gitignore
- + utils/check-cpp/Eval.hs
- + utils/check-cpp/Example1.hs
- + utils/check-cpp/Example10.hs
- + utils/check-cpp/Example11.hs
- + utils/check-cpp/Example12.hs
- + utils/check-cpp/Example13.hs
- + utils/check-cpp/Example2.hs
- + utils/check-cpp/Example3.hs
- + utils/check-cpp/Example4.hs
- + utils/check-cpp/Example5.hs
- + utils/check-cpp/Example6.hs
- + utils/check-cpp/Example7.hs
- + utils/check-cpp/Example8.hs
- + utils/check-cpp/Example9.hs
- + utils/check-cpp/Lexer.x
- + utils/check-cpp/Macro.hs
- + utils/check-cpp/Main.hs
- + utils/check-cpp/ParsePP.hs
- + utils/check-cpp/ParseSimulate.hs
- + utils/check-cpp/Parser.y
- + utils/check-cpp/ParserM.hs
- + utils/check-cpp/PreProcess.hs
- + utils/check-cpp/README.md
- + utils/check-cpp/State.hs
- + utils/check-cpp/run.sh
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Main.hs
- utils/check-exact/Parsers.hs
- utils/check-exact/Preprocess.hs
- utils/check-exact/Utils.hs
- utils/haddock/CHANGES.md
- utils/haddock/doc/cheatsheet/haddocks.md
- utils/haddock/doc/markup.rst
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.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/Parser.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
- + utils/haddock/html-test/ref/RedactTypeSynonyms.html
- + utils/haddock/html-test/src/RedactTypeSynonyms.hs
- + utils/haddock/latex-test/ref/RedactTypeSynonyms/RedactTypeSynonyms.tex
- + utils/haddock/latex-test/src/RedactTypeSynonyms/RedactTypeSynonyms.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ad20e507e1ddceed3366c8dabc76e3…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ad20e507e1ddceed3366c8dabc76e3…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Simon Peyton Jones pushed to branch wip/T26115 at Glasgow Haskell Compiler / GHC
Commits:
714227d7 by Simon Peyton Jones at 2025-06-20T23:50:37+01:00
Wibbles
- - - - -
4 changed files:
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/Tc/Solver/Solve.hs
- testsuite/tests/simplCore/should_compile/T26115.stderr
- testsuite/tests/simplCore/should_compile/all.T
Changes:
=====================================
compiler/GHC/HsToCore/Binds.hs
=====================================
@@ -1168,17 +1168,18 @@ dsSpec_help poly_nm poly_id poly_rhs spec_inl orig_bndrs ds_call
is_local v = v `elemVarSet` locals
rule_bndrs = scopedSort (exprsSomeFreeVarsList is_local rule_lhs_args)
- rn_binds = getRenamings orig_bndrs binds rule_bndrs
- spec_binds = pickSpecBinds is_local (mkVarSet rule_bndrs) binds
+ rn_binds = getRenamings orig_bndrs binds rule_bndrs
+ known_vars = mkVarSet rule_bndrs `extendVarSetList` bindersOfBinds rn_binds
+ picked_binds = pickSpecBinds is_local known_vars binds
-- Make spec_bndrs, the variables to pass to the specialised
-- function, by filtering out the rule_bndrs that aren't needed
- spec_binds_bndr_set = mkVarSet (bindersOfBinds spec_binds)
+ spec_binds_bndr_set = mkVarSet (bindersOfBinds picked_binds)
`minusVarSet` exprsFreeVars (rhssOfBinds rn_binds)
spec_bndrs = filterOut (`elemVarSet` spec_binds_bndr_set) rule_bndrs
- mk_spec_body fn_body = mkLets (rn_binds ++ spec_binds) $
+ mk_spec_body fn_body = mkLets (rn_binds ++ picked_binds) $
mkApps fn_body rule_lhs_args
-- ToDo: not mkCoreApps! That uses exprType on fun which
-- fails in specUnfolding, sigh
@@ -1227,7 +1228,7 @@ dsSpec_help poly_nm poly_id poly_rhs spec_inl orig_bndrs ds_call
, text "rule_bndrs" <+> ppr rule_bndrs
, text "spec_bndrs" <+> ppr spec_bndrs
, text "rn_binds" <+> ppr rn_binds
- , text "spec_binds" <+> ppr spec_binds ]
+ , text "picked_binds" <+> ppr picked_binds ]
; dsWarnOrphanRule rule
=====================================
compiler/GHC/Tc/Solver/Solve.hs
=====================================
@@ -1301,7 +1301,8 @@ tryInertQCs qc
try_inert_qcs :: QCInst -> [QCInst] -> TcS (StopOrContinue ())
try_inert_qcs (QCI { qci_ev = ev_w }) inerts =
case mapMaybe matching_inert inerts of
- [] -> continueWith ()
+ [] -> do { traceTcS "tryInertQCs:nothing" (ppr ev_w $$ ppr inerts)
+ ; continueWith () }
ev_i:_ ->
do { traceTcS "tryInertQCs:KeepInert" (ppr ev_i)
; setEvBindIfWanted ev_w EvCanonical (ctEvTerm ev_i)
@@ -1700,108 +1701,3 @@ runTcPluginSolvers solvers all_cts
addOne (givens, wanteds) (ev,ct) = case ctEvidence ct of
CtGiven {} -> (ct:givens, wanteds)
CtWanted {} -> (givens, (ev,ct):wanteds)
-
---------------------------------------------------------------------------------
-
-{-
--- | If the mode is 'TcSSpecPrag', attempt to fully solve the Wanted
--- constraints that arise from solving 'Ct'.
---
--- If not in 'TcSSpecPrag' mode, simply run 'thing_inside'.
---
--- See Note [TcSSpecPrag] in GHC.Tc.Solver.Monad.
-solveCompletelyIfRequired :: Ct -> TcS (StopOrContinue a) -> TcS (StopOrContinue a)
-solveCompletelyIfRequired ct (TcS thing_inside)
- = TcS $ \ env@(TcSEnv { tcs_ev_binds = outer_ev_binds_var
- , tcs_unified = outer_unified_var
- , tcs_unif_lvl = outer_unif_lvl_var
- , tcs_inerts = outer_inert_var
- , tcs_count = outer_count
- , tcs_mode = mode
- }) ->
- case mode of
- TcSSpecPrag ->
- do { traceTc "solveCompletelyIfRequired {" empty
- -- Create a fresh environment for the inner computation
- ; outer_inerts <- TcM.readTcRef outer_inert_var
- ; let outer_givens = inertGivens outer_inerts
- -- Keep the ambient Given inerts, but drop the Wanteds.
- ; new_inert_var <- TcM.newTcRef outer_givens
- ; new_wl_var <- TcM.newTcRef emptyWorkList
- ; new_ev_binds_var <- TcM.newTcEvBinds
-
- ; let
- inner_env =
- TcSEnv
- -- KEY part: recur with TcSVanilla
- { tcs_mode = TcSVanilla
-
- -- Use new variables for evidence bindings, inerts; and
- -- the work list. We may want to discard all of these if the
- -- inner computation doesn't fully solve all the constraints.
- , tcs_ev_binds = new_ev_binds_var
- , tcs_inerts = new_inert_var
- , tcs_worklist = new_wl_var
-
- -- Inherit the other variables. In particular, inherit the
- -- variables to do with unification, as filling metavariables
- -- is a side-effect that we are not reverting, even when we
- -- discard the result of the inner computation.
- , tcs_unif_lvl = outer_unif_lvl_var
- , tcs_unified = outer_unified_var
- , tcs_count = outer_count
- }
-
- -- Solve the constraint
- ; let wc = emptyWC { wc_simple = unitBag ct }
- ; traceTc "solveCompletelyIfRequired solveWanteds" $
- vcat [ text "ct:" <+> ppr ct
- ]
- ; solved_wc <- unTcS (solveWanteds wc) inner_env
- -- NB: it would probably make more sense to call 'thing_inside',
- -- collecting all constraints that were added to the work list as
- -- a result, and calling 'solveWanteds' on that. This would avoid
- -- restarting from the top of the solver pipeline.
- -- For the time being, we just call 'solveWanteds' on the original
- -- constraint, which is simpler
-
- ; if isSolvedWC solved_wc
- then
- do { -- The constraint was fully solved. Continue with
- -- the inner solver state.
- ; traceTc "solveCompletelyIfRequired: fully solved }" $
- vcat [ text "ct:" <+> ppr ct
- , text "solved_wc:" <+> ppr solved_wc ]
-
- -- Add new evidence bindings to the existing ones
- ; inner_ev_binds <- TcM.getTcEvBindsMap new_ev_binds_var
- ; addTcEvBinds outer_ev_binds_var inner_ev_binds
-
- -- Keep the outer inert set and work list: the inner work
- -- list is empty, and there are no leftover unsolved
- -- Wanteds.
- -- However, we **must not** drop solved implications, due
- -- to Note [Free vars of EvFun] in GHC.Tc.Types.Evidence;
- -- so we re-emit them here.
- ; let re_emit_implic impl = unTcS ( TcS.emitImplication impl ) env
- ; traverse_ re_emit_implic $ wc_impl solved_wc
- ; return $ Stop (ctEvidence ct) (text "Fully solved:" <+> ppr ct)
- }
- else
- do { traceTc "solveCompletelyIfRequired: unsolved }" $
- vcat [ text "ct:" <+> ppr ct
- , text "solved_wc:" <+> ppr solved_wc ]
- -- Failed to fully solve the constraint:
- --
- -- - discard the inner solver state,
- -- - add the original constraint as an inert.
- ; unTcS (updInertIrreds (IrredCt (ctEvidence ct) IrredShapeReason)) env
- -- NB: currently we only call 'solveCompletelyIfRequired'
- -- from 'solveForAll'; so we just stash the unsolved quantified
- -- constraint in the irreds.
-
- ; return $ Stop (ctEvidence ct) (text "Not fully solved; kept as inert:" <+> ppr ct)
- } }
- _notFullySolveMode ->
- thing_inside env
--}
=====================================
testsuite/tests/simplCore/should_compile/T26115.stderr
=====================================
@@ -1,6 +1,6 @@
[GblId[DFunId],
- Unf=DFun: \ (@b_awW) ->
+ Unf=DFun: \ (@b) ->
[GblId[DFunId],
- Unf=DFun: \ (@b_aBU) ->
+ Unf=DFun: \ (@b) ->
[GblId[DFunId],
- Unf=DFun: \ (@p_awR) (@q_awS) (v_B1 :: C p_awR q_awS) ->
+ Unf=DFun: \ (@p) (@q) (v :: C p q) ->
=====================================
testsuite/tests/simplCore/should_compile/all.T
=====================================
@@ -548,6 +548,6 @@ test('T25965', normal, compile, ['-O'])
test('T25703', [grep_errmsg(r'SPEC')], compile, ['-O -fpolymorphic-specialisation -ddump-rule-firings'])
test('T25703a', [grep_errmsg(r'SPEC')], compile, ['-O -fpolymorphic-specialisation -ddump-rule-firings'])
-test('T26115', [grep_errmsg(r'DFun')], compile, ['-O -ddump-simpl'])
+test('T26115', [grep_errmsg(r'DFun')], compile, ['-O -ddump-simpl -dsuppress-uniques'])
test('T26116', normal, compile, ['-O -ddump-rules'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/714227d76e78e5db71cfc808d9e52d7…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/714227d76e78e5db71cfc808d9e52d7…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/ghc-9.14] 26 commits: Improve redundant constraints for instance decls
by Ben Gamari (@bgamari) 20 Jun '25
by Ben Gamari (@bgamari) 20 Jun '25
20 Jun '25
Ben Gamari pushed to branch wip/ghc-9.14 at Glasgow Haskell Compiler / GHC
Commits:
19f20861 by Simon Peyton Jones at 2025-06-13T09:51:11-04:00
Improve redundant constraints for instance decls
Addresses #25992, which showed that the default methods
of an instance decl could make GHC fail to report redundant
constraints.
Figuring out how to do this led me to refactor the computation
of redundant constraints. See the entirely rewritten
Note [Tracking redundant constraints]
in GHC.Tc.Solver.Solve
- - - - -
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.
- - - - -
2575b1b7 by Ben Gamari at 2025-06-20T17:54:38-04:00
compiler: Import AnnotationWrapper from ghc-internal
Since `GHC.Desugar` exported from `base` has been deprecated.
- - - - -
9c80671c by Ben Gamari at 2025-06-20T17:54:38-04:00
ghc-compact: Eliminate dependency on ghc-prim
- - - - -
67e3d352 by Ben Gamari at 2025-06-20T17:54:38-04:00
ghc-heap: Eliminate dependency on ghc-prim
- - - - -
0aee0a92 by Ben Gamari at 2025-06-20T17:54:38-04:00
ghc-heap: Drop redundant import
- - - - -
22f4787a by Ben Gamari at 2025-06-20T17:54:38-04:00
ghc-prim: Bump version to 0.13.1
There are no interface changes from 0.13.0 but the implementation now
lives in `ghc-internal`.
- - - - -
b9ba4267 by Ben Gamari at 2025-06-20T17:54:38-04:00
template-haskell: Bump version number to 2.24.0.0
Bumps exceptions submodule.
- - - - -
d0a9a57a by Ben Gamari at 2025-06-20T17:54:46-04:00
Bump GHC version number to 9.14
- - - - -
4ea2e111 by Ben Gamari at 2025-06-20T17:55:08-04:00
Bump parsec to 3.1.18.0
Bumps parsec submodule.
- - - - -
45339d74 by Ben Gamari at 2025-06-20T17:55:15-04:00
unix: Bump to 2.8.7.0
Bumps unix submodule.
- - - - -
62eb3cdd by Ben Gamari at 2025-06-20T17:55:20-04:00
binary: Bump to 0.8.9.3
Bumps binary submodule.
- - - - -
cafec215 by Ben Gamari at 2025-06-20T17:55:25-04:00
Win32: Bump to 2.14.2.0
Bumps Win32 submodule.
- - - - -
175eb5fb by Ben Gamari at 2025-06-20T17:55:29-04:00
base: Bump version to 4.22.0
Bumps various submodules.
- - - - -
186 changed files:
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Expr.hs-boot
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/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/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/Instance.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/Name/Reader.hs
- compiler/GHC/Types/ThLevelIndex.hs
- compiler/GHC/Utils/Panic.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/ghc.cabal.in
- configure.ac
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/using-warnings.rst
- docs/users_guide/using.rst
- libffi-tarballs
- libraries/Win32
- libraries/array
- libraries/base/base.cabal.in
- libraries/binary
- libraries/deepseq
- libraries/directory
- libraries/exceptions
- libraries/filepath
- libraries/ghc-boot-th/ghc-boot-th.cabal.in
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-compact/GHC/Compact.hs
- libraries/ghc-compact/GHC/Compact/Serialized.hs
- libraries/ghc-compact/ghc-compact.cabal
- libraries/ghc-experimental/ghc-experimental.cabal.in
- libraries/ghc-heap/GHC/Exts/Heap/Utils.hsc
- libraries/ghc-heap/ghc-heap.cabal.in
- libraries/ghc-prim/changelog.md
- libraries/ghc-prim/ghc-prim.cabal
- libraries/ghci/ghci.cabal.in
- libraries/haskeline
- libraries/hpc
- libraries/os-string
- libraries/parsec
- libraries/process
- libraries/semaphore-compat
- libraries/stm
- libraries/template-haskell/template-haskell.cabal.in
- libraries/terminfo
- libraries/text
- libraries/unix
- rts/include/stg/MachRegs.h
- testsuite/tests/annotations/should_fail/annfail03.stderr
- testsuite/tests/annotations/should_fail/annfail09.stderr
- testsuite/tests/dependent/should_fail/T13135_simple.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/linear/should_fail/LinearTHFail.stderr
- testsuite/tests/linters/notes.stdout
- testsuite/tests/perf/compiler/hard_hole_fits.stderr
- testsuite/tests/quasiquotation/T3953.stderr
- testsuite/tests/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/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/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/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/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/T25992.hs
- + testsuite/tests/typecheck/should_compile/T25992.stderr
- testsuite/tests/typecheck/should_compile/all.T
- − 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/all.T
- testsuite/tests/typecheck/should_fail/tcfail097.stderr
- testsuite/tests/vdq-rta/should_fail/T23739_fail_case.hs
- testsuite/tests/vdq-rta/should_fail/T23739_fail_case.stderr
- utils/check-exact/ExactPrint.hs
- utils/haddock/CHANGES.md
- utils/haddock/doc/cheatsheet/haddocks.md
- utils/haddock/doc/markup.rst
- utils/haddock/haddock-api/haddock-api.cabal
- 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-test/haddock-test.cabal
- utils/haddock/haddock.cabal
- + utils/haddock/html-test/ref/RedactTypeSynonyms.html
- + utils/haddock/html-test/src/RedactTypeSynonyms.hs
- + utils/haddock/latex-test/ref/RedactTypeSynonyms/RedactTypeSynonyms.tex
- + utils/haddock/latex-test/src/RedactTypeSynonyms/RedactTypeSynonyms.hs
- utils/hsc2hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/de5e7327eb4b9778bbbffcbc2de687…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/de5e7327eb4b9778bbbffcbc2de687…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc] Pushed new branch wip/teo/fix-containers-upper-bound
by Teo Camarasu (@teo) 20 Jun '25
by Teo Camarasu (@teo) 20 Jun '25
20 Jun '25
Teo Camarasu pushed new branch wip/teo/fix-containers-upper-bound at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/teo/fix-containers-upper-bound
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T25282] 2 commits: Expose ghc-internal unit id through the settings file
by Teo Camarasu (@teo) 20 Jun '25
by Teo Camarasu (@teo) 20 Jun '25
20 Jun '25
Teo Camarasu pushed to branch wip/T25282 at Glasgow Haskell Compiler / GHC
Commits:
6d791567 by Teo Camarasu at 2025-06-20T17:43:18+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
- - - - -
ae14bd72 by Teo Camarasu at 2025-06-20T17:43:35+01:00
linters: lint-whitespace: bump upper-bound for containers
- - - - -
4 changed files:
- compiler/GHC/Driver/Session.hs
- compiler/Setup.hs
- hadrian/src/Rules/Generate.hs
- linters/lint-whitespace/lint-whitespace.cabal
Changes:
=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -3460,6 +3460,7 @@ compilerInfo dflags
("Project Patch Level1", cProjectPatchLevel1),
("Project Patch Level2", cProjectPatchLevel2),
("Project Unit Id", cProjectUnitId),
+ ("ghc-internal Unit Id", cGhcInternalUnitId), -- See Note [Special unit-ids]
("Booter version", cBooterVersion),
("Stage", cStage),
("Build platform", cBuildPlatformString),
@@ -3513,6 +3514,23 @@ compilerInfo dflags
expandDirectories :: FilePath -> Maybe FilePath -> String -> String
expandDirectories topd mtoold = expandToolDir useInplaceMinGW mtoold . expandTopDir topd
+-- Note [Special unit-ids]
+-- ~~~~~~~~~~~~~~~~~~~~~~~
+-- Certain units are special to the compiler:
+-- - Wired-in identifiers reference a specific unit-id of `ghc-internal`.
+-- - GHC plugins must be linked against a specific unit-id of `ghc`,
+-- namely the same one as the compiler.
+-- - When using Template Haskell, splices refer to the Template Haskell
+-- interface defined in `ghc-internal`, and must be linked against the same
+-- unit-id as the compiler.
+--
+-- We therefore expose the unit-id of `ghc-internal` ("ghc-internal Unit Id") and
+-- ghc ("Project Unit Id") through `ghc --info`.
+--
+-- This allows build tools to act accordingly, eg, if a user wishes to build a
+-- GHC plugin, `cabal-install` might force them to use the exact `ghc` unit
+-- that the compiler was linked against.
+
{- -----------------------------------------------------------------------------
Note [DynFlags consistency]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~
=====================================
compiler/Setup.hs
=====================================
@@ -11,6 +11,7 @@ import Distribution.Verbosity
import Distribution.Simple.Program
import Distribution.Simple.Utils
import Distribution.Simple.Setup
+import Distribution.Simple.PackageIndex
import System.IO
import System.Process
@@ -22,6 +23,7 @@ import qualified Data.Map as Map
import GHC.ResponseFile
import System.Environment
+
main :: IO ()
main = defaultMainWithHooks ghcHooks
where
@@ -56,7 +58,7 @@ primopIncls =
]
ghcAutogen :: Verbosity -> LocalBuildInfo -> IO ()
-ghcAutogen verbosity lbi@LocalBuildInfo{pkgDescrFile,withPrograms,componentNameMap}
+ghcAutogen verbosity lbi@LocalBuildInfo{pkgDescrFile,withPrograms,componentNameMap,installedPkgs}
= do
-- Get compiler/ root directory from the cabal file
let Just compilerRoot = takeDirectory <$> pkgDescrFile
@@ -96,9 +98,14 @@ ghcAutogen verbosity lbi@LocalBuildInfo{pkgDescrFile,withPrograms,componentNameM
Just [LibComponentLocalBuildInfo{componentUnitId}] -> unUnitId componentUnitId
_ -> error "Couldn't find unique cabal library when building ghc"
+ let cGhcInternalUnitId = case lookupPackageName installedPkgs (mkPackageName "ghc-internal") of
+ -- We assume there is exactly one copy of `ghc-internal` in our dependency closure
+ [(_,[packageInfo])] -> unUnitId $ installedUnitId packageInfo
+ _ -> error "Couldn't find unique ghc-internal library when building ghc"
+
-- Write GHC.Settings.Config
configHsPath = autogenPackageModulesDir lbi </> "GHC/Settings/Config.hs"
- configHs = generateConfigHs cProjectUnitId settings
+ configHs = generateConfigHs cProjectUnitId cGhcInternalUnitId settings
createDirectoryIfMissingVerbose verbosity True (takeDirectory configHsPath)
rewriteFileEx verbosity configHsPath configHs
@@ -110,8 +117,9 @@ getSetting settings kh kr = go settings kr
Just v -> Right v
generateConfigHs :: String -- ^ ghc's cabal-generated unit-id, which matches its package-id/key
+ -> String -- ^ ghc-internal's cabal-generated unit-id, which matches its package-id/key
-> [(String,String)] -> String
-generateConfigHs cProjectUnitId settings = either error id $ do
+generateConfigHs cProjectUnitId cGhcInternalUnitId settings = either error id $ do
let getSetting' = getSetting $ (("cStage","2"):) settings
buildPlatform <- getSetting' "cBuildPlatformString" "Host platform"
hostPlatform <- getSetting' "cHostPlatformString" "Target platform"
@@ -127,6 +135,7 @@ generateConfigHs cProjectUnitId settings = either error id $ do
, " , cBooterVersion"
, " , cStage"
, " , cProjectUnitId"
+ , " , cGhcInternalUnitId"
, " ) where"
, ""
, "import GHC.Prelude.Basic"
@@ -150,4 +159,7 @@ generateConfigHs cProjectUnitId settings = either error id $ do
, ""
, "cProjectUnitId :: String"
, "cProjectUnitId = " ++ show cProjectUnitId
+ , ""
+ , "cGhcInternalUnitId :: String"
+ , "cGhcInternalUnitId = " ++ show cGhcInternalUnitId
]
=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -601,6 +601,8 @@ generateConfigHs = do
-- 'pkgUnitId' on 'compiler' (the ghc-library package) to create the
-- unit-id in both situations.
cProjectUnitId <- expr . (`pkgUnitId` compiler) =<< getStage
+
+ cGhcInternalUnitId <- expr . (`pkgUnitId` ghcInternal) =<< getStage
return $ unlines
[ "module GHC.Settings.Config"
, " ( module GHC.Version"
@@ -610,6 +612,7 @@ generateConfigHs = do
, " , cBooterVersion"
, " , cStage"
, " , cProjectUnitId"
+ , " , cGhcInternalUnitId"
, " ) where"
, ""
, "import GHC.Prelude.Basic"
@@ -633,6 +636,9 @@ generateConfigHs = do
, ""
, "cProjectUnitId :: String"
, "cProjectUnitId = " ++ show cProjectUnitId
+ , ""
+ , "cGhcInternalUnitId :: String"
+ , "cGhcInternalUnitId = " ++ show cGhcInternalUnitId
]
where
stageString (Stage0 InTreeLibs) = "1"
=====================================
linters/lint-whitespace/lint-whitespace.cabal
=====================================
@@ -24,7 +24,7 @@ executable lint-whitespace
process
^>= 1.6,
containers
- >= 0.6 && <0.8,
+ >= 0.6 && <0.9,
base
>= 4.14 && < 5,
text
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/44c4682da95e578d0024f1728517f5…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/44c4682da95e578d0024f1728517f5…
You're receiving this email because of your account on gitlab.haskell.org.
1
0