[Git][ghc/ghc][wip/T25647] 104 commits: users guide: Fix typo

Patrick (@soulomoon) gitlab at gitlab.haskell.org
Tue Mar 11 22:33:51 UTC 2025


Patrick pushed to branch wip/T25647 at Glasgow Haskell Compiler / GHC


Commits:
cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00
users guide: Fix typo
- - - - -
1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00
testsuite: Don't count fragile passes as failures in JUnit output

As noted in #25806, the testsuite driver's JUnit output
previously considered passes of fragile tests to be failures. Fix this.

Closes #25806.
- - - - -
589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00
Use panic rather than error in expectJust

Otherwise, we would not get a callstack printed out when the exception
occurs.

Fixes #25829

- - - - -
d450e88e by sheaf at 2025-03-11T06:42:59-04:00
Solve Wanted quantified constraints from Givens

This commit ensures we directly solve Wanted quantified constraints from
matching inert Given quantified constraints,instead of going through the
trouble of emitting an implication constraint and processing that.

This is not just an optimisation; it makes our lives easier when
generating RULEs for specialisation.
See Note [Solving Wanted QCs from Given QCs] for details

Fixes #25758

- - - - -
48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00
testsuite: Add testcase for #25577

- - - - -
d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00
testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests

These tests can be expressed perfectly well using the testsuite driver
itself.

- - - - -
2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00
rts/linker/MachO: Assert that GOT relocations have GOT entries

In #25577 we found that some GOT relocation types were not being given
relocation entries. Add assertions to catch this sort of failure in the
future.

- - - - -
8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00
rts/linker/MachO: Account for internal GOT references in GOT construction

Previously we failed to give GOT slots to symbols which were referred to
by GOT relocations in the same module. This lead to #25577.

Fix this by explicitly traversing relocation lists and maintaining a
`needs_got` flag for each symbol.

Fixes #25577.

- - - - -
7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00
One list in ConPat (part of #25127)

This patch changes PrefixCon to use one list instead of two:

	-data HsConDetails tyarg arg rec
	-  = PrefixCon [tyarg] [arg]
	+data HsConDetails arg rec
	+  = PrefixCon [arg]
	   | RecCon    rec
	   | InfixCon  arg arg

The [tyarg] list is now gone. To understand the effect of this change,
recall that there are three instantiations of HsConDetails:

1. type HsConPatDetails p =
      HsConDetails (HsConPatTyArg (NoGhcTc p))  -- tyarg
                   (LPat p)                     -- arg
                   (HsRecFields p (LPat p))     -- rec

2. type HsConDeclH98Details pass =
      HsConDetails Void                              -- tyarg
                   (HsScaled pass (LBangType pass))  -- arg
                   (XRec pass [LConDeclField pass])  -- rec

3. type HsPatSynDetails pass =
      HsConDetails Void                     -- tyarg
                   (LIdP pass)              -- arg
                   [RecordPatSynField pass] -- rec

In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg]
list was always empty. Its removal is basically a no-op.

The interesting case is (1), which is used in ConPat to represent
pattern matching of the form (MkE @tp1 @tp2 p1 p2).
With this patch, its representation is changed as follows:

  ConPat "MkE" [tp1, tp2] [p1, p2]               -- old
  ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2]  -- new

The new mixed-list representation is consintent with lambdas, where
InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body.

The immediate effect of the new representation is an improvement to
error messages. Consider the pattern (Con x @t y). Previously it
resulted in a parse error because @t could not occur after x. Now it is
reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication.

In the long term, this is intended as preparation for #18389 and #25127,
which would make (Con x @t y) potentially valid, e.g. if its type is
  Con :: forall a -> forall b. (a, b) -> T

The TH AST is left unchanged for the moment to avoid breakage.

