[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 16 commits: Solve Wanted quantified constraints from Givens

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Mar 11 16:56:11 UTC 2025



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
c44bc9c5 by sheaf at 2025-03-11T12:54:52-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

- - - - -
0b35caa6 by Ben Gamari at 2025-03-11T12:54:53-04:00
testsuite: Add testcase for #25577

- - - - -
0d4d0e26 by Ben Gamari at 2025-03-11T12:54:53-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.

- - - - -
121ecc47 by Ben Gamari at 2025-03-11T12:54:53-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.

- - - - -
4c96f8a6 by Ben Gamari at 2025-03-11T12:54:53-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.

- - - - -
028d3d52 by Vladislav Zavialov at 2025-03-11T12:54:55-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.

- - - - -
6483a1ee by Vladislav Zavialov at 2025-03-11T12:54:56-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.

- - - - -
8adde5e3 by sheaf at 2025-03-11T12:54:59-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).

- - - - -
cecadbfc by sheaf at 2025-03-11T12:54:59-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

- - - - -
44138b36 by sheaf at 2025-03-11T12:54:59-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.

- - - - -
8495a23c by Teo Camarasu at 2025-03-11T12:55:00-04:00
template-haskell: Add explicit exports lists to all remaining modules

- - - - -
299df80e by Teo Camarasu at 2025-03-11T12:55:00-04:00
template-haskell: fix haddocks

It seems that we need a direct dependency on ghc-internal, otherwise
Haddock cannot find our haddocks

The bug seems to be caused by Hadrian because if I rebuild with
cabal-install (without this extra dependency) then I get accurate
Haddocks.

Resolves #25705

- - - - -
b88eb61f by Matthew Pickering at 2025-03-11T12:55:01-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.

- - - - -
46e72fd8 by Matthew Pickering at 2025-03-11T12:55:01-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`.

- - - - -
d9d6aebf by Matthew Pickering at 2025-03-11T12:55:01-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.

- - - - -
d2f3e064 by Matthew Pickering at 2025-03-11T12:55:01-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`.

- - - - -


100 changed files:

- compiler/GHC.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/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/GREInfo.hs
- compiler/GHC/Types/HpcInfo.hs
- compiler/GHC/Unit/Module/ModGuts.hs
- compiler/GHC/Unit/Module/ModIface.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
- libraries/template-haskell/Language/Haskell/TH/Ppr.hs
- libraries/template-haskell/Language/Haskell/TH/PprLib.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- libraries/template-haskell/template-haskell.cabal.in
- rts/linker/MachO.c
- rts/linker/MachOTypes.h
- 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/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/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
- utils/haddock/html-test/ref/QuasiExpr.html
- utils/haddock/html-test/ref/TH.html
- utils/haddock/html-test/ref/Threaded_TH.html


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6bb0e2617dd771dd9b059dc1906b268f5e53e440...d2f3e064182fcb50c58ffd21bf131a85c98320ae

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6bb0e2617dd771dd9b059dc1906b268f5e53e440...d2f3e064182fcb50c58ffd21bf131a85c98320ae
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/1daff909/attachment-0001.html>


More information about the ghc-commits mailing list