- Feb 22, 2017
-
-
Ben Gamari authored
-
various perf tests have been broken over the course of the past few months. This updates the numbers. Test Plan: ./validate Reviewers: austin, bgamari Subscribers: thomie, #ghc_windows_task_force Differential Revision: https://phabricator.haskell.org/D3160
-
- Feb 21, 2017
-
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
Wiwth -fdefer-type-errors we were generating some top-level equality constraints, just in a corner of checkMain. The fix is easy. Fixes Trac #13292
-
Simon Peyton Jones authored
See Trac #13267 and Note [Instances and constraint synonyms] in TcValidity. We can't easily do a perfect job, because the rename is really trying to do its lookup too early. But this is at least an improvement.
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
Previously TcTyCons were used only for knot-tying, but now they are also used after an error, to add a benign TyCon to the envt so we can carry on; see TyCon.makeRecoveryTyCon. But since it is used in this way, subsequent declarations may see a TcTyCon (e.g. during injectivity checks) and should not have a heart attack as a result. See Note [TcTyCon] in TyCon. This fixes Trac #13271
-
Simon Peyton Jones authored
* Rename SimplEnv.setInScope to setInScopeAndZapFloats, because I keep forgetting that's what it does * Remove unnecessary (and hence confusing) zapJoinFloats from simplLazyBind * Reorder args of simplJoinRhs to put the cont last
-
Ryan Scott authored
These occurrences of pushTcLevelM weren't using the resulting TcLevel, so they can be replaced with the (ostensibly more efficient) pushTcLevelM_. No change in behavior.
-
Ryan Scott authored
[ci skip]
-
Simon Peyton Jones authored
This fixes Trac #13255. The trouble was that we had a bottoming join point, and tried to float it to top level. But it had free JoinIds, so we tried to abstract over them. Disaster. Lint should have caught it, but didn't (now fixed). This patch fixes the original problem.
-
Simon Peyton Jones authored
* lintSingleBinding: check that join points have a valid join-point type (Trac #13281) * lintIdBinder: check that a JoinId is bound by a non-top-level let i.e. not a top level binder not lambda/case binder * Check for empty Rec [] bindings * Rename lintIdBndrs to lintLetBndrs
-
Ben Gamari authored
Previously the comment was correct, but the expected value itself was never updated.
-
Simon Peyton Jones authored
For some odd reason inferConstraints was using a CPS style, which is entirely unnecessary. This patch straightens it out. No change in what it does.
-
Simon Peyton Jones authored
This bug was causing Trac #13297. We were recomputing ds_tvs, and doing it wrongly (by omitting variables that appear only in mtheta). But actually plain 'tvs' is just fine. So code deleted, and bug fixed.
-
Simon Peyton Jones authored
This patch fixes Trac #13272. The general approach was fine, but we were simply not generating the correct implication constraint (in particular generating fresh unification variables). I added a lot more commentary to Note [Gathering and simplifying constraints for DeriveAnyClass] I'm still not very happy with the overall architecture. It feels more complicate than it should.
-
Simon Peyton Jones authored
-
Ben Gamari authored
-
Ben Gamari authored
This unfortunately had quite a number of knock-on effects, including a need for new releases of directory and unix.
-
- Feb 20, 2017
-
-
Ben Gamari authored
-
Ben Gamari authored
These are right on the edge of acceptance and are only reproducible on a stressed machine.
-
Ben Gamari authored
We are now tracking the 2.0 branch.
-
Ben Gamari authored
I forgot to fold these in to the patch merged earlier.
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
If a JoinId (bogusly) ends up in an argument position we printed f jump j rather than f (jump j) Easy to fix.
-
Simon Peyton Jones authored
The desugarer was producing an empty Rec group, which is never supposed to happen. This small patch stops that happening. Next up: Lint should check.
-
Simon Peyton Jones authored
I spent about two hours today hunting fruitlessly for a simplifier bug (when fixing Trac #13255), only to find that it was caused by -ddump-X silently suppressing all ticks in Core. I think this has happened to me once before. So I've changed to make tick-printing on by default (like coercions, etc), with a flag -dsuppress-ticks (like -dsuppress-coercions) to suppress them. Blargh. -dppr-ticks is still there, but deprecated.
-
Gabor Greif authored
-
- Feb 19, 2017
-
-
Alan Zimmerman authored
They take a long time to run, and are effectively superseded by the -ddump-*-ast tests.
-
- Feb 18, 2017
-
-
Edward Z. Yang authored
Test Plan: none Reviewers: simonmar, bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D3148
-
Ben Gamari authored
These things are simply too expensive to generate at the moment. More work is needed here; see #13276 and #13261.
-
Ben Gamari authored
This at long last realizes the ideas for type-indexed Typeable discussed in A Reflection on Types (#11011). The general sketch of the project is described on the Wiki (Typeable/BenGamari). The general idea is that we are adding a type index to `TypeRep`, data TypeRep (a :: k) This index allows the typechecker to reason about the type represented by the `TypeRep`. This index representation mechanism is exposed as `Type.Reflection`, which also provides a number of patterns for inspecting `TypeRep`s, ```lang=haskell pattern TRFun :: forall k (fun :: k). () => forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) (arg :: TYPE r1) (res :: TYPE r2). (k ~ Type, fun ~~ (arg -> res)) => TypeRep arg -> TypeRep res -> TypeRep fun pattern TRApp :: forall k2 (t :: k2). () => forall k1 (a :: k1 -> k2) (b :: k1). (t ~ a b) => TypeRep a -> TypeRep b -> TypeRep t -- | Pattern match on a type constructor. pattern TRCon :: forall k (a :: k). TyCon -> TypeRep a -- | Pattern match on a type constructor including its instantiated kind -- variables. pattern TRCon' :: forall k (a :: k). TyCon -> [SomeTypeRep] -> TypeRep a ``` In addition, we give the user access to the kind of a `TypeRep` (#10343), typeRepKind :: TypeRep (a :: k) -> TypeRep k Moreover, all of this plays nicely with 8.2's levity polymorphism, including the newly levity polymorphic (->) type constructor. Library changes --------------- The primary change here is the introduction of a Type.Reflection module to base. This module provides access to the new type-indexed TypeRep introduced in this patch. We also continue to provide the unindexed Data.Typeable interface, which is simply a type synonym for the existentially quantified SomeTypeRep, data SomeTypeRep where SomeTypeRep :: TypeRep a -> SomeTypeRep Naturally, this change also touched Data.Dynamic, which can now export the Dynamic data constructor. Moreover, I removed a blanket reexport of Data.Typeable from Data.Dynamic (which itself doesn't even import Data.Typeable now). We also add a kind heterogeneous type equality type, (:~~:), to Data.Type.Equality. Implementation -------------- The implementation strategy is described in Note [Grand plan for Typeable] in TcTypeable. None of it was difficult, but it did exercise a number of parts of the new levity polymorphism story which had not yet been exercised, which took some sorting out. The rough idea is that we augment the TyCon produced for each type constructor with information about the constructor's kind (which we call a KindRep). This allows us to reconstruct the monomorphic result kind of an particular instantiation of a type constructor given its kind arguments. Unfortunately all of this takes a fair amount of work to generate and send through the compilation pipeline. In particular, the KindReps can unfortunately get quite large. Moreover, the simplifier will float out various pieces of them, resulting in numerous top-level bindings. Consequently we mark the KindRep bindings as noinline, ensuring that the float-outs don't make it into the interface file. This is important since there is generally little benefit to inlining KindReps and they would otherwise strongly affect compiler performance. Performance ----------- Initially I was hoping to also clear up the remaining holes in Typeable's coverage by adding support for both unboxed tuples (#12409) and unboxed sums (#13276). While the former was fairly straightforward, the latter ended up being quite difficult: while the implementation can support them easily, enabling this support causes thousands of Typeable bindings to be emitted to the GHC.Types as each arity-N sum tycon brings with it N promoted datacons, each of which has a KindRep whose size which itself scales with N. Doing this was simply too expensive to be practical; consequently I've disabled support for the time being. Even after disabling sums this change regresses compiler performance far more than I would like. In particular there are several testcases in the testsuite which consist mostly of types which regress by over 30% in compiler allocations. These include (considering the "bytes allocated" metric), * T1969: +10% * T10858: +23% * T3294: +19% * T5631: +41% * T6048: +23% * T9675: +20% * T9872a: +5.2% * T9872d: +12% * T9233: +10% * T10370: +34% * T12425: +30% * T12234: +16% * 13035: +17% * T4029: +6.1% I've spent quite some time chasing down the source of this regression and while I was able to make som improvements, I think this approach of generating Typeable bindings at time of type definition is doomed to give us unnecessarily large compile-time overhead. In the future I think we should consider moving some of all of the Typeable binding generation logic back to the solver (where it was prior to 91c6b1f5). I've opened #13261 documenting this proposal.
-
Ben Gamari authored
This is generalizes the kind of `(->)`, as discussed in #11714. This involves a few things, * Generalizing the kind of `funTyCon`, adding two new `RuntimeRep` binders, ```lang=haskell (->) :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) (a :: TYPE r1) (b :: TYPE r2). a -> b -> * ``` * Unsaturated applications of `(->)` are expressed as explicit `TyConApp`s * Saturated applications of `(->)` are expressed as `FunTy` as they are currently * Saturated applications of `(->)` are expressed by a new `FunCo` constructor in coercions * `splitTyConApp` needs to ensure that `FunTy`s are split to a `TyConApp` of `(->)` with the appropriate `RuntimeRep` arguments * Teach CoreLint to check that all saturated applications of `(->)` are represented with `FunTy` At the moment I assume that `Constraint ~ *`, which is an annoying source of complexity. This will be simplified once D3023 is resolved. Also, this introduces two known regressions, `tcfail181`, `T10403` ===================== Only shows the instance, instance Monad ((->) r) -- Defined in ‘GHC.Base’ in its error message when -fprint-potential-instances is used. This is because its instance head now mentions 'LiftedRep which is not in scope. I'm not entirely sure of the right way to fix this so I'm just accepting the new output for now. T5963 (Typeable) ================ T5963 is now broken since Data.Typeable.Internals.mkFunTy computes its fingerprint without the RuntimeRep variables that (->) expects. This will be fixed with the merge of D2010. Haddock performance =================== The `haddock.base` and `haddock.Cabal` tests regress in allocations by about 20%. This certainly hurts, but it's also not entirely unexpected: the size of every function type grows with this patch and Haddock has a lot of functions in its heap.
-
Ben Gamari authored
-
Ben Gamari authored
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu>
-
- Feb 17, 2017
-
-
Edward Z. Yang authored
Summary: A number of changes: - Keep the TcGblEnv from typechecking the local signature around when we do merging. In particular, we setup tcg_imports and tcg_rdr_env according to the local signature. This improves our error output (for example, see bkpfail04) and also fixes a bug with reexporting modules in signatures (see bkpreex07) - Fix a bug in thinning, where if we had signature A(module A), this previously would have *thinned out* all of the inherited signatures. Now we treat every inherited signature as having come from an import like "import A", so a module A reexport will pick them up. - Recompilation checking now keeps track of dependent source files of the source signature; previously we forgot to retain this info. There's a manual update too. Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D3133
-
Edward Z. Yang authored
Summary: Previously we weren't tracking these dependencies at all, because we couldn't "find" the interface for {A.H}. Now we've associated hole names to the correct module identity so we will pick them up. Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: bgamari, austin Subscribers: thomie, snowleopard Differential Revision: https://phabricator.haskell.org/D3131
-
Edward Z. Yang authored
Summary: Recompilation avoidance checks if -this-unit-id has changed by relying on the "wanted module" check in readIface ("Something is amiss..."). Unfortunately, this check didn't check if the instantiation made sense, which meant that if you changed the signatures of a Backpack package, we'd still treat the old signatures as up-to-date. The way I fixed this was by having findAndReadIface take in a 'Module' representing the /actual/ module we were intending to lookup. We convert this into the 'Module' we expect to see in 'mi_module' and now do a more elaborate check that will also verify that instantiations make sense. Along the way, I robustified the logging infrastructure for recompilation checking, and folded wrongIfaceModErr (which was dead code) into the error message. Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: bgamari, austin Subscribers: thomie, snowleopard Differential Revision: https://phabricator.haskell.org/D3130
-
Simon Peyton Jones authored
This replaces three methods in OutputableBndr with one, and adds comments. There's also a tiny change in the placement of equals signs in debug-prints. I like it better that way, but if it complicates life for anyone we can put it back.
-