- 18 May, 2016 1 commit
-
-
niteria authored
The order inert_model and intert_eqs fold affects the order that the typechecker looks at things. I've been able to experimentally confirm that the order of equalities and the order of the model matter for determinism. This is just a straigthforward replacement of nondeterministic VarEnv for deterministic DVarEnv. Test Plan: ./validate Reviewers: simonpj, goldfire, austin, bgamari, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2232 GHC Trac Issues: #4012
-
- 16 May, 2016 1 commit
-
-
niteria authored
varSetElems introduces unnecessary non-determinism and while I didn't estabilish experimentally that this matters here I'm convinced that it will, because I expect pattern synonyms to end up in interface files. Test Plan: ./validate Reviewers: austin, simonmar, bgamari, mpickering, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2206 GHC Trac Issues: #4012
-
- 15 May, 2016 1 commit
-
-
Ömer Sinan Ağacan authored
The type synonym expander was doing redundant work by looking at same types again and again. This patch fixes the loop code when both of the types can be expanded, to do `O(min(n, m))` comparisons and `O(n + m)` expansions, where `n` is expansions of the first type and `m` is expansions of the second type. Reported by sjcjoosten in T10547. Test Plan: Added a regression test that was taking several minutes to type check before this patch. Reviewers: bgamari, simonpj, austin, ezyang Reviewed By: bgamari, simonpj, austin, ezyang Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D2198 GHC Trac Issues: #10547
-
- 12 May, 2016 6 commits
-
-
niteria authored
Nondeterminism doesn't matter in these places and pprUFM makes it obvious. I've flipped the order of arguments for convenience. Test Plan: ./validate Reviewers: simonmar, bgamari, austin, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2205 GHC Trac Issues: #4012
-
niteria authored
I've changed it to use nonDetEltsUFM and documented why it's OK. Test Plan: it builds Reviewers: bgamari, austin, simonmar, goldfire, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2204 GHC Trac Issues: #4012
-
Ryan Scott authored
This generalizes the `Generic1` typeclass to be of kind `k -> *`, and this also makes the relevant datatypes and typeclasses in `GHC.Generics` poly-kinded. If `PolyKinds` is enabled, `DeriveGeneric` derives `Generic1` instances such that they use the most general kind possible. Otherwise, deriving `Generic1` defaults to make an instance where the argument is of kind `* -> *` (the current behavior). Fixes #10604. Depends on D2117. Test Plan: ./validate Reviewers: kosmikus, dreixel, goldfire, austin, hvr, simonpj, bgamari Reviewed By: simonpj, bgamari Subscribers: thomie, ekmett Differential Revision: https://phabricator.haskell.org/D2168 GHC Trac Issues: #10604
-
Ryan Scott authored
When `deriveTyData` attempts to unify two kind variables (which can happen if both the typeclass and the datatype are poly-kinded), it mistakenly adds an extra mapping to its substitution which causes the unification to fail when applying the substitution. This can be prevented by checking both the domain and the range of the original substitution to see which kind variables shouldn't be put into the domain of the substitution. A more in-depth explanation is included in `Note [Unification of two kind variables in deriving]`. Fixes #11837. Test Plan: ./validate Reviewers: simonpj, hvr, goldfire, niteria, austin, bgamari Reviewed By: bgamari Subscribers: niteria, thomie Differential Revision: https://phabricator.haskell.org/D2117 GHC Trac Issues: #11837
-
bollmann authored
This commit adds Template Haskell support for pattern synonyms as requested by trac ticket #8761. Test Plan: ./validate Reviewers: thomie, jstolarek, osa1, RyanGlScott, mpickering, austin, goldfire, bgamari Reviewed By: goldfire, bgamari Subscribers: rdragon Differential Revision: https://phabricator.haskell.org/D1940 GHC Trac Issues: #8761
-
Edward Z. Yang authored
Summary: The code was reordered before tcRnImports in 3c44a46b. I don't think the new code is buggy. Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu> Reviewers: simonpj, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2186
-
- 11 May, 2016 1 commit
-
-
niteria authored
I've documented the guarantees that stronglyConnCompFromEdgedVertices provides and commented on the call sites to explain why they are OK from determinism standpoint. I've changed the functions to nonDetUFM versions, so that it's explicit they could introduce nondeterminism. I haven't defined container (VarSet, NameSet) specific versions, so that we have less functions to worry about. Test Plan: this is mostly just documentation, it should have no runtime effect Reviewers: bgamari, simonmar, austin, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2194 GHC Trac Issues: #4012
-
- 10 May, 2016 13 commits
-
-
niteria authored
-
niteria authored
Both Traversable and Foldable can introduce non-determinism and because of typeclass overloading it's implicit and not obvious at the call site. This removes the instances, so that they can't accidentally be used. Test Plan: ./validate Reviewers: austin, goldfire, bgamari, simonmar, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2190 GHC Trac Issues: #4012
-
Simon Peyton Jones authored
In TcSimplify.simplifyInfer, use the context of a partial type signature as 'givens' when simplifying the inferred constraints of the group. This way we get maximum benefit from them. See Note [Add signature contexts as givens]. This (finally) fixes test EqualityConstraints in Trac #9478. And it's a nice tidy-up.
-
Simon Peyton Jones authored
-
niteria authored
simplifyInstanceContexts used cmpType which is nondeterministic for canonicalising typeclass constraints in derived instances. Following changes make it deterministic as explained by the Note [Deterministic simplifyInstanceContexts]. Test Plan: ./validate Reviewers: simonmar, goldfire, simonpj, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2173 GHC Trac Issues: #4012
-
niteria authored
This is the only call site of `lhs_cmp_type` and we only care about equality. `cmpType` is nondeterministic (because `TyCon`s are compared with Uniques in `cmpTc`), so if we don't have to use it, it's better not to. Test Plan: ./validate Reviewers: simonmar, goldfire, bgamari, austin, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2172 GHC Trac Issues: #4012
-
Simon Peyton Jones authored
Previously I had it so that dv_kvs and dv_tvs didn't overlap. Now they can, and quantifyZonkedTyVars removes the former from the latter. This is more economical, and in fact there was a bug where the invariant wasn't re-established. It's much easier to allow dv_kvs and dv_kvs to overlap, and to eliminate the overlap in TcMType.quantifyZonkedTyVars
-
Simon Peyton Jones authored
There's a messy bit of tcSimplifyInfer which concerns how quantify when partial type signatures are involved. This patch tidies it up a lot. Notice that decideQuantification and quantify_tvs get much simpler. And previously the inferred type of a function could be cluttered with phantom variables that were relevant only to the error messgas. See Note [Quantification and partial signatures].
-
Simon Peyton Jones authored
It turns out that GHC 8.0 would accept entirely bogus programs like f2 :: (True, _) -> Char Just f2 = Just (\x->x) (which is now partial-sigs/should_fail/PatBind3) This also fixes Trac #9478, test `PatBind2`.
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
We were failing to emit wild-card hole constraints altogether in the case of pattern bindings. Reason: it was done in tcExtendTyVarEnvFromSig, which isn't called for pattern bindings. This patch make it work right for both pattern and function bindings. Mainly, there is a call to emitWildCardHolds in tcRhs for both PatBind and FunBind. I also killed off TcExpr.typeSigCtxt.
-
Simon Peyton Jones authored
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: docs only Reviewers: simonpj, austin, goldfire, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2180
-
- 06 May, 2016 1 commit
-
-
Simon Peyton Jones authored
We add the default method Ids to the global type envt in tcAddImplicits; and then again in tcInstDcls2 (for reasons explained there). But for some reason in the latter case we added them to the /local/ type envt, via tcExtendLetEnv. This patch just uses tcExtendGlobalValEnv consistently for both. (I found this when reviewing slightly-awkward code from Facundo's static-form error-message patch; turned out that the awkwardness came back to this inconsistency in the handling of default methods.)
-
- 04 May, 2016 2 commits
-
-
niteria authored
Summary: foldUFM introduces unnecessary non-determinism that actually leads to different generated code as explained in Note [TrieMap determinism]. As we're switching from UniqFM to UniqDFM here you might be concerned about performance. There's nothing that ./validate detects. nofib reports no change in Compile Allocations, but Compile Time got better on some tests and worse on some, yielding this summary: -1 s.d. ----- -3.8% +1 s.d. ----- +5.4% Average ----- +0.7% This is not a fair comparison as the order of Uniques changes what GHC is actually doing. One benefit from making this deterministic is also that it will make the performance results more stable. Full nofib results: P108 Test Plan: ./validate, nofib Reviewers: goldfire, simonpj, simonmar, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2169 GHC Trac Issues: #4012
-
Iavor S. Diatchki authored
This fixes #11990. The current rule is simpler than before: if we encounter an unsolved constraint that contains any mentions of properly applied `TypeError`, then we report the type error. If there are multiple `TypeErrors`, then we just report one of them. Reviewers: simonpj, bgamari, austin Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2151 GHC Trac Issues: #11990
-
- 02 May, 2016 2 commits
-
-
Facundo Domínguez authored
Summary: With this patch closed variables are allowed regardless of whether they are bound at the top level or not. The FloatOut pass is always performed. When optimizations are disabled, only expressions that go to the top level are floated. Thus, the applications of the StaticPtr data constructor are always floated. The CoreTidy pass makes sure the floated applications appear in the symbol table of object files. It also collects the floated bindings and inserts them in the static pointer table. The renamer does not check anymore if free variables appearing in the static form are top-level. Instead, the typechecker looks at the tct_closed flag to decide if the free variables are closed. The linter checks that applications of StaticPtr only occur at the top of top-level bindings after the FloatOut pass. The field spInfoName of StaticPtrInfo has been removed. It used to contain the name of the top-level binding that contains the StaticPtr application. However, this information is no longer available when the StaticPtr is constructed, as the binding name is determined now by the FloatOut pass. Test Plan: ./validate Reviewers: goldfire, simonpj, austin, hvr, bgamari Reviewed By: simonpj Subscribers: thomie, mpickering, mboes Differential Revision: https://phabricator.haskell.org/D2104 GHC Trac Issues: #11656
-
Ryan Scott authored
Summary: GHC choked when trying to derive the following: ``` {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE PolyKinds #-} module Example where class Category (cat :: k -> k -> *) where catId :: cat a a catComp :: cat b c -> cat a b -> cat a c newtype T (c :: * -> * -> *) a b = MkT (c a b) deriving Category ``` Unlike in #8865, where we were deriving `Category` for a concrete type like `Either`, in the above example we are attempting to derive an instance of the form: ``` instance Category * c => Category (T * c) where ... ``` (using `-fprint-explicit-kinds` syntax). But `validDerivPred` is checking if `sizePred (Category * c)` equals the number of free type variables in `Category * c`. But note that `sizePred` counts both type variables //and// type constructors, and `*` is a type constructor! So `validDerivPred` erroneously rejects the above instance. The fix is to make `validDerivPred` ignore non-visible arguments to the class type constructor (e.g., ignore `*` is `Category * c`) by using `filterOutInvisibleTypes`. Fixes #11833. Test Plan: ./validate Reviewers: goldfire, hvr, simonpj, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2112 GHC Trac Issues: #11833
-
- 01 May, 2016 1 commit
-
-
niteria authored
Test Plan: it compiles Reviewers: simonpj, austin, goldfire, bgamari, simonmar Reviewed By: simonmar Subscribers: thomie, simonmar Differential Revision: https://phabricator.haskell.org/D2160 GHC Trac Issues: #4012
-
- 30 Apr, 2016 1 commit
-
-
Ryan Scott authored
[ci skip]
-
- 29 Apr, 2016 2 commits
-
-
niteria authored
-
eir@cis.upenn.edu authored
This patch removes splitTelescopeTvs by adding information about scoped type variables to TcTyCon. Vast simplification! This also fixes #11821 by bringing only unzonked vars into scope. Test case: polykinds/T11821
-
- 28 Apr, 2016 7 commits
-
-
niteria authored
There are couple of places where we do `foldUniqSet` just to compute `any` or `all`. `foldUniqSet` is non-deterministic in the general case and `any` and `all` also read nicer. Test Plan: ./validate Reviewers: simonmar, goldfire, simonpj, bgamari, austin Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2156 GHC Trac Issues: #4012
-
Simon Peyton Jones authored
This patch uses the named fields of * FieldLabel * RecordPatSynField in construction and pattern matching. The fields existed before, but we were often using positional notation. Also a minor refactor of the API of mkPatSynRecSelBinds No change in functionality
-
Simon Peyton Jones authored
I'd missed a call to solveEqualities in the partial-type-sig case of TcBinds.tcUserTypeSig. Also the checkValidType test done there best done after inference, in checkInferredPolyId (and is already done there). Fixes Trac #11976
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
"One fewer arguments to ..." rather than "One fewer argument to ..."
-
niteria authored
We want to remove varSetElems at the source level because it might be a source of nondeterminism. I don't think it introduces nondeterminism here, but it's easy to do the same thing deterministically for the same price. instFlexiTcS :: [TKVar] -> TcS (TCvSubst, [TcType]) instFlexiTcS currently gives the range of the produced substitution as the second element of the tuple, but it's not used anywhere right now. If it started to be used in the code I'm modifying it would cause nondeterminism problems. Test Plan: ./validate Reviewers: austin, goldfire, bgamari, simonmar, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2149 GHC Trac Issues: #4012
-
- 26 Apr, 2016 1 commit
-
-
niteria authored
varSetElems introduces unnecessary nondeterminism and it was straighforward to just get a deterministic list. Test Plan: ./validate Reviewers: austin, goldfire, bgamari, simonmar, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2145 GHC Trac Issues: #4012
-