summaryrefslogtreecommitdiff
path: root/compiler/types
Commit message (Collapse)AuthorAgeFilesLines
* Get rid of tcm_smart from TyCoMapperSimon Peyton Jones2019-02-171-40/+24
| | | | | | | | | | | | | | | Following a succession of refactorings of the type checker, culminating in the patch Make a smart mkAppTyM we have got rid of mkNakedAppTy etc. And that in turn meant that the tcm_smart field of the generic TyCoMapper (in Type.hs) was entirely unused. It was always set to True. So this patch just gets rid of it completely. Less code, less complexity, and more efficient because fewer higher-order function calls. Everyone wins. No change in behaviour; this does not cure any bugs!
* Make a smart mkAppTyMSimon Peyton Jones2019-02-146-49/+84
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch finally delivers on Trac #15952. Specifically * Completely remove Note [The tcType invariant], along with its complicated consequences (IT1-IT6). * Replace Note [The well-kinded type invariant] with: Note [The Purely Kinded Type Invariant (PKTI)] * Instead, establish the (PKTI) in TcHsType.tcInferApps, by using a new function mkAppTyM when building a type application. See Note [mkAppTyM]. * As a result we can remove the delicate mkNakedXX functions entirely. Specifically, mkNakedCastTy retained lots of extremly delicate Refl coercions which just cluttered everything up, and(worse) were very vulnerable to being silently eliminated by (say) substTy. This led to a succession of bug reports. The result is noticeably simpler to explain, simpler to code, and Richard and I are much more confident that it is correct. It does not actually fix any bugs, but it brings us closer. E.g. I hoped it'd fix #15918 and #15799, but it doesn't quite do so. However, it makes it much easier to fix. I also did a raft of other minor refactorings: * Use tcTypeKind consistently in the type checker * Rename tcInstTyBinders to tcInvisibleTyBinders, and refactor it a bit * Refactor tcEqType, pickyEqType, tcEqTypeVis Simpler, probably more efficient. * Make zonkTcType zonk TcTyCons, at least if they have any free unification variables -- see zonk_tc_tycon in TcMType.zonkTcTypeMapper. Not zonking these TcTyCons was actually a bug before. * Simplify try_to_reduce_no_cache in TcFlatten (a lot) * Combine checkExpectedKind and checkExpectedKindX. And then combine the invisible-binder instantation code Much simpler now. * Fix a little bug in TcMType.skolemiseQuantifiedTyVar. I'm not sure how I came across this originally. * Fix a little bug in TyCoRep.isUnliftedRuntimeRep (the ASSERT was over-zealous). Again I'm not certain how I encountered this. * Add a missing solveLocalEqualities in TcHsType.tcHsPartialSigType. I came across this when trying to get level numbers right.
* Fix #16188Richard Eisenberg2019-02-121-0/+3
| | | | | | | | | | | | | | There was an awful lot of zipping going on in canDecomposableTyConAppOK, and one of the lists being zipped was too short, causing the result to be too short. Easily fixed. Also fixes #16204 and #16225 test case: typecheck/should_compile/T16188 typecheck/should_compile/T16204[ab] typecheck/should_fail/T16204c typecheck/should_compile/T16225
* Fix #16293 by cleaning up Proxy# infelicitiesRyan Scott2019-02-121-9/+15
| | | | | | | | | | | | | | | | | | | | This bug fixes three problems related to `Proxy#`/`proxy#`: 1. Reifying it with TH claims that the `Proxy#` type constructor has two arguments, but that ought to be one for consistency with TH's treatment for other primitive type constructors like `(->)`. This was fixed by just returning the number of `tyConVisibleTyVars` instead of using `tyConArity` (which includes invisible arguments). 2. The role of `Proxy#`'s visible argument was hard-coded as nominal. Easily fixed by changing it to phantom. 3. The visibility of `proxy#`'s kind argument was specified, which is different from the `Proxy` constructor (which treats it as inferred). Some minor refactoring in `proxyHashId` fixed ths up. Along the way, I had to introduce a `mkSpecForAllTy` function, so I did some related Haddock cleanup in `Type`, where that function lives.
* Fix #14729 by making the normaliser homogeneousRichard Eisenberg2019-02-083-35/+502
| | | | | | | | | | | | | | | | This ports the fix to #12919 to the normaliser. (#12919 was about the flattener.) Because the fix is involved, this is done by moving the critical piece of code to Coercion, and then calling this from both the flattener and the normaliser. The key bit is: simplifying type families in a type is always a *homogeneous* operation. See #12919 for a discussion of why this is the Right Way to simplify type families. Also fixes #15549. test case: dependent/should_compile/T14729{,kind} typecheck/should_compile/T15549[ab]
* Fix #14579 by defining tyConAppNeedsKindSig, and using itRyan Scott2019-02-051-16/+289
|
* Some refactoring in tcInferAppsRichard Eisenberg2019-01-271-0/+3
| | | | | Should be no change in behavior, but this makes the control flow a little more apparent.
* Prepare source-tree for base-4.13 MFP bumpHerbert Valerio Riedel2019-01-181-0/+2
|
* More minor comment improvementsRichard Eisenberg2019-01-112-12/+8
| | | | [skip ci]
* Remove OPTIONS_HADDOCK hide in favour for not-homeAdam Sandberg Eriksson2019-01-061-1/+1
| | | | GHC Trac Issues: #15447
* Fix some typos, etc., in comments.Richard Eisenberg2019-01-032-6/+9
| | | | [ci skip]
* Visible kind applicationmynguyen2019-01-031-0/+7
| | | | | | | | | | | | | | | | | | | | | | | Summary: This patch implements visible kind application (GHC Proposal 15/#12045), as well as #15360 and #15362. It also refactors unnamed wildcard handling, and requires that type equations in type families in Template Haskell be written with full type on lhs. PartialTypeSignatures are on and warnings are off automatically with visible kind application, just like in term-level. There are a few remaining issues with this patch, as documented in ticket #16082. Includes a submodule update for Haddock. Test Plan: Tests T12045a/b/c/TH1/TH2, T15362, T15592a Reviewers: simonpj, goldfire, bgamari, alanz, RyanGlScott, Iceland_jack Subscribers: ningning, Iceland_jack, RyanGlScott, int-index, rwbarton, mpickering, carter GHC Trac Issues: `#12045`, `#15362`, `#15592`, `#15788`, `#15793`, `#15795`, `#15797`, `#15799`, `#15801`, `#15807`, `#15816` Differential Revision: https://phabricator.haskell.org/D5229
* Wibble to Taming the Kind Inference MonsterSimon Peyton Jones2018-12-072-8/+8
| | | | | | | | | | | | | | | | | | | 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.
* Introduce tcTypeKind, and use itSimon Peyton Jones2018-12-033-190/+181
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | In the type checker Constraint and * are distinct; and the function that takes the kind of a type should respect that distinction (Trac #15971). This patch implements the change: * Introduce Type.tcTypeKind, and use it throughout the type inference engine * Add new Note [Kinding rules for types] for the kinding rules, especially for foralls. * Redefine isPredTy ty = tcIsConstraintKind (tcTypeKind ty) (it had a much more complicated definition before) Some miscellaneous refactoring * Get rid of TyCoRep.isTYPE, Kind.isTYPEApp, in favour of TyCoRep.kindRep, kindRep_maybe * Rename Type.getRuntimeRepFromKind_maybe to getRuntimeRep_maybe I did some spot-checks on compiler perf, and it really doesn't budge (as expected).
* Fix #15954 by rejigging check_type's orderRyan Scott2018-12-031-1/+9
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Previously, `check_type` (which catches illegal uses of unsaturated type synonyms without enabling `LiberalTypeSynonyms`, among other things) always checks for uses of polytypes before anything else. There is a problem with this plan, however: checking for polytypes requires decomposing `forall`s and other invisible arguments, an action which itself expands type synonyms! Therefore, if we have something like: ```lang=haskell type A a = Int type B (a :: Type -> Type) = forall x. x -> x type C = B A ``` Then when checking `B A`, `A` will get expanded to `forall x. x -> x` before `check_type` has an opportunity to realize that `A` is an unsaturated type synonym! This is the root cause of #15954. This patch fixes the issue by moving the case of `check_type` that detects polytypes to be //after// the case that checks for `TyConApp`s. That way, the `TyConApp` case will properly flag things like the unsaturated use of `A` in the example above before we ever attempt to check for polytypes. Test Plan: make test TEST=T15954 Reviewers: simonpj, bgamari, goldfire Reviewed By: simonpj Subscribers: rwbarton, carter GHC Trac Issues: #15954 Differential Revision: https://phabricator.haskell.org/D5402
* Taming the Kind Inference MonsterSimon Peyton Jones2018-11-298-279/+371
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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
* Fix unused-import warningsDavid Eichmann2018-11-221-2/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch fixes a fairly long-standing bug (dating back to 2015) in RdrName.bestImport, namely commit 9376249b6b78610db055a10d05f6592d6bbbea2f Author: Simon Peyton Jones <simonpj@microsoft.com> Date: Wed Oct 28 17:16:55 2015 +0000 Fix unused-import stuff in a better way In that patch got the sense of the comparison back to front, and thereby failed to implement the unused-import rules described in Note [Choosing the best import declaration] in RdrName This led to Trac #13064 and #15393 Fixing this bug revealed a bunch of unused imports in libraries; the ones in the GHC repo are part of this commit. The two important changes are * Fix the bug in bestImport * Modified the rules by adding (a) in Note [Choosing the best import declaration] in RdrName Reason: the previosu rules made Trac #5211 go bad again. And the new rule (a) makes sense to me. In unravalling this I also ended up doing a few other things * Refactor RnNames.ImportDeclUsage to use a [GlobalRdrElt] for the things that are used, rather than [AvailInfo]. This is simpler and more direct. * Rename greParentName to greParent_maybe, to follow GHC naming conventions * Delete dead code RdrName.greUsedRdrName Bumps a few submodules. Reviewers: hvr, goldfire, bgamari, simonmar, jrtc27 Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5312
* Overhaul -fprint-explicit-kinds to use VKARyan Scott2018-11-222-9/+12
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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
* Fix #15852 by eta expanding data family instance RHSes, tooRyan Scott2018-11-224-34/+47
| | | | | | | | | | | | | | | | | | | | | | 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
* Introduce Int16# and Word16#Abhiroop Sarkar2018-11-171-0/+4
| | | | | | | | | | | | This builds off of D4475. Bumps binary submodule. Reviewers: carter, AndreasK, hvr, goldfire, bgamari, simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D5006
* Comments adding to the fix for Trac #15859Simon Peyton Jones2018-11-151-1/+4
|
* Comments only, about polykinded TyConAppsSimon Peyton Jones2018-11-151-1/+13
| | | | See Trac #15704 comment:8ff
* Fix #15845 by defining etaExpandFamInstLHS and using itRyan Scott2018-11-084-18/+53
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Both #9692 and #14179 were caused by GHC being careless about using eta-reduced data family instance axioms. Each of those tickets were fixed by manually whipping up some code to eta-expand the axioms. The same sort of issue has now caused #15845, so I figured it was high time to factor out the code that each of these fixes have in common. This patch introduces the `etaExpandFamInstLHS` function, which takes a family instance's type variables, LHS types, and RHS type, and returns type variables and LHS types that have been eta-expanded if necessary, in the case of a data family instance. (If it's a type family instance, `etaExpandFamInstLHS` just returns the supplied type variables and LHS types unchanged). Along the way, I noticed that many references to `Note [Eta reduction for data families]` (in `FamInstEnv`) had slightly bitrotted (they either referred to a somewhat different name, or claimed that the Note lived in a different module), so I took the liberty of cleaning those up. Test Plan: make test TEST="T9692 T15845" Reviewers: goldfire, bgamari Reviewed By: goldfire Subscribers: rwbarton, carter GHC Trac Issues: #15845 Differential Revision: https://phabricator.haskell.org/D5294
* Add Int8# and Word8#Michal Terepeta2018-11-021-0/+4
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This is the first step of implementing: https://github.com/ghc-proposals/ghc-proposals/pull/74 The main highlights/changes: primops.txt.pp gets two new sections for two new primitive types for signed and unsigned 8-bit integers (Int8# and Word8 respectively) along with basic arithmetic and comparison operations. PrimRep/RuntimeRep get two new constructors for them. All of the primops translate into the existing MachOPs. For CmmCalls the codegen will now zero-extend the values at call site (so that they can be moved to the right register) and then truncate them back their original width. x86 native codegen needed some updates, since it wasn't able to deal with the new widths, but all the changes are quite localized. LLVM backend seems to just work. This is the second attempt at merging this, after the first attempt in D4475 had to be backed out due to regressions on i386. Bumps binary submodule. Signed-off-by: Michal Terepeta <michal.terepeta@gmail.com> Test Plan: ./validate (on both x86-{32,64}) Reviewers: bgamari, hvr, goldfire, simonmar Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5258
* Move eta-reduced coaxiom compatibility handling quirks into FamInstEnv.mniip2018-11-012-22/+32
| | | | | | | | | | | | | | | | | | | | The quirk caused an issue where GHC concluded that 'D' is possibly unifiable with 'D a' (the two types could have the same kind if D is a data family). Test Plan: Ensure T9371 stays fixed. Introduce T15704 Reviewers: goldfire, bgamari Reviewed By: goldfire Subscribers: RyanGlScott, rwbarton, carter GHC Trac Issues: #15704 Differential Revision: https://phabricator.haskell.org/D5206
* Fix embarrassing, egregious bug in roles of (->)Richard Eisenberg2018-11-011-1/+1
| | | | | | | | | | | | | | Previously, I had inexplicably decided that (->)'s roles were all Representational. But, of course, its first two parameters are *dependent* RuntimeReps. All dependent parameters have a Nominal role, because all roles in kinds are Nominal. Fix is easy, but I have no idea how the world hasn't come crashing down before now. This was found while investigating #15801, which requires visible type application in types to observe. Hence, the test case will come with the main patch for #12045.
* Finish fix for #14880.Tobias Dammers2018-10-285-79/+171
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The real change that fixes the ticket is described in Note [Naughty quantification candidates] in TcMType. Fixing this required reworking candidateQTyVarsOfType, the function that extracts free variables as candidates for quantification. One consequence is that we now must be more careful when quantifying: any skolems around must be quantified manually, and quantifyTyVars will now only quantify over metavariables. This makes good sense, as skolems are generally user-written and are listed in the AST. As a bonus, we now have more control over the ordering of such skolems. Along the way, this commit fixes #15711 and refines the fix to #14552 (by accepted a program that was previously rejected, as we can now accept that program by zapping variables to Any). This commit also does a fair amount of rejiggering kind inference of datatypes. Notably, we now can skip the generalization step in kcTyClGroup for types with CUSKs, because we get the kind right the first time. This commit also thus fixes #15743 and #15592, which both concern datatype kind generalisation. (#15591 is also very relevant.) For this aspect of the commit, see Note [Required, Specified, and Inferred in types] in TcTyClsDecls. Test cases: dependent/should_fail/T14880{,-2}, dependent/should_fail/T15743[cd] dependent/should_compile/T15743{,e} ghci/scripts/T15743b polykinds/T15592 dependent/should_fail/T15591[bc] ghci/scripts/T15591
* Fix nasty bug in the type free-var finder, at lastSimon Peyton Jones2018-10-261-12/+94
| | | | | | | | | | | | | | | | | | | | | 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.
* Refactor the treatment of predicate typesSimon Peyton Jones2018-10-242-22/+70
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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.
* Fix #15792 by not reifying invisible arguments in AppTysRyan Scott2018-10-241-4/+25
| | | | | | | | | | | | | | | | | | | | | | | | | | Summary: The `reifyType` function in `TcSplice` is carefully designed to avoid reifying visible arguments to `TyConApp`s. However, the same care was not given towards the `AppTy` case, which lead to #15792. This patch changes to the `AppTy` case of `reifyType` so that it consults the kind of the function type to determine which of the argument types are invisible (and therefore should be dropped) during reification. This required crafting a variant of `tyConArgFlags`, which I dubbed `appTyArgFlags`, that accept an arbitrary function `Type` instead of a `TyCon`. Test Plan: make test TEST=T15792 Reviewers: goldfire, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, carter GHC Trac Issues: #15792 Differential Revision: https://phabricator.haskell.org/D5252
* Clarify Note about ForAllCo coercions.Richard Eisenberg2018-10-221-4/+17
| | | | Comments only: [skip ci]
* Adding almost devoid check for covar in ForAllCoNingning Xie2018-10-193-22/+129
| | | | | | | | | | | | | | | | | | | | | | | | | | Summary: For the sake of consistency of the dependent core, there is a restriction on where a coercion variable can appear in ForAllCo: the coercion variable can appear nowhere except in coherence coercions. Currently this restriction is missing in Core. The goal of this patch is to add the missing restriction. After discussion, we decide: coercion variables can appear nowhere except in `GRefl` and `Refl`. Relaxing the restriction to include `Refl` should not break consistency, we premuse. Test Plan: ./validate Reviewers: goldfire, simonpj, bgamari Reviewed By: goldfire Subscribers: rwbarton, carter GHC Trac Issues: #15757 Differential Revision: https://phabricator.haskell.org/D5231
* Use an accumulator version of tyCoVarsOfTypeTobias Dammers2018-10-151-103/+184
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: This is part 1 from #14880: factor out a worker for the tyCoVarsOf... family of function, implementing them in terms of VarSet, but with accumulator-style (like in `FV`) built in, and with the same kind of pre-insert lookup; this has shown to perform better than either FV or plain VarSet in this particular scenario. Original notes from simonpj: In TyCoRep we now have tyCoVarsOfType implemented 1) Using FV -- this is the baseline version in GHC today 2) Using VarSets via unionVarSet 3) Using VarSets in accumulator-style In this patch (3) is enabled. When compiling perf/compiler/T5631 we get Compiler allocs (1) 1,144M (2) 1,175M (3) 1,142M The key new insight in (3) is this: ty_co_vars_of_type (TyVarTy v) is acc | v `elemVarSet` is = acc | v `elemVarSet` acc = acc <---- NB! | otherwise = ty_co_vars_of_type (tyVarKind v) is (extendVarSet acc v) Notice the second line! If the variable is already in the accumulator, don't re-add it. This makes big difference. Without it, allocation is 1,169M or so. One cause is that we only take the free vars of its kind once; that problem will go away when we do the main part of #14088 and close over kinds /afterwards/. But still, another cause is perhaps that every insert into a set overwrites the previous item, and so allocates a new path to the item; it's not a no-op even if the item is there already. Why use (3) rather than (1)? Becuase it just /has/ to be better; * FV carries around an InterestingVarFun, which does nothing useful here, but is tested at every variable * FV carries around a [Var] for the deterministic version. For this very hot operation (finding free vars) I think it makes sense to have speical purpose code. On the way I also simplified the (less used) coVarsOfType/Co family to use FV, by making serious use of the InterestingVarFun! Test Plan: validate, nofib Reviewers: simonpj, bgamari Reviewed By: simonpj Subscribers: rwbarton, carter GHC Trac Issues: #14880 Differential Revision: https://phabricator.haskell.org/D5141
* Fix #15725 with an extra SymRyan Scott2018-10-151-11/+22
| | | | | | | | | | | | | | | | | | | | Summary: We were adding a `Sym` to one argument in the `InstCo` case of `optCoercion` but not another, leading to the two arguments to misaligned when combined via `Trans`. This fixes the issue with a well targeted use of `wrapSym`. Test Plan: make test TEST=T15725 Reviewers: goldfire, ningning, bgamari Reviewed By: goldfire, ningning Subscribers: rwbarton, carter GHC Trac Issues: #15725 Differential Revision: https://phabricator.haskell.org/D5217
* Revert "Add Int8# and Word8#"Ben Gamari2018-10-091-4/+0
| | | | | | | | | This unfortunately broke i386 support since it introduced references to byte-sized registers that don't exist on that architecture. Reverts binary submodule This reverts commit 5d5307f943d7581d7013ffe20af22233273fba06.
* Add Int8# and Word8#Michal Terepeta2018-10-071-0/+4
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This is the first step of implementing: https://github.com/ghc-proposals/ghc-proposals/pull/74 The main highlights/changes: - `primops.txt.pp` gets two new sections for two new primitive types for signed and unsigned 8-bit integers (`Int8#` and `Word8` respectively) along with basic arithmetic and comparison operations. `PrimRep`/`RuntimeRep` get two new constructors for them. All of the primops translate into the existing `MachOP`s. - For `CmmCall`s the codegen will now zero-extend the values at call site (so that they can be moved to the right register) and then truncate them back their original width. - x86 native codegen needed some updates, since it wasn't able to deal with the new widths, but all the changes are quite localized. LLVM backend seems to just work. Bumps binary submodule. Signed-off-by: Michal Terepeta <michal.terepeta@gmail.com> Test Plan: ./validate with new tests Reviewers: hvr, goldfire, bgamari, simonmar Subscribers: Abhiroop, dfeuer, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4475
* Improve generated `GHC.Prim` docsAlec Theriault2018-10-041-0/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: * Extended `genprimcode` to generate Haddock-compatible deprecations, as well as displaying information about which functions are LLVM-only and which functions can fail with an unchecked exception. * Ported existing deprecations to the new format, and also added a deprecation on `par#` (see Trac #15227). * Emit an error on fixity/deprecation of builtins, unless we are processing the module in which that name is defined (see Trac #15233). That means the following is no longer accepted (outside of `GHC.Types`): ``` infixr 7 : {-# DEPRECATED (:) "cons is deprecated" #-} ``` * Generate `data (->) a b` with docs and fixity in `GHC.Prim`. This means: GHC can now parse `data (->) a b` and `infixr 0 ->` (only in `GHC.Prim`) and `genprimcode` can digest `primtype (->) a b` (See Trac #4861) as well as some misc fixes along the way. Reviewers: bgamari, RyanGlScott Reviewed By: RyanGlScott Subscribers: RyanGlScott, rwbarton, mpickering, carter GHC Trac Issues: #15227, #15233, #4861 Differential Revision: https://phabricator.haskell.org/D5167
* Fix #15637 by using VTA more in GNDRyan Scott2018-10-011-29/+44
| | | | | | | | | | | | | | | | | | | | | | Summary: The code that GND was generating before could crumple over if it derived an instance for a class with an ambiguous type variable in the class head, such as the example in #15637. The solution is straightforward: simply instantiate all variables bound by the class head explicitly using visible type application, which will nip any ambiguity in the bud. Test Plan: make test TEST=T15637 Reviewers: bgamari, simonpj, goldfire Reviewed By: simonpj Subscribers: simonpj, rwbarton, carter GHC Trac Issues: #15637 Differential Revision: https://phabricator.haskell.org/D5148
* Add a recursivity check in nonVoidRyan Scott2018-09-231-4/+15
| | | | | | | | | | | | | | | | | | | | | | | Summary: Previously `nonVoid` outright refused to call itself recursively to avoid the risk of hitting infinite loops when checking recurisve types. But this is too conservative—we //can// call `nonVoid` recursively as long as we incorporate a way to detect the presence of recursive types, and bail out if we do detect one. Happily, such a mechanism already exists in the form of `checkRecTc`, so let's use it. Test Plan: make test TEST=T15584 Reviewers: simonpj, bgamari Reviewed By: simonpj Subscribers: rwbarton, carter GHC Trac Issues: #15584 Differential Revision: https://phabricator.haskell.org/D5116
* Coercion Quantificationningning2018-09-158-535/+1202
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch corresponds to #15497. According to https://ghc.haskell.org/trac/ghc/wiki/DependentHaskell/Phase2, we would like to have coercion quantifications back. This will allow us to migrate (~#) to be homogeneous, instead of its current heterogeneous definition. This patch is (lots of) plumbing only. There should be no user-visible effects. An overview of changes: - Both `ForAllTy` and `ForAllCo` can quantify over coercion variables, but only in *Core*. All relevant functions are updated accordingly. - Small changes that should be irrelevant to the main task: 1. removed dead code `mkTransAppCo` in Coercion 2. removed out-dated Note Computing a coercion kind and roles in Coercion 3. Added `Eq4` in Note Respecting definitional equality in TyCoRep, and updated `mkCastTy` accordingly. 4. Various updates and corrections of notes and typos. - Haddock submodule needs to be changed too. Acknowledgments: This work was completed mostly during Ningning Xie's Google Summer of Code, sponsored by Google. It was advised by Richard Eisenberg, supported by NSF grant 1704041. Test Plan: ./validate Reviewers: goldfire, simonpj, bgamari, hvr, erikd, simonmar Subscribers: RyanGlScott, monoidal, rwbarton, carter GHC Trac Issues: #15497 Differential Revision: https://phabricator.haskell.org/D5054
* Reject class instances with type families in kindsRyan Scott2018-09-021-2/+7
| | | | | | | | | | | | | | | | | | | | | Summary: GHC doesn't know how to handle type families that appear in class instances. Unfortunately, GHC didn't reject instances where type families appear in //kinds//, leading to #15515. This is easily rectified by calling `checkValidTypePat` on all arguments to a class in an instance (and not just the type arguments). Test Plan: make test TEST=T15515 Reviewers: bgamari, goldfire, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, carter GHC Trac Issues: #15515 Differential Revision: https://phabricator.haskell.org/D5068
* Comments onlySimon Peyton Jones2018-08-311-2/+2
|
* Minor improvements to comments [skip ci]Richard Eisenberg2018-08-301-6/+0
|
* Rename kind vars in left-to-right order in bindHsQTyVarsRyan Scott2018-08-281-1/+1
| | | | | | | | | | | | | | | | | | | | Summary: When renaming kind variables in an `LHsQTyVars`, we were erroneously putting all of the kind variables in the binders //after// the kind variables in the body, resulting in #15568. The fix is simple: just swap the order of these two around. Test Plan: make test TEST=T15568 Reviewers: simonpj, bgamari, goldfire Reviewed By: goldfire Subscribers: goldfire, rwbarton, carter GHC Trac Issues: #15568 Differential Revision: https://phabricator.haskell.org/D5108
* Add comments about pretty-printing via IfaceSynSimon Peyton Jones2018-08-241-1/+5
| | | | | Provoked by discussion on Phab:D5097 (Trac #15546), I'm adding a big Note explaing the strategy of pretty-printing via IfaceSyn
* Comments onlySimon Peyton Jones2018-08-233-8/+22
|
* Turn infinite loop into a panicSimon Peyton Jones2018-08-221-4/+10
| | | | | | | | | | | | | | In these two functions * TcIface.toIfaceAppTyArgsX * Type.piResultTys we take a type application (f t1 .. tn) and try to find its kind. It turned out that, if (f t1 .. tn) was ill-kinded the function would go into an infinite loop. That's not good: it caused the loop in Trac #15473. This patch doesn't fix the bug in #15473, but it does turn the loop into a decent panic, which is a step forward.
* Replace most occurences of foldl with foldl'.klebinger.andreas@gmx.at2018-08-215-9/+9
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch adds foldl' to GhcPrelude and changes must occurences of foldl to foldl'. This leads to better performance especially for quick builds where GHC does not perform strictness analysis. It does change strictness behaviour when we use foldl' to turn a argument list into function applications. But this is only a drawback if code looks ONLY at the last argument but not at the first. And as the benchmarks show leads to fewer allocations in practice at O2. Compiler performance for Nofib: O2 Allocations: -1 s.d. ----- -0.0% +1 s.d. ----- -0.0% Average ----- -0.0% O2 Compile Time: -1 s.d. ----- -2.8% +1 s.d. ----- +1.3% Average ----- -0.8% O0 Allocations: -1 s.d. ----- -0.2% +1 s.d. ----- -0.1% Average ----- -0.2% Test Plan: ci Reviewers: goldfire, bgamari, simonmar, tdammers, monoidal Reviewed By: bgamari, monoidal Subscribers: tdammers, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4929
* Support typechecking of type literals in backpackPiyush P Kurur2018-08-061-0/+6
| | | | | | | | | | | | | | | | | Backpack is unable to type check signatures that expect a data which is a type level literal. This was reported in issue #15138. These commits are a fix for this. It also includes a minimal test case that was mentioned in the issue. Reviewers: bgamari, ezyang, goldfire Reviewed By: bgamari, ezyang Subscribers: simonpj, ezyang, rwbarton, thomie, carter GHC Trac Issues: #15138 Differential Revision: https://phabricator.haskell.org/D4951
* Remove decideKindGeneralisationPlanRichard Eisenberg2018-08-021-7/+33
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | TypeInType came with a new function: decideKindGeneralisationPlan. This type-level counterpart to the term-level decideGeneralisationPlan chose whether or not a kind should be generalized. The thinking was that if `let` should not be generalized, then kinds shouldn't either (under the same circumstances around -XMonoLocalBinds). However, this is too conservative -- the situation described in the motivation for "let should be be generalized" does not occur in types. This commit thus removes decideKindGeneralisationPlan, always generalizing. One consequence is that tc_hs_sig_type_and_gen no longer calls solveEqualities, which reports all unsolved constraints, instead relying on the solveLocalEqualities in tcImplicitTKBndrs. An effect of this is that reporing kind errors gets delayed more frequently. This seems to be a net benefit in error reporting; often, alongside a kind error, the type error is now reported (and users might find type errors easier to understand). Some of these errors ended up at the top level, where it was discovered that the GlobalRdrEnv containing the definitions in the local module was not in the TcGblEnv, and thus errors were reported with qualified names unnecessarily. This commit rejiggers some of the logic around captureTopConstraints accordingly. One error message (typecheck/should_fail/T1633) is a regression, mentioning the name of a default method. However, that problem is already reported as #10087, its solution is far from clear, and so I'm not addressing it here. This commit fixes #15141. As it's an internal refactor, there is no concrete test case for it. Along the way, we no longer need the hsib_closed field of HsImplicitBndrs (it was used only in decideKindGeneralisationPlan) and so it's been removed, simplifying the datatype structure. Along the way, I removed code in the validity checker that looks at coercions. This isn't related to this patch, really (though it was, at one point), but it's an improvement, so I kept it. This updates the haddock submodule.