- 22 May, 2015 1 commit
-
-
Simon Peyton Jones authored
In the test program from comment:3 of Trac #10370, it turned out that 25% of all compile time was going in OccName.tidyOccName! It was all becuase the algorithm for finding an unused OccName had a quadratic case. This patch fixes it. THe effect is pretty big: Before: total time = 34.30 secs (34295 ticks @ 1000 us, 1 processor) total alloc = 15,496,011,168 bytes (excludes profiling overheads) After total time = 25.41 secs (25415 ticks @ 1000 us, 1 processor) total alloc = 11,812,744,816 bytes (excludes profiling overheads)
-
- 18 May, 2015 1 commit
-
-
Simon Peyton Jones authored
Make tuple constraints be handled by a perfectly ordinary type class, with the component constraints being the superclasses: class (c1, c2) => (c2, c2) This change was provoked by #10359 inability to re-use a given tuple constraint as a whole #9858 confusion between term tuples and constraint tuples but it's generally a very nice simplification. We get rid of - In Type, the TuplePred constructor of PredTree, and all the code that dealt with TuplePreds - In TcEvidence, the constructors EvTupleMk, EvTupleSel See Note [How tuples work] in TysWiredIn. Of course, nothing is ever entirely simple. This one proved quite fiddly. - I did quite a bit of renaming, which makes this patch touch a lot of modules. In partiuclar tupleCon -> tupleDataCon. - I made constraint tuples known-key rather than wired-in. This is different to boxed/unboxed tuples, but it proved awkward to have all the superclass selectors wired-in. Easier just to use the standard mechanims. - While I was fiddling with known-key names, I split the TH Name definitions out of DsMeta into a new module THNames. That meant that the known-key names can all be gathered in PrelInfo, without causing module loops. - I found that the parser was parsing an import item like T( .. ) as a *data constructor* T, and then using setRdrNameSpace to fix it. Stupid! So I changed the parser to parse a *type constructor* T, which means less use of setRdrNameSpace. I also improved setRdrNameSpace to behave better on Exact Names. Largely on priciple; I don't think it matters a lot. - When compiling a data type declaration for a wired-in thing like tuples (,), or lists, we don't really need to look at the declaration. We have the wired-in thing! And not doing so avoids having to line up the uniques for data constructor workers etc. See Note [Declarations for wired-in things] - I found that FunDeps.oclose wasn't taking superclasses into account; easily fixed. - Some error message refactoring for invalid constraints in TcValidity - Haddock needs to absorb the change too; so there is a submodule update
-
- 14 May, 2015 1 commit
-
-
Austin Seipp authored
This reverts multiple commits from Simon: - 04a484ea Test Trac #10359 - a9ccd37a Test Trac #10403 - c0aae6f6 Test Trac #10248 - eb6ca851 Make the "matchable-given" check happen first - ca173aa3 Add a case to checkValidTyCon - 51cbad15 Update haddock submodule - 6e1174da Separate transCloVarSet from fixVarSet - a8493e03 Fix imports in HscMain (stage2) - a154944b Two wibbles to fix the build - 5910a1bc Change in capitalisation of error msg - 130e93aa Refactor tuple constraints - 8da785d5 Delete commented-out line These break the build by causing Haddock to fail mysteriously when trying to examine GHC.Prim it seems.
-
- 13 May, 2015 1 commit
-
-
Simon Peyton Jones authored
Make tuple constraints be handled by a perfectly ordinary type class, with the component constraints being the superclasses: class (c1, c2) => (c2, c2) This change was provoked by #10359 inability to re-use a given tuple constraint as a whole #9858 confusion between term tuples and constraint tuples but it's generally a very nice simplification. We get rid of - In Type, the TuplePred constructor of PredTree, and all the code that dealt with TuplePreds - In TcEvidence, the constructors EvTupleMk, EvTupleSel See Note [How tuples work] in TysWiredIn. Of course, nothing is ever entirely simple. This one proved quite fiddly. - I did quite a bit of renaming, which makes this patch touch a lot of modules. In partiuclar tupleCon -> tupleDataCon. - I made constraint tuples known-key rather than wired-in. This is different to boxed/unboxed tuples, but it proved awkward to have all the superclass selectors wired-in. Easier just to use the standard mechanims. - While I was fiddling with known-key names, I split the TH Name definitions out of DsMeta into a new module THNames. That meant that the known-key names can all be gathered in PrelInfo, without causing module loops. - I found that the parser was parsing an import item like T( .. ) as a *data constructor* T, and then using setRdrNameSpace to fix it. Stupid! So I changed the parser to parse a *type constructor* T, which means less use of setRdrNameSpace. I also improved setRdrNameSpace to behave better on Exact Names. Largely on priciple; I don't think it matters a lot. - When compiling a data type declaration for a wired-in thing like tuples (,), or lists, we don't really need to look at the declaration. We have the wired-in thing! And not doing so avoids having to line up the uniques for data constructor workers etc. See Note [Declarations for wired-in things] - I found that FunDeps.oclose wasn't taking superclasses into account; easily fixed. - Some error message refactoring for invalid constraints in TcValidity
-
- 22 Apr, 2015 1 commit
-
-
Simon Peyton Jones authored
-
- 09 Apr, 2015 1 commit
-
-
Simon Peyton Jones authored
Note [Bind new Givens immediately] in TcRnTypes We were never using the generality. Result: less code, more efficient. Cake for everyone.
-
- 15 Feb, 2015 1 commit
-
-
Simon Peyton Jones authored
This fixes Trac #10072. Previously the type-hole constraint was escaping to top level, but it belongs in the scope of the skolems bound by the RULE.
-
- 11 Feb, 2015 1 commit
-
-
eir@cis.upenn.edu authored
This really should have done a while ago, with the ReturnTv factoring. It's surprising that I can't tickle the bug! Please merge to ghc-7.10.
-
- 06 Jan, 2015 1 commit
-
-
Simon Peyton Jones authored
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
-
- 23 Dec, 2014 1 commit
-
-
Simon Peyton Jones authored
The purpose of silent superclass parameters was to solve the awkward problem of superclass dictinaries being bound to bottom. See THE PROBLEM in Note [Recursive superclasses] in TcInstDcls Although the silent-superclass idea worked, * It had non-local consequences, and had effects even in Haddock, where we had to discard silent parameters before displaying instance declarations * It had unexpected peformance costs, shown up by Trac #3064 and its test case. In monad-transformer code, when constructing a Monad dictionary you had to pass an Applicative dictionary; and to construct that you neede a Functor dictionary. Yet these extra dictionaries were often never used. (All this got much worse when we added Applicative as a superclass of Monad.) Test T3064 compiled *far* faster after silent superclasses were eliminated. * It introduced new bugs. For example SilentParametersOverlapping, T5051, and T7862, all failed to compile because of instance overlap directly because of the silent-superclass trick. So this patch takes a new approach, which I worked out with Dimitrios in the closing hours before Christmas. It is described in detail in THE PROBLEM in Note [Recursive superclasses] in TcInstDcls. Seems to work great! Quite a bit of knock-on effect * The main implementation work is in tcSuperClasses in TcInstDcls Everything else is fall-out * IdInfo.DFunId no longer needs its n-silent argument * Ditto IDFunId in IfaceSyn * Hence interface file format changes * Now that DFunIds do not have silent superclass parameters, printing out instance declarations is simpler. There is tiny knock-on effect in Haddock, so that submodule is updated * I realised that when computing the "size of a dictionary type" in TcValidity.sizePred, we should be rather conservative about type functions, which can arbitrarily increase the size of a type. Hence the new datatype TypeSize, which has a TSBig constructor for "arbitrarily big". * instDFunType moves from TcSMonad to Inst * Interestingly, CmmNode and CmmExpr both now need a non-silent (Ord r) in a couple of instance declarations. These were previously silent but must now be explicit. * Quite a bit of wibbling in error messages
-
- 12 Dec, 2014 2 commits
-
-
eir@cis.upenn.edu authored
-
eir@cis.upenn.edu authored
Summary: This is a rewrite of the algorithm to solve for Coercible "instances". A preliminary form of these ideas is at https://ghc.haskell.org/trac/ghc/wiki/Design/NewCoercibleSolver The basic idea here is that the `EqPred` constructor of `PredTree` now is parameterised by a new type `EqRel` (where `data EqRel = NomEq | ReprEq`). Thus, every equality constraint can now talk about nominal equality (the usual case) or representational equality (the `Coercible` case). This is a change from the previous behavior where `Coercible` was just considered a regular class with a special case in `matchClassInst`. Because of this change, representational equalities are now canonicalized just like nominal ones, allowing more equalities to be solved -- in particular, the case at the top of #9117. A knock-on effect is that the flattener must be aware of the choice of equality relation, because the inert set now stores both representational inert equalities alongside the nominal inert equalities. Of course, we can use representational equalities to rewrite only within another representational equality -- thus the parameterization of the flattener. A nice side effect of this change is that I've introduced a new type `CtFlavour`, which tracks G vs. W vs. D, removing some ugliness in the flattener. This commit includes some refactoring as discussed on D546. It also removes the ability of Deriveds to rewrite Deriveds. This fixes bugs #9117 and #8984. Reviewers: simonpj, austin, nomeata Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D546 GHC Trac Issues: #9117, #8984
-
- 10 Dec, 2014 1 commit
-
-
Simon Peyton Jones authored
Hardly used, not helpful. Use newEvVar instead.
-
- 03 Dec, 2014 1 commit
-
-
Austin Seipp authored
Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
- 02 Dec, 2014 1 commit
-
-
Simon Peyton Jones authored
This is a long-overdue renaming Untouchables --> TcLevel It is renaming only; no change in functionality. We really wanted to get this done before the 7.10 fork.
-
- 28 Nov, 2014 1 commit
-
-
thomasw authored
Summary: Add support for Partial Type Signatures, i.e. holes in types, see: https://ghc.haskell.org/trac/ghc/wiki/PartialTypeSignatures This requires an update to the Haddock submodule. Test Plan: validate Reviewers: austin, goldfire, simonpj Reviewed By: simonpj Subscribers: thomie, Iceland_jack, dominique.devriese, simonmar, carter, goldfire Differential Revision: https://phabricator.haskell.org/D168 GHC Trac Issues: #9478
-
- 21 Nov, 2014 1 commit
-
-
Simon Peyton Jones authored
-
- 12 Nov, 2014 1 commit
-
-
eir@cis.upenn.edu authored
See the ticket for more info about the new algorithm. This is a small simplification, unifying the treatment of type checking in a few similar situations.
-
- 04 Nov, 2014 3 commits
-
-
Simon Peyton Jones authored
The driving change is this: * The canonical CFunEqCan constraints now have the form [G] F xis ~ fsk [W] F xis ~ fmv where fsk is a flatten-skolem, and fmv is a flatten-meta-variable Think of them as the name of the type-function application See Note [The flattening story] in TcFlatten. A flatten-meta-variable is distinguishable by its MetaInfo of FlatMetaTv This in turn led to an enormous cascade of other changes, which simplify and modularise the constraint solver. In particular: * Basic data types * I got rid of inert_solved_funeqs altogether. It serves no useful role that inert_flat_cache does not solve. * I added wl_implics to the WorkList, as a convenient place to accumulate newly-emitted implications; see Note [Residual implications] in TcSMonad. * I eliminated tcs_ty_binds altogether. These were the bindings for unification variables that we have now solved by unification. We kept them in a finite map and did the side-effecting unification later. But in cannonicalisation we had to look up in the side-effected mutable tyvars anyway, so nothing was being gained. Our original idea was that the solver would be pure, and would be a no-op if you discarded its results, but this was already not-true for implications since we update their evidence bindings in an imperative way. So rather than the uneasy compromise, it's now clearly imperative! * I split out the flatten/unflatten code into a new module, TcFlatten * I simplified and articulated explicitly the (rather hazy) invariants for the inert substitution inert_eqs. See Note [eqCanRewrite] and See Note [Applying the inert substitution] in TcFlatten * Unflattening is now done (by TcFlatten.unflatten) after solveFlats, before solving nested implications. This turned out to simplify a lot of code. Previously, unflattening was done as part of zonking, at the very very end. * Eager unflattening allowed me to remove the unpleasant ic_fsks field of an Implication (hurrah) * Eager unflattening made the TcSimplify.floatEqualities function much simpler (just float equalities looking like a ~ ty, where a is an untouchable meta-tyvar). * Likewise the idea of "pushing wanteds in as givens" could be completely eliminated. * I radically simplified the code that determines when there are 'given' equalities, and hence whether we can float 'wanted' equalies out. See TcSMonad.getNoGivenEqs, and Note [When does an implication have given equalities?]. This allowed me to get rid of the unpleasant inert_no_eqs flag in InertCans. * As part of this given-equality stuff, I fixed Trac #9211. See Note [Let-bound skolems] in TcSMonad * Orientation of tyvar/tyvar equalities (a ~ b) was partly done during canonicalisation, but then repeated in the spontaneous-solve stage (trySpontaneousSolveTwoWay). Now it is done exclusively during canonicalisation, which keeps all the code in one place. See Note [Canonical orientation for tyvar/tyvar equality constraints] in TcCanonical
-
Simon Peyton Jones authored
This makes newClsInst (was mkInstance) look more like newFamInst, and simplifies the plumbing of the overlap flag, and ensures that freshening (required by the InstEnv stuff) happens in one place. On the way I also tided up the rather ragged family of tcInstSkolTyVars and friends. The result at least has more uniform naming.
-
Simon Peyton Jones authored
-
- 26 Sep, 2014 1 commit
-
-
Simon Peyton Jones authored
-
- 15 May, 2014 1 commit
-
-
Herbert Valerio Riedel authored
In some cases, the layout of the LANGUAGE/OPTIONS_GHC lines has been reorganized, while following the convention, to - place `{-# LANGUAGE #-}` pragmas at the top of the source file, before any `{-# OPTIONS_GHC #-}`-lines. - Moreover, if the list of language extensions fit into a single `{-# LANGUAGE ... -#}`-line (shorter than 80 characters), keep it on one line. Otherwise split into `{-# LANGUAGE ... -#}`-lines for each individual language extension. In both cases, try to keep the enumeration alphabetically ordered. (The latter layout is preferable as it's more diff-friendly) While at it, this also replaces obsolete `{-# OPTIONS ... #-}` pragma occurences by `{-# OPTIONS_GHC ... #-}` pragmas.
-
- 14 Apr, 2014 1 commit
-
-
Simon Peyton Jones authored
-
- 17 Mar, 2014 1 commit
-
-
Simon Peyton Jones authored
There was even a comment to warn about this possiblity, and it finally showed up in practice! This patch fixes it quite nicely, with commens to explain.
-
- 07 Mar, 2014 1 commit
-
-
Simon Peyton Jones authored
The issue here is described in Note [Binding scoped type variables] in TcPat. When implementing this fix I was able to make things quite a bit simpler: * The type variables in a type signature now never unify with each other, and so can be straightfoward skolems. * We only need the SigTv stuff for signatures in patterns, and for kind variables.
-
- 26 Jan, 2014 1 commit
-
-
Gabor Greif authored
-
- 28 Dec, 2013 1 commit
-
-
Simon Peyton Jones authored
This patch doesn't include the changes to TcCanonical and TcSMonad, which are a bigger follow-up patch, so it is tightly coupled to the follow-up.
-
- 03 Dec, 2013 1 commit
-
-
Joachim Breitner authored
When doing non-standalone deriving, annotate each individual unsimplified constraint with its own CtOrigin. This is just the refactoring, so the CtOrigin is still CtDeriv in each case.
-
- 27 Nov, 2013 1 commit
-
-
Joachim Breitner authored
Previously, TcCoercion were only used to represent boxed Nominal coercions. In order to also talk about boxed Representational coercions in the type checker, we add Roles to TcCoercion. Again, we closely mirror Coercion. The roles are verified by a few assertions, and at the latest after conversion to Coercion. I have put my trust in the comprehensiveness of the testsuite here, but any role error after desugaring popping up now might be caused by this refactoring.
-
- 22 Nov, 2013 1 commit
-
-
Joachim Breitner authored
-
- 01 Oct, 2013 1 commit
-
-
Simon Marlow authored
-
- 18 Sep, 2013 1 commit
-
-
Simon Peyton Jones authored
If we have class (F a ~ b) => C a b then we can produce *derived* CFunEqCans. These were not being treated properly in two places: a) in TcMType.zonkFlats (Trac #8134) b) in TcSMonad.prepareInertsForImplications (Trac #8129) This patch fixes both.
-
- 10 Sep, 2013 1 commit
-
-
Simon Peyton Jones authored
-
- 02 Sep, 2013 1 commit
-
-
Simon Peyton Jones authored
This is a lingering bug from the introduction of polymorphic kinds. In the specialiser we were specialising over a type, but failing to specialise over the kinds it mentions. The fix is simple: add a call to closeOverKinds. Most of the patch is to add closeOverKinds, and to use it in a few other places where we are doing essentially the same thing.
-
- 28 Jun, 2013 1 commit
-
-
eir@cis.upenn.edu authored
Now, all open type families have result kinds that default to *. Top-level type families have all arguments default to *, and associated type families have all arguments that are not mentioned in the class header default to *. Closed type families perform kind inference, but generalize only over those kind variables that are parametric in their use. This is all a little fiddly and specific, but it seems to follow use cases. This commit also includes a large Note [Kind-checking strategies] in TcHsType that helps keep all of this straight.
-
- 19 Jun, 2013 1 commit
-
-
thoughtpolice authored
Clang doesn't like whitespace between macro and arguments. Signed-off-by:
Austin Seipp <aseipp@pobox.com>
-
- 30 May, 2013 1 commit
-
-
Simon Peyton Jones authored
Finally (I hope) fixes Trac #7903. See Note [Zonking inside the knot] in TcHsSyn
-
- 21 May, 2013 1 commit
-
-
Simon Peyton Jones authored
A buglet that exposed an opportunity for some welcome refactoring and simplification. Main changes * TcMType.zonkQuantifiedTyVars is replaced by quantifyTyVars, which does a bit more zonking (so that its clients do not need to) * TcHsType.kindGeneralise becomes a bit simpler, and hands off to quantifyTyVars * A bit of simplification of the hacky code in TcTyClsDcls.tcConDecl, where we figure out how to generalise the data constructor's type * Improve the error message from badExistential when a constructor has an existential type, by printing the offending type * Some consequential simplification in simplifyInfer.
-
- 03 May, 2013 1 commit
-
-
Simon Peyton Jones authored
We simply weren't quantifying kind variables at the points we were claiming. In paritcular, in forall (a:k). blah we quantify the 'k' around the 'forall a', provided k isn't already in scope
-