| Commit message (Collapse) | Author | Age | Files | Lines |
|
|
|
|
|
|
|
|
| |
When instances overlap, we now include additional information
about why we weren't able to select an instance: perhaps
one instance overlapped another but was not strictly more specific,
so we aren't able to directly choose it.
Fixes #20542
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
As #19918 pointed out, the CallStack mechanism didn't work well with
RebindableSyntax.
This patch improves matters. See GHC.Tc.Types.Evidence
Note [Overview of implicit CallStacks]
* New predicate isPushCallStackOrigin distinguishes when a CallStack
constraint should be solved "directly" or by pushing an item on the
stack.
* The constructor EvCsPushCall now has a FastString, which can
describe not only a function call site, but also things like
"the literal 42" or "an if-then-else expression".
* I also fixed #20126 thus:
exprCtOrigin (HsIf {}) = IfThenElseOrigin
(Previously it was "can't happen".)
|
|
|
|
|
| |
Also document deprecation of Wnoncanonical-monadfail-instances
and -Wimplicit-kind-vars
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
When implementing Quick Look I'd failed to remember that overloaded
labels, like #foo, should be treated as a "head", so that they can be
instantiated with Visible Type Application. This caused #19154.
A very similar ticket covers overloaded literals: #19167.
This patch fixes both problems, but (annoyingly, albeit temporarily)
in two different ways.
Overloaded labels
I dealt with overloaded labels by buying fully into the
Rebindable Syntax approach described in GHC.Hs.Expr
Note [Rebindable syntax and HsExpansion].
There is a good overview in GHC.Rename.Expr
Note [Handling overloaded and rebindable constructs].
That module contains much of the payload for this patch.
Specifically:
* Overloaded labels are expanded in the renamer, fixing #19154.
See Note [Overloaded labels] in GHC.Rename.Expr.
* Left and right sections used to have special code paths in the
typechecker and desugarer. Now we just expand them in the
renamer. This is harder than it sounds. See GHC.Rename.Expr
Note [Left and right sections].
* Infix operator applications are expanded in the typechecker,
specifically in GHC.Tc.Gen.App.splitHsApps. See
Note [Desugar OpApp in the typechecker] in that module
* ExplicitLists are expanded in the renamer, when (and only when)
OverloadedLists is on.
* HsIf is expanded in the renamer when (and only when) RebindableSyntax
is on. Reason: the coverage checker treats HsIf specially. Maybe
we could instead expand it unconditionally, and fix up the coverage
checker, but I did not attempt that.
Overloaded literals
Overloaded literals, like numbers (3, 4.2) and strings with
OverloadedStrings, were not working correctly with explicit type
applications (see #19167). Ideally I'd also expand them in the
renamer, like the stuff above, but I drew back on that because they
can occur in HsPat as well, and I did not want to to do the HsExpanded
thing for patterns.
But they *can* now be the "head" of an application in the typechecker,
and hence something like ("foo" @T) works now. See
GHC.Tc.Gen.Head.tcInferOverLit. It's also done a bit more elegantly,
rather than by constructing a new HsExpr and re-invoking the
typechecker. There is some refactoring around tcShortCutLit.
Ultimately there is more to do here, following the Rebindable Syntax
story.
There are a lot of knock-on effects:
* HsOverLabel and ExplicitList no longer need funny (Maybe SyntaxExpr)
fields to support rebindable syntax -- good!
* HsOverLabel, OpApp, SectionL, SectionR all become impossible in the
output of the typecheker, GhcTc; so we set their extension fields to
Void. See GHC.Hs.Expr Note [Constructor cannot occur]
* Template Haskell quotes for HsExpanded is a bit tricky. See
Note [Quotation and rebindable syntax] in GHC.HsToCore.Quote.
* In GHC.HsToCore.Match.viewLExprEq, which groups equal HsExprs for the
purpose of pattern-match overlap checking, I found that dictionary
evidence for the same type could have two different names. Easily
fixed by comparing types not names.
* I did quite a bit of annoying fiddling around in GHC.Tc.Gen.Head and
GHC.Tc.Gen.App to get error message locations and contexts right,
esp in splitHsApps, and the HsExprArg type. Tiresome and not very
illuminating. But at least the tricky, higher order, Rebuilder
function is gone.
* Some refactoring in GHC.Tc.Utils.Monad around contexts and locations
for rebindable syntax.
* Incidentally fixes #19346, because we now print renamed, rather than
typechecked, syntax in error mesages about applications.
The commit removes the vestigial module GHC.Builtin.RebindableNames,
and thus triggers a 2.4% metric decrease for test MultiLayerModules
(#19293).
Metric Decrease:
MultiLayerModules
T12545
|
|
|
|
|
|
|
|
|
| |
-------------------------
Metric Decrease:
T12425
Metric Increase:
T17516
-------------------------
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Executing on the plan described in #17582, this patch changes the way if expressions
are handled in the compiler in the presence of rebindable syntax. We get rid of the
SyntaxExpr field of HsIf and instead, when rebindable syntax is on, we rewrite the HsIf
node to the appropriate sequence of applications of the local `ifThenElse` function.
In order to be able to report good error messages, with expressions as they were
written by the user (and not as desugared by the renamer), we make use of TTG
extensions to extend GhcRn expression ASTs with an `HsExpansion` construct, which
keeps track of a source (GhcPs) expression and the desugared (GhcRn) expression that
it gives rise to. This way, we can typecheck the latter while reporting the former in
error messages.
In order to discard the error context lines that arise from typechecking the desugared
expressions (because they talk about expressions that the user has not written), we
carefully give a special treatment to the nodes fabricated by this new renaming-time
transformation when typechecking them. See Note [Rebindable syntax and HsExpansion]
for more details. The note also includes a recipe to apply the same treatment to
other rebindable constructs.
Tests 'rebindable11' and 'rebindable12' have been added to make sure we report
identical error messages as before this patch under various circumstances.
We also now disable rebindable syntax when processing untyped TH quotes, as per
the discussion in #18102 and document the interaction of rebindable syntax and
Template Haskell, both in Note [Template Haskell quotes and Rebindable Syntax]
and in the user guide, adding a test to make sure that we do not regress in
that regard.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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)
|
| |
|
|
|
|
|
|
| |
As per https://prime.haskell.org/wiki/Libraries/Proposals/MonadFail
Coauthored-by: Ben Gamari <ben@well-typed.com>
|
|
|
|
|
| |
This moves all URL references to Trac tickets to their corresponding
GitLab counterparts.
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
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
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
This contains two commits:
----
Make GHC's code-base compatible w/ `MonadFail`
There were a couple of use-sites which implicitly used pattern-matches
in `do`-notation even though the underlying `Monad` didn't explicitly
support `fail`
This refactoring turns those use-sites into explicit case
discrimations and adds an `MonadFail` instance for `UniqSM`
(`UniqSM` was the worst offender so this has been postponed for a
follow-up refactoring)
---
Turn on MonadFail desugaring by default
This finally implements the phase scheduled for GHC 8.6 according to
https://prime.haskell.org/wiki/Libraries/Proposals/MonadFail#Transitionalstrategy
This also preserves some tests that assumed MonadFail desugaring to be
active; all ghc boot libs were already made compatible with this
`MonadFail` long ago, so no changes were needed there.
Test Plan: Locally performed ./validate --fast
Reviewers: bgamari, simonmar, jrtc27, RyanGlScott
Reviewed By: bgamari
Subscribers: bgamari, RyanGlScott, rwbarton, thomie, carter
Differential Revision: https://phabricator.haskell.org/D5028
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We have wanted quantified constraints for ages and, as I hoped,
they proved remarkably simple to implement. All the machinery was
already in place.
The main ticket is Trac #2893, but also relevant are
#5927
#8516
#9123 (especially! higher kinded roles)
#14070
#14317
The wiki page is
https://ghc.haskell.org/trac/ghc/wiki/QuantifiedConstraints
which in turn contains a link to the GHC Proposal where the change
is specified.
Here is the relevant Note:
Note [Quantified constraints]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The -XQuantifiedConstraints extension allows type-class contexts like
this:
data Rose f x = Rose x (f (Rose f x))
instance (Eq a, forall b. Eq b => Eq (f b))
=> Eq (Rose f a) where
(Rose x1 rs1) == (Rose x2 rs2) = x1==x2 && rs1 >= rs2
Note the (forall b. Eq b => Eq (f b)) in the instance contexts.
This quantified constraint is needed to solve the
[W] (Eq (f (Rose f x)))
constraint which arises form the (==) definition.
Here are the moving parts
* Language extension {-# LANGUAGE QuantifiedConstraints #-}
and add it to ghc-boot-th:GHC.LanguageExtensions.Type.Extension
* A new form of evidence, EvDFun, that is used to discharge
such wanted constraints
* checkValidType gets some changes to accept forall-constraints
only in the right places.
* Type.PredTree gets a new constructor ForAllPred, and
and classifyPredType analyses a PredType to decompose
the new forall-constraints
* Define a type TcRnTypes.QCInst, which holds a given
quantified constraint in the inert set
* TcSMonad.InertCans gets an extra field, inert_insts :: [QCInst],
which holds all the Given forall-constraints. In effect,
such Given constraints are like local instance decls.
* When trying to solve a class constraint, via
TcInteract.matchInstEnv, use the InstEnv from inert_insts
so that we include the local Given forall-constraints
in the lookup. (See TcSMonad.getInstEnvs.)
* topReactionsStage calls doTopReactOther for CIrredCan and
CTyEqCan, so they can try to react with any given
quantified constraints (TcInteract.matchLocalInst)
* TcCanonical.canForAll deals with solving a
forall-constraint. See
Note [Solving a Wanted forall-constraint]
Note [Solving a Wanted forall-constraint]
* We augment the kick-out code to kick out an inert
forall constraint if it can be rewritten by a new
type equality; see TcSMonad.kick_out_rewritable
Some other related refactoring
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
* Move SCC on evidence bindings to post-desugaring, which fixed
#14735, and is generally nicer anyway because we can use
existing CoreSyn free-var functions. (Quantified constraints
made the free-vars of an ev-term a bit more complicated.)
* In LookupInstResult, replace GenInst with OneInst and NotSure,
using the latter for multiple matches and/or one or more
unifiers
|
|
|
|
|
|
|
|
| |
Subscribers: rwbarton, thomie, carter
GHC Trac Issues: #14670
Differential Revision: https://phabricator.haskell.org/D4314
|
|
|
|
|
|
|
|
|
|
|
| |
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.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Now that `mtl` and `parsec` are boot libraries, there's no need to
qualify various tests in the testsuite with `reqlib('mtl')` or
`reqlib('parsec')`.
Test Plan: make test TEST="T4809 tcfail126 T4355 tc232 tc223 tc220
tc217 tc183 T5303 DoParamM qq005 qq006 galois_raytrace T1074 mod133
T3787 T4316 prog011 drvfail006 drvfail008"
Reviewers: bgamari, austin
Subscribers: rwbarton, thomie
Differential Revision: https://phabricator.haskell.org/D3855
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
1. DoParamM requires the FlexibleContexts pragma now.
2. topHandler02 and topHandler03 were broken as timeout.py failed to
translate signals to exit codes.
3. topHandler03 does not produce a consistent stderr, as it depends on
what the user has /bin/sh set to. dash writes "Terminated" whereas
bash and zsh produce nothing in non-interactive mode.
4. The remaining tests are broken due to changes in the error message
formatting.
Test Plan: validate
Reviewers: thomie, dfeuer, austin, hvr, bgamari
Reviewed By: bgamari
Subscribers: Phyx, dfeuer
Differential Revision: https://phabricator.haskell.org/D2807
|
|
|
|
| |
Fixes #11216.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
Add prettyprinter tests, which take a file, parse it, pretty print it,
re-parse the pretty printed version and then compare the original and
new ASTs (ignoring locations)
Updates haddock submodule to match the AST changes.
There are three issues outstanding
1. Extra parens around a context are not reproduced. This will require an
AST change and will be done in a separate patch.
2. Currently if an `HsTickPragma` is found, this is not pretty-printed,
to prevent noise in the output.
I am not sure what the desired behaviour in this case is, so have left
it as before. Test Ppr047 is marked as expected fail for this.
3. Apart from in a context, the ParsedSource AST keeps all the parens from
the original source. Something is happening in the renamer to remove the
parens around visible type application, causing T12530 to fail, as the
dumped splice decl is after the renamer.
This needs to be fixed by keeping the parens, but I do not know where they
are being removed. I have amended the test to pass, by removing the parens
in the expected output.
Test Plan: ./validate
Reviewers: goldfire, mpickering, simonpj, bgamari, austin
Reviewed By: simonpj, bgamari
Subscribers: simonpj, goldfire, thomie, mpickering
Differential Revision: https://phabricator.haskell.org/D2752
GHC Trac Issues: #3384
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch does a raft of useful tidy-ups in the type checker.
I've been meaning to do this for some time, and finally made
time to do it en route to ICFP.
1. Modify TcType.ExpType to make a distinct data type,
InferResult for the Infer case, and consequential
refactoring.
2. Define a new function TcUnify.fillInferResult, to fill in
an InferResult. It uses TcMType.promoteTcType to promote
the type to the level of the InferResult.
See TcMType Note [Promoting a type]
This refactoring is in preparation for an improvement
to typechecking pattern bindings, coming next.
I flirted with an elaborate scheme to give better
higher rank inference, but it was just too complicated.
See TcMType Note [Promotion and higher rank types]
3. Add to InferResult a new field ir_inst :: Bool to say
whether or not the type used to fill in the
InferResult should be deeply instantiated. See
TcUnify Note [Deep instantiation of InferResult].
4. Add a TcLevel to SkolemTvs. This will be useful generally
- it's a fast way to see if the type
variable escapes when floating (not used yet)
- it provides a good consistency check when updating a
unification variable (TcMType.writeMetaTyVarRef, the
level_check_ok check)
I originally had another reason (related to the flirting
in (2), but I left it in because it seems like a step in
the right direction.
5. Reduce and simplify the plethora of uExpType,
tcSubType and related functions in TcUnify. It was
such an opaque mess and it's still not great, but it's
better.
6. Simplify the uo_expected field of TypeEqOrigin. Richard
had generatlised it to a ExpType, but it was almost always
a Check type. Now it's back to being a plain TcType which
is much, much easier.
7. Improve error messages by refraining from skolemisation when
it's clear that there's an error: see
TcUnify Note [Don't skolemise unnecessarily]
8. Type.isPiTy and isForAllTy seem to be missing a coreView check,
so I added it
9. Kill off tcs_used_tcvs. Its purpose is to track the
givens used by wanted constraints. For dictionaries etc
we do that via the free vars of the /bindings/ in the
implication constraint ic_binds. But for coercions we
just do update-in-place in the type, rather than
generating a binding. So we need something analogous to
bindings, to track what coercions we have added.
That was the purpose of tcs_used_tcvs. But it only
worked for a /single/ iteration, whereas we may have
multiple iterations of solving an implication. Look
at (the old) 'setImplicationStatus'. If the constraint
is unsolved, it just drops the used_tvs on the floor.
If it becomes solved next time round, we'll pick up
coercions used in that round, but ignore ones used in
the first round.
There was an outright bug. Result = (potentialy) bogus
unused-constraint errors. Constructing a case where this
actually happens seems quite trick so I did not do so.
Solution: expand EvBindsVar to include the (free vars of
the) coercions, so that the coercions are tracked in
essentially the same way as the bindings.
This turned out to be much simpler. Less code, more
correct.
10. Make the ic_binds field in an implication have type
ic_binds :: EvBindsVar
instead of (as previously)
ic_binds :: Maybe EvBindsVar
This is notably simpler, and faster to use -- less
testing of the Maybe. But in the occaional situation
where we don't have anywhere to put the bindings, the
belt-and-braces error check is lost. So I put it back
as an ASSERT in 'setImplicationStatus' (see the use of
'termEvidenceAllowed')
All these changes led to quite bit of error message wibbling
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Before this patch, following the TypeInType innovations,
each TyCon had two lists:
- tyConBinders :: [TyBinder]
- tyConTyVars :: [TyVar]
They were in 1-1 correspondence and contained
overlapping information. More broadly, there were many
places where we had to pass around this pair of lists,
instead of a single list.
This commit tidies all that up, by having just one list of
binders in a TyCon:
- tyConBinders :: [TyConBinder]
The new data types look like this:
Var.hs:
data TyVarBndr tyvar vis = TvBndr tyvar vis
data VisibilityFlag = Visible | Specified | Invisible
type TyVarBinder = TyVarBndr TyVar VisibilityFlag
TyCon.hs:
type TyConBinder = TyVarBndr TyVar TyConBndrVis
data TyConBndrVis
= NamedTCB VisibilityFlag
| AnonTCB
TyCoRep.hs:
data TyBinder
= Named TyVarBinder
| Anon Type
Note that Var.TyVarBdr has moved from TyCoRep and has been
made polymorphic in the tyvar and visiblity fields:
type TyVarBinder = TyVarBndr TyVar VisibilityFlag
-- Used in ForAllTy
type TyConBinder = TyVarBndr TyVar TyConBndrVis
-- Used in TyCon
type IfaceForAllBndr = TyVarBndr IfaceTvBndr VisibilityFlag
type IfaceTyConBinder = TyVarBndr IfaceTvBndr TyConBndrVis
-- Ditto, in interface files
There are a zillion knock-on changes, but everything
arises from these types. It was a bit fiddly to get the
module loops to work out right!
Some smaller points
~~~~~~~~~~~~~~~~~~~
* Nice new functions
TysPrim.mkTemplateKiTyVars
TysPrim.mkTemplateTyConBinders
which help you make the tyvar binders for dependently-typed
TyCons. See comments with their definition.
* The change showed up a bug in TcGenGenerics.tc_mkRepTy, where the code
was making an assumption about the order of the kind variables in the
kind of GHC.Generics.(:.:). I fixed this; see TcGenGenerics.mkComp.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Deriving clauses (Ord especially) generated if-expressions with nlHsIf
which were subject to RebindableSyntax. This changes nlHsIf to generate
concrete if-expressions.
There was also an error about calling tagToEnum# at a polymorphic type,
which is not allowed. Fixing nlHsIf didn't fix this for some reason, so
I generated a type ascription around the call to tagToEnum#. Not sure
why the typechecker could not figure this out.
Test Plan: Added a test, ran validate.
Reviewers: simonpj, simonmar, austin, bgamari
Reviewed By: bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D2247
GHC Trac Issues: #12080
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
foldUFM introduces unnecessary non-determinism that actually
leads to different generated code as explained in
Note [TrieMap determinism].
As we're switching from UniqFM to UniqDFM here you might be
concerned about performance. There's nothing that ./validate
detects. nofib reports no change in Compile Allocations, but
Compile Time got better on some tests and worse on some,
yielding this summary:
-1 s.d. ----- -3.8%
+1 s.d. ----- +5.4%
Average ----- +0.7%
This is not a fair comparison as the order of Uniques
changes what GHC is actually doing. One benefit from making
this deterministic is also that it will make the
performance results more stable.
Full nofib results: P108
Test Plan: ./validate, nofib
Reviewers: goldfire, simonpj, simonmar, austin, bgamari
Reviewed By: simonpj
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D2169
GHC Trac Issues: #4012
|
|
|
|
|
|
|
|
|
| |
These aren't run very often, because they require external libraries.
https://ghc.haskell.org/trac/ghc/wiki/Building/RunningTests/Running#AdditionalPackages
maessen-hashtab still doesn't compile, QuickCheck api changed.
Update submodule hpc.
|
| |
|
| |
|
| |
|
|
|
|
|
|
|
|
| |
Since we're not consisently keeping track of which tests should pass
with which compiler versions, there is no point in keeping these
functions.
Update submodules containers, hpc and stm.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The idea here is described in [wiki:Typechecker]. Briefly,
this refactor keeps solid track of "synthesis" mode vs
"checking" in GHC's bidirectional type-checking algorithm.
When in synthesis mode, the expected type is just an IORef
to write to.
In addition, this patch does a significant reworking of
RebindableSyntax, allowing much more freedom in the types
of the rebindable operators. For example, we can now have
`negate :: Int -> Bool` and
`(>>=) :: m a -> (forall x. a x -> m b) -> m b`. The magic
is in tcSyntaxOp.
This addresses tickets #11397, #11452, and #11458.
Tests:
typecheck/should_compile/{RebindHR,RebindNegate,T11397,T11458}
th/T11452
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This warning flag was recently introduced as part of #10751. However,
it was missed during code-review that almost all existing warning
flags use a plural-form, so for consistency this commit renames
that warning flag to `-Wmissing-monadfail-instances`.
Test Plan: local validate (still running)
Reviewers: quchen, goldfire, austin, bgamari
Reviewed By: bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1842
GHC Trac Issues: #10751
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Commit 547c597112954353cef7157cb0a389bc4f6303eb modifies the
pretty-printer to render names from a set of core packages (`base`,
`ghc-prim`, `template-haskell`) as unqualified. The idea here was that
many of these names typically are not in scope but are well-known by the
user and therefore qualification merely introduces noise.
This, however, is a very large hammer and potentially breaks any
consumer who relies on parsing GHC output (hence #11208). This commit
partially reverts this change, now only printing `Constraint` (which
appears quite often in errors) as unqualified.
Fixes #11208.
Updates tests in `array` submodule.
Test Plan: validate
Reviewers: hvr, thomie, austin
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1619
GHC Trac Issues: #11208
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Example error message:
MonadFailErrors.hs:16:5: error:
Could not deduce (MonadFail m)
arising from a do statement
with the failable pattern ‘Just x’
Depends on D1248
Reviewers: austin, bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1489
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This implements phase 1 of the MonadFail proposal (MFP, #10751).
- MonadFail warnings are all issued as desired, tunable with two new flags
- GHC was *not* made warning-free with `-fwarn-missing-monadfail-warnings`
(but it's disabled by default right now)
Credits/thanks to
- Franz Thoma, whose help was crucial to implementing this
- My employer TNG Technology Consulting GmbH for partially funding us
for this work
Reviewers: goldfire, austin, #core_libraries_committee, hvr, bgamari, fmthoma
Reviewed By: hvr, bgamari, fmthoma
Subscribers: thomie
Projects: #ghc
Differential Revision: https://phabricator.haskell.org/D1248
GHC Trac Issues: #10751
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Improved error messages are only printed when the old message would be
"No instance for...", since they're not as helpful for "Could not deduce..."
No special test case as error messages are tested by other tests already.
Signed-off-by: David Kraeutmann <kane@kane.cx>
Reviewed By: austin, goldfire
Differential Revision: https://phabricator.haskell.org/D1182
GHC Trac Issues: #10733
|
|
|
|
|
|
|
|
|
|
| |
Summary: See Note [Displaying potential instances].
Reviewers: austin
Subscribers: KaneTW, thomie
Differential Revision: https://phabricator.haskell.org/D1176
|
|
|
|
|
| |
No point in pretending other compilers can use the GHC testsuite. This
makes the *.T files a bit shorter.
|
|
|
|
|
|
|
|
| |
GHC can't yest build a TypeRep for a type involving kind variables.
(We await kinds = types for that.) But the error message was terrible,
as fixing #10524 reminded me.
This improves it a lot.
|
| |
|
| |
|
|
|
|
| |
And rename the wrongly named rebindable/T5821 to T5908 (Trac #5908)
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The idea was promted by Trac #9939, but it was Christmas, so I did
some recreational programming that went much further.
The idea is to warn when a constraint in a user-supplied context is
redundant. Everything is described in detail in
Note [Tracking redundant constraints]
in TcSimplify.
Main changes:
* The new ic_status field in an implication, of type ImplicStatus.
It replaces ic_insol, and includes information about redundant
constraints.
* New function TcSimplify.setImplicationStatus sets the ic_status.
* TcSigInfo has sig_report_redundant field to say whenther a
redundant constraint should be reported; and similarly
the FunSigCtxt constructor of UserTypeCtxt
* EvBinds has a field eb_is_given, to record whether it is a given
or wanted binding. Some consequential chagnes to creating an evidence
binding (so that we record whether it is given or wanted).
* AbsBinds field abs_ev_binds is now a *list* of TcEvBiinds;
see Note [Typechecking plan for instance declarations] in
TcInstDcls
* Some significant changes to the type checking of instance
declarations; Note [Typechecking plan for instance declarations]
in TcInstDcls.
* I found that TcErrors.relevantBindings was failing to zonk the
origin of the constraint it was looking at, and hence failing to
find some relevant bindings. Easy to fix, and orthogonal to
everything else, but hard to disentangle.
Some minor refactorig:
* TcMType.newSimpleWanteds moves to Inst, renamed as newWanteds
* TcClassDcl and TcInstDcls now have their own code for typechecking
a method body, rather than sharing a single function. The shared
function (ws TcClassDcl.tcInstanceMethodBody) didn't have much code
and the differences were growing confusing.
* Add new function TcRnMonad.pushLevelAndCaptureConstraints, and
use it
* Add new function Bag.catBagMaybes, and use it in TcSimplify
|
|
|
|
|
|
|
|
|
|
|
|
| |
In particular
In the type signature for:
f :: Int -> Int
I added the colon
Also reword the "maybe you haven't applied a function to enough arguments?"
suggestion to make grammatical sense.
These tiny changes affect a lot of error messages.
|
|
|
|
|
|
|
|
|
|
| |
Test Plan: Compiled ghc fine. Opened ghci and fed it invalid code. It gave the improved error messages in response.
Reviewers: austin
Subscribers: thomie, simonpj, spacekitteh, rwbarton, simonmar, carter
Differential Revision: https://phabricator.haskell.org/D201
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
This includes pretty much all the changes needed to make `Applicative`
a superclass of `Monad` finally. There's mostly reshuffling in the
interests of avoid orphans and boot files, but luckily we can resolve
all of them, pretty much. The only catch was that
Alternative/MonadPlus also had to go into Prelude to avoid this.
As a result, we must update the hsc2hs and haddock submodules.
Signed-off-by: Austin Seipp <austin@well-typed.com>
Test Plan: Build things, they might not explode horribly.
Reviewers: hvr, simonmar
Subscribers: simonmar
Differential Revision: https://phabricator.haskell.org/D13
|
|
|
|
|
|
|
| |
This checks that all the required extensions are enabled for the
inferred type signature.
Updates binary and vector submodules.
|