- - - - -
cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00
Error message with EmptyCase and RequiredTypeArguments (#25004)

Fix a panic triggered by a combination of \case{} and forall t ->

  ghci> let f :: forall (xs :: Type) -> (); f = \case {}
  panic! (the 'impossible' happened)
    GHC version 9.10.1:
          Util: only

The new error message looks like this:

  ghci> let f :: forall (xs :: Type) -> (); f = \case {}
  <interactive>:5:41: error: [GHC-48010]
      • Empty list of alternatives in \case expression
        checked against a forall-type: forall xs -> ...

This is achieved as follows:

* A new data type, BadEmptyCaseReason, is now used to describe
  why an empty case has been rejected. Used in TcRnEmptyCase.

* HsMatchContextRn is passed to tcMatches, so that the type checker
  can attach the syntactic context to the error message.

* tcMatches now rejects type arguments if the list of alternatives is
  empty. This is what fixes the bug.

- - - - -
37d8b50b by sheaf at 2025-03-11T06:43:06-04:00
user's guide: consolidate defaulting documentation

This commit adds a new section on defaulting, which consolidates various
parts of documentation surrounding defaulting into one central place.

It explains type class defaulting in detail, extensions to it with
OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well
as other defaulting mechanisms (e.g. kind-based defaulting such as
RuntimeRep defaulting, and defaulting of equalities).

- - - - -
0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00
user's guide: flesh out XOverloadedStrings docs

This commit extends the documentation of the OverloadedStrings extension
with some usage information, in particular suggestions to:

  - use default declarations, such as `default (Text)` or
    `default IsString(Text)` (with the NamedDefaults extension),

  - enable the ExtendedDefaultRules extension to relax the requirement
    that a defaultable type variable must only appear in unary standard
    classes

Fixes #23388

- - - - -
2df171d4 by sheaf at 2025-03-11T06:43:06-04:00
user's guide: NamedDefaults vs ExtendedDefaultRules

This commit clarifies the defaulting rules with NamedDefaults,
in particular in situations where a type variable appears in other
constraints than standard/unary constraints.

- - - - -
77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00
Take into account all flags when computing iface_hash

The "interface hash" should contain a hash of everything in the
interface file. We are not doing that yet but at least a start is to
include a hash of everything in `mi_self_recomp`, rather than just
`mi_src_hash` and `mi_usages`.

In particular, this fixes #25837, a bug where we should recompile a
`dyn_hi` file but fail to do so.

- - - - -
48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00
Pass -fPIC to dynamicToo001 test to avoid platform dependence issues

On darwin platforms, `-fPIC` is always enabled but on linux it is only
enabled in the dynamic flavour. This can cause a difference in
interface files (see #25836).

The purpose of this test isn't to test module A recompilation, so we
avoid this platform dependency by always passing `-fPIC`.

- - - - -
03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00
Remove mi_used_th field from interface files

In the distant past, recompilation checking was disabled for interfaces which used
TemplateHaskell, but for several years now recompilation checking has
been more fine-grained. This has rendered this field unused and
lingering in an interface file.

- - - - -
6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00
Remove mi_hpc field from interface files

The `mi_hpc` field is not used for anything as far as I can discern so
there is no reason to record in the private interface of a module that
there are modules in the transitive closure which use `hpc`.

You can freely mix modules which use `-fhpc` and ones which don't.

Whether to recompile a module due to `-fhpc` being passed to the module
itself is determined in `fingerprintDynFlags`.

- - - - -
b7ac06e0 by Simon Peyton Jones at 2025-03-11T22:33:40+00:00
WIP towards #25267

- - - - -
e6f340e8 by Simon Peyton Jones at 2025-03-11T22:33:40+00:00
Wibbles

- - - - -
ad87c5f9 by Simon Peyton Jones at 2025-03-11T22:33:40+00:00
Default tyvars in data/newtype insnstances

This is what fixes #25647

- - - - -
7cb18d6f by Simon Peyton Jones at 2025-03-11T22:33:40+00:00
wibbles

Including fix for #25725

- - - - -
afd12256 by Simon Peyton Jones at 2025-03-11T22:33:40+00:00
Wibble

- - - - -
e2111440 by Patrick at 2025-03-11T22:33:40+00:00
add more tests

- - - - -
d4400437 by Patrick at 2025-03-11T22:33:40+00:00
Fix up T25611d with explicit kind annotation

- - - - -
17bec497 by Patrick at 2025-03-11T22:33:40+00:00
fix up T25647_fail

- - - - -
cd29ab41 by Patrick at 2025-03-11T22:33:40+00:00
cleanup whitespace

- - - - -
0095077f by Patrick at 2025-03-11T22:33:40+00:00
fix up T23512a

- - - - -
cbf6480c by Patrick at 2025-03-11T22:33:40+00:00
add more examples to T25647b

- - - - -
9abefe96 by Patrick at 2025-03-11T22:33:40+00:00
add Dix6 to T25647_fail

- - - - -
ad24b4f4 by Patrick at 2025-03-11T22:33:40+00:00
add Dix7 for T25647a

- - - - -
62552e63 by Patrick at 2025-03-11T22:33:40+00:00
change DefaultingStrategy of tcTyFamInstEqnGuts as well

- - - - -
45e1ed99 by Patrick at 2025-03-11T22:33:40+00:00
align wildcard with named typevar on wether it is skolem

- - - - -
b86ec2c2 by Patrick at 2025-03-11T22:33:40+00:00
fix T17536c

- - - - -
801fba89 by Patrick at 2025-03-11T22:33:40+00:00
Fix T9357

- - - - -
0ff2deb6 by Patrick at 2025-03-11T22:33:40+00:00
remove wildcard usage

- - - - -
46c87176 by Patrick at 2025-03-11T22:33:40+00:00
Revert "align wildcard with named typevar on wether it is skolem"

This reverts commit d1f61858328cc190de9b34c9a24e8d6b28ee5fa9.

- - - - -
76ce2a21 by Patrick at 2025-03-11T22:33:40+00:00
add WildCardTv to forbid wildcard from defaulting

- - - - -
9b04b9f0 by Patrick at 2025-03-11T22:33:40+00:00
Fix wildcard related tests

- - - - -
d815a968 by Patrick at 2025-03-11T22:33:40+00:00
add wildcards testcase for T25647a

- - - - -
f1beffa3 by Patrick at 2025-03-11T22:33:40+00:00
Fix T25647a

- - - - -
a4fdd09c by Patrick at 2025-03-11T22:33:40+00:00
Revert "Fix wildcard related tests"

This reverts commit 8756ab87f4e3d74968d3937f84f811f78a861852.

- - - - -
05d4bd34 by Patrick at 2025-03-11T22:33:40+00:00
limit WildCardTv to only HM_FamPat

- - - - -
d70f6c91 by Patrick at 2025-03-11T22:33:40+00:00
fix

- - - - -
69f63d22 by Patrick at 2025-03-11T22:33:40+00:00
Revert "remove wildcard usage"

This reverts commit ccc9152f23177ab7a542852ffedf626edcdcef95.

- - - - -
2df6083d by Patrick at 2025-03-11T22:33:40+00:00
rename WildCardTv to NoDefTauTv

- - - - -
e3653b97 by Patrick at 2025-03-11T22:33:40+00:00
update note

- - - - -
3aead0e8 by Patrick at 2025-03-11T22:33:40+00:00
rename isWildCardMetaTyVar to isNoDefTauMetaTyVar and fix defaultTyVarTcS

- - - - -
53847779 by Patrick at 2025-03-11T22:33:40+00:00
fix comment

- - - - -
c5865082 by Patrick at 2025-03-11T22:33:40+00:00
format

- - - - -
3ac78064 by Patrick at 2025-03-11T22:33:40+00:00
remove NonStandardDefaultingStrategy
and update Note [NoDefTauTv]

- - - - -
102570b7 by Patrick at 2025-03-11T22:33:40+00:00
add DixC10 to T25647a

- - - - -
abefc50a by Patrick at 2025-03-11T22:33:40+00:00
use TyVarTv for wildcard in HM_FamPat

- - - - -
8b421622 by Patrick at 2025-03-11T22:33:40+00:00
Revert "use TyVarTv for wildcard in HM_FamPat"

This reverts commit 638d6763d0b972f3c9a0e2c4218d8c7ce34dc800.

- - - - -
f8c558a1 by Patrick at 2025-03-11T22:33:40+00:00
Add FamArgType to in AssocInstInfo
to guide the create of tv for wildcard

- - - - -
29905f62 by Patrick at 2025-03-11T22:33:40+00:00
Fix mode args passing down

- - - - -
35faff5a by Patrick at 2025-03-11T22:33:40+00:00
Fix under application for data fam

- - - - -
dd972ec0 by Patrick at 2025-03-11T22:33:40+00:00
use HM_Sig for (a :: _) in type family

- - - - -
67a18f37 by Patrick at 2025-03-11T22:33:40+00:00
add and use HM_FamSig for (a :: _) in type family

- - - - -
08ba204a by Patrick at 2025-03-11T22:33:40+00:00
use TyVarTv instead of SkolemTv for freeArg `_`, since we also do not default TyVarTv in defaultTyVar and defaultTyVarTcS

- - - - -
85d3ef9d by Patrick at 2025-03-11T22:33:40+00:00
Revert "add and use HM_FamSig for (a :: _) in type family"
and use ClassArg for _ in (a :: _) in type family

This reverts commit 9ab780da39c2afbce2411c2b96fef4108d6b8b70.

- - - - -
d2356cf3 by Patrick at 2025-03-11T22:33:40+00:00
fix

- - - - -
80ff8a93 by Patrick at 2025-03-11T22:33:40+00:00
remove unused updateHoleMode function from TcTyMode

- - - - -
10dac28a by Patrick at 2025-03-11T22:33:40+00:00
flip the classVar to TyVarTv to observe any breakage

- - - - -
c4a81aa3 by Patrick at 2025-03-11T22:33:40+00:00
fix

- - - - -
ece07a03 by Patrick at 2025-03-11T22:33:40+00:00
disable DixC10 from T25647a

- - - - -
d9b320d5 by Patrick at 2025-03-11T22:33:40+00:00
update ExplicitForAllFams4b

- - - - -
c30abf32 by Patrick at 2025-03-11T22:33:40+00:00
cleanup NoDefTauTv

- - - - -
56194258 by Patrick at 2025-03-11T22:33:40+00:00
move [FamArgFlavour] to tyCon

- - - - -
cc2bd567 by Patrick at 2025-03-11T22:33:40+00:00
add note

- - - - -
04015cd7 by Patrick at 2025-03-11T22:33:40+00:00
refactor documentation for FamArgFlavour and clean up comments

- - - - -
dd96a62e by Patrick at 2025-03-11T22:33:40+00:00
enhance trace logging in tcConArg and cloneAnonMetaTyVar for better debugging

- - - - -
c77bead4 by Patrick at 2025-03-11T22:33:40+00:00
Ensure wildcard behave correctly

- - - - -
b4a39611 by Patrick at 2025-03-11T22:33:40+00:00
Revert "update ExplicitForAllFams4b"

This reverts commit 90a2858278668bc6ad66ef43a5651808d8f24a0f.

- - - - -
abf51bbe by Patrick at 2025-03-11T22:33:40+00:00
Add detailed notes on wildcard handling in type families and refine related documentation

- - - - -
9d907f79 by Patrick at 2025-03-11T22:33:40+00:00
Refine documentation on wildcard handling in type families and clarify design choices for FamArgFlavour

- - - - -
47819b2b by Patrick at 2025-03-11T22:33:40+00:00
Fix typos in documentation regarding wildcards in type families and clarify references

- - - - -
bf73073e by Patrick at 2025-03-11T22:33:40+00:00
Clarify wildcard handling in type families documentation and improve explanations for FamArgFlavour

- - - - -
36a7fcaa by Patrick at 2025-03-11T22:33:40+00:00
Enhance documentation on FamArgFlavour handling in type families and clarify implementation details in TyCon and HsType modules

- - - - -
2ceeeaed by Patrick at 2025-03-11T22:33:40+00:00
format

- - - - -
c76c36be by Patrick at 2025-03-11T22:33:40+00:00
Refactor documentation on wildcards in type families and clarify implementation details in TyCon, Rename, and HsType modules

- - - - -
2b5926d1 by Patrick at 2025-03-11T22:33:40+00:00
Rename variable `famArgFlvs` to `fam_arg_flvs` for consistency in type inference functions

- - - - -
54f359cc by Patrick at 2025-03-11T22:33:40+00:00
Improve documentation on wildcard interpretation in type families, clarifying the relationship with class arguments and enhancing the explanation of FamArgFlavour categories.

- - - - -
06bde324 by Patrick at 2025-03-11T22:33:40+00:00
Add comment to clarify implementation details for wildcards in family instances

- - - - -
270e7926 by Patrick at 2025-03-11T22:33:40+00:00
Refactor HsOuterTyVarBndrs to include implicit variable bindings and update related functions for consistency

- - - - -
0298c37b by Patrick at 2025-03-11T22:33:40+00:00
Enhance HsOuterTyVarBndrs to support implicit variable bindings and update related functions for consistency

- - - - -
dc1f2793 by Patrick at 2025-03-11T22:33:40+00:00
Add new test case T25647d

- - - - -
091f3d72 by Patrick at 2025-03-11T22:33:40+00:00
Remove unused implicit variable bindings from HsOuterExplicit in addHsOuterSigTyVarBinds function

- - - - -
573b42fb by Patrick at 2025-03-11T22:33:40+00:00
Add forall quantifiers to MultMul type family for clarity

- - - - -
3ea58357 by Patrick at 2025-03-11T22:33:40+00:00
Refactor bindHsOuterTyVarBndrs'

- - - - -
70743b27 by Patrick at 2025-03-11T22:33:40+00:00
Add empty implicit variable bindings to HsOuterExplicit in mkEmptySigType

- - - - -
dfb12376 by Patrick at 2025-03-11T22:33:40+00:00
Add empty implicit variable bindings to HsOuterExplicit in synifyDataCon

- - - - -
d01357a5 by Patrick at 2025-03-11T22:33:40+00:00
Add missing implicit variable bindings to HsOuterExplicit in ExactPrint instance

- - - - -
9216bcf9 by Patrick at 2025-03-11T22:33:40+00:00
Add implicit variable bindings to HsOuterExplicit in various instances

- - - - -
da8ce4bb by Patrick at 2025-03-11T22:33:40+00:00
Add forall quantifier to D Int newtype instance

- - - - -
ecd9d190 by Patrick at 2025-03-11T22:33:40+00:00
zonk_quant outer binders for families

- - - - -
1d9226c8 by Patrick at 2025-03-11T22:33:40+00:00
revert to old behaviour

- - - - -
079d7d2b by Patrick at 2025-03-11T22:33:40+00:00
add note and comment

- - - - -
1036d373 by Patrick at 2025-03-11T22:33:40+00:00
refactor

- - - - -
d2194233 by Patrick at 2025-03-11T22:33:40+00:00
fix test T25647d

- - - - -
dbead5da by Patrick at 2025-03-11T22:33:40+00:00
handle [Naughty quantification candidates]

- - - - -
7e441222 by Patrick at 2025-03-11T22:33:40+00:00
handle explicit implicit binders seperately

- - - - -
f5f3fcfe by Patrick at 2025-03-11T22:33:40+00:00
handle explicit implicit binders seperately fix

- - - - -
272fd5d3 by Patrick at 2025-03-11T22:33:40+00:00
fix lint

- - - - -
7e1ac9a3 by Patrick at 2025-03-11T22:33:40+00:00
some renaming

- - - - -


120 changed files:

- compiler/GHC.hs
- compiler/GHC/Data/Maybe.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Match/Constructor.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Rule.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Types/LclEnv.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Zonk/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/GREInfo.hs
- compiler/GHC/Types/HpcInfo.hs
- compiler/GHC/Unit/Module/ModGuts.hs
- compiler/GHC/Unit/Module/ModIface.hs
- compiler/GHC/Utils/Panic.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/Language/Haskell/Syntax/Pat.hs
- compiler/Language/Haskell/Syntax/Type.hs
- docs/users_guide/exts/named_defaults.rst
- docs/users_guide/exts/overloaded_strings.rst
- docs/users_guide/exts/poly_kinds.rst
- + docs/users_guide/exts/type_defaulting.rst
- docs/users_guide/exts/types.rst
- docs/users_guide/ghci.rst
- docs/users_guide/using-concurrent.rst
- rts/linker/MachO.c
- rts/linker/MachOTypes.h
- testsuite/driver/junit.py
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile
- + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout
- + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs
- testsuite/tests/driver/dynamicToo/dynamicToo001/test.T
- testsuite/tests/ghc-api/Makefile
- + testsuite/tests/ghc-api/T25577.hs
- testsuite/tests/ghc-api/all.T
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- + testsuite/tests/indexed-types/should_compile/T11450a.hs
- testsuite/tests/indexed-types/should_compile/T25611d.hs
- testsuite/tests/indexed-types/should_compile/all.T
- testsuite/tests/indexed-types/should_fail/T9357.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/printer/Test24533.stdout
- testsuite/tests/rename/should_fail/T22478b.stderr
- testsuite/tests/rename/should_fail/T22478e.stderr
- testsuite/tests/rename/should_fail/T22478f.stderr
- testsuite/tests/rename/should_fail/T23512a.stderr
- + testsuite/tests/typecheck/should_compile/T25647_fail.hs
- + testsuite/tests/typecheck/should_compile/T25647_fail.stderr
- + testsuite/tests/typecheck/should_compile/T25647a.hs
- + testsuite/tests/typecheck/should_compile/T25647b.hs
- + testsuite/tests/typecheck/should_compile/T25647c.hs
- + testsuite/tests/typecheck/should_compile/T25647d.hs
- + testsuite/tests/typecheck/should_compile/T25647d_fail.hs
- + testsuite/tests/typecheck/should_compile/T25647d_fail.stderr
- + testsuite/tests/typecheck/should_compile/T25725.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/T19109.stderr
- testsuite/tests/typecheck/should_fail/T23776.stderr
- + testsuite/tests/typecheck/should_fail/T25004.hs
- + testsuite/tests/typecheck/should_fail/T25004.stderr
- testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs
- testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr
- testsuite/tests/typecheck/should_fail/all.T
- utils/check-exact/ExactPrint.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs
- utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/GhcUtils.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/214aa94c6a723c926f581ed4157724f70daed1d0...7e1ac9a36b0b9a7cfe2cc1857958bee8780d05b9

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/214aa94c6a723c926f581ed4157724f70daed1d0...7e1ac9a36b0b9a7cfe2cc1857958bee8780d05b9
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20250311/3a94c43a/attachment-0001.html>


More information about the ghc-commits mailing list