[Git][ghc/ghc][wip/backports-9.8] 23 commits: Be more eager in TyCon boot validity checking

Zubin (@wz1000) gitlab at gitlab.haskell.org
Thu Feb 8 17:32:13 UTC 2024



Zubin pushed to branch wip/backports-9.8 at Glasgow Haskell Compiler / GHC


Commits:
931a0c34 by Antoine Leblanc at 2024-02-08T23:01:53+05:30
Be more eager in TyCon boot validity checking

This commit performs boot-file consistency checking for TyCons into
checkValidTyCl. This ensures that we eagerly catch any mismatches,
which prevents the compiler from seeing these inconsistencies and
panicking as a result.

See Note [TyCon boot consistency checking] in GHC.Tc.TyCl.

Fixes #16127

(cherry picked from commit 1420b8cb8a7d6196eec80dc5293864c780379560)

- - - - -
e7cf6437 by sheaf at 2024-02-08T23:01:53+05:30
Unused tyvars in FamInst: only report user tyvars

This commit changes how we perform some validity checking for
coercion axioms to mirror how we handle default declarations for
associated type families. This allows us to keep track of whether
type variables in type and data family instances were user-written
or not, in order to only report the user-written ones in
"unused type variable" error messages.

Consider for example:

  {-# LANGUAGE PolyKinds #-}
  type family F
  type instance forall a. F = ()

In this case, we get two quantified type variables,
(k :: Type) and (a :: k); the second being user-written, but the first
is introduced by the typechecker. We should only report 'a' as being
unused, as the user has no idea what 'k' is.

Fixes #23734

(cherry picked from commit 28dd52eec98e50c711cd00df22f6ab9e054c8b75)

- - - - -
ebc725b2 by sheaf at 2024-02-08T23:01:53+05:30
Validity: refactor treatment of data families

This commit refactors the reporting of unused type variables in type
and data family instances to be more principled. This avoids ad-hoc
logic in the treatment of data family instances.

(cherry picked from commit 1eed645c8b03b19a14cf58d9be5317cb81cbd30a)

- - - - -
dcd8ca74 by Krzysztof Gogolewski at 2024-02-08T23:01:53+05:30
docs: fix ScopedTypeVariables example (#24101)

The previous example didn't compile.

Furthermore, it wasn't demonstrating the point properly.
I have changed it to an example which shows that 'a' in the signature
must be the same 'a' as in the instance head.

(cherry picked from commit 7a90020f167ab016cbfa95decafaa1a54a974bc6)

- - - - -
f47a95f2 by PHO at 2024-02-08T23:01:53+05:30
Don't assume the current locale is *.UTF-8, set the encoding explicitly

primops.txt contains Unicode characters:
> LC_ALL=C ./genprimopcode --data-decl < ./primops.txt
> genprimopcode: <stdin>: hGetContents: invalid argument (cannot decode byte sequence starting from 226)

Hadrian must also avoid using readFile' to read primops.txt because it
tries to decode the file with a locale-specific encoding.

(cherry picked from commit 52c0fc691e6501e99a96693ec1fc02e3c93a4fbc)

- - - - -
73600e14 by Simon Peyton Jones at 2024-02-08T23:01:53+05:30
Add an extra check in kcCheckDeclHeader_sig

Fix #24083 by checking for a implicitly-scoped type variable that is not
actually bound.  See Note [Disconnected type variables] in GHC.Tc.Gen.HsType

For some reason, on aarch64-darwin we saw a 2.8% decrease in compiler
allocations for MultiLayerModulesTH_Make; but 0.0% on other architectures.

Metric Decrease:
    MultiLayerModulesTH_Make

(cherry picked from commit 6dbab1808bfbe484b3fb396aab1d105314f918d8)

- - - - -
39179586 by Simon Peyton Jones at 2024-02-08T23:01:53+05:30
Second fix to #24083

My earlier fix turns out to be too aggressive for data/type families

See wrinkle (DTV1) in Note [Disconnected type variables]

(cherry picked from commit 2776920e642544477a38d0ed9205d4f0b48a782e)
(cherry picked from commit 110efc9813ba5f68668ab7fc3f95b9febca52880)

- - - - -
aa339700 by Matthew Pickering at 2024-02-08T23:01:53+05:30
libraries: Bump filepath to 1.4.200.1 and unix to 2.8.4.0

Updates filepath submodule
Updates unix submodule

Fixes #24240

(cherry picked from commit 36b9a38cc45a26865c4e45f4949e519a5dede76d)

- - - - -
4058ecba by Matthew Pickering at 2024-02-08T23:01:54+05:30
Submodule linter: Allow references to tags

We modify the submodule linter so that if the bumped commit is a
specific tag then the commit is accepted.

Fixes #24241

(cherry picked from commit 91ff0971df64b04938d011fe1562320c5d90849a)

- - - - -
ab835c3f by Matthew Craven at 2024-02-08T23:01:54+05:30
Fix loopification in the presence of void arguments

This also removes Note [Void arguments in self-recursive tail calls],
which was just misleading.  It's important to count void args both
in the function's arity and at the call site.

Fixes #24295.

(cherry picked from commit ae9cc1a84c9f470b77d98423400e6dfa95b2449b)

- - - - -
275997f7 by Andreas Klebinger at 2024-02-08T23:01:54+05:30
Aarch64: Enable -mfma by default.

Fixes #24311

(cherry picked from commit 7e95f738620dc805868d198f980e1bdd53e27a2d)

- - - - -
bb4f3878 by Matthew Pickering at 2024-02-08T23:01:54+05:30
eventlog: Fix off-by-one error in postIPE

We were missing the extra_comma from the calculation of the size of the
payload of postIPE. This was causing assertion failures when the event
would overflow the buffer by one byte, as ensureRoomForVariable event
would report there was enough space for `n` bytes but then we would
write `n + 1` bytes into the buffer.

Fixes #24287

(cherry picked from commit 5776008c7a5581193c3e72e59451ad49abac9d81)

- - - - -
8fac10a2 by Jade at 2024-02-08T23:01:54+05:30
Enhance Documentation of functions exported by Data.Function

This patch aims to improve the documentation of functions exported
in Data.Function

Tracking: #17929
Fixes: #10065
(cherry picked from commit 1fa1c00c95325761a5aa914af53d71ba5e7072b3)

- - - - -
758ff906 by Jade at 2024-02-08T23:01:54+05:30
Improve documentation of hGetLine.

- Add explanation for whether a newline is returned
- Add examples

Fixes #14804

(cherry picked from commit ab47a43d64f6b7d4fc181645171c31ba2db1eebe)

- - - - -
5205b93d by sheaf at 2024-02-08T23:01:54+05:30
Fix FMA instruction on LLVM

We were emitting the wrong instructions for fused multiply-add
operations on LLVM:

  - the instruction name is "llvm.fma.f32" or "llvm.fma.f64", not "fmadd"
  - LLVM does not support other instructions such as "fmsub"; instead
    we implement these by flipping signs of some arguments
  - the instruction is an LLVM intrinsic, which requires handling it
    like a normal function call instead of a machine instruction

Fixes #24223

(cherry picked from commit a40f4ab21bcc088e63892cd5e85edbec20d3fc69)

- - - - -
7ddb1418 by Hécate Moonlight at 2024-02-08T23:01:54+05:30
Clarification for newtype constructors when using `coerce`

(cherry picked from commit 699da01bbbf3e42c7d38b9cfe443dd0e8e256342)

- - - - -
4593f490 by Andreas Klebinger at 2024-02-08T23:01:54+05:30
Fix fma warning when using llvm on aarch64.

On aarch64 fma is always on so the +fma flag doesn't exist for that
target. Hence no need to try and pass +fma to llvm.

Fixes #24379

(cherry picked from commit 9294a08643b89509a0e0957cb73c186a39d4f3db)

- - - - -
10de6db4 by Patrick at 2024-02-08T23:01:54+05:30
Fix bug wrong span of nested_doc_comment #24378

close #24378
1. Update the start position of span in `nested_doc_comment` correctly.
and hence the spans of identifiers of haddoc can be computed correctly.
2. add test `HaddockSpanIssueT24378`.

(cherry picked from commit 8eeadfad3a0035f8c5b339782676ff23572e0e5e)

- - - - -
85ef42ce by sheaf at 2024-02-08T23:01:54+05:30
No shadowing warnings for NoFieldSelector fields

This commit ensures we don't emit shadowing warnings when a user
shadows a field defined with NoFieldSelectors.

Fixes #24381

(cherry picked from commit ced2e7312b692e3f5402e4db6cfec390653a6a06)

- - - - -
e59bae2a by Teo Camarasu at 2024-02-08T23:01:54+05:30
doc: Add -Dn flag to user guide

Resolves #24394

(cherry picked from commit 94ce031ddc84ee702c12a11793028ef21e65fa00)

- - - - -
81cb68aa by Rodrigo Mesquita at 2024-02-08T23:01:54+05:30
Work around autotools setting C11 standard in CC/CXX

In autoconf >=2.70, C11 is set by default for $CC and $CXX via the
-std=...11 flag. In this patch, we split the "-std" flag out of the $CC
and $CXX variables, which we traditionally assume to be just the
executable name/path, and move it to $CFLAGS/$CXXFLAGS instead.

Fixes #24324

(cherry picked from commit cdddeb0f1280b40cc194028bbaef36e127175c4c)

- - - - -
a7421910 by Zubin Duggal at 2024-02-08T23:01:54+05:30
driver: Really don't lose track of nodes when we fail to resolve cycles

This fixes a bug in 8db8d2fd1c881032b1b360c032b6d9d072c11723, where we could lose
track of acyclic components at the start of an unresolved cycle. We now ensure we
never loose track of any of these components.

As T24275 demonstrates, a "cyclic" SCC might not really be a true SCC:

When viewed without boot files, we have a single SCC

```
[REC main:T24275B [main:T24275B {-# SOURCE #-},
                   main:T24275A {-# SOURCE #-}]
     main:T24275A [main:T24275A {-# SOURCE #-}]]
```

But with boot files this turns into

```
[NONREC main:T24275B {-# SOURCE #-} [],
 REC main:T24275B [main:T24275B {-# SOURCE #-},
                   main:T24275A {-# SOURCE #-}]
    main:T24275A {-# SOURCE #-} [main:T24275B],
 NONREC main:T24275A [main:T24275A {-# SOURCE #-}]]
```

Note that this is truly not an SCC, as no nodes are reachable from T24275B.hs-boot.
However, we treat this entire group as a single "SCC" because it seems so when we
analyse the graph without taking boot files into account.

Indeed, we must return a single ResolvedCycle element in the BuildPlan for this
as described in Note [Upsweep].

However, since after resolving this is not a true SCC anymore, `findCycle` fails
to find a cycle and we have a sub-optimal error message as a result.

To handle this, I extended `findCycle` to not assume its input is an SCC, and to
try harder to find cycles in its input.

Fixes #24275

(cherry picked from commit 532993c8160d960f848e7abd401774b6879e3ee8)

- - - - -
ba0a5d95 by Matthew Pickering at 2024-02-08T23:01:54+05:30
distrib/configure: Fix typo in CONF_GCC_LINKER_OPTS_STAGE2 variable

Instead we were setting CONF_GCC_LINK_OPTS_STAGE2 which meant that we
were missing passing `--target` when invoking the linker.

Fixes #24414

(cherry picked from commit d309f4e7e37f3795c6d6b150c407d5a9b332854e)

- - - - -


30 changed files:

- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/Core/Class.hs
- compiler/GHC/Core/Coercion/Axiom.hs
- compiler/GHC/Data/Graph/Directed.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Llvm/Ppr.hs
- compiler/GHC/Llvm/Syntax.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/StgToCmm/Bind.hs
- compiler/GHC/StgToCmm/Closure.hs
- compiler/GHC/StgToCmm/Expr.hs
- compiler/GHC/StgToCmm/Heap.hs
- compiler/GHC/StgToCmm/Monad.hs
- compiler/GHC/StgToCmm/Sequel.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/Tc/Zonk/Type.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57dae38abc976eca2f432d6f2a14823f27123876...ba0a5d957bcdccb0357f20d9d7dfff4ac1c63407

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57dae38abc976eca2f432d6f2a14823f27123876...ba0a5d957bcdccb0357f20d9d7dfff4ac1c63407
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/20240208/7feb08c3/attachment-0001.html>


More information about the ghc-commits mailing list