[Git][ghc/ghc][wip/int-index/release-notes-9.10] 15 commits: rnImports: var shouldn't import NoFldSelectors

Vladislav Zavialov (@int-index) gitlab at gitlab.haskell.org
Tue Jul 18 16:03:42 UTC 2023



Vladislav Zavialov pushed to branch wip/int-index/release-notes-9.10 at Glasgow Haskell Compiler / GHC


Commits:
c7bbad9a by sheaf at 2023-07-17T02:48:19-04:00
rnImports: var shouldn't import NoFldSelectors

In an import declaration such as

  import M ( var )

the import of the variable "var" should **not** bring into scope record
fields named "var" which are defined with NoFieldSelectors.
Doing so can cause spurious "unused import" warnings, as reported in
ticket #23557.

Fixes #23557

- - - - -
1af2e773 by sheaf at 2023-07-17T02:48:19-04:00
Suggest similar names in imports

This commit adds similar name suggestions when importing. For example

  module A where { spelling = 'o' }
  module B where { import B ( speling ) }

will give rise to the error message:

  Module ‘A’ does not export ‘speling’.
  Suggested fix: Perhaps use ‘spelling’

This also provides hints when users try to import record fields defined
with NoFieldSelectors.

- - - - -
654fdb98 by Alan Zimmerman at 2023-07-17T02:48:55-04:00
EPA: Store leading AnnSemi for decllist in al_rest

This simplifies the markAnnListA implementation in ExactPrint

- - - - -
22565506 by sheaf at 2023-07-17T21:12:59-04:00
base: add COMPLETE pragma to BufferCodec PatSyn

This implements CLC proposal #178, rectifying an oversight in the
implementation of CLC proposal #134 which could lead to spurious
pattern match warnings.

https://github.com/haskell/core-libraries-committee/issues/178
https://github.com/haskell/core-libraries-committee/issues/134

- - - - -
860f6269 by sheaf at 2023-07-17T21:13:00-04:00
exactprint: silence incomplete record update warnings

- - - - -
df706de3 by sheaf at 2023-07-17T21:13:00-04:00
Re-instate -Wincomplete-record-updates

Commit e74fc066 refactored the handling of record updates to use
the HsExpanded mechanism. This meant that the pattern matching inherent
to a record update was considered to be "generated code", and thus we
stopped emitting "incomplete record update" warnings entirely.

This commit changes the "data Origin = Source | Generated" datatype,
adding a field to the Generated constructor to indicate whether we
still want to perform pattern-match checking. We also have to do a bit
of plumbing with HsCase, to record that the HsCase arose from an
HsExpansion of a RecUpd, so that the error message continues to mention
record updates as opposed to a generic "incomplete pattern matches in case"
error.

Finally, this patch also changes the way we handle inaccessible code
warnings. Commit e74fc066 was also a regression in this regard, as we
were emitting "inaccessible code" warnings for case statements spuriously
generated when desugaring a record update (remember: the desugaring mechanism
happens before typechecking; it thus can't take into account e.g. GADT information
in order to decide which constructors to include in the RHS of the desugaring
of the record update).
We fix this by changing the mechanism through which we disable inaccessible
code warnings: we now check whether we are in generated code in
GHC.Tc.Utils.TcMType.newImplication in order to determine whether to
emit inaccessible code warnings.

Fixes #23520
Updates haddock submodule, to avoid incomplete record update warnings

- - - - -
1d05971e by sheaf at 2023-07-17T21:13:00-04:00
Propagate long-distance information in do-notation

The preceding commit re-enabled pattern-match checking inside record
updates. This revealed that #21360 was in fact NOT fixed by e74fc066.

This commit makes sure we correctly propagate long-distance information
in do blocks, e.g. in

```haskell
data T = A { fld :: Int } | B

f :: T -> Maybe T
f r = do
  a at A{} <- Just r
  Just $ case a of { A _ -> A 9 }
```

we need to propagate the fact that "a" is headed by the constructor "A"
to see that the case expression "case a of { A _ -> A 9 }" cannot fail.

Fixes #21360

- - - - -
bea0e323 by sheaf at 2023-07-17T21:13:00-04:00
Skip PMC for boring patterns

