[Git][ghc/ghc][wip/haddock-accum] 17 commits: Implement the proposed -XQualifiedDo extension

Vladislav Zavialov gitlab at gitlab.haskell.org
Tue Jun 30 21:21:21 UTC 2020



Vladislav Zavialov pushed to branch wip/haddock-accum at Glasgow Haskell Compiler / GHC


Commits:
9ee58f8d by Matthias Pall Gissurarson at 2020-06-26T17:12:45+00:00
Implement the proposed -XQualifiedDo extension

Co-authored-by: Facundo Domínguez <facundo.dominguez at tweag.io>

QualifiedDo is implemented using the same placeholders for operation names in
the AST that were devised for RebindableSyntax. Whenever the renamer checks
which names to use for do syntax, it first checks if the do block is qualified
(e.g. M.do { stmts }), in which case it searches for qualified names in
the module M.

This allows users to write

    {-# LANGUAGE QualifiedDo #-}
    import qualified SomeModule as M

    f x = M.do           -- desugars to:
      y <- M.return x    -- M.return x M.>>= \y ->
      M.return y         -- M.return y M.>>
      M.return y         -- M.return y

See Note [QualifiedDo] and the users' guide for more details.

Issue #18214

Proposal:
https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0216-qualified-do.rst

Since we change the constructors `ITdo` and `ITmdo` to carry the new module
name, we need to bump the haddock submodule to account or the new shape of
these constructors.

- - - - -
ce987865 by Ryan Scott at 2020-06-27T11:55:21-04:00
Revamp the treatment of auxiliary bindings for derived instances

This started as a simple fix for #18321 that organically grew into a
much more sweeping refactor of how auxiliary bindings for derived
instances are handled. I have rewritten `Note [Auxiliary binders]`
in `GHC.Tc.Deriv.Generate` to explain all of the moving parts, but
the highlights are:

* Previously, the OccName of each auxiliary binding would be given
  a suffix containing a hash of its package name, module name, and
  parent data type to avoid name clashes. This was needlessly
  complicated, so we take the more direct approach of generating
  `Exact` `RdrName`s for each auxiliary binding with the same
  `OccName`, but using an underlying `System` `Name` with a fresh
  `Unique` for each binding. Unlike hashes, allocating new `Unique`s
  does not require any cleverness and avoid name clashes all the
  same...
* ...speaking of which, in order to convince the renamer that multiple
  auxiliary bindings with the same `OccName` (but different
  `Unique`s) are kosher, we now use `rnLocalValBindsLHS` instead of
  `rnTopBindsLHS` to rename auxiliary bindings. Again, see
  `Note [Auxiliary binders]` for the full story.
* I have removed the `DerivHsBind` constructor for
  `DerivStuff`—which was only used for `Data.Data`-related
  auxiliary bindings—and refactored `gen_Data_binds` to use
  `DerivAuxBind` instead. This brings the treatment of
  `Data.Data`-related auxiliary bindings in line with every other
  form of auxiliary binding.

Fixes #18321.

- - - - -
a403eb91 by Sylvain Henry at 2020-06-27T11:55:59-04:00
ghc-bignum: fix division by zero (#18359)

- - - - -
1b3d13b6 by Sylvain Henry at 2020-06-27T11:55:59-04:00
Fix ghc-bignum exceptions

We must ensure that exceptions are not simplified. Previously we used:

   case raiseDivZero of
      _ -> 0## -- dummyValue

But it was wrong because the evaluation of `raiseDivZero` was removed and
the dummy value was directly returned. See new Note [ghc-bignum exceptions].

I've also removed the exception triggering primops which were fragile.
We don't need them to be primops, we can have them exported by ghc-prim.

I've also added a test for #18359 which triggered this patch.

- - - - -
a74ec37c by Simon Peyton Jones at 2020-06-27T11:56:34-04:00
Better loop detection in findTypeShape

Andreas pointed out, in !3466, that my fix for #18304 was not
quite right.  This patch fixes it properly, by having just one
RecTcChecker rather than (implicitly) two nested ones, in
findTypeShape.

- - - - -
a04020b8 by Sylvain Henry at 2020-06-27T11:57:11-04:00
DynFlags: don't store buildTag

`DynFlags.buildTag` was a field created from the set of Ways in
`DynFlags.ways`. It had to be kept in sync with `DynFlags.ways` which
was fragile. We want to avoid global state like this (#17957).

Moreover in #14335 we also want to support loading units with different
ways: target units would still use `DynFlags.ways` but plugins would use
`GHC.Driver.Ways.hostFullWays`. To avoid having to deal both with build
tag and with ways, we recompute the buildTag on-the-fly (should be
pretty cheap) and we remove `DynFlags.buildTag` field.

- - - - -
0e83efa2 by Krzysztof Gogolewski at 2020-06-27T11:57:49-04:00
Don't generalize when typechecking a tuple section

The code is simpler and cleaner.

- - - - -
d8ba9e6f by Peter Trommler at 2020-06-28T09:19:11-04:00
RTS: Refactor Haskell-C glue for PPC 64-bit

Make sure the stack is 16 byte aligned even when reserved stack
bytes are not a multiple of 16 bytes.

Avoid saving r2 (TOC). On ELF v1 the function descriptor of StgReturn
has the same TOC as StgRun, on ELF v2 the TOC is recomputed in the
function prologue.

Use the ABI provided functions to save clobbered GPRs and FPRs.

Improve comments. Describe what the stack looks like and how it relates
to the respective ABIs.

- - - - -
42f797b0 by Ryan Scott at 2020-06-28T09:19:46-04:00
Use NHsCoreTy to embed types into GND-generated code

`GeneralizedNewtypeDeriving` is in the unique situation where it must
produce an `LHsType GhcPs` from a Core `Type`. Historically, this was
done with the `typeToLHsType` function, which walked over the entire
`Type` and attempted to construct an `LHsType` with the same overall
structure. `typeToLHsType` is quite complicated, however, and has
been the subject of numerous bugs over the years (e.g., #14579).

Luckily, there is an easier way to accomplish the same thing: the
`XHsType` constructor of `HsType`. `XHsType` bundles an `NHsCoreTy`,
which allows embedding a Core `Type` directly into an `HsType`,
avoiding the need to laboriously convert from one to another (as
`typeToLHsType` did). Moreover, renaming and typechecking an
`XHsType` is simple, since one doesn't need to do anything to a
Core `Type`...

...well, almost. For the reasons described in
`Note [Typechecking NHsCoreTys]` in `GHC.Tc.Gen.HsType`, we must
apply a substitution that we build from the local `tcl_env` type
environment. But that's a relatively modest price to pay.

Now that `GeneralizedNewtypeDeriving` uses `NHsCoreTy`, the
`typeToLHsType` function no longer has any uses in GHC, so this patch
rips it out. Some additional tweaks to `hsTypeNeedsParens` were
necessary to make the new `-ddump-deriv` output correctly
parenthesized, but other than that, this patch is quite
straightforward.

This is a mostly internal refactoring, although it is likely that
`GeneralizedNewtypeDeriving`-generated code will now need fewer
language extensions in certain situations than it did before.

- - - - -
68530b1c by Jan Hrček at 2020-06-28T09:20:22-04:00
Fix duplicated words and typos in comments and user guide

- - - - -
15b79bef by Ryan Scott at 2020-06-28T09:20:57-04:00
Add integer-gmp's ghc.mk and GNUmakefile to .gitignore

- - - - -
bfa5698b by Simon Peyton Jones at 2020-06-28T09:21:32-04:00
Fix a typo in Lint

This simple error in GHC.Core.Litn.lintJoinLams meant that
Lint reported bogus errors.

Fixes #18399

- - - - -
71006532 by Ryan Scott at 2020-06-30T07:10:42-04:00
Reject nested foralls/contexts in instance types more consistently

GHC is very wishy-washy about rejecting instance declarations with
nested `forall`s or contexts that are surrounded by outermost
parentheses. This can even lead to some strange interactions with
`ScopedTypeVariables`, as demonstrated in #18240. This patch makes
GHC more consistently reject instance types with nested
`forall`s/contexts so as to prevent these strange interactions.

On the implementation side, this patch tweaks `splitLHsInstDeclTy`
and `getLHsInstDeclHead` to not look through parentheses, which can
be semantically significant. I've added a
`Note [No nested foralls or contexts in instance types]` in
`GHC.Hs.Type` to explain why. This also introduces a
`no_nested_foralls_contexts_err` function in `GHC.Rename.HsType` to
catch nested `forall`s/contexts in instance types. This function is
now used in `rnClsInstDecl` (for ordinary instance declarations) and
`rnSrcDerivDecl` (for standalone `deriving` declarations), the latter
of which fixes #18271.

On the documentation side, this adds a new
"Formal syntax for instance declaration types" section to the GHC
User's Guide that presents a BNF-style grammar for what is and isn't
allowed in instance types.

Fixes #18240. Fixes #18271.

- - - - -
bccf3351 by Sylvain Henry at 2020-06-30T07:10:46-04:00
Add ghc-bignum to 8.12 release notes

- - - - -
81704a6f by David Eichmann at 2020-06-30T07:10:48-04:00
Update ssh keys in CI performance metrics upload script

- - - - -
85310fb8 by Joshua Price at 2020-06-30T07:10:49-04:00
Add missing Ix instances for tuples of size 6 through 15 (#16643)

- - - - -
b935cd85 by Vladislav Zavialov at 2020-07-01T00:13:40+03:00
Accumulate Haddock comments in P (#17544, #17561)

Haddock comments are, first and foremost, comments. It's very annoying
to incorporate them into the grammar. We can take advantage of an
important property: adding a Haddock comment does not change the parse
tree in any way other than wrapping some nodes in HsDocTy and the like
(and if it does, that's a bug).

This patch implements the following:

* Accumulate Haddock comments with their locations in the P monad.
  This is handled in the lexer.

* After parsing, do a pass over the AST to associate Haddock comments
  with AST nodes using location info.

* Report the leftover comments to the user as a warning (-Winvalid-haddock).

Metric Increase:
    T13719
    ManyConstructors
    haddock.Cabal
    haddock.base
    haddock.compiler

- - - - -


30 changed files:

- .gitlab/test-metrics.sh
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/PrimOps.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/Types/Prim.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/Cmm/Info/Build.hs
- compiler/GHC/Cmm/Monad.hs
- compiler/GHC/CmmToAsm/BlockLayout.hs
- compiler/GHC/CmmToAsm/SPARC/Regs.hs
- compiler/GHC/CmmToAsm/X86/Ppr.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Multiplicity.hs
- compiler/GHC/Core/Opt/Driver.hs
- compiler/GHC/Core/Opt/Simplify.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Data/Bitmap.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/CodeOutput.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/724bdb0c22594512604236ebc776cb04fd32bdc9...b935cd856c2e11efc30805c9233e21760005df1f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/724bdb0c22594512604236ebc776cb04fd32bdc9...b935cd856c2e11efc30805c9233e21760005df1f
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/20200630/131bc561/attachment-0001.html>


More information about the ghc-commits mailing list