[Git][ghc/ghc][wip/always-use-rnImplicitBndrs] 14 commits: gitlab-ci: Ensure that workaround for #18280 applies to bindisttest

Ryan Scott gitlab at gitlab.haskell.org
Fri Jun 5 17:04:46 UTC 2020



Ryan Scott pushed to branch wip/always-use-rnImplicitBndrs at Glasgow Haskell Compiler / GHC


Commits:
d6279ff0 by Ben Gamari at 2020-06-02T13:03:30-04:00
gitlab-ci: Ensure that workaround for #18280 applies to bindisttest

We need to ensure that the `configure` flags working around #18280 are
propagated to the bindisttest `configure` as well.

- - - - -
cb5c31b5 by Ben Gamari at 2020-06-03T17:55:04-04:00
gitlab-ci: Allow ARMv7 job to fail

Due to #18298.

- - - - -
32a4ae90 by John Ericson at 2020-06-04T04:34:42-04:00
Clean up boot vs non-boot disambiguating types

We often have (ModuleName, Bool) or (Module, Bool) pairs for "extended"
module names (without or with a unit id) disambiguating boot and normal
modules. We think this is important enough across the compiler that it
deserves a new nominal product type. We do this with synnoyms and a
functor named with a `Gen` prefix, matching other newly created
definitions.

It was also requested that we keep custom `IsBoot` / `NotBoot` sum type.
So we have it too. This means changing many the many bools to use that
instead.

Updates `haddock` submodule.

- - - - -
c05756cd by Niklas Hambüchen at 2020-06-04T04:35:24-04:00
docs: Add more details on InterruptibleFFI.

Details from https://gitlab.haskell.org/ghc/ghc/issues/8684
and https://github.com/takano-akio/filelock/pull/7#discussion_r280332430

- - - - -
1b975aed by Andrew Martin at 2020-06-04T04:36:03-04:00
Allow finalizeForeignPtr to be called on FinalPtr/PlainPtr.

MR 2165 (commit 49301ad6226d9a83d110bee8c419615dd94f5ded) regressed
finalizeForeignPtr by throwing exceptions when PlainPtr was encounterd.
This regression did not make it into a release of GHC. Here, the
original behavior is restored, and FinalPtr is given the same treatment
as PlainPtr.

- - - - -
2bd3929a by Luke Lau at 2020-06-04T04:36:41-04:00
Fix documentation on type families not being extracted

It looks like the location of the Names used for CoAxioms on type
families are now located at their type constructors. Previously, Docs.hs
thought the Names were located in the RHS, so the RealSrcSpan in the
instanceMap and getInstLoc didn't match up. Fixes #18241

- - - - -
6735b9d9 by Ben Gamari at 2020-06-04T04:37:21-04:00
GHC.Hs.Instances: Compile with -O0