Some patterns introduce no new information to the pattern-match
checker (such as plain variable or wildcard patterns). We can thus
skip doing any pattern-match checking on them when the sole purpose
for doing so was introducing new long-distance information.

See Note [Boring patterns] in GHC.Hs.Pat.

Doing this avoids regressing in performance now that we do additional
pattern-match checking inside do notation.

- - - - -
ddcdd88c by Rodrigo Mesquita at 2023-07-17T21:13:36-04:00
Split GHC.Platform.ArchOS from ghc-boot into ghc-platform

Split off the `GHC.Platform.ArchOS` module from the `ghc-boot` package
into this reinstallable standalone package which abides by the PVP, in
part motivated by the ongoing work on `ghc-toolchain` towards runtime
retargetability.

- - - - -
b55a8ea7 by Sylvain Henry at 2023-07-17T21:14:27-04:00
JS: better implementation for plusWord64 (#23597)

- - - - -
889c2bbb by sheaf at 2023-07-18T06:37:32-04:00
Do primop rep-poly checks when instantiating

This patch changes how we perform representation-polymorphism checking
for primops (and other wired-in Ids such as coerce).
When instantiating the primop, we check whether each type variable
is required to instantiated to a concrete type, and if so we create a
new concrete metavariable (a ConcreteTv) instead of a simple MetaTv.
(A little subtlety is the need to apply the substitution obtained from
instantiating to the ConcreteTvOrigins, see
Note [substConcreteTvOrigin] in GHC.Tc.Utils.TcMType.)

This allows us to prevent representation-polymorphism in non-argument
position, as that is required for some of these primops.

We can also remove the logic in tcRemainingValArgs, except for
the part concerning representation-polymorphic unlifted newtypes.
The function has been renamed rejectRepPolyNewtypes; all it does now
is reject unsaturated occurrences of representation-polymorphic newtype
constructors when the representation of its argument isn't a concrete
RuntimeRep (i.e. still a PHASE 1 FixedRuntimeRep check).
The Note [Eta-expanding rep-poly unlifted newtypes] in GHC.Tc.Gen.Head
gives more explanation about a possible path to PHASE 2, which would be
in line with the treatment for primops taken in this patch.

We also update the Core Lint check to handle this new framework. This
means Core Lint now checks representation-polymorphism in continuation
position like needed for catch#.

Fixes #21906

-------------------------
Metric Increase:
    LargeRecord
-------------------------

- - - - -
00648e5d by Krzysztof Gogolewski at 2023-07-18T06:38:10-04:00
Core Lint: distinguish let and letrec in locations

Lint messages were saying "in the body of letrec" even for non-recursive
let.

I've also renamed BodyOfLetRec to BodyOfLet in stg, since there's no
separate letrec.

- - - - -
787bae96 by Krzysztof Gogolewski at 2023-07-18T06:38:50-04:00
Use extended literals when deriving Show

This implements GHC proposal
https://github.com/ghc-proposals/ghc-proposals/pull/596

Also add support for Int64# and Word64#; see testcase ShowPrim.

- - - - -
257f1567 by Jaro Reinders at 2023-07-18T06:39:29-04:00
Add StgFromCore and StgCodeGen linting

- - - - -
a2bfbbb0 by Vladislav Zavialov at 2023-07-18T16:03:32+00:00
Initialize 9.10.1-notes.rst

Create new release notes for the next GHC release (GHC 9.10)

- - - - -


30 changed files:

- compiler/GHC/Builtin/PrimOps.hs
- compiler/GHC/Builtin/PrimOps/Ids.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/Core.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Driver/Config/Core/Lint.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Arrows.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/GuardedRHSs.hs
- compiler/GHC/HsToCore/ListComp.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Match.hs-boot
- compiler/GHC/HsToCore/Match/Constructor.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/HsToCore/Pmc.hs
- compiler/GHC/HsToCore/Pmc/Utils.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Parser.y


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7603f6f49a452aa8d274102e8ba7887f79a7563e...a2bfbbb091739d4e4b21ec435565f957a6a838d3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7603f6f49a452aa8d274102e8ba7887f79a7563e...a2bfbbb091739d4e4b21ec435565f957a6a838d3
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/20230718/5a1d64e5/attachment-0001.html>


More information about the ghc-commits mailing list