- 16 Jan, 2008 1 commit
-
-
simonpj@microsoft.com authored
The core type-matcher Unify.match was previouly using tcView to expand types, because it must treat newtypes as distinct from their representation. But that meant that it also treated the PredType {C Int} as distinct from its representation type (:TC Int). And that in turn was causing a rule not to fire, because the argument types didn't match up. For this to happen we need to get a situation where we have a = :DC blah blah -- Dictionary ....(f a)..... Now a has type (:TC Int), bu the RULE for f expects an argument of type {C Int}. Roman found that just this was happening.
-
- 29 Sep, 2007 1 commit
-
-
simonpj@microsoft.com authored
The Cast case of the rule-matcher was simply wrong. This patch fixes it; see Trac #1746. I also fixed the rule generation in SpecConstr to generate a wild-card for the cast expression, which we don't want to match on. This makes the rule more widely applicable; it wasn't the cause of the bug.
-
- 04 Sep, 2007 1 commit
-
-
Ian Lynagh authored
-
- 03 Sep, 2007 1 commit
-
-
Ian Lynagh authored
Older GHCs can't parse OPTIONS_GHC. This also changes the URL referenced for the -w options from WorkingConventions#Warnings to CodingStyle#Warnings for the compiler modules.
-
- 01 Sep, 2007 1 commit
-
-
Ian Lynagh authored
-
- 04 May, 2007 1 commit
-
-
simonpj@microsoft.com authored
This fixes Trac #1251; test case is gadt/CasePrune GHC was being over-eager about pruning dead alternatives from case expressions, and that led to a crash because the case expression ended up with no alternatives at all! See the long comments Note [Pruning dead case alternatives] in Unify.
-
- 22 Apr, 2007 1 commit
-
-
simonpj@microsoft.com authored
nominolo@gmail.com pointed out (Trac #1204) that indexed data types aren't quite right. I investigated and found that the wrapper functions for indexed data types, generated in MkId, are really very confusing. In particular, we'd like these combinations to work newtype + indexed data type GADT + indexted data type The wrapper situation gets a bit complicated! I did a bit of refactoring, and improved matters, I think. I am not certain that I have gotten it right yet, but I think it's better. I'm committing it now becuase it's been on my non-backed-up laptop for a month and I want to get it into the repo. I don't think I've broken anything, but I don't regard it as 'done'.
-
- 02 Feb, 2007 1 commit
-
-
simonpj@microsoft.com authored
-
- 01 Nov, 2006 1 commit
-
-
simonpj@microsoft.com authored
-
- 11 Oct, 2006 1 commit
-
-
Simon Marlow authored
-
- 20 Sep, 2006 1 commit
-
-
chak@cse.unsw.edu.au. authored
Mon Sep 18 14:43:22 EDT 2006 Manuel M T Chakravarty <chak@cse.unsw.edu.au> * Complete the evidence generation for GADTs Sat Aug 5 21:39:51 EDT 2006 Manuel M T Chakravarty <chak@cse.unsw.edu.au> * Complete the evidence generation for GADTs Thu Jul 13 17:18:07 EDT 2006 simonpj@microsoft.com This patch completes FC evidence generation for GADTs. It doesn't work properly yet, because part of the compiler thinks (t1 :=: t2) => t3 is represented with FunTy/PredTy, while the rest thinks it's represented using ForAllTy. Once that's done things should start to work.
-
- 04 Aug, 2006 1 commit
-
-
chak@cse.unsw.edu.au. authored
Broken up massive patch -=chak Original log message: This is (sadly) all done in one patch to avoid Darcs bugs. It's not complete work... more FC stuff to come. A compiler using just this patch will fail dismally.
-
- 12 Apr, 2006 1 commit
-
-
simonpj@microsoft.com authored
Consider data T a where T1 :: T Int T2 :: T Bool T3 :: T Char f :: T Bool -> Int f x = case x of DEFAULT -> ... T2 -> 3 Here the DEFAULT case covers multiple constructors (T1,T3), but none of them can match a scrutinee of type (T Bool). So we can prune away the default case altogether. In implementing this, I re-factored this bit of the simplifier, elminiating prepareAlts from SimplUtils, and putting all the work into simplAlts in Simplify The proximate cause was a program written by Manuel using PArrays
-
- 07 Apr, 2006 1 commit
-
-
Simon Marlow authored
Most of the other users of the fptools build system have migrated to Cabal, and with the move to darcs we can now flatten the source tree without losing history, so here goes. The main change is that the ghc/ subdir is gone, and most of what it contained is now at the top level. The build system now makes no pretense at being multi-project, it is just the GHC build system. No doubt this will break many things, and there will be a period of instability while we fix the dependencies. A straightforward build should work, but I haven't yet fixed binary/source distributions. Changes to the Building Guide will follow, too.
-
- 08 Feb, 2006 1 commit
-
-
simonpj@microsoft.com authored
This commit fixes a bug in 6.4.1 and the HEAD. Consider this code, recorded **in an interface file** \(x::a) -> case y of MkT -> case x of { True -> ... } (where MkT forces a=Bool) In the "case x" we need to know x's type, because we use that to find which module to look for "True" in. x's type comes from the envt, so we must refine the envt. The alternative would be to record more info with an IfaceCase, but that would change the interface file format. (This stuff will go away when we have proper coercions.)
-
- 25 Jan, 2006 1 commit
-
-
simonpj@microsoft.com authored
This very large commit adds impredicativity to GHC, plus numerous other small things. *** WARNING: I have compiled all the libraries, and *** a stage-2 compiler, and everything seems *** fine. But don't grab this patch if you *** can't tolerate a hiccup if something is *** broken. The big picture is this: a) GHC handles impredicative polymorphism, as described in the "Boxy types: type inference for higher-rank types and impredicativity" paper b) GHC handles GADTs in the new simplified (and very sligtly less epxrssive) way described in the "Simple unification-based type inference for GADTs" paper But there are lots of smaller changes, and since it was pre-Darcs they are not individually recorded. Some things to watch out for: c) The story on lexically-scoped type variables has changed, as per my email. I append the story below for completeness, but I am still not happy with it, and it may change again. In particular, the new story does not allow a pattern-bound scoped type variable to be wobbly, so (\(x::[a]) -> ...) is usually rejected. This is more restrictive than before, and we might loosen up again. d) A consequence of adding impredicativity is that GHC is a bit less gung ho about converting automatically between (ty1 -> forall a. ty2) and (forall a. ty1 -> ty2) In particular, you may need to eta-expand some functions to make typechecking work again. Furthermore, functions are now invariant in their argument types, rather than being contravariant. Again, the main consequence is that you may occasionally need to eta-expand function arguments when using higher-rank polymorphism. Please test, and let me know of any hiccups Scoped type variables in GHC ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ January 2006 0) Terminology. A *pattern binding* is of the form pat = rhs A *function binding* is of the form f pat1 .. patn = rhs A binding of the formm var = rhs is treated as a (degenerate) *function binding*. A *declaration type signature* is a separate type signature for a let-bound or where-bound variable: f :: Int -> Int A *pattern type signature* is a signature in a pattern: \(x::a) -> x f (x::a) = x A *result type signature* is a signature on the result of a function definition: f :: forall a. [a] -> a head (x:xs) :: a = x The form x :: a = rhs is treated as a (degnerate) function binding with a result type signature, not as a pattern binding. 1) The main invariants: A) A lexically-scoped type variable always names a (rigid) type variable (not an arbitrary type). THIS IS A CHANGE. Previously, a scoped type variable named an arbitrary *type*. B) A type signature always describes a rigid type (since its free (scoped) type variables name rigid type variables). This is also a change, a consequence of (A). C) Distinct lexically-scoped type variables name distinct rigid type variables. This choice is open; 2) Scoping 2(a) If a declaration type signature has an explicit forall, those type variables are brought into scope in the right hand side of the corresponding binding (plus, for function bindings, the patterns on the LHS). f :: forall a. a -> [a] f (x::a) = [x :: a, x] Both occurences of 'a' in the second line are bound by the 'forall a' in the first line A declaration type signature *without* an explicit top-level forall is implicitly quantified over all the type variables that are mentioned in the type but not already in scope. GHC's current rule is that this implicit quantification does *not* bring into scope any new scoped type variables. f :: a -> a f x = ...('a' is not in scope here)... This gives compatibility with Haskell 98 2(b) A pattern type signature implicitly brings into scope any type variables mentioned in the type that are not already into scope. These are called *pattern-bound type variables*. g :: a -> a -> [a] g (x::a) (y::a) = [y :: a, x] The pattern type signature (x::a) brings 'a' into scope. The 'a' in the pattern (y::a) is bound, as is the occurrence on the RHS. A pattern type siganture is the only way you can bring existentials into scope. data T where MkT :: forall a. a -> (a->Int) -> T f x = case x of MkT (x::a) f -> f (x::a) 2a) QUESTION class C a where op :: forall b. b->a->a instance C (T p q) where op = <rhs> Clearly p,q are in scope in <rhs>, but is 'b'? Not at the moment. Nor can you add a type signature for op in the instance decl. You'd have to say this: instance C (T p q) where op = let op' :: forall b. ... op' = <rhs> in op' 3) A pattern-bound type variable is allowed only if the pattern's expected type is rigid. Otherwise we don't know exactly *which* skolem the scoped type variable should be bound to, and that means we can't do GADT refinement. This is invariant (A), and it is a big change from the current situation. f (x::a) = x -- NO; pattern type is wobbly g1 :: b -> b g1 (x::b) = x -- YES, because the pattern type is rigid g2 :: b -> b g2 (x::c) = x -- YES, same reason h :: forall b. b -> b h (x::b) = x -- YES, but the inner b is bound k :: forall b. b -> b k (x::c) = x -- NO, it can't be both b and c 3a) You cannot give different names for the same type variable in the same scope (Invariant (C)): f1 :: p -> p -> p -- NO; because 'a' and 'b' would be f1 (x::a) (y::b) = (x::a) -- bound to the same type variable f2 :: p -> p -> p -- OK; 'a' is bound to the type variable f2 (x::a) (y::a) = (x::a) -- over which f2 is quantified -- NB: 'p' is not lexically scoped f3 :: forall p. p -> p -> p -- NO: 'p' is now scoped, and is bound to f3 (x::a) (y::a) = (x::a) -- to the same type varialble as 'a' f4 :: forall p. p -> p -> p -- OK: 'p' is now scoped, and its occurences f4 (x::p) (y::p) = (x::p) -- in the patterns are bound by the forall 3b) You can give a different name to the same type variable in different disjoint scopes, just as you can (if you want) give diferent names to the same value parameter g :: a -> Bool -> Maybe a g (x::p) True = Just x :: Maybe p g (y::q) False = Nothing :: Maybe q 3c) Scoped type variables respect alpha renaming. For example, function f2 from (3a) above could also be written: f2' :: p -> p -> p f2' (x::b) (y::b) = x::b where the scoped type variable is called 'b' instead of 'a'. 4) Result type signatures obey the same rules as pattern types signatures. In particular, they can bind a type variable only if the result type is rigid f x :: a = x -- NO g :: b -> b g x :: b = x -- YES; binds b in rhs 5) A *pattern type signature* in a *pattern binding* cannot bind a scoped type variable (x::a, y) = ... -- Legal only if 'a' is already in scope Reason: in type checking, the "expected type" of the LHS pattern is always wobbly, so we can't bind a rigid type variable. (The exception would be for an existential type variable, but existentials are not allowed in pattern bindings either.) Even this is illegal f :: forall a. a -> a f x = let ((y::b)::a, z) = ... in Here it looks as if 'b' might get a rigid binding; but you can't bind it to the same skolem as a. 6) Explicitly-forall'd type variables in the *declaration type signature(s)* for a *pattern binding* do not scope AT ALL. x :: forall a. a->a -- NO; the forall a does Just (x::a->a) = Just id -- not scope at all y :: forall a. a->a Just y = Just (id :: a->a) -- NO; same reason THIS IS A CHANGE, but one I bet that very few people will notice. Here's why: strange :: forall b. (b->b,b->b) strange = (id,id) x1 :: forall a. a->a y1 :: forall b. b->b (x1,y1) = strange This is legal Haskell 98 (modulo the forall). If both 'a' and 'b' both scoped over the RHS, they'd get unified and so cannot stand for distinct type variables. One could *imagine* allowing this: x2 :: forall a. a->a y2 :: forall a. a->a (x2,y2) = strange using the very same type variable 'a' in both signatures, so that a single 'a' scopes over the RHS. That seems defensible, but odd, because though there are two type signatures, they introduce just *one* scoped type variable, a. 7) Possible extension. We might consider allowing \(x :: [ _ ]) -> <expr> where "_" is a wild card, to mean "x has type list of something", without naming the something.
-
- 16 Nov, 2005 1 commit
-
-
simonpj authored
Two significant changes to the representation of types 1. Change the representation of type synonyms Up to now, type synonym applications have been held in *both* expanded *and* un-expanded form. Unfortunately, this has exponential (!) behaviour when type synonyms are deeply nested. E.g. type P a b = (a,b) f :: P a (P b (P c (P d e))) This showed up in a program of Joel Reymont, now immortalised as typecheck/should_compile/syn-perf.hs So now synonyms are held as ordinary TyConApps, and expanded only on demand. SynNote has disappeared altogether, so the only remaining TyNote is a FTVNote. I'm not sure if it's even useful. 2. Eta-reduce newtypes See the Note [Newtype eta] in TyCon.lhs If we have newtype T a b = MkT (S a b) then, in Core land, we would like S = T, even though the application of T is then not saturated. This commit eta-reduces T's RHS, and keeps that inside the TyCon (in nt_etad_rhs). Result is that coreEqType can be simpler, and has less need of expanding newtypes.
-
- 14 Oct, 2005 1 commit
-
-
simonpj authored
Add record syntax for GADTs ~~~~~~~~~~~~~~~~~~~~~~~~~~~ Atrijus Tang wanted to add record syntax for GADTs and existential types, so he and I worked on it a bit at ICFP. This commit is the result. Now you can say data T a where T1 { x :: a } :: T [a] T2 { x :: a, y :: Int } :: T [a] forall b. Show b => T3 { naughty :: b, ok :: Int } :: T Int T4 :: Eq a => a -> b -> T (a,b) Here the constructors are declared using record syntax. Still to come after this commit: - User manual documentation - More regression tests - Some missing cases in the parser (e.g. T3 won't parse) Autrijus is going to do these. Here's a quick summary of the rules. (Atrijus is going to write proper documentation shortly.) Defnition: a 'vanilla' constructor has a type of the form forall a1..an. t1 -> ... -> tm -> T a1 ... an No existentials, no context, nothing. A constructor declared with Haskell-98 syntax is vanilla by construction. A constructor declared with GADT-style syntax is vanilla iff its type looks like the above. (In the latter case, the order of the type variables does not matter.) * You can mix record syntax and non-record syntax in a single decl * All constructors that share a common field 'x' must have the same result type (T [a] in the example). * You can use field names without restriction in record construction and record pattern matching. * Record *update* only works for data types that only have 'vanilla' constructors. * Consider the field 'naughty', which uses a type variable that does not appear in the result type ('b' in the example). You can use the field 'naughty' in pattern matching and construction, but NO SELECTOR function is generated for 'naughty'. [An attempt to use 'naughty' as a selector function will elicit a helpful error message.] * Data types declared in GADT syntax cannot have a context. So this is illegal: data (Monad m) => T a where .... * Constructors in GADT syntax can have a context (t.g. T3, T4 above) and that context is stored in the constructor and made available when the constructor is pattern-matched on. WARNING: not competely implemented yet, but that's the plan. Implementation notes ~~~~~~~~~~~~~~~~~~~~ - Data constructors (even vanilla ones) no longer share the type variables of their parent type constructor. - HsDecls.ConDecl has changed quite a bit - TyCons don't record the field labels and type any more (doesn't make sense for existential fields) - GlobalIdDetails records which selectors are 'naughty', and hence don't have real code.
-
- 27 Jun, 2005 1 commit
-
-
simonpj authored
MERGE TO STABLE Fix a typechecker bug, which made the typechecker loop under certain circumstances, notably when we have type Foo a = a and try to unify b :=: Foo b typecheck/should_compile/tc195 tests this case now.
-
- 31 Jan, 2005 1 commit
-
-
simonpj authored
--------------------------- Types and evaluated-ness in CoreTidy and CorePrep --------------------------- This commmit fixes two problems. 1. DataToTagOp requires its argument to be evaluated, otherwise it silently gives the wrong answer. This was not happening because we had case (tag2Enum x) of y -> ...(dataToTag y)... and the tag2Enum was being inlined (it's non-speculative), giving ...(dataToTag (tag2Enum x))... Rather than relying on a somewhat-delicate global invariant, CorePrep now establishes the invariant that DataToTagOp's argument is evaluated. It does so by putting up-to-date is-evaluated information into each binder's UnfoldingInfo; not a full unfolding, just the (OtherCon []) for evaluated binders. Then there's a special case for DataToTag where applications are dealt with. Finally, we make DataToTagOp strict, which it really is. 2. CoreTidy now does GADT refinement as it goes. This is important to ensure that each variable occurrence has informative type information, which in turn is essential to make exprType work (otherwise it can simply crash). [This happened in test gadt/tdpe] CorePrep has the same problem, but the solution is a little different: when looking up in the cloning environment, use the type at the occurrence site if we're inside a GADT. It might be cleaner to use the same story as CoreTidy, but then we'd need to keep an in-scope set for type variables. No big deal either way.
-
- 05 Jan, 2005 1 commit
-
-
simonpj authored
------------------------ GADTs and unification ------------------------ 1. Adjustment to typechecking of pattern matching the call to gadtRefineTys in TcPat. Now wobbly types are treated as wild cards in the unification process. 2. Add the WildCard possibility to the BindFlag in types/Unify.lhs 3. Some related refactoring of tcMatchTys etc.
-
- 30 Dec, 2004 1 commit
-
-
simonpj authored
Fix to the pre-Xmas simplifier changes, which should make everything work again. I'd forgotten to attend to this corner. Still not properly tested I fear. Also remove dead code from SimplEnv, and simplify the remainder (hooray).
-
- 22 Dec, 2004 1 commit
-
-
simonpj authored
---------------------------------------- Add more scoped type variables ---------------------------------------- Now the top-level forall'd variables of a type signature scope over the right hand side of that function. f :: a -> a f x = .... The type variable 'a' is in scope in the RHS, and in f's patterns. It's implied by -fglasgow-exts, but can also be switched off independently using -fscoped-type-variables (and the -fno variant)
-
- 21 Dec, 2004 2 commits
-
-
simonpj authored
--------------------------------- Improve handling of lexically scoped type variables --------------------------------- If we have f :: T a -> a f (x :: T b) = ... then the lexically scoped variable 'b' should refer to the rigid type variable 'a', without any intervening wobbliness. Previously the in-scope type variables were always mutable TyVars, which were instantatiated to point to the type they were bound to; but since the advent of GADTs the intervening mutable type variable is a bad thing. Hence * In the type environment, ATyVar now carries a type * The call to refineTyVars in tc_pat on SigPatIn finds the types by matching * Then tcExtendTyVarEnv3 extends the type envt appropriately Rater a lot of huff and puff, but it's quite natural for ATyVar to contain a type. Various other small nomenclature changes along the way.
-
simonpj authored
Add missing NoteTy cases to unify_
-
- 20 Dec, 2004 1 commit
-
-
simonpj authored
-------------------------------- Deal properly with dual-renaming -------------------------------- When comparing types and terms, and during matching, we are faced with \x.e1 ~ \y.e2 There are many pitfalls here, and GHC has never done the job properly. Now, at last it does, using a new abstraction VarEnv.RnEnv2. See comments there for how it works. There are lots of consequential changes to use the new stuff, especially in types/Type (type comparison), types/Unify (matching on types) coreSyn/CoreUtils (equality on expressions), specialise/Rules (matching). I'm not 100% certain of that I've covered all the bases, so let me know if something unexpected happens after you update. Maybe wait until a nightly build has worked ok first!
-
- 01 Oct, 2004 1 commit
-
-
simonpj authored
------------------------------------ Simplify the treatment of newtypes Complete hi-boot file consistency checking ------------------------------------ In the representation of types, newtypes used to have a special constructor all to themselves, very like TyConApp, called NewTcApp. The trouble is that means we have to *know* when a newtype is a newtype, and in an hi-boot context we may not -- the data type might be declared as data T in the hi-boot file, but as newtype T = ... in the source file. In GHCi, which accumulates stuff from multiple compiles, this makes a difference. So I've nuked NewTcApp. Newtypes are represented using TyConApps again. This turned out to reduce the total amount of code, and simplify the Type data type, which is all to the good. This commit also fixes a few things in the hi-boot consistency checking stuff.
-
- 30 Sep, 2004 1 commit
-
-
simonpj authored
------------------------------------ Add Generalised Algebraic Data Types ------------------------------------ This rather big commit adds support for GADTs. For example, data Term a where Lit :: Int -> Term Int App :: Term (a->b) -> Term a -> Term b If :: Term Bool -> Term a -> Term a ..etc.. eval :: Term a -> a eval (Lit i) = i eval (App a b) = eval a (eval b) eval (If p q r) | eval p = eval q | otherwise = eval r Lots and lots of of related changes throughout the compiler to make this fit nicely. One important change, only loosely related to GADTs, is that skolem constants in the typechecker are genuinely immutable and constant, so we often get better error messages from the type checker. See TcType.TcTyVarDetails. There's a new module types/Unify.lhs, which has purely-functional unification and matching for Type. This is used both in the typechecker (for type refinement of GADTs) and in Core Lint (also for type refinement).
-
- 25 Jun, 2001 1 commit
-
-
simonpj authored
---------------- Squash newtypes ---------------- This commit squashes newtypes and their coerces, from the typechecker onwards. The original idea was that the coerces would not get in the way of optimising transformations, but despite much effort they continue to do so. There's no very good reason to retain newtype information beyond the typechecker, so now we don't. Main points: * The post-typechecker suite of Type-manipulating functions is in types/Type.lhs, as before. But now there's a new suite in types/TcType.lhs. The difference is that in the former, newtype are transparent, while in the latter they are opaque. The typechecker should only import TcType, not Type. * The operations in TcType are all non-monadic, and most of them start with "tc" (e.g. tcSplitTyConApp). All the monadic operations (used exclusively by the typechecker) are in a new module, typecheck/TcMType.lhs * I've grouped newtypes with predicate types, thus: data Type = TyVarTy Tyvar | .... | SourceTy SourceType data SourceType = NType TyCon [Type] | ClassP Class [Type] | IParam Type [SourceType was called PredType.] This is a little wierd in some ways, because NTypes can't occur in qualified types. However, the idea is that a SourceType is a type that is opaque to the type checker, but transparent to the rest of the compiler, and newtypes fit that as do implicit parameters and dictionaries. * Recursive newtypes still retain their coreces, exactly as before. If they were transparent we'd get a recursive type, and that would make various bits of the compiler diverge (e.g. things which do type comparison). * I've removed types/Unify.lhs (non-monadic type unifier and matcher), merging it into TcType. Ditto typecheck/TcUnify.lhs (monadic unifier), merging it into TcMType.
-
- 30 Jan, 2001 1 commit
-
-
simonpj authored
More on functional dependencies My last commit allowed this: instance C a b => C [a] [b] where ... if we have class C a b | a -> b This commit completes the change, by making the improvement stages improve only the 'shape' of the second argument of C. I also had to change the iteration in TcSimplify -- see the comments in TcSimplify.inferLoop.
-
- 25 Jan, 2001 1 commit
-
-
simonpj authored
------------------------------------ Mainly FunDeps (23 Jan 01) ------------------------------------ This commit re-engineers the handling of functional dependencies. A functional dependency is no longer an Inst; instead, the necessary dependencies are snaffled out of their Class when necessary. As part of this exercise I found that I had to re-work how to do generalisation in a binding group. There is rather exhaustive documentation on the new Plan at the top of TcSimplify. ****************** WARNING: I have compiled all the libraries with this new compiler and all looks well, but I have not run many programs. Things may break. Let me know if so. ****************** The main changes are these: 1. typecheck/TcBinds and TcSimplify have a lot of changes due to the new generalisation and context reduction story. There are extensive comments at the start of TcSimplify 2. typecheck/TcImprove is removed altogether. Instead, improvement is interleaved with context reduction (until a fixpoint is reached). All this is done in TcSimplify. 3. types/FunDeps has new exports * 'improve' does improvement, returning a list of equations * 'grow' and 'oclose' close a list of type variables wrt a set of PredTypes, but in slightly different ways. Comments in file. 4. I improved the way in which we check that main::IO t. It's tidier now. In addition * typecheck/TcMatches: a) Tidy up, introducing a common function tcCheckExistentialPat b) Improve the typechecking of parallel list comprehensions, which wasn't quite right before. (see comments with tcStmts) WARNING: (b) is untested! Jeff, you might want to check. * Numerous other incidental changes in the typechecker * Manuel found that rules don't fire well when you have partial applications from overloading. For example, we may get f a (d::Ord a) = let m_g = g a d in \y :: a -> ...(m_g (h y))... The 'method' m_g doesn't get inlined because (g a d) might be a redex. Yet a rule that looks like g a d (h y) = ... won't fire because that doesn't show up. One way out would be to make the rule matcher a bit less paranoid about duplicating work, but instead I've added a flag -fno-method-sharing which controls whether we generate things like m_g in the first place. It's not clear that they are a win in the first place. The flag is actually consulted in Inst.tcInstId
-
- 07 Nov, 2000 1 commit
-
-
simonmar authored
This commit completes the merge of compiler part of the HEAD with the before-ghci-branch to before-ghci-branch-merged.
-
- 23 Oct, 2000 1 commit
-
-
simonpj authored
Mainly renamer
-
- 14 Jul, 2000 1 commit
-
-
simonpj authored
This commit completely re-does the kind-inference mechanism. Previously it was inter-wound with type inference, but that was always hard to understand, and it finally broke when we started checking for ambiguity when type-checking a type signature (details irrelevant). So now kind inference is more clearly separated, so that it never takes place at the same time as type inference. The biggest change is in TcTyClsDecls, which does the kind inference for a group of type and class declarations. It now contains comments to explain how it all works. There are also comments in TypeRep which describes the slightly tricky way in which we deal with the fact that kind 'type' (written '*') actually has 'boxed type' and 'unboxed type' as sub-kinds. The whole thing is a bit of a hack, because we don't really have sub-kinding, but it's less of a hack than before. A lot of general tidying up happened at the same time. In particular, I removed some dead code here and there
-
- 11 Jul, 2000 1 commit
-
-
simonmar authored
remove unused imports
-
- 27 Mar, 2000 1 commit
-
-
simonpj authored
Fix a bug in import listing in interface files that meant we lost track of interface files. This fixes the problem that led Sven to add lots of import PprType() decls. I've removed them all again!
-
- 15 Jul, 1999 1 commit
-
-
keithw authored
This commit makes a start at implementing polymorphic usage annotations. * The module Type has now been split into TypeRep, containing the representation Type(..) and other information for `friends' only, and Type, providing the public interface to Type. Due to a bug in the interface-file slurping prior to ghc-4.04, {-# SOURCE #-} dependencies must unfortunately still refer to TypeRep even though they are not friends. * Unfoldings in interface files now print as __U instead of __u. UpdateInfo now prints as __UA instead of __U. * A new sort of variables, UVar, in their own namespace, uvName, has been introduced for usage variables. * Usage binders __fuall uv have been introduced. Usage annotations are now __u - ty (used once), __u ! ty (used possibly many times), __u uv ty (used uv times), where uv is a UVar. __o and __m have gone. All this still lives only in a TyNote, *for now* (but not for much longer). * Variance calculation for TyCons has moved from typecheck/TcTyClsDecls to types/Variance. * Usage annotation and inference are now done together in a single pass. Provision has been made for inferring polymorphic usage annotations (with __fuall) but this has not yet been implemented. Watch this space!
-
- 18 May, 1999 1 commit
-
-
simonpj authored
RULES-NOTES
-
- 18 Dec, 1998 1 commit
-
-
simonpj authored
Another big commit from Simon. Actually, the last one didn't all go into the main trunk; because of a CVS glitch it ended up in the wrong branch. So this commit includes: * Scoped type variables * Warnings for unused variables should work now (they didn't before) * Simplifier improvements: - Much better treatment of strict arguments - Better treatment of bottoming Ids - No need for w/w split for fns that are merely strict - Fewer iterations needed, I hope * Less gratuitous renaming in interface files and abs C * OccName is a separate module, and is an abstract data type I think the whole Prelude and Exts libraries compile correctly. Something isn't quite right about typechecking existentials though.
-
- 02 Dec, 1998 1 commit
-
-
simonm authored
Move 4.01 onto the main trunk.
-