This module contains exclusively Data instances, which are going to be
slow no matter what we do. Furthermore, they are incredibly slow to
compile with optimisation (see #9557). Consequently we compile this with
-O0.  See #18254.

- - - - -
c330331a by nineonine at 2020-06-04T04:37:59-04:00
Add test for #17669

- - - - -
cab684f0 by Ben Gamari at 2020-06-04T04:38:36-04:00
rts: Add Windows-specific implementation of rtsSleep

Previously we would use the POSIX path, which uses `nanosleep`. However,
it turns out that `nanosleep` is provided by `libpthread` on Windows. In
general we don't want to incur such a dependency. Avoid this by simply
using `Sleep` on Windows.

Fixes #18272.

- - - - -
ad44b504 by Ben Gamari at 2020-06-04T04:38:36-04:00
compiler: Disable use of process jobs with process < 1.6.9

Due to #17926.

- - - - -
6a4098a4 by Moritz Angermann at 2020-06-04T04:55:51-04:00
[linker] Adds void printLoadedObjects(void);

This allows us to dump in-memory object code locations for debugging.

Fixup printLoadedObjects prototype

- - - - -
af5e3a88 by Artem Pelenitsyn at 2020-06-05T03:18:49-04:00
base: fix sign confusion in log1mexp implementation (fix #17125)

author: claude (https://gitlab.haskell.org/trac-claude)

The correct threshold for log1mexp is -(log 2) with the current specification
of log1mexp. This change improves accuracy for large negative inputs.

To avoid code duplication, a small helper function is added;
it isn't the default implementation in Floating because it needs Ord.

This patch does nothing to address that the Haskell specification is
different from that in common use in other languages.

- - - - -
2b792fac by Simon Peyton Jones at 2020-06-05T09:27:50-04:00
Simple subsumption

This patch simplifies GHC to use simple subsumption.
  Ticket #17775

Implements GHC proposal #287
   https://github.com/ghc-proposals/ghc-proposals/blob/master/
   proposals/0287-simplify-subsumption.rst

All the motivation is described there; I will not repeat it here.
The implementation payload:
 * tcSubType and friends become noticably simpler, because it no
   longer uses eta-expansion when checking subsumption.
 * No deeplyInstantiate or deeplySkolemise

That in turn means that some tests fail, by design; they can all
be fixed by eta expansion.  There is a list of such changes below.

Implementing the patch led me into a variety of sticky corners, so
the patch includes several othe changes, some quite significant:

* I made String wired-in, so that
    "foo" :: String   rather than
    "foo" :: [Char]
  This improves error messages, and fixes #15679

* The pattern match checker relies on knowing about in-scope equality
  constraints, andd adds them to the desugarer's environment using
  addTyCsDs.  But the co_fn in a FunBind was missed, and for some reason
  simple-subsumption ends up with dictionaries there. So I added a
  call to addTyCsDs.  This is really part of #18049.

* I moved the ic_telescope field out of Implication and into
  ForAllSkol instead.  This is a nice win; just expresses the code
  much better.

* There was a bug in GHC.Tc.TyCl.Instance.tcDataFamInstHeader.
  We called checkDataKindSig inside tc_kind_sig, /before/
  solveEqualities and zonking.  Obviously wrong, easily fixed.

* solveLocalEqualitiesX: there was a whole mess in here, around
  failing fast enough.  I discovered a bad latent bug where we
  could successfully kind-check a type signature, and use it,
  but have unsolved constraints that could fill in coercion
  holes in that signature --  aargh.

  It's all explained in Note [Failure in local type signatures]
  in GHC.Tc.Solver. Much better now.

* I fixed a serious bug in anonymous type holes. IN
    f :: Int -> (forall a. a -> _) -> Int
  that "_" should be a unification variable at the /outer/
  level; it cannot be instantiated to 'a'.  This was plain
  wrong.  New fields mode_lvl and mode_holes in TcTyMode,
  and auxiliary data type GHC.Tc.Gen.HsType.HoleMode.

  This fixes #16292, but makes no progress towards the more
  ambitious #16082

* I got sucked into an enormous refactoring of the reporting of
  equality errors in GHC.Tc.Errors, especially in
      mkEqErr1
      mkTyVarEqErr
      misMatchMsg
      misMatchMsgOrCND
  In particular, the very tricky mkExpectedActualMsg function
  is gone.

  It took me a full day.  But the result is far easier to understand.
  (Still not easy!)  This led to various minor improvements in error
  output, and an enormous number of test-case error wibbles.

  One particular point: for occurs-check errors I now just say
     Can't match 'a' against '[a]'
  rather than using the intimidating language of "occurs check".

* Pretty-printing AbsBinds

Tests review

* Eta expansions
   T11305: one eta expansion
   T12082: one eta expansion (undefined)
   T13585a: one eta expansion
   T3102:  one eta expansion
   T3692:  two eta expansions (tricky)
   T2239:  two eta expansions
   T16473: one eta
   determ004: two eta expansions (undefined)
   annfail06: two eta (undefined)
   T17923: four eta expansions (a strange program indeed!)
   tcrun035: one eta expansion

* Ambiguity check at higher rank.  Now that we have simple
  subsumption, a type like
     f :: (forall a. Eq a => Int) -> Int
  is no longer ambiguous, because we could write
     g :: (forall a. Eq a => Int) -> Int
     g = f
  and it'd typecheck just fine.  But f's type is a bit
  suspicious, and we might want to consider making the
  ambiguity check do a check on each sub-term.  Meanwhile,
  these tests are accepted, whereas they were previously
  rejected as ambiguous:
     T7220a
     T15438
     T10503
     T9222

* Some more interesting error message wibbles
   T13381: Fine: one error (Int ~ Exp Int)
           rather than two (Int ~ Exp Int, Exp Int ~ Int)
   T9834:  Small change in error (improvement)
   T10619: Improved
   T2414:  Small change, due to order of unification, fine
   T2534:  A very simple case in which a change of unification order
           means we get tow unsolved constraints instead of one
   tc211: bizarre impredicative tests; just accept this for now

Updates Cabal and haddock submodules.

Metric Increase:
  T12150
  T12234
  T5837
  haddock.base
Metric Decrease:
  haddock.compiler
  haddock.Cabal
  haddock.base

Merge note: This appears to break the
`UnliftedNewtypesDifficultUnification` test. It has been marked as
broken in the interest of merging.

(cherry picked from commit 66b7b195cb3dce93ed5078b80bf568efae904cc5)

- - - - -
6858859d by Ryan Scott at 2020-06-05T12:28:36-04:00
Always use rnImplicitBndrs to bring implicit tyvars into scope

This implements a first step towards #16762 by changing the renamer
to always use `rnImplicitBndrs` to bring implicitly bound type
variables into scope. The main change is in `rnFamInstEqn` and
`bindHsQTyVars`, which previously used _ad hoc_ methods of binding
their implicit tyvars.

There are a number of knock-on consequences:

* One of the reasons that `rnFamInstEqn` used an _ad hoc_ binding
  mechanism was to give more precise source locations in
  `-Wunused-type-patterns` warnings. (See
  https://gitlab.haskell.org/ghc/ghc/issues/16762#note_273343 for an
  example of this.) However, these warnings are actually a little
  _too_ precise, since implicitly bound type variables don't have
  exact binding sites like explicitly bound type variables do.
  A similar problem existed for
  "`Different names for the same type variable`" errors involving
  implicit tyvars bound by `bindHsQTyVars`.
  Therefore, we simply accept the less precise (but more accurate)
  source locations from `rnImplicitBndrs` in `rnFamInstEqn` and
  `bindHsQTyVars`. See
  `Note [Source locations for implicitly bound type variables]` in
  `GHC.Rename.HsType` for the full story.
* In order for `rnImplicitBndrs` to work in `rnFamInstEqn`, it needs
  to be able to look up names from the parent class (in the event
  that we are renaming an associated type family instance). As a
  result, `rnImplicitBndrs` now takes an argument of type
  `Maybe assoc`, which is `Just` in the event that a type family
  instance is associated with a class.
* Previously, GHC kept track of three type synonyms for free type
  variables in the renamer: `FreeKiTyVars`, `FreeKiTyVarsDups`
  (which are allowed to contain duplicates), and
  `FreeKiTyVarsNoDups` (which contain no duplicates). However, making
  is a distinction between `-Dups` and `-NoDups` is now pointless, as
  all code that returns `FreeKiTyVars{,Dups,NoDups}` will eventually
  end up being passed to `rnImplicitBndrs`, which removes duplicates.
  As a result, I decided to just get rid of `FreeKiTyVarsDups` and
  `FreeKiTyVarsNoDups`, leaving only `FreeKiTyVars`.
* The `bindLRdrNames` and `deleteBys` functions are now dead code, so
  I took the liberty of removing them.

- - - - -


30 changed files:

- .gitlab-ci.yml
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Data/List/SetOps.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Types.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/HsToCore/PmCheck.hs
- compiler/GHC/HsToCore/Usage.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Names.hs


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/00d38d2af6cd755b7ed175f5f87b90d309be2a5c...6858859d1d448e0ef10e05406d4e03b1c0aae68f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/00d38d2af6cd755b7ed175f5f87b90d309be2a5c...6858859d1d448e0ef10e05406d4e03b1c0aae68f
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/20200605/63d70a90/attachment-0001.html>


More information about the ghc-commits mailing list