- 29 Jul, 2017 1 commit
-
-
Richard Eisenberg authored
Previously, we checked the number of patterns in a data instances for all data families whose kind did not end in a kind variable. But, of course, undersaturating instances can happen even without the kind ending in a kind variable. So I've omitted the arity check. Data families aren't as particular about their arity as type families are (because data families can be undersaturated). Still, this change degrades error messages when instances don't have the right arity; now, instead of reporting a simple mismatch in the number of patterns, GHC reports kind errors. The new errors are fully accurate, but perhaps not as easy to work with. Still, with the new flexibility of allowing data family instances with varying numbers of patterns, I don't see a better way. This commit also improves source fidelity in some error messages, requiring more changes than really are necessary. But without these changes, error messages around mismatched associated instance heads were poor. test cases: indexed-types/should_compile/T14045, indexed-types/should_fail/T14045a
-
- 28 Jul, 2017 12 commits
-
-
Andreas Klebinger authored
These ignore commandline arguments for ignore and commandline as well as GHCRTS arguments for ignoreAll. Passing RTS flags given on the command line along to the program by simply skipping processing of these flags by the RTS. This fixes #12870. Test Plan: ./validate Reviewers: austin, hvr, bgamari, erikd, simonmar Reviewed By: simonmar Subscribers: Phyx, rwbarton, thomie GHC Trac Issues: #12870 Differential Revision: https://phabricator.haskell.org/D3740
-
Edward Z. Yang authored
Fixes #13710. Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: bgamari, austin, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #13710 Differential Revision: https://phabricator.haskell.org/D3743
-
Sven Tennie authored
This was an old workaround for #5252. Fixes #13173. Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3763
-
Ben Gamari authored
ld.gold is particularly picky that we declare all of our link dependencies on Nix. See #14022. Test Plan: Validate on Nix Reviewers: austin Subscribers: hvr, rwbarton, thomie GHC Trac Issues: #14022 Differential Revision: https://phabricator.haskell.org/D3787
-
Michal Terepeta authored
This is another change needed for #13825 (also based on D38 by Simon Marlow). With the change, we count the stack depth in bytes (instead of words). We also introduce some `newtype`s to help with the change. Note that this only changes how `ByteCodeGen` works and shouldn't affect the generated bytecode. Signed-off-by:
Michal Terepeta <michal.terepeta@gmail.com> Test Plan: ./validate Reviewers: bgamari, simonmar, austin, hvr Reviewed By: bgamari, simonmar Subscribers: rwbarton, thomie GHC Trac Issues: #13825 Differential Revision: https://phabricator.haskell.org/D3746
-
Ryan Scott authored
Summary: Types and kinds are now the same in GHC... well, except in the code that involves Template Haskell, where types and kinds are given separate treatment. This aims to unify that treatment in the `DsMeta` module. The gist of this patch is replacing all uses of `repLKind` with `repLTy`. This is isn't quite as simple as one might imagine, since `repLTy` returns a `Core (Q Type)` (a monadic expression), whereas `repLKind` returns a `Core Kind` (a pure expression). This causes many awkward impedance mismatches. One option would be to change every combinator in `Language.Haskell.TH.Lib` to take `KindQ` as an argument instead of `Kind`. But this would be a breaking change of colossal proportions. Instead, this patch takes a somewhat different approach. This migrates the existing `Language.Haskell.TH.Lib` module to `Language.Haskell.TH.Lib.Internal`, and changes all `Kind`-related combinators in `Language.Haskell.TH.Lib.Internal` to live in `Q`. The new `Language.Haskell.TH.Lib` module then re-exports most of `Language.Haskell.TH.Lib.Internal` with the exception of the `Kind`-related combinators, for which it redefines them to be their current definitions (which don't live in `Q`). This allows us to retain backwards compatibility with previous `template-haskell` releases, but more importantly, it allows GHC to make as many changes to the `Internal` code as it wants for its purposes without fear of disrupting the public API. This solves half of #11785 (the other half being `TcSplice`). Test Plan: ./validate Reviewers: goldfire, austin, bgamari Reviewed By: goldfire Subscribers: rwbarton, thomie GHC Trac Issues: #11785 Differential Revision: https://phabricator.haskell.org/D3751
-
Ryan Scott authored
Summary: Previously, if `reifyInstances` failed to discover a `Name` during renaming, it would blindy charge into typechecking, at which point GHC would become very confused at the absence of that `Name` and throw an internal error. A simple workaround is to fail eagerly after renaming errors. Test Plan: make test TEST=T13837 Reviewers: goldfire, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #13837 Differential Revision: https://phabricator.haskell.org/D3793
-
Simon Peyton Jones authored
This was provoked by an ASSERT failure when debugging #14038, but it's a godo idea anyway.
-
Simon Peyton Jones authored
Trac #14000 showed up two errors * In TcRnTypes.dropInsolubles we dropped all implications, which might contain the very insolubles we wanted to keep. This was an outright error, and is why the out-of-scope error was actually lost altogether in Trac #14000 * In TcSimplify.simplifyInfer, if there are definite (insoluble) errors, it's better to suppress the following ambiguity test, because the type may be bogus anyway. See TcSimplify Note [Quantification with errors]. This fix seems a bit clunky, but it'll do for now.
-
Simon Peyton Jones authored
This ASSERT failure (in substTy) was reported in Trac #14024. This patch gets the in-scope set right. (Does not fix tests T13822 or T13594.)
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
In Check.hs (pattern match ovelap checking) we to figure out the instantiation of a pattern synonym from the type of the pattern. We were doing this utterly wrongly. Trac #13768 demonstrated this bogosity. The fix is easy; and is described in PatSyn.hs Note [Pattern synonym result type]
-
- 27 Jul, 2017 11 commits
-
-
Richard Eisenberg authored
With the changes caused by the fix to #12369, it is now clearer how to rewrite tcInferApps and friends. This should change no behavior, but it does clean up a nasty corner of the type checker. This commit also removes some uses of substTyUnchecked.
-
Richard Eisenberg authored
Previously, a data family's kind had to end in `Type`, and data instances had to list all the type patterns for the family. However, both of these restrictions were unnecessary: - A data family's kind can usefully end in a kind variable `k`. See examples on #12369. - A data instance need not list all patterns, much like how a GADT-style data declaration need not list all type parameters, when a kind signature is in place. This is useful, for example, here: data family Sing (a :: k) data instance Sing :: Bool -> Type where ... This patch also improved a few error messages, as some error plumbing had to be moved around. See new Note [Arity of data families] in FamInstEnv for more info. test case: indexed-types/should_compile/T12369
-
Richard Eisenberg authored
Previously, looking up a TyCon that said "no" to mightBeUnsaturated would then instantiate all of its invisible binders. But this is wrong for vanilla type synonyms, whose RHS kind might legitimately start with invisible binders. So a little more care is taken now, only to instantiate those invisible binders that need to be (so that the TyCon isn't unsaturated).
-
Richard Eisenberg authored
This is a straightforward fix -- there were just some omitted checks. test case: typecheck/should_fail/T11963
-
Richard Eisenberg authored
A type equality error can arise from a mismatch between *invisible* arguments just as easily as from visible arguments. But we should really prefer printing out errors from visible arguments over invisible ones. Suppose we have a mismatch between `Proxy Int` and `Proxy Maybe`. Would you rather get an error between `Int` and `Maybe`? Or between `*` and `* -> *`? I thought so, too. There is a fair amount of plumbing with this one, but I think it's worth it. This commit introduces a performance regression in test perf/compiler/T5631. The cause of the regression is not the new visibility stuff, directly: it's due to a change from zipWithM to zipWith3M in TcUnify. To my surprise, zipWithM is nicely optimized (it fuses away), but zipWith3M is not. There are other examples of functions that could be made faster, so I've posted a separate ticket, #14037, to track these improvements. For now, I've accepted the small (6.6%) regression.
-
Richard Eisenberg authored
The uo_thing field of TypeEqOrigin is used to track the "thing" (either term or type) that has the type (kind) stored in the TypeEqOrigin fields. Previously, this was sometimes a proper Core Type, which needed zonking and tidying. Now, it is only HsSyn: much simpler, and the error messages now use the user-written syntax. But this aspect of uo_thing didn't cause #13819; it was the sibling field uo_arity that did. uo_arity stored the number of arguments of uo_thing, useful when reporting something like "should have written 2 fewer arguments". We wouldn't want to say that if the thing didn't have two arguments. However, in practice, GHC was getting this wrong, and this message didn't seem all that helpful. Furthermore, the calculation of the number of arguments is what caused #13819 to fall over. This patch just removes uo_arity. In my opinion, the change to error messages is a nudge in the right direction. Test case: typecheck/should_fail/T13819
-
Richard Eisenberg authored
Now, all coercions are printed from IfaceType, just like types. This also changes the rendering of TransCo to use ; instead of a prefix operator.
-
Richard Eisenberg authored
Previously, we did this for Types, but not for Coercions.
-
Richard Eisenberg authored
This makes variables print more consistenty in, say, -ddump-tc-trace.
-
Richard Eisenberg authored
Previously, when canonicalizing (or unifying, in uType) a heterogeneous equality, we emitted a kind equality and used the resulting coercion to cast one side of the heterogeneous equality. While sound, this led to terrible error messages. (See the bugs listed below.) The problem is that using the coercion built from the emitted kind equality is a bit like a wanted rewriting a wanted. The solution is to keep heterogeneous equalities as irreducible. See Note [Equalities with incompatible kinds] in TcCanonical. This commit also removes a highly suspicious switch to FM_SubstOnly when flattening in the kinds of a type variable. I have no idea why this was there, other than as a holdover from pre-TypeInType. I've not left a Note because there is simply no reason I can conceive of that the FM_SubstOnly should be there. One challenge with this patch is that the emitted derived equalities might get emitted several times: when a heterogeneous equality is in an implication and then gets floated out from the implication, the Derived is present both in and out of the implication. This causes a duplicate error message. (Test case: typecheck/should_fail/T7368) Solution: track the provenance of Derived constraints and refuse to float out a constraint that has an insoluble Derived. Lastly, this labels one test (dependent/should_fail/RAE_T32a) as expect_broken, because the problem is really #12919. The different handling of constraints in this patch exposes the error. This fixes bugs #11198, #12373, #13530, and #13610. test cases: typecheck/should_fail/{T8262,T8603,tcail122,T12373,T13530,T13610}
-
Gabor Greif authored
-
- 26 Jul, 2017 6 commits
-
-
Ryan Scott authored
Summary: We were unconditionally reporting `Illegal binding of built-in syntax` in an error message, but this error doesn't make sense in certain Template Haskell scenarios which can trigger it. Let's give a more sensible error message by first checking if the name we're binding really is built-in syntax, using the handy `isBuiltInOcc_maybe` function. Test Plan: make test TEST=T13968 Reviewers: bgamari, austin, goldfire Reviewed By: goldfire Subscribers: goldfire, rwbarton, thomie GHC Trac Issues: #13968 Differential Revision: https://phabricator.haskell.org/D3789
-
Gabor Greif authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
Trac #13998 showed that default methods were getting bogus tyvar binder visiblity info; and that it matters in the code genreated by the default-method fill-in mechanism * The actual fix: in TcTyDecls.mkDefaultMethodType, make TyVarBinders with the right visibility info by getting TyConBinders from the class TyCon. (Previously we made up visiblity info, but that caused #13998.) * Define TyCon.tyConTyVarBinders :: [TyConBinder] -> [TyVarBinder] which can build correct forall binders for a) default methods (Trac #13998) b) data constructors This was originally BuildTyCl.mkDataConUnivTyVarBinders * Move mkTyVarBinder, mkTyVarBinders from Type to Var
-
Simon Peyton Jones authored
-
- 25 Jul, 2017 5 commits
-
-
Ryan Scott authored
Summary: Previously, one could experience error cascades with deriving clauses when one class in a set of many failed to derive, causing the other derived classes to be skipped entirely and resulting in other errors down the line. The solution is to process each class in a data type's set of deriving clauses individually, and engineer it so that failure to derive an individual class within that set doesn't cancel out the others. Test Plan: make test TEST="T10684 T12801" Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #10684, #12801 Differential Revision: https://phabricator.haskell.org/D3771
-
Matthew Pickering authored
This reverts commit 7d1909ad. It is actually used for Callstacks, woops!
-
Matthew Pickering authored
-
Matthew Pickering authored
It is mentioned in the API but not exported.
-
Eugene Akentyev authored
Reviewers: austin, bgamari, mpickering Reviewed By: bgamari Subscribers: mpickering, rwbarton, thomie GHC Trac Issues: #13168 Differential Revision: https://phabricator.haskell.org/D3738
-
- 24 Jul, 2017 2 commits
-
-
Ben Gamari authored
Since #847 we have used libthr due to reported hangs with FreeBSD's KSE-based M:N pthread implementation. However, this was nearly 12 years ago and today libpthread seems to work fine. Moreover, adding -lthr to the linker flags break when used in conjunction with -r when gold is used (since -l and -r are incompatible although BFD ld doesn't complain). Test Plan: Validate on FreeBSD Reviewers: kgardas, austin Subscribers: rwbarton, thomie GHC Trac Issues: #847 Differential Revision: https://phabricator.haskell.org/D3773
-
Ben Gamari authored
This wasn't used anywhere; the RTS build tag is now constructed in Packages.packageHsLibs. Test Plan: Validate Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3768
-
- 22 Jul, 2017 2 commits
-
-
Bartosz Nitka authored
I've encountered an issue with following reproduction steps: * `:load` a large number of modules (~2000) * compile a BCO that depends on many other BCOs from many other modules * `:reload` * try to compile anything, even `1` works Before this patch the last step takes ~5s. It takes 80ms after. Test Plan: harbormaster Reviewers: simonmar, austin, hvr, bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3770
-
Ryan Scott authored
Test Plan: If it builds, ship it Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3772
-
- 20 Jul, 2017 1 commit
-
-
Ben Gamari authored
This is a conservative assumption which will limit some uses of spliced patterns, but it fixes #13984. Test Plan: Validate Reviewers: RyanGlScott, AaronFriel, austin Reviewed By: RyanGlScott Subscribers: rwbarton, thomie GHC Trac Issues: #13984 Differential Revision: https://phabricator.haskell.org/D3766
-