| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This fixes a variety of testsuite failures with integer-simple of the form
```
--- typecheck/should_fail/tcfail072.run/tcfail072.stderr.normalised
+++ typecheck/should_fail/tcfail072.run/tcfail072.comp.stderr.normalised
@@ -12,7 +12,7 @@
-- Defined in ‘integer-<IMPL>-<VERSION>:GHC.Integer.Type’
instance Ord () -- Defined in ‘GHC.Classes’
...plus 21 others
- ...plus three instances involving out-of-scope types
+ ...plus two instances involving out-of-scope types
(use -fprint-potential-instances to see them all)
In the expression: g A
In an equation for ‘g’: g (B _ _) = g A
```
In service of fixing #16043.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
I had allowed rename/should_fail/T15828 (Trac #15828) to regress a bit.
The main payload of this patch is to fix that problem, at the cost of
more contortions in checkConsistentFamInst. Oh well, at least they are
highly localised.
I also update the -ddump-types code in TcRnDriver to print out some
more expicit information about each type constructor, thus instead of
DF{3} :: forall k. * -> k -> *
we get
data family DF{3} :: forall k. * -> k -> *
Remember, this is debug-printing only. This change is the reason
that so many .stderr files change.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
My original goal was (Trac #15809) to move towards using level numbers
as the basis for deciding which type variables to generalise, rather
than searching for the free varaibles of the environment. However
it has turned into a truly major refactoring of the kind inference
engine.
Let's deal with the level-numbers part first:
* Augment quantifyTyVars to calculate the type variables to
quantify using level numbers, and compare the result with
the existing approach. That is; no change in behaviour,
just a WARNing if the two approaches give different answers.
* To do this I had to get the level number right when calling
quantifyTyVars, and this entailed a bit of care, especially
in the code for kind-checking type declarations.
* However, on the way I was able to eliminate or simplify
a number of calls to solveEqualities.
This work is incomplete: I'm not /using/ level numbers yet.
When I subsequently get rid of any remaining WARNings in
quantifyTyVars, that the level-number answers differ from
the current answers, then I can rip out the current
"free vars of the environment" stuff.
Anyway, this led me into deep dive into kind inference for type and
class declarations, which is an increasingly soggy part of GHC.
Richard already did some good work recently in
commit 5e45ad10ffca1ad175b10f6ef3327e1ed8ba25f3
Date: Thu Sep 13 09:56:02 2018 +0200
Finish fix for #14880.
The real change that fixes the ticket is described in
Note [Naughty quantification candidates] in TcMType.
but I kept turning over stones. So this patch has ended up
with a pretty significant refactoring of that code too.
Kind inference for types and classes
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
* Major refactoring in the way we generalise the inferred kind of
a TyCon, in kcTyClGroup. Indeed, I made it into a new top-level
function, generaliseTcTyCon. Plus a new Note to explain it
Note [Inferring kinds for type declarations].
* We decided (Trac #15592) not to treat class type variables specially
when dealing with Inferred/Specified/Required for associated types.
That simplifies things quite a bit. I also rewrote
Note [Required, Specified, and Inferred for types]
* Major refactoring of the crucial function kcLHsQTyVars:
I split it into
kcLHsQTyVars_Cusk and kcLHsQTyVars_NonCusk
because the two are really quite different. The CUSK case is
almost entirely rewritten, and is much easier because of our new
decision not to treat the class variables specially
* I moved all the error checks from tcTyClTyVars (which was a bizarre
place for it) into generaliseTcTyCon and/or the CUSK case of
kcLHsQTyVars. Now tcTyClTyVars is extremely simple.
* I got rid of all the all the subtleties in tcImplicitTKBndrs. Indeed
now there is no difference between tcImplicitTKBndrs and
kcImplicitTKBndrs; there is now a single bindImplicitTKBndrs.
Same for kc/tcExplicitTKBndrs. None of them monkey with level
numbers, nor build implication constraints. scopeTyVars is gone
entirely, as is kcLHsQTyVarBndrs. It's vastly simpler.
I found I could get rid of kcLHsQTyVarBndrs entirely, in favour of
the bnew bindExplicitTKBndrs.
Quantification
~~~~~~~~~~~~~~
* I now deal with the "naughty quantification candidates"
of the previous patch in candidateQTyVars, rather than in
quantifyTyVars; see Note [Naughty quantification candidates]
in TcMType.
I also killed off closeOverKindsCQTvs in favour of the same
strategy that we use for tyCoVarsOfType: namely, close over kinds
at the occurrences.
And candidateQTyVars no longer needs a gbl_tvs argument.
* Passing the ContextKind, rather than the expected kind itself,
to tc_hs_sig_type_and_gen makes it easy to allocate the expected
result kind (when we are in inference mode) at the right level.
Type families
~~~~~~~~~~~~~~
* I did a major rewrite of the impenetrable tcFamTyPats. The result
is vastly more comprehensible.
* I got rid of kcDataDefn entirely, quite a big function.
* I re-did the way that checkConsistentFamInst works, so
that it allows alpha-renaming of invisible arguments.
* The interaction of kind signatures and family instances is tricky.
Type families: see Note [Apparently-nullary families]
Data families: see Note [Result kind signature for a data family instance]
and Note [Eta-reduction for data families]
* The consistent instantation of an associated type family is tricky.
See Note [Checking consistent instantiation] and
Note [Matching in the consistent-instantation check]
in TcTyClsDecls. It's now checked in TcTyClsDecls because that is
when we have the relevant info to hand.
* I got tired of the compromises in etaExpandFamInst, so I did the
job properly by adding a field cab_eta_tvs to CoAxBranch.
See Coercion.etaExpandCoAxBranch.
tcInferApps and friends
~~~~~~~~~~~~~~~~~~~~~~~
* I got rid of the mysterious and horrible ClsInstInfo argument
to tcInferApps, checkExpectedKindX, and various checkValid
functions. It was horrible!
* I got rid of [Type] result of tcInferApps. This list was used
only in tcFamTyPats, when checking the LHS of a type instance;
and if there is a cast in the middle, the list is meaningless.
So I made tcInferApps simpler, and moved the complexity
(not much) to tcInferApps.
Result: tcInferApps is now pretty comprehensible again.
* I refactored the many function in TcMType that instantiate skolems.
Smaller things
* I rejigged the error message in checkValidTelescope; I think it's
quite a bit better now.
* checkValidType was not rejecting constraints in a kind signature
forall (a :: Eq b => blah). blah2
That led to further errors when we then do an ambiguity check.
So I make checkValidType reject it more aggressively.
* I killed off quantifyConDecl, instead calling kindGeneralize
directly.
* I fixed an outright bug in tyCoVarsOfImplic, where we were not
colleting the tyvar of the kind of the skolems
* Renamed ClsInstInfo to AssocInstInfo, and made it into its
own data type
* Some fiddling around with pretty-printing of family
instances which was trickier than I thought. I wanted
wildcards to print as plain "_" in user messages, although
they each need a unique identity in the CoAxBranch.
Some other oddments
* Refactoring around the trace messages from reportUnsolved.
* A bit of extra tc-tracing in TcHsSyn.commitFlexi
This patch fixes a raft of bugs, and includes tests for them.
* #14887
* #15740
* #15764
* #15789
* #15804
* #15817
* #15870
* #15874
* #15881
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch changes the behavior of `-fprint-explicit-kinds`
so that it displays kind argument using visible kind application.
In other words, the flag now:
1. Prints instantiations of specified variables with `@(...)`.
2. Prints instantiations of inferred variables with `@{...}`.
In addition, this patch removes the `Use -fprint-explicit-kinds to
see the kind arguments` error message that often arises when a type
mismatch occurs due to different kinds. Instead, whenever there is a
kind mismatch, we now enable the `-fprint-explicit-kinds` flag
locally to help cue to the programmer where the error lies.
(See `Note [Kind arguments in error messages]` in `TcErrors`.)
As a result, these funny `@{...}` things can now appear to the user
even without turning on the `-fprint-explicit-kinds` flag explicitly,
so I took the liberty of documenting them in the users' guide.
Test Plan: ./validate
Reviewers: goldfire, simonpj, bgamari
Reviewed By: simonpj
Subscribers: rwbarton, carter
GHC Trac Issues: #15871
Differential Revision: https://phabricator.haskell.org/D5314
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
When I defined `etaExpandFamInstLHS`, I blatantly forgot
to eta expand the RHSes of data family instances. (Actually, I
claimed that they didn't //need// to be eta expanded. I'm not sure
what I was thinking.)
This fixes the issue by changing `etaExpandFamInstLHS` to
`etaExpandFamInst` and, well, making it actually eta expand the RHS.
Test Plan: make test TEST=T15852
Reviewers: goldfire, bgamari
Reviewed By: goldfire
Subscribers: rwbarton, carter
GHC Trac Issues: #15852
Differential Revision: https://phabricator.haskell.org/D5328
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Consider the type
forall k. b -> k
where
b :: k -> Type
Here the 'k' in b's kind must be a different 'k' to the forall k,
because 'b' is free in the expression. So we must return 'k'
among the free vars returned from tyCoVarsOfType applied that
type. But we weren't.
This is an outright bug, although we don't have a program that
fails because of it.
It's easy to fix, too: see TyCoRep
Note [Closing over free variable kinds]
This fix has been in the pipeline for ages because it fell into
the Trac #14880 swamp. But this patch nails it.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Trac #15648 showed that GHC was a bit confused about the
difference between the types for
* Predicates
* Coercions
* Evidence (in the typechecker constraint solver)
This patch cleans it up. See especially Type.hs
Note [Types for coercions, predicates, and evidence]
Particular changes
* Coercion types (a ~# b) and (a ~#R b) are not predicate types
(so isPredTy reports False for them) and are not implicitly
instantiated by the type checker. This is a real change, but
it consistently reflects that fact that (~#) and (~R#) really
are different from predicates.
* isCoercionType is renamed to isCoVarType
* During type inference, simplifyInfer, we do /not/ want to infer
a constraint (a ~# b), because that is no longer a predicate type.
So we 'lift' it to (a ~ b). See TcType
Note [Lift equality constaints when quantifying]
* During type inference for pattern synonyms, we need to 'lift'
provided constraints of type (a ~# b) to (a ~ b). See
Note [Equality evidence in pattern synonyms] in PatSyn
* But what about (forall a. Eq a => a ~# b)? Is that a
predicate type? No -- it does not have kind Constraint.
Is it an evidence type? Perhaps, but awkwardly so.
In the end I decided NOT to make it an evidence type,
and to ensure the the type inference engine never
meets it. This made me /simplify/ the code in
TcCanonical.makeSuperClasses; see TcCanonical
Note [Equality superclasses in quantified constraints]
Instead I moved the special treatment for primitive
equality to TcInteract.doTopReactOther. See TcInteract
Note [Looking up primitive equalities in quantified constraints]
Also see Note [Evidence for quantified constraints] in Type.
All this means I can have
isEvVarType ty = isCoVarType ty || isPredTy ty
which is nice.
All in all, rather a lot of work for a small refactoring,
but I think it's a real improvement.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch makes a number of improvements to the output
generated by -ddump-types
* Prints data constructor separately
* Omits empty chunks of output
I was driven initially by the unhelpful existing output for
data constructors, but ended up doing some refactoring.
Lots of error message wibbles, but nothing significant.
Certainly no change in user behaviour.
(NB: It is just possible that I have failed to cleanly
separate this patch from the next one, about
isPredTy and friends.)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Enabling -Werror=compat in the testsuite allows us to easily see the
impact that a new warning has on code. It also means that in the period
between adding the warning and making the actual breaking change, all
new test cases that are being added to the testsuite will be
forwards-compatible. This is good because it will make the actual
breaking change contain less irrelevant testsuite updates.
Things that -Wcompat warns about are things that are going to break in
the future, so we can be proactive and keep our testsuite
forwards-compatible.
This patch consists of two main changes:
* Add `TEST_HC_OPTS += -Werror=compat` to the testsuite configuration.
* Fix all broken test cases.
Test Plan: Validate
Reviewers: hvr, goldfire, bgamari, simonpj, RyanGlScott
Reviewed By: goldfire, RyanGlScott
Subscribers: rwbarton, carter
GHC Trac Issues: #15278
Differential Revision: https://phabricator.haskell.org/D5200
|
|
|
|
|
|
|
|
|
|
|
| |
The debug flag -ddump-types is supposed to show the type
of Ids, and the kinds of type constructors. It was doing
the former but not the latter -- instead it was using
showTyTying, which is actually less helpful when debugging.
This patch changes it to print the kind and roles of the thing.
I also made -ddump-types show pattern synonyms
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Test Plan: Validate
Reviewers: goldfire, simonpj, bgamari
Reviewed By: simonpj
Subscribers: RyanGlScott, rwbarton, thomie, carter
GHC Trac Issues: #15415
Differential Revision: https://phabricator.haskell.org/D5022
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Implementation of the "Embrace TypeInType" proposal was done according
to the spec, which specified that TypeOperators must imply NoStarIsType.
This implication was meant to prevent breakage and to be removed in 2
releases. However, compiling head.hackage has shown that this
implication only magnified the breakage, so there is no reason to have
it in the first place.
To remain in compliance with the three-release policy, we add a
workaround to define the (*) type operator even when -XStarIsType is on.
Test Plan: ./validate
Reviewers: bgamari, RyanGlScott, goldfire, phadej, hvr
Reviewed By: bgamari, RyanGlScott
Subscribers: harpocrates, rwbarton, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4865
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
Currently, an `IfaceAppTy` has no way to tell whether its
argument is visible or not, so it simply treats all arguments as
visible, leading to #15330. We already have a solution for this
problem in the form of the `IfaceTcArgs` data structure, used by
`IfaceTyConApp` to represent the arguments to a type constructor.
Therefore, it makes sense to reuse this machinery for `IfaceAppTy`,
so this patch does just that.
This patch:
1. Renames `IfaceTcArgs` to `IfaceAppArgs` to reflect its more
general purpose.
2. Changes the second field of `IfaceAppTy` from `IfaceType` to
`IfaceAppArgs`, and propagates the necessary changes through. In
particular, pretty-printing an `IfaceAppTy` now goes through the
`IfaceAppArgs` pretty-printer, which correctly displays arguments
as visible or not for free, fixing #15330.
3. Changes `toIfaceTypeX` and related functions so that when
converting an `AppTy` to an `IfaceAppTy`, it flattens as many
argument `AppTy`s as possible, and then converts those arguments
into an `IfaceAppArgs` list, using the kind of the function
`Type` as a guide. (Doing so minimizes the number of times we need
to call `typeKind`, which is more expensive that finding the kind
of a `TyCon`.)
Test Plan: make test TEST=T15330
Reviewers: goldfire, simonpj, bgamari
Reviewed By: simonpj
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #15330
Differential Revision: https://phabricator.haskell.org/D4938
|
|
|
|
|
|
|
|
|
|
|
| |
Previously, checking whether (tv |> co) ~ (tv |> co) got deferred,
because we looked for vars before stripping casts. (The left type
would get stripped, and then tv ~ (tv |> co) would scare the occurs-
checker.)
This opportunity for improvement presented itself in other work.
This is just an optimization. Some programs can now report more
errors simultaneously.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
There are several changes here.
* TcInteract has gotten too big, so I moved all the class-instance
matching out of TcInteract into a new module ClsInst. It parallels
the FamInst module.
The main export of ClsInst is matchGlobalInst.
This now works in TcM not TcS.
* A big reason to make matchGlobalInst work in TcM is that we can
then use it from TcValidity.checkSimplifiableClassConstraint.
That extends checkSimplifiableClassConstraint to work uniformly
for built-in instances, which means that we now get a warning
if we have givens (Typeable x, KnownNat n); see Trac #15322.
* This change also made me refactor LookupInstResult, in particular
by adding the InstanceWhat field. I also changed the name of the
type to ClsInstResult.
Then instead of matchGlobalInst reporting a staging error (which is
inappropriate for the call from TcValidity), we can do so in
TcInteract.checkInstanceOK.
* In TcValidity, we now check quantified constraints for termination.
For example, this signature should be rejected:
f :: (forall a. Eq (m a) => Eq (m a)) => blah
as discussed in Trac #15316. The main change here is that
TcValidity.check_pred_help now uses classifyPredType, and has a
case for ForAllPred which it didn't before.
This had knock-on refactoring effects in TcValidity.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Add support for built-in Natural literals in Core.
- Replace MachInt,MachWord, LitInteger, etc. with a single LitNumber
constructor with a LitNumType field
- Support built-in Natural literals
- Add desugar warning for negative literals
- Move Maybe(..) from GHC.Base to GHC.Maybe for module dependency
reasons
This patch introduces only a few rules for Natural literals (compared
to Integer's rules). Factorization of the built-in rules for numeric
literals will be done in another patch as this one is already big to
review.
Test Plan:
validate
test build with integer-simple
Reviewers: hvr, bgamari, goldfire, Bodigrim, simonmar
Reviewed By: bgamari
Subscribers: phadej, simonpj, RyanGlScott, carter, hsyl20, rwbarton,
thomie
GHC Trac Issues: #14170, #14465
Differential Revision: https://phabricator.haskell.org/D4212
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
Implement the "Embrace Type :: Type" GHC proposal,
.../ghc-proposals/blob/master/proposals/0020-no-type-in-type.rst
GHC 8.0 included a major change to GHC's type system: the Type :: Type
axiom. Though casual users were protected from this by hiding its
features behind the -XTypeInType extension, all programs written in GHC
8+ have the axiom behind the scenes. In order to preserve backward
compatibility, various legacy features were left unchanged. For example,
with -XDataKinds but not -XTypeInType, GADTs could not be used in types.
Now these restrictions are lifted and -XTypeInType becomes a redundant
flag that will be eventually deprecated.
* Incorporate the features currently in -XTypeInType into the
-XPolyKinds and -XDataKinds extensions.
* Introduce a new extension -XStarIsType to control how to parse * in
code and whether to print it in error messages.
Test Plan: Validate
Reviewers: goldfire, hvr, bgamari, alanz, simonpj
Reviewed By: goldfire, simonpj
Subscribers: rwbarton, thomie, mpickering, carter
GHC Trac Issues: #15195
Differential Revision: https://phabricator.haskell.org/D4748
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
I've changed the name from `Valid substitutions` to `Valid hole fits`,
since "substitution" already has a well defined meaning within the
theory. As part of this change, the flags and output is reanamed, with
substitution turning into hole-fit in most cases. "hole fit" was already
used internally in the code, it's clear and shouldn't cause any
confusion.
In this update, I've also reworked how we manage side-effects in the
hole we are considering.
This allows us to consider local bindings such as where clauses and
arguments to functions, suggesting e.g. `a` for `head (x:xs) where head
:: [a] -> a`.
It also allows us to find suggestions such as `maximum` for holes of
type `Ord a => a -> [a]`, and `max` when looking for a match for the
hole in `g = foldl1 _`, where `g :: Ord a => [a] -> a`.
We also show much improved output for refinement hole fits, and
fixes #14990. We now show the correct type of the function, but we also
now show what the arguments to the function should be e.g. `foldl1 (_ ::
Integer -> Integer -> Integer)` when looking for `[Integer] -> Integer`.
I've moved the bulk of the code from `TcErrors.hs` to a new file,
`TcHoleErrors.hs`, since it was getting too big to not live on it's own.
This addresses the considerations raised in #14969, and takes proper
care to set the `tcLevel` of the variables to the right level before
passing it to the simplifier.
We now also zonk the suggestions properly, which improves the output of
the refinement hole fits considerably.
This also filters out suggestions from the `GHC.Err` module, since even
though `error` and `undefined` are indeed valid hole fits, they are
"trivial", and almost never useful to the user.
We now find the hole fits using the proper manner, namely by solving
nested implications. This entails that the givens are passed along using
the implications the hole was nested in, which in turn should mean that
there will be fewer weird bugs in the typed holes.
I've also added a new sorting method (as suggested by SPJ) and sort by
the size of the types needed to turn the hole fits into the type of the
hole. This gives a reasonable approximation to relevance, and is much
faster than the subsumption check. I've also added a flag to toggle
whether to use this new sorting algorithm (as is done by default) or the
subsumption algorithm. This fixes #14969
I've also added documentation for these new flags and update the
documentation according to the new output.
Reviewers: bgamari, goldfire
Reviewed By: bgamari
Subscribers: simonpj, rwbarton, thomie, carter
GHC Trac Issues: #14969, #14990, #10946
Differential Revision: https://phabricator.haskell.org/D4444
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
The way we were pretty-printing conflicting data family
instances in an error message was far from ideal:
1. If a data type had no constructors, it would print an equals sign
with nothing to the right of it.
2. It would try to print GADTs using Haskell98 syntax.
3. It eta-reduced away some type variables from the LHS.
This patch addresses these three issues:
1. We no longer print constructors at all in this error message.
There's really no reason to do so in the first place, since
duplicate data family instances always conflict, regardless of
their constructors.
2. Since we no longer print constructors, we no longer have to
worry about whether we're using GADT or Haskell98 syntax.
3. I've put in a fix to ensure that type variables are no longer
eta-reduced away from the LHS.
Test Plan: make test TEST=T14179
Reviewers: goldfire, bgamari
Reviewed By: bgamari
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #14179
Differential Revision: https://phabricator.haskell.org/D4711
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
unpackClosure#'s behavior and type has changed. This caused a CPP guard
in the new ghc-heap package to fail when bootstrapping with GHC 8.4.
Test Plan: Validate bootstrapping with GHC 8.4
Reviewers: RyanGlScott
Subscribers: rwbarton, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4716
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This finally gets us to a green ./validate --slow on linux for a ghc
checkout from the beginning of this week, see
https://circleci.com/gh/ghc/ghc/4739
This is hopefully the final (or second to final) patch to
address #14890.
Test Plan: ./validate --slow
Reviewers: bgamari, hvr, simonmar
Reviewed By: bgamari
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #14890
Differential Revision: https://phabricator.haskell.org/D4712
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Trac #15009 showed that, for Given TyVar/TyVar equalities, we really
want to orient them with the deepest-bound skolem on the left. As it
happens, we also want to do the same for Wanteds, but for a different
reason (more likely to be touchable). Either way, deepest wins:
see TcUnify Note [Deeper level on the left].
This observation led me to some significant changes:
* A SkolemTv already had a TcLevel, but the level wasn't really being
used. Now it is!
* I updated added invariant (SkolInf) to TcType
Note [TcLevel and untouchable type variables], documenting that
the level number of all the ic_skols should be the same as the
ic_tclvl of the implication
* FlatSkolTvs and FlatMetaTvs previously had a dummy level-number of
zero, which messed the scheme up. Now they get a level number the
same way as all other TcTyVars, instead of being a special case.
* To make sure that FlatSkolTvs and FlatMetaTvs are untouchable (which
was previously done via their magic zero level) isTouchableMetaTyVar
just tests for those two cases.
* TcUnify.swapOverTyVars is the crucial orientation function; see the
new Note [TyVar/TyVar orientation]. I completely rewrote this function,
and it's now much much easier to understand.
I ended up doing some related refactoring, of course
* I noticed that tcImplicitTKBndrsX and tcExplicitTKBndrsX were doing
a lot of useless work in the case where there are no skolems; I
added a fast-patch
* Elminate the un-used tcExplicitTKBndrsSig; and thereby get rid of
the higher-order parameter to tcExpliciTKBndrsX.
* Replace TcHsType.emitTvImplication with TcUnify.checkTvConstraints,
by analogy with TcUnify.checkConstraints.
* Inline TcUnify.buildImplication into its only call-site in
TcUnify.checkConstraints
* TcS.buildImplication becomes TcS.CheckConstraintsTcS, with a
simpler API
* Now that we have NoEvBindsVar we have no need of termEvidenceAllowed;
nuke the latter, adding Note [No evidence bindings] to TcEvidence.
|
|
|
|
|
| |
Happily, both of these issues appear to have been fixed in GHC 8.2.
Let's add regression tests for them to ensure that they stay fixed.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
GHC previously had a handful of special cases for
pretty-printing equalities in a more user-friendly manner, but they
were far from comprehensive (see #15039 for an example of where this
fell apart).
This patch makes the pretty-printing of equalities much more
systematic. I've adopted the approach laid out in
https://ghc.haskell.org/trac/ghc/ticket/15039#comment:4, and updated
`Note [Equality predicates in IfaceType]` accordingly. We are now
more careful to respect the properties of the
`-fprint-explicit-kinds` and `-fprint-equality-relations` flags,
which led to some improvements in error message outputs.
Along the way, I also tweaked the error-reporting machinery not to
print out the type of a typed hole when the type is an unlifted
equality, since it's kind (`TYPE ('TupleRep '[])`) was more
confusing than anything.
Test Plan: make test TEST="T15039a T15039b T15039c T15039d"
Reviewers: simonpj, goldfire, bgamari
Reviewed By: simonpj
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #15039
Differential Revision: https://phabricator.haskell.org/D4696
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Trac #15152 showed that when a flag turned an error into a warning, we
were still (alas) suppressing subequent errors; includign their
essential addTcEvBind. That led (rightly) to a Lint error.
This patch fixes it, and incidentally tidies up an ad-hoc special
case of out-of-scope variables (see the old binding for
'out_of_scope_killer' in 'tryReporters').
No test, because the problem was only shown up when turning
inaccessible code into a warning.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This is mostly for congruence with 'subWordC#' and '{add,sub}IntC#'.
I found 'plusWord2#' while implementing this, which both lacks
documentation and has a slightly different specification than
'addWordC#', which means the generic implementation is unnecessarily
complex.
While I was at it, I also added lacking meta-information on PrimOps
and refactored 'subWordC#'s generic implementation to be branchless.
Reviewers: bgamari, simonmar, jrtc27, dfeuer
Reviewed By: bgamari, dfeuer
Subscribers: dfeuer, thomie, carter
Differential Revision: https://phabricator.haskell.org/D4592
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary: Bumps several submodules.
Test Plan: ./validate
Reviewers: hvr, bgamari
Reviewed By: bgamari
Subscribers: thomie, carter
GHC Trac Issues: #15018
Differential Revision: https://phabricator.haskell.org/D4609
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This takes care of bumping the `base` and `integer-gmp`
minor version numbers in anticipation of a GHC 8.4.2 release.
While I was in town, I also filled in a `@since TODO` Haddock
annotation for `powModSecInteger` in `integer-gmp` with
`1.0.2.0`, and updated the changelog accordingly.
Test Plan: ./validate
Reviewers: hvr, goldfire, bgamari
Reviewed By: bgamari
Subscribers: thomie, carter
GHC Trac Issues: #15025
Differential Revision: https://phabricator.haskell.org/D4586
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The main job of this commit is to track more accurately the scope
of tyvars introduced by user-written foralls. For example, it would
be to have something like this:
forall a. Int -> (forall k (b :: k). Proxy '[a, b]) -> Bool
In that type, a's kind must be k, but k isn't in scope. We had a
terrible way of doing this before (not worth repeating or describing
here, but see the old tcImplicitTKBndrs and friends), but now
we have a principled approach: make an Implication when kind-checking
a forall. Doing so then hooks into the existing machinery for
preventing skolem-escape, performing floating, etc. This also means
that we bump the TcLevel whenever going into a forall.
The new behavior is done in TcHsType.scopeTyVars, but see also
TcHsType.tc{Im,Ex}plicitTKBndrs, which have undergone significant
rewriting. There are several Notes near there to guide you. Of
particular interest there is that Implication constraints can now
have skolems that are out of order; this situation is reported in
TcErrors.
A major consequence of this is a slightly tweaked process for type-
checking type declarations. The new Note [Use SigTvs in kind-checking
pass] in TcTyClsDecls lays it out.
The error message for dependent/should_fail/TypeSkolEscape has become
noticeably worse. However, this is because the code in TcErrors goes to
some length to preserve pre-8.0 error messages for kind errors. It's time
to rip off that plaster and get rid of much of the kind-error-specific
error messages. I tried this, and doing so led to a lovely error message
for TypeSkolEscape. So: I'm accepting the error message quality regression
for now, but will open up a new ticket to fix it, along with a larger
error-message improvement I've been pondering. This applies also to
dependent/should_fail/{BadTelescope2,T14066,T14066e}, polykinds/T11142.
Other minor changes:
- isUnliftedTypeKind didn't look for tuples and sums. It does now.
- check_type used check_arg_type on both sides of an AppTy. But the left
side of an AppTy isn't an arg, and this was causing a bad error message.
I've changed it to use check_type on the left-hand side.
- Some refactoring around when we print (TYPE blah) in error messages.
The changes decrease the times when we do so, to good effect.
Of course, this is still all controlled by
-fprint-explicit-runtime-reps
Fixes #14066 #14749
Test cases: dependent/should_compile/{T14066a,T14749},
dependent/should_fail/T14066{,c,d,e,f,g,h}
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
At its core, this patch is a simple tweak that allows a user
to write:
```lang=haskell
deriving instance _ => Eq (Foo a)
```
Which is functionally equivalent to:
```lang=haskell
data Foo a = ...
deriving Eq
```
But with the added flexibility that `StandaloneDeriving` gives you
(namely, the ability to use it anywhere, not just in the same module
that `Foo` was declared in). This fixes #13324, and should hopefully
address a use case brought up in #10607.
Currently, only the use of a single, extra-constraints wildcard is
permitted in a standalone deriving declaration. Any other wildcard
is rejected, so things like
`deriving instance (Eq a, _) => Eq (Foo a)` are currently forbidden.
There are quite a few knock-on changes brought on by this change:
* The `HsSyn` type used to represent standalone-derived instances
was previously `LHsSigType`, which isn't sufficient to hold
wildcard types. This needed to be changed to `LHsSigWcType` as a
result.
* Previously, `DerivContext` was a simple type synonym for
`Maybe ThetaType`, under the assumption that you'd only ever be in
the `Nothing` case if you were in a `deriving` clause. After this
patch, that assumption no longer holds true, as you can also be
in this situation with standalone deriving when an
extra-constraints wildcard is used.
As a result, I changed `DerivContext` to be a proper datatype that
reflects the new wrinkle that this patch adds, and plumbed this
through the relevant parts of `TcDeriv` and friends.
* Relatedly, the error-reporting machinery in `TcErrors` also assumed
that if you have any unsolved constraints in a derived instance,
then you should be able to fix it by switching over to standalone
deriving. This was always sound advice before, but with this new
feature, it's possible to have unsolved constraints even when
you're standalone-deriving something!
To rectify this, I tweaked some constructors of `CtOrigin` a bit
to reflect this new subtlety.
This requires updating the Haddock submodule. See my fork at
https://github.com/RyanGlScott/haddock/commit/067d52fd4be15a1842cbb05f42d9d482de0ad3a7
Test Plan: ./validate
Reviewers: simonpj, goldfire, bgamari
Reviewed By: simonpj
Subscribers: goldfire, rwbarton, thomie, mpickering, carter
GHC Trac Issues: #13324
Differential Revision: https://phabricator.haskell.org/D4383
|
|
|
|
|
|
|
|
|
|
|
| |
This patch is preparatory for the main fix for Trac #13324
Here, we simplify rnLHsInstType so that it does not try
to figure out the class name. This turns out to have a good
(rather than bad) effect on error messages, and it prepares
the way for the main event.
Plus, less code!
|
|
|
|
|
| |
Arguably the warning should just be disabled for this test to eliminate
unnecessary wiggle in the future.
|
|
|
|
|
|
|
| |
runTcSWithEvBinds does some unification, so the zonkWC
must be after, not before! Yikes. An outright bug.
This fixes Trac #14715.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
These were shown up by Trac #14643
Bug 1: if we had a single partial signature for
two functions
f, g :: forall a. _ -> a
then we made two different SigTvs but with the sane Name.
This was jolly confusing and ultimately led to deeply bogus
results with Any's appearing in the resulting program. Yikes.
Fix: clone the quantified variables in TcSigs.tcInstSig (as
indeed its name suggests).
Bug 2: we were not eliminating duplicate/superclass constraints
in the partial signatures of a mutually recursive group.
Easy to fix: we are already doing dup/superclass elim in
TcSimplify.decideQuantification. So we move the partial-sig
constraints there too.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This rather subtle patch fixes Trac #14584. The problem was
that we'd allowed a coercion, bound in a nested scope, to escape
into an outer scope.
The main changes are
* TcSimplify.floatEqualities takes more care when floating
equalities to make sure we don't float one out that mentions
a locally-bound coercion.
See Note [What prevents a constraint from floating]
* TcSimplify.emitResidualConstraints (which emits the residual
constraints in simplifyInfer) now avoids burying the constraints
for escaping CoVars inside the implication constraint.
* Since I had do to this stuff with CoVars, I moved the
fancy footwork about not quantifying over CoVars from
TcMType.quantifyTyVars to its caller
TcSimplify.decideQuantifiedTyVars. I think its other
callers don't need to worry about all this CoVar stuff.
This turned out to be surprisigly tricky, and took me a solid
day to get right. I think the result is reasonably neat, though,
and well documented with Notes.
|
|
|
|
|
|
|
| |
This fixes Trac #14479. Not difficult.
See Note [Quantification and partial signatures] Wrinkle 4,
in TcSimplify.
|
|
|
|
|
|
|
|
| |
This adds a regression test for the original program in #14040.
This does not fix #14040 entirely, though, as the program in
https://ghc.haskell.org/trac/ghc/ticket/14040#comment:2 still
panics, so there is more work to be done there.
|
|
|
|
|
|
|
|
|
|
|
| |
Trac #14449 showed that we were failing to check that the
quantified type variables of a partial type signature remained
distinct.
See Note [Quantified variables in partial type signatures]
in TcBinds.
A little refactoring along the way.
|
|
|
|
|
|
|
|
|
|
|
| |
Trac #14394 showed that it's possible to get redundant
constraints in the inferred provided constraints of a pattern
synonym. This patch removes the redundancy with mkMinimalBySCs.
To do this I had to generalise the type of mkMinimalBySCs slightly.
And, to reduce confusing reversal, I made it stable: it now returns
its result in the same order as its input. That led to a raft of
error message wibbles, mostly for the better.
|
|
|
|
|
|
|
| |
This is prompted by the addition of `compareByteArrays#` in
e3ba26f8b49700b41ff4672f3f7f6a4e453acdcc
NOTE: We may switch to synchronise `ghc-prim` with GHC's version at some point
|
|
|
|
|
|
|
|
|
|
|
| |
This patch does two things:
* When reporting a hole, we now include its kind if the
kind is not just '*'. This addresses Trac #14265
* When reporting things like "'a' is a rigid type varaible
bound by ...", this patch arranges to group the type variables
together, so we don't repeat the "bound by..." stuff endlessly
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
For reasons explained in TcHsType
Note [Extra-constraint holes in partial type signatures],
if we had
f :: (_) => blahs
and the '_' was filled in by more than a 62-tuple of contraints,
GHC crashed.
The same Note explains the hacky solution I have adopted to
evade this. Maybe there is some better way, but I couldn't
see one that didn't involve a great deal of work. And the problem
is a very narrow one! If the hack bites us we'll need to think
again.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This builds on the previous "Valid substitutions include..." functionality,
but add subsumption checking as well, so that the suggested valid substitutions
show not only exact matches, but also identifiers that fit the hole by virtue of
subsuming the type of the hole (i.e. being more general than the type of the
hole).
Building on the previous example, in the given program
```
ps :: String -> IO ()
ps = putStrLn
ps2 :: a -> IO ()
ps2 _ = putStrLn "hello, world"
main :: IO ()
main = _ "hello, world"
```
The results would be something like
```
• Found hole: _ :: [Char] -> IO ()
• In the expression: _
In the expression: _ "hello, world"
In an equation for ‘main’: main = _ "hello, world"
• Relevant bindings include main :: IO () (bound at t1.hs:8:1)
Valid substitutions include
ps :: String -> IO () (defined at t1.hs:2:1)
ps2 :: forall a. a -> IO () (defined at t1.hs:5:1)
putStrLn :: String -> IO ()
(imported from ‘Prelude’ at t1.hs:1:1
(and originally defined in ‘System.IO’))
fail :: forall (m :: * -> *). Monad m => forall a. String -> m a
(imported from ‘Prelude’ at t1.hs:1:1
(and originally defined in ‘GHC.Base’))
mempty :: forall a. Monoid a => a
(imported from ‘Prelude’ at t1.hs:1:1
(and originally defined in ‘GHC.Base’))
print :: forall a. Show a => a -> IO ()
(imported from ‘Prelude’ at t1.hs:1:1
(and originally defined in ‘System.IO’))
(Some substitutions suppressed;
use -fmax-valid-substitutions=N or -fno-max-valid-substitutions)
```
Signed-off-by: Matthías Páll Gissurarson <mpg@mpg.is>
Modified according to suggestions from Simon PJ
Accept tests that match the expectations, still a few to look better at
Swithced to using tcLookup, after sit down with SPJ at ICFP. Implications are WIP.
Now works with polymorphism and constraints!
We still need to merge the latest master, before we can make a patch.
Wrap the type of the hole, instead of implication shenanigans,
As per SPJs suggestion, this is simpler and feels closer to
what we actually want to do.
Updated tests with the new implementation
Remove debugging trace and update documentation
Reviewers: austin, bgamari
Reviewed By: bgamari
Subscribers: RyanGlScott, rwbarton, thomie
Differential Revision: https://phabricator.haskell.org/D3930
|
|
|
|
|
|
|
|
|
|
| |
Bumps numerous submodules.
Reviewers: austin, hvr
Subscribers: rwbarton, thomie
Differential Revision: https://phabricator.haskell.org/D3974
|
|
|
|
|
|
| |
This is a preparatory refactoring for Semigroup=>Monoid
as it prevents a messy .hs-boot file which would interact
inconveniently with the buildsystem...
|
|
|
|
| |
(cherry picked from commit 8c5405f63c2de0c445ec171aab63c35786544b9e)
|
|
|
|
|
|
|
|
|
|
|
|
| |
Test Plan: If it builds, ship it
Reviewers: austin, bgamari
Reviewed By: bgamari
Subscribers: rwbarton, thomie
Differential Revision: https://phabricator.haskell.org/D3772
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Triggered by the changes in #13677, I ended up doing a bit of
refactoring in type pretty-printing.
* We were using TyOpPrec and FunPrec rather inconsitently, so
I made it consisent.
* That exposed the fact that we were a bit undecided about whether
to print
a + b -> c + d vs (a+b) -> (c+d)
and similarly
a ~ [b] => blah vs (a ~ [b]) => blah
I decided to make TyOpPrec and FunPrec compare equal
(in BasicTypes), so (->) is treated as equal precedence with
other type operators, so you get the unambiguous forms above,
even though they have more parens.
We could readily reverse this decision.
See Note [Type operator precedence] in BasicTypes
* I fixed a bug in pretty-printing of HsType where some
parens were omitted by mistake.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Previously, we were unconditionally pretty-printing all type variable
binders when pretty-printing closed type families (e.g., in the output
of `:info` in GHCi). This threw me for a loop, so let's guard this behind
the `-fprint-explicit-foralls` flag.
Test Plan: make test TEST=T13420
Reviewers: goldfire, austin, bgamari
Reviewed By: bgamari
Subscribers: rwbarton, thomie
GHC Trac Issues: #13420
Differential Revision: https://phabricator.haskell.org/D3497
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The proximate cause for this patch is Trac #13482, which pointed out
further subtle interactions between
- Inferring the most general type of a function
- A partial type signature for that function
That led me into /further/ changes to the shiny new stuff in
TcSimplify.simplifyInfer, decideQuantification, decideMonoTyVars,
and related functions.
Happily, I was able to make some of it quite a bit simpler,
notably the bit about promoting free tyvars. I'm happy with
the result.
Moreover I fixed Trac #13524 at the same time. Happy days.
|