
Sjoerd Visscher pushed to branch wip/T18570 at Glasgow Haskell Compiler / GHC
Commits:
2d419d8d by Matthew Pickering at 2025-04-02T16:12:36-04:00
Use unsafePerformIO in definition of computeFingerprint
computeFingerprint is morally a pure function, which is implemented by
mutating a buffer. Using unsafePerformIO inside the definition allows it
to be used in pure contexts, fixing one place where an ad-hoc call to
unsafePerformIO is already needed.
- - - - -
ccdf979b by Matthew Pickering at 2025-04-02T16:12:37-04:00
driver: Fix recompilation checking for exported defaults
Since the exported defaults are not associated with any identifier from
the module, they are just added to the export hash rather than
the fine-grained recompilation logic.
Fixes #25855
- - - - -
c5bf9892 by Matthew Pickering at 2025-04-02T16:12:37-04:00
driver: Fix recompilation checking for COMPLETE pragmas
A {-# COMPLETE P, Q #-} pragma is associated with the pattern synonyms P
and Q during recompilation checking. Therefore, the existence of a
pattern synonym becomes part of the ABI hash for P and Q.
Then if a module uses these pattern synonyms and a complete pragma
changes, it will trigger recompilation in that module.
Fixes #25854
- - - - -
d0fd9370 by sheaf at 2025-04-02T16:14:05-04:00
Handle named default exports separately
This commit changes the way we check for duplicate exports of named
default declarations. They are now treated entirely separately from
other exports, because in an export list of the form
module M ( default Cls, Cls )
the default declaration does not export the class 'Cls', but only its
default declarations.
Also fixes a bug in Backpack where named default exports were getting
dropped entirely. No test for that.
Fixes #25857
- - - - -
62d04494 by Cheng Shao at 2025-04-03T05:56:17-04:00
ci: add x86_64-linux-ubuntu24_04 nightly/release jobs
- - - - -
327952e4 by Cheng Shao at 2025-04-03T05:56:17-04:00
rel-eng: add ubuntu24_04 bindists to ghcup metadata and fetch gitlab scripts
- - - - -
aa1e3b8b by sheaf at 2025-04-03T05:57:24-04:00
GHC settings: always unescape escaped spaces
In #25204, it was noted that GHC didn't properly deal with having
spaces in its executable path, as it would compute an invalid path
for the C compiler.
The original fix in 31bf85ee49fe2ca0b17eaee0774e395f017a9373 used a
trick: escape spaces before splitting up flags into a list. This fixed
the behaviour with extra flags (e.g. -I), but forgot to also unescape
for non-flags, e.g. for an executable path (such as the C compiler).
This commit rectifies this oversight by consistently unescaping the
spaces that were introduced in order to split up argument lists.
Fixes #25204
- - - - -
34a9b55d by lazyLambda at 2025-04-04T06:22:26-04:00
Driver: make MonadComprehensions imply ParallelListComp
This commit changes GHC.Driver.Flags.impliedXFlags to make the
MonadComprehensions extension enable the ParallelListComp extension.
Fixes #25645
- - - - -
d99eb7cd by sheaf at 2025-04-04T06:23:28-04:00
NamedDefaults: handle poly-kinded unary classes
With this commit, we accept named default declarations for poly-kinded
classes such as Typeable, e.g.
default Typeable (Char)
This used to fail because we assumed the kind of the class was monomorphic,
e.g.
Type -> Constraint
(Type -> Type) -> Constraint
Nat -> Constraint
Now, we can handle a simple polymorphic class such as
Typeable :: forall k. k -> Constraint
Note that we keep the restriction that the class must only have
one visible argument.
This is all explained in the new Note [Instance check for default declarations]
in GHC.Tc.Gen.Default.
Fixes #25882
- - - - -
4cbc90de by sheaf at 2025-04-04T11:39:05-04:00
LLVM: add type annotations to AtomicFetch_cmm.cmm
- - - - -
e2237305 by sheaf at 2025-04-04T11:39:05-04:00
Cmm lint: lint argument types of CallishMachOps
This commit adds a new check to Cmm lint to ensure that the argument
types to a CallishMachOp are correct. The lack of this check was
detected in the AtomicFetch test: the literals being passed as the
second arguments to operations such as 'fetch_add', 'fetch_and'... were
of the wrong width, which tripped up the LLVM backend.
- - - - -
9363e547 by Cheng Shao at 2025-04-04T11:39:50-04:00
ci: add ghc-wasm-meta integration testing jobs
This patch adds ghc-wasm-meta integration testing jobs to the CI
pipeline, which are only triggered via the `test-wasm` MR label or
manually when the `wasm` label is set.
These jobs will fetch the wasm bindists and test them against a
variety of downstream projects, similarly to head.hackage jobs for
native bindists, offering a convenient way to catch potential
downstream breakage while refactoring the wasm backend.
- - - - -
27029e60 by Adam Gundry at 2025-04-04T11:40:36-04:00
base: Minor fixes to GHC.Records haddocks
This corrects a stale reference to OverloadedRecordFields (which should
be OverloadedRecordDot), fixes the haddock link syntax and adds an
@since pragma.
- - - - -
f827c4c6 by Rodrigo Mesquita at 2025-04-07T11:22:10-04:00
Parametrize default logger action with Handles
Introduce `defaultLogActionWithHandles` to allow GHC applications to use
GHC's formatting but using custom handles.
`defaultLogAction` is then trivially reimplemented as
```
defaultLogActionWithHandles stdout stderr
```
- - - - -
5dade5fd by sheaf at 2025-04-07T11:23:02-04:00
Finer-grained recompilation checking for exports
This commit refines the recompilation checking logic, to avoid
recompiling modules with an explicit import list when the modules they
import start exporting new items.
More specifically, when:
1. module N imports module M,
2. M is changed, but in a way that:
a. preserves the exports that N imports
b. does not introduce anything that forces recompilation downstream,
such as orphan instances
then we no longer require recompilation of N.
Note that there is more to (2a) as initially meets the eye:
- if N includes a whole module or "import hiding" import of M,
then we require that the export list of M does not change,
- if N only includes explicit imports, we check that the imported
items don't change, e.g.
- if we have @import M(T(K, f), g)@, we must check that N
continues to export all these identifiers, with the same Avail
structure (i.e. we should error if N stops bundling K or f with
T)
- if we have @import M(T(..))@, we must check that the children
of T have not changed
See Note [When to recompile when export lists change?] in GHC.Iface.Recomp.
This is all tested in the new tests RecompExports{1,2,3,4,5}
Fixes #25881
- - - - -
f32d6c2b by Andreas Klebinger at 2025-04-07T22:01:25-04:00
NCG: AArch64 - Add -finter-module-far-jumps.
When enabled the arm backend will assume jumps to targets outside of the
current module are further than 128MB away.
This will allow for code to work if:
* The current module results in less than 128MB of code.
* The whole program is loaded within a 4GB memory region.
We have seen a few reports of broken linkers (#24648) where this flag might allow
a program to compile/run successfully at a very small performance cost.
-------------------------
Metric Increase:
T783
-------------------------
- - - - -
553c280b by Andreas Klebinger at 2025-04-07T22:02:11-04:00
Revert "rts: fix small argument passing on big-endian arch (fix #23387)"
Based on analysis documented in #25791 this doesn't fully fix the big
while introducing new bugs on little endian architectures.
A more complete fix will have to be implemented to fix #23387
This reverts commit 4f02d3c1a7b707e609bb3aea1dc6324fa19a5c39.
- - - - -
b0dc6599 by Andreas Klebinger at 2025-04-07T22:02:11-04:00
Interpreter: Fixes to handling of subword value reads/writes.
Load subword values as full words from the stack truncating/expanding as
neccesary when dealing with subwords. This way byte order is implicitly
correct.
This commit also fixes the order in which we are pushing literals onto
the stack on big endian archs.
Last but not least we enable a test for ghci which actually tests these
subword operations.
- - - - -
ed38c09b by Cheng Shao at 2025-04-07T22:02:53-04:00
testsuite: don't test WasmControlFlow stdout
This patch solves a potential test flakiness in `WasmControlFlow` by
removing `WasmControlFlow.stdout` which is not so portable/stable as
it seems. See added `Note [WasmControlFlow]` for more detailed
explanation.
- - - - -
f807c590 by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00
debugger: Add docs to obtainTermFromId
- - - - -
5dba052d by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00
Move logic to find and set Breakpoint to GHC
Breakpoints are uniquely identified by a module and an index unique
within that module. `ModBreaks` of a Module contains arrays mapping from
this unique breakpoint index to information about each breakpoint. For
instance, `modBreaks_locs` stores the `SrcSpan` for each breakpoint.
To find a breakpoint using the line number you need to go through all
breakpoints in the array for a given module and look at the line and
column stored in the `SrcSpan`s. Similarly for columns and finding
breakpoints by name.
This logic previously lived within the `GHCi` application sources,
however, it is common to any GHC applications wanting to set
breakpoints, like the upcoming `ghc-debugger`.
This commit moves this logic for finding and setting breakpoints to the
GHC library so it can be used by both `ghci` and `ghc-debugger`.
- - - - -
bc0b9f73 by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00
Refactor and move logic for identifier breakpoints
Breakpoints can be set on functions using syntax of the form
`[Module.]function`. The parsing, resolution (e.g. inferring implicit
module), and validation of this syntax for referring to functions was
tightly coupled with its GHCi use.
This commit extracts the general purpose bits of resolving this syntax
into `GHC.Runtime.Debugger.Breakpoints` so it can be further used by
other GHC applications and to improve the code structure of GHCi.
Moreover, a few utilities that do splitting and joining of identifiers
as strings were moved to `GHC.Runtime.Eval.Utils`, which also can be
used in the future to clean up `GHC.Runtime.Eval` a bit.
- - - - -
4f728d21 by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00
debugger: derive Ord for BreakpointIds
- - - - -
5528771c by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00
debugger: Move context utils from GHCi to GHC
Moves `enclosingTickSpan`, `getCurrentBreakSpan`, and
`getCurrentBreakModule`, general utilities on the internal debugger
state, into the GHC library.
- - - - -
4871f543 by sheaf at 2025-04-08T17:42:43-04:00
Implicit quantification in type synonyms: add test
This adds a test for ticket #24090, which involves implicit
quantification in type synonyms.
The underlying issue was fixed in 0d4ee209dfe53e5074d786487f531dabc36d561c.
- - - - -
48917d3c by sheaf at 2025-04-08T17:42:44-04:00
Turn on implicit-rhs-quantification by default
This flag was added to GHC 9.8, and will be removed in a future GHC
release. In preparation, this commit adds it to the default warning
flags.
- - - - -
629be068 by Rodrigo Mesquita at 2025-04-08T17:43:26-04:00
debugger: Add breakpoints to every Stmt
While single-stepping through a Haskell program we stop at every
breakpoint. However, we don't introduce breakpoints at every single
expression (e.g. single variables) because they would be too many and
uninteresting.
That said, in a do-block, it is expected that stepping over would break
at every line, even if it isn't particularly interesting (e.g. a single
arg like getArgs). Moreover, let-statements in do-blocks, despite only
being evaluated once needed, lead to surprising jumps while stepping
through because some have outermost (outside the let) breakpoints
while others don't.
This commit makes every statement in a do-block have a breakpoint.
This leads to predictable stepping through in a do-block.
Duplicate breakpoints in the same location are avoided using the
existing blacklist mechanism, which was missing a check in one relevant place.
Fixes #25932
- - - - -
99a3affd by Matthew Pickering at 2025-04-08T17:44:08-04:00
driver: refactor: Split downsweep and MakeAction into separate modules.
This will facilitate using the downsweep functions in other parts of
the compiler than just --make mode.
Also, the GHC.Driver.Make module was huge. Now it's still huge but
slightly smaller!
- - - - -
ecfec4df by sheaf at 2025-04-09T14:13:12-04:00
Store user-written qualification in the GhcRn AST
This commit ensures we store the original user-written module
qualification in the renamed AST. This allows us to take into account
the user-written qualification in error messages.
Fixes #25877
- - - - -
97c884e2 by sheaf at 2025-04-09T14:13:12-04:00
TcRnIllegalTermLevelUse: simpler error when possible
This commit makes GHC emit a simple error message in the case of an
illegal term-level use of a data constructor: we will try to report an
out-of-scope error instead of a "Illegal term level use" error, as the
latter might be a bit overwhelming for newcomers.
We do this when we have a data constructor import suggestion to provide
to the user. For example:
module M where { data A = A }
module N where
import M(A)
x = Bool
-- Illegal term-level use of Bool
y = A
-- Data constructor not in scope: A.
-- Perhaps add 'A' to the import list of 'M'.
This commit also revamps the "similar names" suggestion mechanism,
and in particular its treatment of name spaces. Now, which name spaces
we suggest is based solely on what we are looking for, and no longer on
the NameSpace of the Name we have. This is because, for illegal term-level
use errors, it doesn't make much sense to change the suggestions based
on the fact that we resolved to e.g. a type constructor/class; what
matters is what we were expecting to see in this position.
See GHC.Rename.Unbound.{suggestionIsRelevant,relevantNameSpace} as well
as the new constructors to GHC.Tc.Errors.Types.WhatLooking.
Fixes #23982
- - - - -
bff645ab by Rodrigo Mesquita at 2025-04-09T14:13:57-04:00
driver: Split Session functions out of Main
This commit moves out functions that help in creating and validating a
GHC multi session from Main into the ghc library where they can be used by
other GHC applications.
Moreover, `Mode` processing and `checkOptions` linting were moved to
separate modules within the ghc-bin executable package.
In particular:
- Move `Mode` types and functions (referring to the mode GHC is running
on) to `ghc-bin:GHC.Driver.Session.Mode`
- Move `checkOptions` and aux functions, which validates GHC DynFlags
based on the mode, to `ghc-bin:GHC.Driver.Session.Lint`
- Moves `initMulti`, `initMake`, and aux functions, which initializes a make/multi-unit
session, into `ghc:GHC.Driver.Session.Units`.
- - - - -
501b015e by Rodrigo Mesquita at 2025-04-09T14:13:57-04:00
docs: Improve haddock of ExecComplete
- - - - -
dea98988 by Andreas Klebinger at 2025-04-09T19:23:57-04:00
Avoid oversaturing constructor workers.
Constructor applications always need to take the exact number of
arguments. If we can't ensure that instead apply the constructor worker
like a regular function.
Fixes #23865
- - - - -
f1acdd2c by sheaf at 2025-04-09T19:25:41-04:00
NamedDefaults: require the class to be standard
We now only default type variables if they only appear in constraints
of the form `C v`, where `C` is either a standard class or a class with
an in-scope default declaration.
This rectifies an oversight in the original implementation of the
NamedDefault extensions that was remarked in #25775; that implementation
allowed type variables to appear in unary constraints which had arbitrary
classes at the head.
See the rewritten Note [How type-class constraints are defaulted] for
details of the implementation.
Fixes #25775
Fixes #25778
- - - - -
5712e0d6 by Vladislav Zavialov at 2025-04-10T05:17:38+00:00
Retry type/class declarations and instances (#12088)
Retry type/class declarations and instances to account for non-lexical
dependencies arising from type/data family instances.
This patch improves the kind checker's ability to use type instances in kind
checking of other declarations in the same module.
* Key change: tcTyAndClassDecls now does multiple passes over the TyClGroups,
as long as it is able to make progress.
See the new Note [Retrying TyClGroups] in GHC.Tc.TyCl
* Supporting change: FVs of a TyClGroup are now recorded in its extension
field, namely XCTyClGroup.
See the new Note [Prepare TyClGroup FVs] in GHC.Rename.Module
* Instances are no longer inserted at the earliest positions where their FVs
are bound. This is a simplification.
See the new Note [Put instances at the end] in GHC.Rename.Module
* Automatic unpacking is now more predictable, but fewer fields get unpacked
by default. Use explicit {-# UNPACK #-} pragmas instead.
See the new Note [Flaky -funbox-strict-fields with type/data families]
For the wide range of newly accepted programs, consult the added test cases.
Fixed tickets:
#12088, #12239, #14668, #15561, #16410, #16448, #16693,
#19611, #20875, #21172, #22257, #25238, #25834
Metric Decrease:
T8095
- - - - -
bc73a78d by sheaf at 2025-04-10T15:07:24-04:00
checkFamApp: don't be so eager to cycle break
As remarked in #25933, a pure refactoring of checkTyEqRhs in
ab77fc8c7adebd610aa0bd99d653f9a6cc78a374 inadvertently changed behaviour,
as it caused GHC to introduce cycle-breaker variables in some
unnecessary circumstances.
This commit refactors 'GHC.Tc.Utils.Unify.checkFamApp' in a way that
should restore the old behaviour, so that, when possible, we first
recur into the arguments and only introduce a cycle breaker if this
recursion fails (e.g. due to an occurs check failure).
Fixes #25933
- - - - -
3acd8182 by Andreas Klebinger at 2025-04-10T22:32:12-04:00
Expand docs for RTS flag `-M`.
The behaviour of how/when exceptions are raised was not really covered
in the docs.
- - - - -
026c1a39 by Adam Sandberg Ericsson at 2025-04-10T22:32:56-04:00
add cases for more SchedulerStatus codes in rts_checkSchedStatus
- - - - -
5977c6a1 by sheaf at 2025-04-10T22:33:46-04:00
Squash warnings in GHC.Runtime.Heap.Inspect
There were incomplete record selector warnings in GHC.Runtime.Heap.Inspect
due to the use of the partial 'dataArgs' record selector. This is fixed
by passing the fields to the 'extractSubTerms' function directly,
rather than passing a value of the parent data type.
- - - - -
6a3e38f5 by Andreas Klebinger at 2025-04-11T15:13:53-04:00
hadrian: Make ghcWithInterpreter the universal source of truth about availability of the interpreter
We were doing some ad-hoc checks in different places in hadrian to
determine whether we supported the interprter or not. Now this check if
confined to one function, `ghcWithInterpreter`, and all the places which
use this information consult `ghcWithInterpreter` to determine what to
do.
Fixes #25533.
- - - - -
207de6f1 by Matthew Pickering at 2025-04-11T15:14:37-04:00
testsuite: Fix running TH tests with profiled dynamic compiler
Previously, I had failed to update the ghc_th_way_flags logic for the
profiled dynamic compiler.
In addition to this `ghc_dynamic` was incorrectly set for profiled
dynamic compiler.
I also updated MultiLayerModulesTH_OneShot test to work for any compiler
linkage rather than just dynamic.
Fixes #25947
-------------------------
Metric Decrease:
MultiLayerModulesTH_Make
-------------------------
- - - - -
5455f2b9 by Matthew Pickering at 2025-04-12T08:31:36-04:00
driver: Add support for "Fixed" nodes in the ModuleGraph
A fixed node in the module graph is one which we presume is already
built. It's therefore up to the user to make sure that the interface
file and any relevant artifacts are available for a fixed node.
Fixed/Compile nodes are represented by the ModuleNodeInfo type, which
abstracts the common parts of Fixed/Compile nodes with accessor
functions of type `ModuleNodeInfo -> ...`.
Fixed nodes can only depend on other fixed nodes. This invariant can be
checked by the function `checkModuleGraph` or `mkModuleGraphChecked`.
--make mode is modified to work with fixed mode. In order to "compile" a
fixed node, the artifacts are just loaded into the HomePackageTable.
Currently nothing in the compiler will produce Fixed nodes but this is
tested with the FixedNodes GHC API test.
In subsequent patches we are going to remove the ExternalModuleGraph and
use Fixed nodes for modules in the module graph in oneshot mode.
Fixes #25920
- - - - -
ad64d5c2 by Cheng Shao at 2025-04-12T08:32:19-04:00
ci: remove manual case of ghc-wasm-meta downstream testing jobs
This patch removes the manual case of ghc-wasm-meta downstream testing
jobs; now the only way of including them in the pipeline and running
them is via the test-wasm label.
The reason of the removal is it proves to be problematic for MRs with
only the wasm label; the wasm job would succeed, then the pipeline
status would be waiting for manual action instead of succeeding. There
needs to be separate jobs for the label-triggered and manual-triggered
cases, but I don't think it's worth that extra complexity, the
label-triggered case is already sufficient.
- - - - -
b34890c7 by Vladislav Zavialov at 2025-04-13T01:08:21+03:00
Fix EmptyCase panic in tcMatches (#25960)
Due to faulty reasoning in Note [Pattern types for EmptyCase],
tcMatches was too keen to panic.
* Old (incorrect) assumption: pat_tys is a singleton list.
This does not hold when \case{} is checked against a function type
preceded by invisible forall. See the new T25960 test case.
* New (hopefully correct) assumption: vis_pat_tys is a singleton list.
This should follow from:
checkArgCounts :: MatchGroup GhcRn ... -> TcM VisArity
checkArgCounts (MG { mg_alts = L _ [] })
= return 1
...
- - - - -
84806ebc by Vladislav Zavialov at 2025-04-13T11:40:08-04:00
Remove unused type: TokenLocation
- - - - -
05eb50df by Vladislav Zavialov at 2025-04-13T19:16:38-04:00
Register EpToken in Parser.PostProcess.Haddock (#22558)
This change allows us to reject more badly placed Haddock comments.
Examples:
module
-- | Bad comment for the module
T17544_kw where
data Foo -- | Bad comment for MkFoo
where MkFoo :: Foo
newtype Bar -- | Bad comment for MkBar
where MkBar :: () -> Bar
class Cls a
-- | Bad comment for clsmethod
where
clsmethod :: a
- - - - -
01944e5e by Vladislav Zavialov at 2025-04-13T19:17:21-04:00
Reject puns in T2T (#24153)
This patch implements pun detection in T2T. Consider:
x = 42
f, g :: forall a -> ...
f (type x) = g x
In accordance with the specification, the `g x` function call is renamed
as a term, so `x` refers to the top-level binding `x = 42`, not to the
type variable binding `type x` as one might expect.
This is somewhat counterintuitive because `g` expects a type argument.
Forbidding puns in T2T allows us to produce a helpful error message:
Test.hs:5:16: error: [GHC-09591]
Illegal punned variable occurrence in a required type argument.
The name ‘x’ could refer to:
‘x’ defined at Test.hs:3:1
‘x’ bound at Test.hs:5:9
This commit is a follow up to 0dfb1fa799af254c8a1e1045fc3996af2d57a613
where checking for puns was left as future work.
- - - - -
cc580552 by Vladislav Zavialov at 2025-04-13T19:18:02-04:00
Additional test cases for #12088, #13790
Extract more test cases from ticket discussions, including multi-module
examples. Follow up to 5712e0d646f611dfbfedfd7ef6dff3a18c016edb
- - - - -
d47bf776 by Matthew Pickering at 2025-04-14T16:44:41+01:00
driver: Use ModuleGraph for oneshot and --make mode
This patch uses the `hsc_mod_graph` field for both oneshot and --make
mode. Therefore, if part of the compiler requires usage of the module
graph, you do so in a uniform way for the two different modes.
The `ModuleGraph` describes the relationship between the modules in the
home package and units in external packages. The `ModuleGraph` can be
queried when information about the transitive closure of a package is
needed. For example, the primary use of the ModuleGraph from within the
compiler is in the loader, which needs to know the transitive closure of
a module so it can load all the relevant objects for evaluation.
In --make mode, downsweep computes the ModuleGraph before any
compilation starts.
In oneshot mode, a thunk is created at the start of compilation, which
when forced will compute the module graph beneath the current module.
The thunk is only forced at the moment when the user uses Template
Haskell.
Finally, there are some situations where we need to discover what
dependencies to load but haven't loaded a module graph at all. In this
case, there is a fallback which computes the transitive closure on the
fly and doesn't cache the result. Presumably if you are going to call
getLinkDeps a lot, you would compute the right ModuleGraph before you
started.
Importantly, this removes the ExternalModuleGraph abstraction. This was quite
awkward to work with since it stored information about the home package
inside the EPS.
This patch will also be very useful when implementing explicit level
imports, which requires more significant use of the module graph in
order to determine which level instances are available at.
Towards #25795
-------------------------
Metric Decrease:
MultiLayerModulesTH_Make
MultiLayerModulesTH_OneShot
-------------------------
- - - - -
395e0ad1 by sheaf at 2025-04-16T12:33:26-04:00
base: remove .Internal modules (e.g. GHC.TypeLits)
This commit removes the following internal modules from base,
as per CLC proposal 217:
- GHC.TypeNats.Internal
- GHC.TypeLits.Internal
- GHC.ExecutionStack.Internal
Fixes #25007
- - - - -
e0f3ff11 by Patrick at 2025-04-17T04:31:12-04:00
Refactor Handling of Multiple Default Declarations
Fixes: #25912, #25914, #25934
Previously, GHC discarded all loaded defaults (tcg_default) when local
defaults were encountered during typechecking. According to the
exportable-named-default proposal (sections 2.4.2 and 2.4.3), local
defaults should be merged into tcg_default, retaining any defaults
already present while overriding where necessary.
Key Changes:
* Introduce DefaultProvenance to track the origin of default declarations
(local, imported, or built-in), replacing the original cd_module
in ClassDefaults with cd_provenance :: DefaultProvenance.
* Rename tcDefaults to tcDefaultDecls, limiting its responsibility to only
converting renamed class defaults into ClassDefaults.
* Add extendDefaultEnvWithLocalDefaults to merge local defaults into the
environment, with proper duplication checks:
- Duplicate local defaults for a class trigger an error.
- Local defaults override imported or built-in defaults.
* Update and add related notes: Note [Builtin class defaults],
Note [DefaultProvenance].
* Add regression tests: T25912, T25914, T25934.
Thanks sam and simon for the help on this patch.
Co-authored-by: sheaf
do { forever (return ()); blah }
where `forever :: forall a b. IO a -> IO b`. Nothing constrains `b`, so it will be instantiates with `Any` or `ZonkAny`. But we certainly don't want to complain about a discarded do-binding. Fixes #25895 - - - - - e46c6b18 by Rodrigo Mesquita at 2025-05-06T09:01:57-04:00 Refactor mkTopLevImportedEnv out of mkTopLevEnv This makes the code clearer and allows the top-level import context to be fetched directly from the HomeModInfo through the API (e.g. useful for the debugger). - - - - - 0ce0d263 by Rodrigo Mesquita at 2025-05-06T09:01:57-04:00 Export sizeOccEnv from GHC.Types.Name.Occurrence Counts the number of OccNames in an OccEnv - - - - - 165f98d8 by Simon Peyton Jones at 2025-05-06T09:02:39-04:00 Fix a bad untouchability bug im simplifyInfer This patch addresses #26004. The root cause was that simplifyInfer was willing to unify variables "far out". The fix, in runTcSWithEvBinds', is to initialise the inert set given-eq level with the current level. See (TGE6) in Note [Tracking Given equalities] in GHC.Tc.Solver.InertSet Two loosely related refactors: * Refactored approximateWCX to return just the free type variables of the un-quantified constraints. That avoids duplication of work (these free vars are needed in simplifyInfer) and makes it clearer that the constraints themselves are irrelevant. * A little local refactor of TcSMode, which reduces the number of parameters to runTcSWithEvBinds - - - - - 6e67fa08 by Ben Gamari at 2025-05-08T06:21:21-04:00 llvmGen: Fix built-in variable predicate Previously the predicate to identify LLVM builtin global variables was checking for `$llvm` rather than `@llvm` as it should. - - - - - a9d0a22c by Ben Gamari at 2025-05-08T06:21:22-04:00 llvmGen: Fix linkage of built-in arrays LLVM now insists that built-in arrays use Appending linkage, not Internal. Fixes #25769. - - - - - 9c6d2b1b by sheaf at 2025-05-08T06:22:11-04:00 Use mkTrAppChecked in ds_ev_typeable This change avoids violating the invariant of mkTrApp according to which the argument should not be a fully saturated function type. This ensures we don't return false negatives for type equality involving function types. Fixes #25998 - - - - - 75cadf81 by Ryan Hendrickson at 2025-05-08T06:22:55-04:00 haddock: Preserve indentation in multiline examples Intended for use with :{ :}, but doesn't look for those characters. Any consecutive lines with birdtracks will only have initial whitespace stripped up to the column of the first line. - - - - - fee9b351 by Cheng Shao at 2025-05-08T06:23:36-04:00 ci: re-enable chrome for wasm ghci browser tests Currently only firefox is enabled for wasm ghci browser tests, for some reason testing with chrome works on my machine but gets stuck on gitlab instance runners. This patch re-enables testing with chrome by passing `--no-sandbox`, since chrome sandboxing doesn't work in containers without `--cap-add=SYS_ADMIN`. - - - - - 282df905 by Vladislav Zavialov at 2025-05-09T03:18:25-04:00 Take subordinate 'type' specifiers into account This patch fixes multiple bugs (#22581, #25983, #25984, #25991) in name resolution of subordinate import lists. Bug #22581 ---------- In subordinate import lists, the use of the `type` namespace specifier used to be ignored. For example, this import statement was incorrectly accepted: import Prelude (Bool(type True)) Now it results in an error message: <interactive>:2:17: error: [GHC-51433] In the import of ‘Prelude’: a data type called ‘Bool’ is exported, but its subordinate item ‘True’ is not in the type namespace. Bug #25983 ---------- In subordinate import lists within a `hiding` clause, non-existent items led to a poor warning message with -Wdodgy-imports. Consider: import Prelude hiding (Bool(X)) The warning message for this import statement used to misreport the cause of the problem: <interactive>:3:24: warning: [GHC-56449] [-Wdodgy-imports] In the import of ‘Prelude’: an item called ‘Bool’ is exported, but it is a type. Now the warning message is correct: <interactive>:2:24: warning: [GHC-10237] [-Wdodgy-imports] In the import of ‘Prelude’: a data type called ‘Bool’ is exported, but it does not export any constructors or record fields called ‘X’. Bug #25984 ---------- In subordinate import lists within a `hiding` clause, non-existent items resulted in the entire import declaration being discarded. For example, this program was incorrectly accepted: import Prelude hiding (Bool(True,X)) t = True Now it results in an error message: <interactive>:2:5: error: [GHC-88464] Data constructor not in scope: True Bug #25991 ---------- In subordinate import lists, it was not possible to refer to a class method if there was an associated type of the same name: module M_helper where class C a b where type a # b (#) :: a -> b -> () module M where import M_helper (C((#))) This import declaration failed with: M.hs:2:28: error: [GHC-10237] In the import of ‘M_helper’: an item called ‘C’ is exported, but it does not export any children (constructors, class methods or field names) called ‘#’. Now it is accepted. Summary ------- The changes required to fix these bugs are almost entirely confined to GHC.Rename.Names. Other than that, there is a new error constructor BadImportNonTypeSubordinates with error code [GHC-51433]. Test cases: T22581a T22581b T22581c T22581d T25983a T25983b T25983c T25983d T25983e T25983f T25983g T25984a T25984b T25991a T25991b1 T25991b2 - - - - - 51b0ce8f by Simon Peyton Jones at 2025-05-09T03:19:07-04:00 Slighty improve `dropMisleading` Fix #26105, by upgrading the (horrible, hacky) `dropMisleading` function. This fix makes things a bit better but does not cure the underlying problem. - - - - - 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. - - - - - d6efc862 by Sjoerd Visscher at 2025-05-12T15:31:20+02:00 Calculate multiplicity for record selector functions Until now record selector functions always had multiplicity Many, but when all the other fields have been declared with multiplicity Many (including the case when there are no other fields), then the selector function is allowed to be used linearly too, as it is allowed to discard all the other fields. Since in that case the multiplicity can be both One and Many, the selector function is made multiplicity-polymorphic. - - - - - c23bbed5 by Sjoerd Visscher at 2025-05-12T19:18:01+02:00 Test setting linearEnabled always true - - - - - 802 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/hello.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/CodeGen.Platform.h - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/Lint.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Type.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/Data.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/Data/Graph/Directed/Reachability.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Config/CmmToAsm.hs - + compiler/GHC/Driver/Downsweep.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Env/Types.hs - compiler/GHC/Driver/Errors/Ppr.hs - compiler/GHC/Driver/Errors/Types.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - + compiler/GHC/Driver/MakeAction.hs - compiler/GHC/Driver/MakeFile.hs - + compiler/GHC/Driver/Messager.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline.hs-boot - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Driver/Session.hs - + compiler/GHC/Driver/Session/Units.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Breakpoints.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Solver/Types.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Binary.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Tidy.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Linker/Deps.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Parser/String.hs - compiler/GHC/Platform/Regs.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Unbound.hs - compiler/GHC/Rename/Utils.hs - + compiler/GHC/Runtime/Debugger/Breakpoints.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Eval/Types.hs - + compiler/GHC/Runtime/Eval/Utils.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/SysTools/Process.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Utils.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Default.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Solver/Rewrite.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Types/ErrCtxt.hs - compiler/GHC/Tc/Types/LclEnv.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Types/TH.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Tc/Utils/Concrete.hs - compiler/GHC/Tc/Utils/Env.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Avail.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Breakpoint.hs - compiler/GHC/Types/DefaultEnv.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/GREInfo.hs - compiler/GHC/Types/Name.hs - compiler/GHC/Types/Name/Occurrence.hs - compiler/GHC/Types/Name/Ppr.hs - compiler/GHC/Types/Name/Reader.hs - + compiler/GHC/Types/ThLevelIndex.hs - compiler/GHC/Types/TyThing/Ppr.hs - compiler/GHC/Unit/External.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Home/PackageTable.hs - compiler/GHC/Unit/Module/Deps.hs - − compiler/GHC/Unit/Module/External/Graph.hs - compiler/GHC/Unit/Module/Graph.hs - compiler/GHC/Unit/Module/Imported.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Unit/Module/ModNodeKey.hs - compiler/GHC/Unit/Module/ModSummary.hs - + compiler/GHC/Unit/Module/Stage.hs - compiler/GHC/Unit/Types.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Logger.hs - compiler/GHC/Utils/Outputable.hs - compiler/GHC/Utils/Panic/Plain.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/Language/Haskell/Syntax/ImpExp.hs - + compiler/Language/Haskell/Syntax/ImpExp/IsBoot.hs - compiler/Language/Haskell/Syntax/Module/Name.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/ghc.cabal.in - configure.ac - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/control.rst - docs/users_guide/exts/explicit_namespaces.rst - docs/users_guide/exts/instances.rst - docs/users_guide/exts/monad_comprehensions.rst - docs/users_guide/exts/named_defaults.rst - docs/users_guide/exts/parallel_list_comprehensions.rst - docs/users_guide/exts/template_haskell.rst - docs/users_guide/javascript.rst - docs/users_guide/phases.rst - docs/users_guide/runtime_control.rst - docs/users_guide/using-optimisation.rst - docs/users_guide/using-warnings.rst - + ghc/GHC/Driver/Session/Lint.hs - + ghc/GHC/Driver/Session/Mode.hs - ghc/GHCi/UI.hs - ghc/GHCi/UI/Monad.hs - ghc/Main.hs - ghc/ghc-bin.cabal.in - hadrian/README.md - hadrian/hadrian.cabal - hadrian/src/Oracles/Flag.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/BinaryDist.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Settings/Builders/Cabal.hs - hadrian/src/Settings/Builders/RunTest.hs - hadrian/src/Settings/Packages.hs - libraries/Cabal - libraries/Win32 - libraries/base/base.cabal.in - libraries/base/changelog.md - − libraries/base/src/GHC/ExecutionStack/Internal.hs - libraries/base/src/GHC/Records.hs - − libraries/base/src/GHC/TypeLits/Internal.hs - − libraries/base/src/GHC/TypeNats/Internal.hs - libraries/base/src/System/CPUTime/Windows.hsc - libraries/base/tests/IO/Makefile - libraries/base/tests/perf/encodingAllocations.hs - libraries/directory - libraries/ghc-internal/jsbits/base.js - libraries/ghc-internal/jsbits/errno.js - libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs - libraries/ghc-internal/src/GHC/Internal/System/Posix/Internals.hs - libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ResolvedBCO.hs - libraries/ghci/GHCi/Run.hs - libraries/haskeline - libraries/process - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - libraries/template-haskell/changelog.md - libraries/unix - llvm-targets - m4/fp_cc_supports_target.m4 - m4/fp_setup_windows_toolchain.m4 - m4/fptools_set_platform_vars.m4 - m4/ghc_tables_next_to_code.m4 - rts/Exception.cmm - rts/Interpreter.c - rts/RtsAPI.c - rts/RtsUtils.c - rts/StgCRun.c - rts/include/RtsAPI.h - rts/linker/PEi386.c - rts/win32/veh_excn.c - testsuite/config/ghc - testsuite/driver/testlib.py - testsuite/ghc-config/ghc-config.hs - testsuite/mk/boilerplate.mk - testsuite/tests/ado/ado004.stderr - testsuite/tests/annotations/should_fail/annfail03.stderr - testsuite/tests/annotations/should_fail/annfail04.stderr - testsuite/tests/annotations/should_fail/annfail06.stderr - testsuite/tests/annotations/should_fail/annfail09.stderr - testsuite/tests/backpack/should_fail/bkpfail51.stderr - + testsuite/tests/bytecode/T25975.hs - + testsuite/tests/bytecode/T25975.stdout - testsuite/tests/bytecode/all.T - testsuite/tests/cmm/should_run/AtomicFetch_cmm.cmm - + testsuite/tests/core-to-stg/T23865.hs - testsuite/tests/core-to-stg/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - + testsuite/tests/default/T25775.hs - + testsuite/tests/default/T25775.stderr - + testsuite/tests/default/T25857.hs - + testsuite/tests/default/T25857.stderr - + testsuite/tests/default/T25882.hs - + testsuite/tests/default/T25912.hs - + testsuite/tests/default/T25912.stdout - + testsuite/tests/default/T25912_helper.hs - + testsuite/tests/default/T25914.hs - + testsuite/tests/default/T25934.hs - testsuite/tests/default/all.T - testsuite/tests/default/default-fail01.stderr - testsuite/tests/default/default-fail02.stderr - testsuite/tests/default/default-fail03.stderr - testsuite/tests/default/default-fail04.stderr - testsuite/tests/default/default-fail08.stderr - + testsuite/tests/dependent/should_compile/GADTSingletons.hs - + testsuite/tests/dependent/should_compile/T12088a.hs - + testsuite/tests/dependent/should_compile/T12088b.hs - + testsuite/tests/dependent/should_compile/T12088c.hs - + testsuite/tests/dependent/should_compile/T12088d.hs - + testsuite/tests/dependent/should_compile/T12088e.hs - + testsuite/tests/dependent/should_compile/T12088f.hs - + testsuite/tests/dependent/should_compile/T12088g.hs - + testsuite/tests/dependent/should_compile/T12088i.hs - + testsuite/tests/dependent/should_compile/T12088j.hs - + testsuite/tests/dependent/should_compile/T12088mm1.hs - + testsuite/tests/dependent/should_compile/T12088mm1_helper.hs - + testsuite/tests/dependent/should_compile/T12088mm2.hs - + testsuite/tests/dependent/should_compile/T12088mm2_helper.hs - + testsuite/tests/dependent/should_compile/T12088mm3.hs - + testsuite/tests/dependent/should_compile/T12088mm3_helper.hs - + testsuite/tests/dependent/should_compile/T12088sg1.hs - + testsuite/tests/dependent/should_compile/T12088sg2.hs - + testsuite/tests/dependent/should_compile/T12088sg3.hs - + testsuite/tests/dependent/should_compile/T12239.hs - + testsuite/tests/dependent/should_compile/T13790.hs - + testsuite/tests/dependent/should_compile/T14668a.hs - + testsuite/tests/dependent/should_compile/T14668b.hs - testsuite/tests/dependent/should_compile/T14729.stderr - + testsuite/tests/dependent/should_compile/T15561.hs - testsuite/tests/dependent/should_compile/T15743.stderr - testsuite/tests/dependent/should_compile/T15743e.stderr - + testsuite/tests/dependent/should_compile/T16410.hs - + testsuite/tests/dependent/should_compile/T16448.hs - + testsuite/tests/dependent/should_compile/T16693.hs - + testsuite/tests/dependent/should_compile/T19611.hs - + testsuite/tests/dependent/should_compile/T20875.hs - + testsuite/tests/dependent/should_compile/T21172.hs - + testsuite/tests/dependent/should_compile/T22257a.hs - + testsuite/tests/dependent/should_compile/T22257b.hs - + testsuite/tests/dependent/should_compile/T25238.hs - + testsuite/tests/dependent/should_compile/T25834.hs - testsuite/tests/dependent/should_compile/all.T - testsuite/tests/deriving/should_compile/T14682.stderr - testsuite/tests/deriving/should_compile/T17339.stderr - testsuite/tests/determinism/determ021/determ021.stdout - testsuite/tests/diagnostic-codes/codes.stdout - + testsuite/tests/driver/RecompCompletePragma/A1.hs - + testsuite/tests/driver/RecompCompletePragma/A2.hs - + testsuite/tests/driver/RecompCompletePragma/A3.hs - + testsuite/tests/driver/RecompCompletePragma/A4.hs - + testsuite/tests/driver/RecompCompletePragma/B1.hs - + testsuite/tests/driver/RecompCompletePragma/C1.hs - + testsuite/tests/driver/RecompCompletePragma/C2.hs - + testsuite/tests/driver/RecompCompletePragma/C3.hs - + testsuite/tests/driver/RecompCompletePragma/Makefile - + testsuite/tests/driver/RecompCompletePragma/RecompCompleteFixity.stderr - + testsuite/tests/driver/RecompCompletePragma/RecompCompleteFixity.stdout - + testsuite/tests/driver/RecompCompletePragma/RecompCompleteFixityA.hs - + testsuite/tests/driver/RecompCompletePragma/RecompCompleteFixityB.hs - + testsuite/tests/driver/RecompCompletePragma/RecompCompleteIndependence.hs - + testsuite/tests/driver/RecompCompletePragma/RecompCompleteIndependence.stdout - + testsuite/tests/driver/RecompCompletePragma/RecompCompletePragma.stderr - + testsuite/tests/driver/RecompCompletePragma/RecompCompletePragma.stdout - + testsuite/tests/driver/RecompCompletePragma/RecompCompletePragma2.stdout - + testsuite/tests/driver/RecompCompletePragma/RecompCompletePragmaA.hs - + testsuite/tests/driver/RecompCompletePragma/RecompCompletePragmaB.hs - + testsuite/tests/driver/RecompCompletePragma/all.T - + testsuite/tests/driver/RecompExportedDefault/A.hs - + testsuite/tests/driver/RecompExportedDefault/A2.hs - + testsuite/tests/driver/RecompExportedDefault/A3.hs - + testsuite/tests/driver/RecompExportedDefault/A4.hs - + testsuite/tests/driver/RecompExportedDefault/Makefile - + testsuite/tests/driver/RecompExportedDefault/RecompExportedDefault.hs - + testsuite/tests/driver/RecompExportedDefault/RecompExportedDefault.stdout - + testsuite/tests/driver/RecompExportedDefault/all.T - + testsuite/tests/driver/RecompExports/Makefile - + testsuite/tests/driver/RecompExports/RecompExports1.stderr - + testsuite/tests/driver/RecompExports/RecompExports1.stdout - + testsuite/tests/driver/RecompExports/RecompExports1_M.hs_1 - + testsuite/tests/driver/RecompExports/RecompExports1_M.hs_2 - + testsuite/tests/driver/RecompExports/RecompExports1_M.hs_3 - + testsuite/tests/driver/RecompExports/RecompExports1_N.hs - + testsuite/tests/driver/RecompExports/RecompExports2.stderr - + testsuite/tests/driver/RecompExports/RecompExports2.stdout - + testsuite/tests/driver/RecompExports/RecompExports2_M.hs_1 - + testsuite/tests/driver/RecompExports/RecompExports2_M.hs_2 - + testsuite/tests/driver/RecompExports/RecompExports2_M.hs_3 - + testsuite/tests/driver/RecompExports/RecompExports2_N.hs - + testsuite/tests/driver/RecompExports/RecompExports3.stderr - + testsuite/tests/driver/RecompExports/RecompExports3.stdout - + testsuite/tests/driver/RecompExports/RecompExports3_M.hs_1 - + testsuite/tests/driver/RecompExports/RecompExports3_M.hs_2 - + testsuite/tests/driver/RecompExports/RecompExports3_M.hs_3 - + testsuite/tests/driver/RecompExports/RecompExports3_N.hs - + testsuite/tests/driver/RecompExports/RecompExports4.stderr - + testsuite/tests/driver/RecompExports/RecompExports4.stdout - + testsuite/tests/driver/RecompExports/RecompExports4_M.hs_1 - + testsuite/tests/driver/RecompExports/RecompExports4_M.hs_2 - + testsuite/tests/driver/RecompExports/RecompExports4_N.hs - + testsuite/tests/driver/RecompExports/RecompExports5.stdout - + testsuite/tests/driver/RecompExports/RecompExports5_M.hs_1 - + testsuite/tests/driver/RecompExports/RecompExports5_M.hs_2 - + testsuite/tests/driver/RecompExports/RecompExports5_N.hs - + testsuite/tests/driver/RecompExports/all.T - testsuite/tests/driver/T20459.stderr - testsuite/tests/driver/T24196/T24196.stderr - testsuite/tests/driver/T24275/T24275.stderr - + testsuite/tests/driver/T4437.stdout - testsuite/tests/driver/json2.stderr - testsuite/tests/gadt/T19847a.stderr - + testsuite/tests/gadt/T23298.hs - + testsuite/tests/gadt/T23298.stderr - testsuite/tests/gadt/all.T - + testsuite/tests/ghc-api/fixed-nodes/FixedNodes.hs - + testsuite/tests/ghc-api/fixed-nodes/FixedNodes.stdout - + testsuite/tests/ghc-api/fixed-nodes/InterfaceModuleGraph.hs - + testsuite/tests/ghc-api/fixed-nodes/InterfaceModuleGraph.stdout - + testsuite/tests/ghc-api/fixed-nodes/Makefile - + testsuite/tests/ghc-api/fixed-nodes/ModuleGraphInvariants.hs - + testsuite/tests/ghc-api/fixed-nodes/ModuleGraphInvariants.stdout - + testsuite/tests/ghc-api/fixed-nodes/T1.hs - + testsuite/tests/ghc-api/fixed-nodes/T1A.hs - + testsuite/tests/ghc-api/fixed-nodes/T1B.hs - + testsuite/tests/ghc-api/fixed-nodes/T1C.hs - + testsuite/tests/ghc-api/fixed-nodes/all.T - testsuite/tests/ghc-api/settings-escape/T11938.hs → testsuite/tests/ghc-api/settings-escape/T24265.hs - testsuite/tests/ghc-api/settings-escape/T11938.stderr → testsuite/tests/ghc-api/settings-escape/T24265.stderr - + testsuite/tests/ghc-api/settings-escape/T25204.hs - + testsuite/tests/ghc-api/settings-escape/T25204.stdout - + testsuite/tests/ghc-api/settings-escape/T25204_C.c - testsuite/tests/ghc-api/settings-escape/all.T - + testsuite/tests/ghc-api/settings-escape/ghc-install-folder/ghc version.h - testsuite/tests/ghc-api/settings-escape/ghc-install-folder/lib/.gitkeep → testsuite/tests/ghc-api/settings-escape/ghc-install-folder/lib with spaces/.gitkeep - testsuite/tests/ghc-e/should_fail/T9930fail.stderr - + testsuite/tests/ghci.debugger/scripts/T25932.hs - + testsuite/tests/ghci.debugger/scripts/T25932.script - + testsuite/tests/ghci.debugger/scripts/T25932.stdout - testsuite/tests/ghci.debugger/scripts/T8487.script - testsuite/tests/ghci.debugger/scripts/all.T - testsuite/tests/ghci.debugger/scripts/break018.script - testsuite/tests/ghci.debugger/scripts/break018.stdout - testsuite/tests/ghci.debugger/scripts/dynbrk004.stdout - testsuite/tests/ghci.debugger/scripts/dynbrk007.script - testsuite/tests/ghci.debugger/scripts/dynbrk007.stdout - + testsuite/tests/ghci/scripts/GhciPackageRename.hs - + testsuite/tests/ghci/scripts/GhciPackageRename.script - + testsuite/tests/ghci/scripts/GhciPackageRename.stdout - testsuite/tests/ghci/scripts/T12550.stdout - testsuite/tests/ghci/scripts/T4175.stdout - testsuite/tests/ghci/scripts/all.T - testsuite/tests/ghci/scripts/ghci024.stdout - testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 - testsuite/tests/ghci/scripts/ghci064.stdout - testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.hs - testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr - testsuite/tests/hpc/fork/hpc_fork.stdout - testsuite/tests/hpc/function/tough.stdout - testsuite/tests/hpc/function2/tough2.stdout - testsuite/tests/indexed-types/should_compile/T15711.stderr - testsuite/tests/indexed-types/should_compile/T15852.stderr - testsuite/tests/indexed-types/should_compile/T3017.stderr - testsuite/tests/indexed-types/should_fail/T3330c.stderr - testsuite/tests/indexed-types/should_fail/T4174.stderr - testsuite/tests/indexed-types/should_fail/T8227.stderr - testsuite/tests/indexed-types/should_fail/T8550.stderr - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/interface-stability/template-haskell-exports.stdout - + testsuite/tests/linear/should_compile/LinearRecordSelector.hs - testsuite/tests/linear/should_compile/all.T - + testsuite/tests/linear/should_fail/LinearRecordSelectorFail.hs - + testsuite/tests/linear/should_fail/LinearRecordSelectorFail.stderr - testsuite/tests/linear/should_fail/all.T - testsuite/tests/linters/notes.stdout - testsuite/tests/module/T21826.stderr - testsuite/tests/module/all.T - testsuite/tests/module/mod132.stderr - testsuite/tests/module/mod147.stderr - testsuite/tests/module/mod185.stderr - testsuite/tests/module/mod58.stderr - testsuite/tests/module/mod73.hs - testsuite/tests/module/mod73.stderr - testsuite/tests/module/mod81.stderr - testsuite/tests/module/mod91.stderr - testsuite/tests/parser/should_compile/DumpParsedAst.stderr - testsuite/tests/parser/should_compile/DumpRenamedAst.stderr - testsuite/tests/parser/should_compile/DumpSemis.stderr - testsuite/tests/parser/should_compile/KindSigs.stderr - testsuite/tests/parser/should_compile/T14189.stderr - testsuite/tests/parser/should_fail/readFail038.stderr - + testsuite/tests/parser/should_run/T25937.hs - + testsuite/tests/parser/should_run/T25937.stdout - testsuite/tests/parser/should_run/all.T - + testsuite/tests/parser/should_run/parser_unit_tests.hs - testsuite/tests/partial-sigs/should_compile/ADT.stderr - testsuite/tests/partial-sigs/should_compile/AddAndOr1.stderr - testsuite/tests/partial-sigs/should_compile/AddAndOr2.stderr - testsuite/tests/partial-sigs/should_compile/AddAndOr3.stderr - testsuite/tests/partial-sigs/should_compile/AddAndOr4.stderr - testsuite/tests/partial-sigs/should_compile/AddAndOr5.stderr - testsuite/tests/partial-sigs/should_compile/AddAndOr6.stderr - testsuite/tests/partial-sigs/should_compile/BoolToBool.stderr - testsuite/tests/partial-sigs/should_compile/DataFamilyInstanceLHS.stderr - testsuite/tests/partial-sigs/should_compile/Defaulting1MROn.stderr - testsuite/tests/partial-sigs/should_compile/Defaulting2MROff.stderr - testsuite/tests/partial-sigs/should_compile/Defaulting2MROn.stderr - testsuite/tests/partial-sigs/should_compile/Either.stderr - testsuite/tests/partial-sigs/should_compile/EqualityConstraint.stderr - testsuite/tests/partial-sigs/should_compile/Every.stderr - testsuite/tests/partial-sigs/should_compile/EveryNamed.stderr - testsuite/tests/partial-sigs/should_compile/ExpressionSig.stderr - testsuite/tests/partial-sigs/should_compile/ExpressionSigNamed.stderr - testsuite/tests/partial-sigs/should_compile/ExtraConstraints1.stderr - testsuite/tests/partial-sigs/should_compile/ExtraConstraints2.stderr - testsuite/tests/partial-sigs/should_compile/ExtraConstraints3.stderr - testsuite/tests/partial-sigs/should_compile/ExtraNumAMROff.stderr - testsuite/tests/partial-sigs/should_compile/ExtraNumAMROn.stderr - testsuite/tests/partial-sigs/should_compile/Forall1.stderr - testsuite/tests/partial-sigs/should_compile/GenNamed.stderr - testsuite/tests/partial-sigs/should_compile/HigherRank1.stderr - testsuite/tests/partial-sigs/should_compile/HigherRank2.stderr - testsuite/tests/partial-sigs/should_compile/LocalDefinitionBug.stderr - testsuite/tests/partial-sigs/should_compile/Meltdown.stderr - testsuite/tests/partial-sigs/should_compile/MonoLocalBinds.stderr - testsuite/tests/partial-sigs/should_compile/NamedTyVar.stderr - testsuite/tests/partial-sigs/should_compile/NamedWildcardInDataFamilyInstanceLHS.stderr - testsuite/tests/partial-sigs/should_compile/NamedWildcardInTypeFamilyInstanceLHS.stderr - testsuite/tests/partial-sigs/should_compile/ParensAroundContext.stderr - testsuite/tests/partial-sigs/should_compile/PatBind.stderr - testsuite/tests/partial-sigs/should_compile/PatBind2.stderr - testsuite/tests/partial-sigs/should_compile/PatternSig.stderr - testsuite/tests/partial-sigs/should_compile/Recursive.stderr - testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcards.stderr - testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcardsGood.stderr - testsuite/tests/partial-sigs/should_compile/ShowNamed.stderr - testsuite/tests/partial-sigs/should_compile/SimpleGen.stderr - testsuite/tests/partial-sigs/should_compile/SkipMany.stderr - testsuite/tests/partial-sigs/should_compile/SomethingShowable.stderr - testsuite/tests/partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr - testsuite/tests/partial-sigs/should_compile/Uncurry.stderr - testsuite/tests/partial-sigs/should_compile/UncurryNamed.stderr - testsuite/tests/partial-sigs/should_compile/WarningWildcardInstantiations.stderr - testsuite/tests/perf/compiler/Makefile - testsuite/tests/perf/compiler/WWRec.hs - testsuite/tests/perf/compiler/all.T - testsuite/tests/perf/compiler/hard_hole_fits.stderr - testsuite/tests/plugins/defaulting-plugin/DefaultLifted.hs - testsuite/tests/polykinds/T15592.stderr - testsuite/tests/polykinds/T15592b.stderr - testsuite/tests/polykinds/T18300.hs - testsuite/tests/polykinds/T18300.stderr - testsuite/tests/primops/should_run/all.T - testsuite/tests/printer/T17697.stderr - testsuite/tests/printer/T18052a.stderr - testsuite/tests/quasiquotation/T7918.hs - testsuite/tests/quasiquotation/qq001/qq001.stderr - testsuite/tests/quasiquotation/qq002/qq002.stderr - testsuite/tests/quasiquotation/qq003/qq003.stderr - testsuite/tests/quasiquotation/qq004/qq004.stderr - + testsuite/tests/quotes/T5721.stderr - + testsuite/tests/rename/should_compile/T22581c.hs - + testsuite/tests/rename/should_compile/T22581c_helper.hs - + testsuite/tests/rename/should_compile/T22581d.script - + testsuite/tests/rename/should_compile/T22581d.stdout - + testsuite/tests/rename/should_compile/T25983a.hs - + testsuite/tests/rename/should_compile/T25983a.stderr - + testsuite/tests/rename/should_compile/T25983b.hs - + testsuite/tests/rename/should_compile/T25983b.stderr - + testsuite/tests/rename/should_compile/T25983c.hs - + testsuite/tests/rename/should_compile/T25983c.stderr - + testsuite/tests/rename/should_compile/T25983d.hs - + testsuite/tests/rename/should_compile/T25983d.stderr - + testsuite/tests/rename/should_compile/T25983e.hs - + testsuite/tests/rename/should_compile/T25983e.stderr - + testsuite/tests/rename/should_compile/T25983f.hs - + testsuite/tests/rename/should_compile/T25983f.stderr - + testsuite/tests/rename/should_compile/T25983g.hs - + testsuite/tests/rename/should_compile/T25983g.stderr - + testsuite/tests/rename/should_compile/T25984a.hs - + testsuite/tests/rename/should_compile/T25984a.stderr - + testsuite/tests/rename/should_compile/T25984a_helper.hs - + testsuite/tests/rename/should_compile/T25991a.hs - + testsuite/tests/rename/should_compile/T25991a_helper.hs - testsuite/tests/rename/should_compile/all.T - testsuite/tests/rename/should_fail/SimilarNamesImport.stderr - testsuite/tests/rename/should_fail/T19843c.stderr - + testsuite/tests/rename/should_fail/T22581a.hs - + testsuite/tests/rename/should_fail/T22581a.stderr - + testsuite/tests/rename/should_fail/T22581a_helper.hs - + testsuite/tests/rename/should_fail/T22581b.hs - + testsuite/tests/rename/should_fail/T22581b.stderr - + testsuite/tests/rename/should_fail/T22581b_helper.hs - testsuite/tests/rename/should_fail/T23510a.hs - testsuite/tests/rename/should_fail/T23510a.stderr - + testsuite/tests/rename/should_fail/T23982.hs - + testsuite/tests/rename/should_fail/T23982.stderr - + testsuite/tests/rename/should_fail/T23982_aux.hs - + testsuite/tests/rename/should_fail/T23982b.hs - + testsuite/tests/rename/should_fail/T23982b.stderr - + testsuite/tests/rename/should_fail/T23982b_aux.hs - + testsuite/tests/rename/should_fail/T25877.hs - + testsuite/tests/rename/should_fail/T25877.stderr - + testsuite/tests/rename/should_fail/T25877_aux.hs - + testsuite/tests/rename/should_fail/T25984b.hs - + testsuite/tests/rename/should_fail/T25984b.stderr - + testsuite/tests/rename/should_fail/T25991b1.hs - + testsuite/tests/rename/should_fail/T25991b1.stderr - + testsuite/tests/rename/should_fail/T25991b2.hs - + testsuite/tests/rename/should_fail/T25991b2.stderr - + testsuite/tests/rename/should_fail/T25991b_helper.hs - testsuite/tests/rename/should_fail/T9006.stderr - testsuite/tests/rename/should_fail/all.T - testsuite/tests/roles/should_compile/Roles1.stderr - testsuite/tests/roles/should_compile/Roles14.stderr - testsuite/tests/roles/should_compile/Roles2.stderr - testsuite/tests/roles/should_compile/Roles3.stderr - testsuite/tests/roles/should_compile/Roles4.stderr - testsuite/tests/roles/should_compile/T8958.stderr - testsuite/tests/rts/T13082/Makefile - testsuite/tests/rts/T13082/T13082_fail.stderr → testsuite/tests/rts/T13082/T13082_fail.stdout - testsuite/tests/showIface/DocsInHiFile1.stdout - testsuite/tests/showIface/DocsInHiFileTH.stdout - testsuite/tests/showIface/HaddockIssue849.stdout - testsuite/tests/showIface/HaddockOpts.stdout - testsuite/tests/showIface/HaddockSpanIssueT24378.stdout - testsuite/tests/showIface/LanguageExts.stdout - testsuite/tests/showIface/MagicHashInHaddocks.stdout - testsuite/tests/showIface/NoExportList.stdout - testsuite/tests/showIface/Orphans.stdout - testsuite/tests/showIface/PragmaDocs.stdout - testsuite/tests/showIface/ReExports.stdout - testsuite/tests/simplCore/should_compile/Makefile - testsuite/tests/simplCore/should_compile/T23307c.stderr - + testsuite/tests/simplCore/should_compile/T25703.hs - + testsuite/tests/simplCore/should_compile/T25703.stderr - + testsuite/tests/simplCore/should_compile/T25703a.hs - + testsuite/tests/simplCore/should_compile/T25703a.stderr - + testsuite/tests/simplCore/should_compile/T25883.hs - + testsuite/tests/simplCore/should_compile/T25883.substr-simpl - + testsuite/tests/simplCore/should_compile/T25883b.hs - + testsuite/tests/simplCore/should_compile/T25883b.substr-simpl - + testsuite/tests/simplCore/should_compile/T25883c.hs - + testsuite/tests/simplCore/should_compile/T25883c.substr-simpl - + testsuite/tests/simplCore/should_compile/T25883d.hs - + testsuite/tests/simplCore/should_compile/T25883d.stderr - + testsuite/tests/simplCore/should_compile/T25883d_import.hs - + testsuite/tests/simplCore/should_compile/T25965.hs - + testsuite/tests/simplCore/should_compile/T25976.hs - + testsuite/tests/simplCore/should_compile/T3990b.hs - + testsuite/tests/simplCore/should_compile/T3990b.stdout - + testsuite/tests/simplCore/should_compile/T3990c.hs - + testsuite/tests/simplCore/should_compile/T3990c.stdout - testsuite/tests/simplCore/should_compile/all.T - testsuite/tests/simplCore/should_fail/T25672.stderr - + testsuite/tests/simplCore/should_run/T23429.hs - + testsuite/tests/simplCore/should_run/T23429.stdout - testsuite/tests/simplCore/should_run/all.T - + testsuite/tests/splice-imports/ClassA.hs - + testsuite/tests/splice-imports/InstanceA.hs - + testsuite/tests/splice-imports/Makefile - + testsuite/tests/splice-imports/SI01.hs - + testsuite/tests/splice-imports/SI01A.hs - + testsuite/tests/splice-imports/SI02.hs - + testsuite/tests/splice-imports/SI03.hs - + testsuite/tests/splice-imports/SI03.stderr - + testsuite/tests/splice-imports/SI04.hs - + testsuite/tests/splice-imports/SI05.hs - + testsuite/tests/splice-imports/SI05.stderr - + testsuite/tests/splice-imports/SI05A.hs - + testsuite/tests/splice-imports/SI06.hs - + testsuite/tests/splice-imports/SI07.hs - + testsuite/tests/splice-imports/SI07.stderr - + testsuite/tests/splice-imports/SI07A.hs - + testsuite/tests/splice-imports/SI08.hs - + testsuite/tests/splice-imports/SI08.stderr - + testsuite/tests/splice-imports/SI08_oneshot.stderr - + testsuite/tests/splice-imports/SI09.hs - + testsuite/tests/splice-imports/SI10.hs - + testsuite/tests/splice-imports/SI13.hs - + testsuite/tests/splice-imports/SI14.hs - + testsuite/tests/splice-imports/SI14.stderr - + testsuite/tests/splice-imports/SI15.hs - + testsuite/tests/splice-imports/SI15.stderr - + testsuite/tests/splice-imports/SI16.hs - + testsuite/tests/splice-imports/SI16.stderr - + testsuite/tests/splice-imports/SI17.hs - + testsuite/tests/splice-imports/SI18.hs - + testsuite/tests/splice-imports/SI18.stderr - + testsuite/tests/splice-imports/SI19.hs - + testsuite/tests/splice-imports/SI19A.hs - + testsuite/tests/splice-imports/SI20.hs - + testsuite/tests/splice-imports/SI20.stderr - + testsuite/tests/splice-imports/SI21.hs - + testsuite/tests/splice-imports/SI21.stderr - + testsuite/tests/splice-imports/SI22.hs - + testsuite/tests/splice-imports/SI22.stderr - + testsuite/tests/splice-imports/SI23.hs - + testsuite/tests/splice-imports/SI23A.hs - + testsuite/tests/splice-imports/SI24.hs - + testsuite/tests/splice-imports/SI25.hs - + testsuite/tests/splice-imports/SI25.stderr - + testsuite/tests/splice-imports/SI25Helper.hs - + testsuite/tests/splice-imports/SI26.hs - + testsuite/tests/splice-imports/SI27.hs - + testsuite/tests/splice-imports/SI27.stderr - + testsuite/tests/splice-imports/SI28.hs - + testsuite/tests/splice-imports/SI28.stderr - + testsuite/tests/splice-imports/SI29.hs - + testsuite/tests/splice-imports/SI29.stderr - + testsuite/tests/splice-imports/SI30.script - + testsuite/tests/splice-imports/SI30.stdout - + testsuite/tests/splice-imports/SI31.script - + testsuite/tests/splice-imports/SI31.stderr - + testsuite/tests/splice-imports/SI32.script - + testsuite/tests/splice-imports/SI32.stdout - + testsuite/tests/splice-imports/SI33.script - + testsuite/tests/splice-imports/SI33.stdout - + testsuite/tests/splice-imports/SI34.hs - + testsuite/tests/splice-imports/SI34.stderr - + testsuite/tests/splice-imports/SI34M1.hs - + testsuite/tests/splice-imports/SI34M2.hs - + testsuite/tests/splice-imports/SI35.hs - + testsuite/tests/splice-imports/SI35A.hs - + testsuite/tests/splice-imports/SI36.hs - + testsuite/tests/splice-imports/SI36.stderr - + testsuite/tests/splice-imports/SI36_A.hs - + testsuite/tests/splice-imports/SI36_B1.hs - + testsuite/tests/splice-imports/SI36_B2.hs - + testsuite/tests/splice-imports/SI36_B3.hs - + testsuite/tests/splice-imports/SI36_C1.hs - + testsuite/tests/splice-imports/SI36_C2.hs - + testsuite/tests/splice-imports/SI36_C3.hs - + testsuite/tests/splice-imports/all.T - testsuite/tests/th/T15365.stderr - testsuite/tests/th/T16976z.stderr - testsuite/tests/th/T17820a.stderr - testsuite/tests/th/T17820b.stderr - testsuite/tests/th/T17820c.stderr - testsuite/tests/th/T17820d.stderr - testsuite/tests/th/T17820e.stderr - testsuite/tests/th/T1835.stdout - testsuite/tests/th/T21547.stderr - testsuite/tests/th/T23829_hasty.stderr - testsuite/tests/th/T23829_hasty_b.stderr - testsuite/tests/th/T23829_tardy.ghc.stderr - testsuite/tests/th/T5795.stderr - testsuite/tests/th/TH_Roles2.stderr - testsuite/tests/typecheck/should_compile/LoopOfTheDay1.hs - testsuite/tests/typecheck/should_compile/LoopOfTheDay2.hs - testsuite/tests/typecheck/should_compile/LoopOfTheDay3.hs - testsuite/tests/typecheck/should_compile/T12763.stderr - testsuite/tests/typecheck/should_compile/T18406b.stderr - testsuite/tests/typecheck/should_compile/T18529.stderr - testsuite/tests/typecheck/should_compile/T21023.stderr - testsuite/tests/typecheck/should_compile/T25266a.stderr - + testsuite/tests/typecheck/should_compile/T25960.hs - + testsuite/tests/typecheck/should_compile/T26020.hs - + testsuite/tests/typecheck/should_compile/T26020a.hs - + testsuite/tests/typecheck/should_compile/T26020a_help.hs - testsuite/tests/typecheck/should_compile/T7050.stderr - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T12729.stderr - testsuite/tests/typecheck/should_fail/T12921.stderr - testsuite/tests/typecheck/should_fail/T18851.stderr - testsuite/tests/typecheck/should_fail/T19978.stderr - + testsuite/tests/typecheck/should_fail/T24090a.hs - + testsuite/tests/typecheck/should_fail/T24090a.stderr - + testsuite/tests/typecheck/should_fail/T24090b.hs - testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr → testsuite/tests/typecheck/should_fail/T24090b.stderr - + testsuite/tests/typecheck/should_fail/T25004k.hs - + testsuite/tests/typecheck/should_fail/T25004k.stderr - + testsuite/tests/typecheck/should_fail/T26004.hs - + testsuite/tests/typecheck/should_fail/T26004.stderr - + testsuite/tests/typecheck/should_fail/T26015.hs - + testsuite/tests/typecheck/should_fail/T26015.stderr - testsuite/tests/typecheck/should_fail/T3966.stderr - + testsuite/tests/typecheck/should_fail/T3966b.hs - + testsuite/tests/typecheck/should_fail/T3966b.stderr - testsuite/tests/typecheck/should_fail/T6018fail.stderr - testsuite/tests/typecheck/should_fail/T7453.stderr - testsuite/tests/typecheck/should_fail/all.T - + testsuite/tests/typecheck/should_run/T25998.hs - + testsuite/tests/typecheck/should_run/T25998.stdout - testsuite/tests/typecheck/should_run/all.T - testsuite/tests/unboxedsums/unpack_sums_5.stderr - + testsuite/tests/vdq-rta/should_fail/T23738_fail_pun.hs - + testsuite/tests/vdq-rta/should_fail/T23738_fail_pun.stderr - testsuite/tests/vdq-rta/should_fail/all.T - testsuite/tests/warnings/should_compile/WarnNoncanonical.stderr - testsuite/tests/wasm/should_run/control-flow/README.md - − testsuite/tests/wasm/should_run/control-flow/WasmControlFlow.stdout - testsuite/tests/wasm/should_run/control-flow/all.T - testsuite/tests/wcompat-warnings/Template.hs - utils/check-exact/ExactPrint.hs - utils/count-deps/Main.hs - utils/ghc-toolchain/exe/Main.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/Interface/RenameType.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs - utils/haddock/haddock-library/test/Documentation/Haddock/ParserSpec.hs - utils/hsc2hs - utils/llvm-targets/gen-data-layout.sh The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8dc4ca415059b4ac67a17000bbc43f0... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8dc4ca415059b4ac67a17000bbc43f0... You're receiving this email because of your account on gitlab.haskell.org.