- 14 Aug, 2012 1 commit
-
-
Simon Peyton Jones authored
-
- 23 Jul, 2012 1 commit
-
-
Simon Peyton Jones authored
The main thing is that we now keep unsolved Derived constraints in the wc_flats of a WantedConstraints, rather than discarding them each time. This actually fixes a poential (admittedly obscure) bug, when we currently discard a superclass constraint, and may never re-generate it, and may thereby miss a functional dependency. Instead, reportErrors filters out Derived constraints that we don't want to report. The other changes are all small refactorings following our walk-through.
-
- 10 Jul, 2012 1 commit
-
-
Simon Peyton Jones authored
These should fix #7024 and #7022, among others. The main difficulty was that we were getting occ-name clashes between kind and type variables in TyCons, when spat into an interface file. The new scheme is to tidy TyCons during the conversoin into IfaceSyn, rather than trying to generate them pre-tidied, which was the already-unsatisfactory previous plan. There is the usual wave of refactorig as well.
-
- 13 Jun, 2012 1 commit
-
-
Simon Peyton Jones authored
This patch re-implements implicit parameters via a class with a functional dependency: class IP (n::Symbol) a | n -> a where ip :: a This definition is in the library module GHC.IP. Notice how it use a type-literal, so we can have constraints like IP "x" Int Now all the functional dependency machinery works right to make implicit parameters behave as they should. Much special-case processing for implicit parameters can be removed entirely. One particularly nice thing is not having a dedicated "original-name cache" for implicit parameters (the nsNames field of NameCache). But many other cases disappear: * BasicTypes.IPName * IPTyCon constructor in Tycon.TyCon * CIPCan constructor in TcRnTypes.Ct * IPPred constructor in Types.PredTree Implicit parameters remain special in a few ways: * Special syntax. Eg the constraint (IP "x" Int) is parsed and printed as (?x::Int). And we still have local bindings for implicit parameters, and occurrences thereof. * A implicit-parameter binding (let ?x = True in e) amounts to a local instance declaration, which we have not had before. It just generates an implication contraint (easy), but when going under it we must purge any existing bindings for ?x in the inert set. See Note [Shadowing of Implicit Parameters] in TcSimplify * TcMType.sizePred classifies implicit parameter constraints as size-0, as before the change There are accompanying patches to libraries 'base' and 'haddock' All the work was done by Iavor Diatchki
-
- 11 Jun, 2012 1 commit
-
-
Simon Marlow authored
-
- 08 Jun, 2012 1 commit
-
-
dimitris authored
simplifyTop, code beautification etc. Important things: (a) New top-level defaulting plan, gotten rid of the SimplContext field. See Note [Top-level Defaulting Plan] (b) Serious bug fix in the floatEqualities mechanism See Note [Extra TcS Untouchables],[Float Equalities out of Implications] The changes are mostly confined in TcSimplify but there is a simplification wave affecting other modules as well.
-
- 07 Jun, 2012 1 commit
-
-
Simon Peyton Jones authored
This is (I hope) the last major patch for kind polymorphism. The big new feature is polymorphic kind recursion when you supply a complete kind signature for a type constructor. (I've documented it in the user manual too.) This fixes Trac #6137, #6093, #6049. The patch also makes type/data families less polymorphic by default. data family T a now defaults to T :: * -> * If you want T :: forall k. k -> *, use data family T (a :: k) This defaulting to * is done whenever there is a "complete, user-specified kind signature", something that is carefully defined in the user manual. Hurrah!
-
- 05 Jun, 2012 1 commit
-
-
Ian Lynagh authored
By using Haskell's debugIsOn rather than CPP's "#ifdef DEBUG", we don't need to kludge things to keep the warning checker happy etc.
-
- 07 May, 2012 1 commit
-
-
Simon Peyton Jones authored
This is the result of Simon and Dimitrios doing a code walk through. There is no change in behaviour, but the structure is much better. Main changes: * Given constraints contain an EvTerm not an EvVar * Correspondingly, TcEvidence is a recursive types that uses EvTerms rather than EvVars * Rename CtFlavor to CtEvidence * Every CtEvidence has a ctev_pred field. And use record fields consistently for CtEvidence * The solved-constraint fields of InertSet (namely inert_solved and inert_solved_funeqs) contain CtEvidence, not Ct There is a long cascade of follow-on changes.
-
- 10 Apr, 2012 1 commit
-
-
dimitris authored
constraint generation during solveInteractCts, needed for polytype equality decomposition. More commentary to follow.
-
- 29 Mar, 2012 3 commits
- 28 Mar, 2012 1 commit
-
-
dimitris authored
(i) Replaced a lot of clunky and fragile EvVar handling code with a more uniform ``flavor transformer'' API in the canonicalizer and the interaction solver. Now EvVars are just fields inside the CtFlavors. (ii) Significantly simplified our caching story This patch does not validate yet and more refactoring is on the way.
-
- 02 Mar, 2012 1 commit
-
-
Simon Peyton Jones authored
which (finally) fills out the functionality of polymorphic kinds. It also fixes numerous bugs. Main changes are: Renaming stuff ~~~~~~~~~~~~~~ * New type in HsTypes: data HsBndrSig sig = HsBSig sig [Name] which is used for type signatures in patterns, and kind signatures in types. So when you say f (x :: [a]) = x ++ x or data T (f :: k -> *) (x :: *) = MkT (f x) the signatures in both cases are a HsBndrSig. * The [Name] in HsBndrSig records the variables bound by the pattern, that is 'a' in the first example, 'k' in the second, and nothing in the third. The renamer initialises the field. * As a result I was able to get rid of RnHsSyn.extractHsTyNames :: LHsType Name -> NameSet and its friends altogether. Deleted the entire module! This led to some knock-on refactoring; in particular the type renamer now returns the free variables just like the term renamer. Kind-checking types: mainly TcHsType ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ A major change is that instead of kind-checking types in two passes, we now do one. Under the old scheme, the first pass did kind-checking and (hackily) annotated the HsType with the inferred kinds; and the second pass desugared the HsType to a Type. But now that we have kind variables inside types, the first pass (TcHsType.tc_hs_type) can go straight to Type, and zonking will squeeze out any kind unification variables later. This is much nicer, but it was much more fiddly than I had expected. The nastiest corner is this: it's very important that tc_hs_type uses lazy constructors to build the returned type. See Note [Zonking inside the knot] in TcHsType. Type-checking type and class declarations: mainly TcTyClsDecls ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ I did tons of refactoring in TcTyClsDecls. Simpler and nicer now. Typechecking bindings: mainly TcBinds ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ I rejigged (yet again) the handling of type signatures in TcBinds. It's a bit simpler now. The main change is that tcTySigs goes right through to a TcSigInfo in one step; previously it was split into two, part here and part later. Unsafe coercions ~~~~~~~~~~~~~~~~ Usually equality coercions have exactly the same kind on both sides. But we do allow an *unsafe* coercion between Int# and Bool, say, used in case error Bool "flah" of { True -> 3#; False -> 0# } --> (error Bool "flah") |> unsafeCoerce Bool Int# So what is the instantiation of (~#) here? unsafeCoerce Bool Int# :: (~#) ??? Bool Int# I'm using OpenKind here for now, but it's un-satisfying that the lhs and rhs of the ~ don't have precisely the same kind. More minor ~~~~~~~~~~ * HsDecl.TySynonym has its free variables attached, which makes the cycle computation in TcTyDecls.mkSynEdges easier. * Fixed a nasty reversed-comparison bug in FamInstEnv: @@ -490,7 +490,7 @@ lookup_fam_inst_env' match_fun one_sided ie fam tys n_tys = length tys extra_tys = drop arity tys (match_tys, add_extra_tys) - | arity > n_tys = (take arity tys, \res_tys -> res_tys ++ extra_tys) + | arity < n_tys = (take arity tys, \res_tys -> res_tys ++ extra_tys) | otherwise = (tys, \res_tys -> res_tys)
-
- 16 Feb, 2012 1 commit
-
-
Simon Peyton Jones authored
-
- 19 Jan, 2012 1 commit
-
-
Ian Lynagh authored
This patch defines a flag -fno-warn-pointless-pragmas, and uses it to disable some warnings in the containers package. Along the way, also made a ContainsDynFlags class, and added a HasDynFlags instance for IOEnv (and thus TcRnIf and DsM).
-
- 12 Jan, 2012 1 commit
-
-
Simon Peyton Jones authored
This patch implements the idea of deferring (most) type errors to runtime, instead emitting only a warning at compile time. The basic idea is very simple: * The on-the-fly unifier in TcUnify never fails; instead if it gets stuck it emits a constraint. * The constraint solver tries to solve the constraints (and is entirely unchanged, hooray). * The remaining, unsolved constraints (if any) are passed to TcErrors.reportUnsolved. With -fdefer-type-errors, instead of emitting an error message, TcErrors emits a warning, AND emits a binding for the constraint witness, binding it to (error "the error message"), via the new form of evidence TcEvidence.EvDelayedError. So, when the program is run, when (and only when) that witness is needed, the program will crash with the exact same error message that would have been given at compile time. Simple really. But, needless to say, the exercise forced me into some major refactoring. * TcErrors is almost entirely rewritten * EvVarX and WantedEvVar have gone away entirely * ErrUtils is changed a bit: * New Severity field in ErrMsg * Renamed the type Message to MsgDoc (this change touches a lot of files trivially) * One minor change is that in the constraint solver we try NOT to combine insoluble constraints, like Int~Bool, else all such type errors get combined together and result in only one error message! * I moved some definitions from TcSMonad to TcRnTypes, where they seem to belong more
-
- 03 Jan, 2012 1 commit
-
-
Simon Peyton Jones authored
This patch should have no user-visible effect. It implements a significant internal refactoring of the way that FC axioms are handled. The ultimate goal is to put us in a position to implement "pattern-matching axioms". But the changes here are only does refactoring; there is no change in functionality. Specifically: * We now treat data/type family instance declarations very, very similarly to types class instance declarations: - Renamed InstEnv.Instance as InstEnv.ClsInst, for symmetry with FamInstEnv.FamInst. This change does affect the GHC API, but for the better I think. - Previously, each family type/data instance declaration gave rise to a *TyCon*; typechecking a type/data instance decl produced that TyCon. Now, each type/data instance gives rise to a *FamInst*, by direct analogy with each class instance declaration giving rise to a ClsInst. - Just as each ClsInst contains its evidence, a DFunId, so each FamInst contains its evidence, a CoAxiom. See Note [FamInsts and CoAxioms] in FamInstEnv. The CoAxiom is a System-FC thing, and can relate any two types, whereas the FamInst relates directly to the Haskell source language construct, and always has a function (F tys) on the LHS. - Just as a DFunId has its own declaration in an interface file, so now do CoAxioms (see IfaceSyn.IfaceAxiom). These changes give rise to almost all the refactoring. * We used to have a hack whereby a type family instance produced a dummy type synonym, thus type instance F Int = Bool -> Bool translated to axiom FInt :: F Int ~ R:FInt type R:FInt = Bool -> Bool This was always a hack, and now it's gone. Instead the type instance declaration produces a FamInst, whose axiom has kind axiom FInt :: F Int ~ Bool -> Bool just as you'd expect. * Newtypes are done just as before; they generate a CoAxiom. These CoAxioms are "implicit" (do not generate an IfaceAxiom declaration), unlike the ones coming from family instance declarations. See Note [Implicit axioms] in TyCon On the whole the code gets significantly nicer. There were consequential tidy-ups in the vectoriser, but I think I got them right.
-
- 22 Dec, 2011 1 commit
-
-
dimitris authored
-
- 05 Dec, 2011 1 commit
-
-
Simon Peyton Jones authored
The main idea is that when we unify forall a. t1 ~ forall a. t2 we get constraints from unifying t1~t2 that mention a. We are producing a coercion witnessing the equivalence of the for-alls, and inside *that* coercion we need bindings for the solved constraints arising from t1~t2. We didn't have way to do this before. The big change is that here's a new type TcEvidence.TcCoercion, which is much like Coercion.Coercion except that there's a slot for TcEvBinds in it. This has a wave of follow-on changes. Not deep but broad. * New module TcEvidence, which now contains the HsWrapper TcEvBinds, EvTerm etc types that used to be in HsBinds * The typechecker works exclusively in terms of TcCoercion. * The desugarer converts TcCoercion to Coercion * The main payload is in TcUnify.unifySigmaTy. This is the function that had a gross hack before, but is now beautiful. * LCoercion is gone! Hooray. Many many fiddly changes in conssequence. But it's nice.
-
- 29 Nov, 2011 1 commit
-
-
dimitris authored
that evVarPred.cc_id must be equal to ctPred needs no longer be true.
-
- 28 Nov, 2011 2 commits
-
-
dimitris authored
Adding commentary, and fixing a knot-tie related bug. Commentary only.
-
dimitris authored
1) Stopped rewriting and caching solveds in the inerts because profiling showed that a lot of time was spent on rewriting already solved goals. 2) Optimisations in zonkEvBinds for common-case evidence bindings generated from the constraint solver. 3) Now solved goals cache their evidence terms, so that we can more aggressively optimize Refl coercions during constraint solving. This patch also includes a rewrite of rewriteInertEqsFromInertEq which greatly improves its efficiency.
-
- 18 Nov, 2011 1 commit
-
-
Simon Marlow authored
This was pretty straightforward: collect the filenames in the lexer, and add them in to the tcg_dependent_files list that the typechecker collects. Note that we still don't get #included files in the ghc -M output. Since we don't normally lex the whole file in ghc -M, this same mechanism can't be used directly.
-
- 16 Nov, 2011 1 commit
-
-
dimitris authored
-
- 11 Nov, 2011 1 commit
-
-
dreixel authored
This big patch implements a kind-polymorphic core for GHC. The current implementation focuses on making sure that all kind-monomorphic programs still work in the new core; it is not yet guaranteed that kind-polymorphic programs (using the new -XPolyKinds flag) will work. For more information, see http://haskell.org/haskellwiki/GHC/Kinds
-
- 05 Nov, 2011 1 commit
-
-
GregWeber authored
Let GHC know about an external dependency that Template Haskell uses so that GHC can recompile when the dependency changes. No support for ghc -M There is a corresponding addition to the template-haskell library
-
- 04 Nov, 2011 1 commit
-
-
Ian Lynagh authored
We only use it for "compiler" sources, i.e. not for libraries. Many modules have a -fno-warn-tabs kludge for now.
-
- 01 Nov, 2011 1 commit
-
-
dterei authored
Conflicts: compiler/main/DynFlags.hs compiler/main/HscMain.lhs
-
- 26 Oct, 2011 1 commit
-
-
Ian Lynagh authored
This reverts commit bb0eb57e.
-
- 25 Oct, 2011 1 commit
-
-
dterei authored
-
- 29 Sep, 2011 1 commit
-
-
Simon Peyton Jones authored
-
- 21 Sep, 2011 2 commits
-
-
Simon Marlow authored
-
Simon Marlow authored
This is work mostly done by Daniel Winograd-Cort during his internship at MSR Cambridge, with some further refactoring by me. This commit adds support to GHCi for most top-level declarations that can be used in Haskell source files. Class, data, newtype, type, instance are all supported, as are Type Family-related declarations. The current set of declarations are shown by :show bindings. As with variable bindings, entities bound by newer declarations shadow earlier ones. Tests are in testsuite/tests/ghci/scripts/ghci039--ghci054. Documentation to follow.
-
- 06 Sep, 2011 1 commit
-
-
batterseapower authored
Basically as documented in http://hackage.haskell.org/trac/ghc/wiki/KindFact, this patch adds a new kind Constraint such that: Show :: * -> Constraint (?x::Int) :: Constraint (Int ~ a) :: Constraint And you can write *any* type with kind Constraint to the left of (=>): even if that type is a type synonym, type variable, indexed type or so on. The following (somewhat related) changes are also made: 1. We now box equality evidence. This is required because we want to give (Int ~ a) the *lifted* kind Constraint 2. For similar reasons, implicit parameters can now only be of a lifted kind. (?x::Int#) => ty is now ruled out 3. Implicit parameter constraints are now allowed in superclasses and instance contexts (this just falls out as OK with the new constraint solver) Internally the following major changes were made: 1. There is now no PredTy in the Type data type. Instead GHC checks the kind of a type to figure out if it is a predicate 2. There is now no AClass TyThing: we represent classes as TyThings just as a ATyCon (classes had TyCons anyway) 3. What used to be (~) is now pretty-printed as (~#). The box constructor EqBox :: (a ~# b) -> (a ~ b) 4. The type LCoercion is used internally in the constraint solver and type checker to represent coercions with free variables of type (a ~ b) rather than (a ~# b)
-
- 01 Sep, 2011 1 commit
-
-
Simon Peyton Jones authored
For the bind_fvs field of FunBind/PatBind, we need to be careful to keep track of uses of all functions in this module (although not imported ones). Moreover in TcBinds.decideGeneralisationPlan we need to take note of uses of lexically scoped type variables. These two buglets led to a (useful) assertion failure in TcEnv.
-
- 16 Aug, 2011 1 commit
-
-
Simon Peyton Jones authored
This patch makes a number of related improvements a) Implements the Haskell Prime semantics for pattern bindings (Trac #2357). That is, a pattern binding p = e is typed just as if it had been written t = e f = case t of p -> f g = case t of p -> g ... etc ... where f,g are the variables bound by p. In paricular it's ok to say (f,g) = (\x -> x, \y -> True) and f and g will get propertly inferred types f :: a -> a g :: a -> Int b) Eliminates the MonoPatBinds flag altogether. (For the moment it is deprecated and has no effect.) Pattern bindings are now generalised as per (a). Fixes Trac #2187 and #4940, in the way the users wanted! c) Improves the OutsideIn algorithm generalisation decision. Given a definition without a type signature (implying "infer the type"), the published algorithm rule is this: - generalise *top-level* functions, and - do not generalise *nested* functions The new rule is - generalise a binding whose free variables have Guaranteed Closed Types - do not generalise other bindings Generally, a top-level let-bound function has a Guaranteed Closed Type, and so does a nested function whose free vaiables are top-level functions, and so on. (However a top-level function that is bitten by the Monomorphism Restriction does not have a GCT.) Example: f x = let { foo y = y } in ... Here 'foo' has no free variables, so it is generalised despite being nested. d) When inferring a type f :: ty for a definition f = e, check that the compiler would accept f :: ty as a type signature for that same definition. The type is rejected precisely when the type is ambiguous. Example: class Wob a b where to :: a -> b from :: b -> a foo x = [x, to (from x)] GHC 7.0 would infer the ambiguous type foo :: forall a b. Wob a b => b -> [b] but that type would give an error whenever it is called; and GHC 7.0 would reject that signature if given by the programmer. The new type checker rejects it up front. Similarly, with the advent of type families, ambiguous types are easy to write by mistake. See Trac #1897 and linked tickets for many examples. Eg type family F a :: * f ::: F a -> Int f x = 3 This is rejected because (F a ~ F b) does not imply a~b. Previously GHC would *infer* the above type for f, but was unable to check it. Now even the inferred type is rejected -- correctly. The main implemenation mechanism is to generalise the abe_wrap field of ABExport (in HsBinds), from [TyVar] to HsWrapper. This beautiful generalisation turned out to make everything work nicely with minimal programming effort. All the work was fiddling around the edges; the core change was easy!
-
- 03 Aug, 2011 1 commit
-
-
batterseapower authored
-
- 20 Jul, 2011 1 commit
-
-
Simon Marlow authored
being used. We now track whether a module used any TH splices in the ModIface (and at compile time in the TcGblEnv and ModGuts). If a module used TH splices last time it was compiled, then we ignore the results of the normal recompilation check and recompile anyway, *unless* the module is "stable" - that is, none of its dependencies (direct or indirect) have changed. The stability test is pretty important - otherwise ghc --make would always recompile TH modules even if nothing at all had changed, but it does require some extra plumbing to get this information from GhcMake into HscMain. test in driver/recomp009
-