- 11 Aug, 2005 1 commit
-
-
simonpj authored
Further wibbles to moving dependency analysis back to renamer; fixes ghci failures
-
- 10 Aug, 2005 1 commit
-
-
simonpj authored
It turned out that doing all binding dependency analysis in the typechecker meant that the renamer's unused-binding error messages got worse. So now I've put the first dep anal back into the renamer, while the second (which is specific to type checking) remains in the type checker. I've also made the pretty printer sort the decls back into source order before printing them (except with -dppr-debug). Fixes rn041.
-
- 25 Jul, 2005 1 commit
-
-
simonpj authored
Better error recovery for type signatures
-
- 22 Jul, 2005 1 commit
-
-
simonpj authored
Do refined dependency analysis in typechecking only with -fglasgow-exts
-
- 19 Jul, 2005 1 commit
-
-
simonpj authored
WARNING: this is a big commit. You might want to wait a few days before updating, in case I've broken something. However, if any of the changes are what you wanted, please check it out and test! This commit does three main things: 1. A re-organisation of the way that GHC handles bindings in HsSyn. This has been a bit of a mess for quite a while. The key new types are -- Bindings for a let or where clause data HsLocalBinds id = HsValBinds (HsValBinds id) | HsIPBinds (HsIPBinds id) | EmptyLocalBinds -- Value bindings (not implicit parameters) data HsValBinds id = ValBindsIn -- Before typechecking (LHsBinds id) [LSig id] -- Not dependency analysed -- Recursive by default | ValBindsOut -- After typechecking [(RecFlag, LHsBinds id)]-- Dependency analysed 2. Implement Mark Jones's idea of increasing polymoprhism by using type signatures to cut the strongly-connected components of a recursive group. As a consequence, GHC no longer insists on the contexts of the type signatures of a recursive group being identical. This drove a significant change: the renamer no longer does dependency analysis. Instead, it attaches a free-variable set to each binding, so that the type checker can do the dep anal. Reason: the typechecker needs to do *two* analyses: one to find the true mutually-recursive groups (which we need so we can build the right CoreSyn) one to find the groups in which to typecheck, taking account of type signatures 3. Implement non-ground SPECIALISE pragmas, as promised, and as requested by Remi and Ross. Certainly, this should fix the current problem with GHC, namely that if you have g :: Eq a => a -> b -> b then you can now specialise thus SPECIALISE g :: Int -> b -> b (This didn't use to work.) However, it goes further than that. For example: f :: (Eq a, Ix b) => a -> b -> b then you can make a partial specialisation SPECIALISE f :: (Eq a) => a -> Int -> Int In principle, you can specialise f to *any* type that is "less polymorphic" (in the sense of subsumption) than f's actual type. Such as SPECIALISE f :: Eq a => [a] -> Int -> Int But I haven't tested that. I implemented this by doing the specialisation in the typechecker and desugarer, rather than leaving around the strange SpecPragmaIds, for the specialiser to find. Indeed, SpecPragmaIds have vanished altogether (hooray). Pragmas in general are handled more tidily. There's a new data type HsBinds.Prag, which lives in an AbsBinds, and carries pragma info from the typechecker to the desugarer. Smaller things - The loop in the renamer goes via RnExpr, instead of RnSource. (That makes it more like the type checker.) - I fixed the thing that was causing 'check_tc' warnings to be emitted.
-
- 12 Jul, 2005 1 commit
-
-
simonpj authored
Check for an unboxed tuple binding f = (# True, False #) A fairly recent change, that treats specially non-recursive bindings of a single variable, failed to take this into account. tcfail141 tests this case. (Was simpl008.) -
-
- 26 May, 2005 1 commit
-
-
simonpj authored
MERGE TO STABLE Put back in a missing case for higher-rank types. When the definition is a) non-recursive b) a function binding c) lacks a type signature we want to *infer* a perhaps-higher-rank type for the RHS, before making a monomorphically-typed Id for the LHS. E.g. f = \(x :: forall a. a->a) -> (x True, x 'c') This case got lost in the transition to 6.4 tc194 tests it
-
- 03 May, 2005 1 commit
-
-
simonpj authored
Check for illegal declarations in hs-boot files
-
- 15 Apr, 2005 1 commit
-
-
simonpj authored
Be consistent about quotes in error messages; MERGE TO STABLE
-
- 18 Mar, 2005 1 commit
-
-
simonmar authored
Flags cleanup. Basically the purpose of this commit is to move more of the compiler's global state into DynFlags, which is moving in the direction we need to go for the GHC API which can have multiple active sessions supported by a single GHC instance. Before: $ grep 'global_var' */*hs | wc -l 78 After: $ grep 'global_var' */*hs | wc -l 27 Well, it's an improvement. Most of what's left won't really affect our ability to host multiple sessions. Lots of static flags have become dynamic flags (yay!). Notably lots of flags that we used to think of as "driver" flags, like -I and -L, are now dynamic. The most notable static flags left behind are the "way" flags, eg. -prof. It would be nice to fix this, but it isn't urgent. On the way, lots of cleanup has happened. Everything related to static and dynamic flags lives in StaticFlags and DynFlags respectively, and they share a common command-line parser library in CmdLineParser. The flags related to modes (--makde, --interactive etc.) are now private to the front end: in fact private to Main itself, for now.
-
- 17 Mar, 2005 1 commit
-
-
simonpj authored
Buglet in compiling hs-boot files We should make GlobalIds not LocalIds Merge to STABLE
-
- 07 Mar, 2005 1 commit
-
-
simonpj authored
----------------------------------------- Fix scoping bug for quantified type variables ----------------------------------------- Merge to STABLE When instantiating a declaration type signature, make sure to instantiate fresh names for non-scoped type variables, else they may be spuriously shared. Turns out that the test lib/Generics/reify tests this, which is good. Comments are with TcMType.tcInstSigType
-
- 01 Mar, 2005 1 commit
-
-
simonpj authored
Type signatures and skolem constants (again) Merge to STABLE This commit lays to rest the vexed question of skolem constants and type signatures. My fix last week made type-signature variables into ordinary meta type variables, because they can be unified together (see Note [Signature skolems] in TcType). But that was wrong becuase GADTs will only refine skolems. So this commit extends TcTyVarDetails with a new constructors, SigSkolTv, which is a skolem (like SkolemTv) but is unifiable (like MetaTv). It's a bit of a hack, but the code came out quite nicely. Now the GADT tests work.
-
- 25 Feb, 2005 1 commit
-
-
simonpj authored
--------------------------------------------- Type signatures are no longer instantiated with skolem constants --------------------------------------------- Merge to STABLE Consider p :: a q :: b (p,q,r) = (r,r,p) Here, 'a' and 'b' end up being the same, because they are both bound to the type for 'r', which is just a meta type variable. So 'a' and 'b' can't be skolems. Sigh. This commit goes back to an earlier way of doing things, by arranging that type signatures get instantiated with *meta* type variables; then at the end we must check that they have not been unified with types, nor with each other. This is a real bore. I had to do quite a bit of related fiddling around to make error messages come out right. Improved one or two. Also a small unrelated fix to make :i (:+) print with parens in ghci. Sorry this got mixed up in the same commit.
-
- 04 Feb, 2005 1 commit
-
-
simonpj authored
------------------------------------------------------ Report top-level implicit parameter errors more nicely ------------------------------------------------------ Consider module Main where main = let ?x = 5 in print foo foo = woggle 3 woggle :: (?x :: Int) => Int -> Int woggle y = ?x + y GHC's current rules say that 'foo' is monomorphic, so we get foo :: Int but we also get an unbound top-level constraint (?x::Int). GHC 6.2 emits a message like: Unbound implicit parameter (?x::Int) arising from use of `woggle' at ... The point is that THERE IS NO WAY FOR THIS CONSTRAINT TO GET BOUND, because we don't have a top-level binding form for implicit parameters. So it's stupid for 'foo' to be monomorphic. This commit improves matters by giving a much nicer error message: Implicit parameters escape from the monomorphic top-level binding(s) of `foo': ?x::Int arising from use of `woggle' at tcfail130.hs:10:6-11 Probably fix: add type signatures for the top-level binding(s) When generalising the type(s) for `foo'
-
- 31 Jan, 2005 1 commit
-
-
simonpj authored
Rename mkTvSubst to mkOpenTvSubst; add new mkTvSubst
-
- 27 Jan, 2005 1 commit
-
-
simonpj authored
-------------------------------------------- Replace hi-boot files with hs-boot files -------------------------------------------- This major commit completely re-organises the way that recursive modules are dealt with. * It should have NO EFFECT if you do not use recursive modules * It is a BREAKING CHANGE if you do ====== Warning: .hi-file format has changed, so if you are ====== updating into an existing HEAD build, you'll ====== need to make clean and re-make The details: [documentation still to be done] * Recursive loops are now broken with Foo.hs-boot (or Foo.lhs-boot), not Foo.hi-boot * An hs-boot files is a proper source file. It is compiled just like a regular Haskell source file: ghc Foo.hs generates Foo.hi, Foo.o ghc Foo.hs-boot generates Foo.hi-boot, Foo.o-boot * hs-boot files are precisely a subset of Haskell. In particular: - they have the same import, export, and scoping rules - errors (such as kind errors) in hs-boot files are checked You do *not* need to mention the "original" name of something in an hs-boot file, any more than you do in any other Haskell module. * The Foo.hi-boot file generated by compiling Foo.hs-boot is a machine- generated interface file, in precisely the same format as Foo.hi * When compiling Foo.hs, its exports are checked for compatibility with Foo.hi-boot (previously generated by compiling Foo.hs-boot) * The dependency analyser (ghc -M) knows about Foo.hs-boot files, and generates appropriate dependencies. For regular source files it generates Foo.o : Foo.hs Foo.o : Baz.hi -- Foo.hs imports Baz Foo.o : Bog.hi-boot -- Foo.hs source-imports Bog For a hs-boot file it generates similar dependencies Bog.o-boot : Bog.hs-boot Bog.o-boot : Nib.hi -- Bog.hs-boto imports Nib * ghc -M is also enhanced to use the compilation manager dependency chasing, so that ghc -M Main will usually do the job. No need to enumerate all the source files. * The -c flag is no longer a "compiler mode". It simply means "omit the link step", and synonymous with -no-link.
-
- 24 Dec, 2004 1 commit
-
-
simonpj authored
Further wibbles to the scoped-tyvar story. This commit tidies up the ATyVar in TcTyThing, making it ATyVar Name Type instead of the previous misleading ATyVar TyVar Type But the main thing is that we must take care with definitions like this: type T a = forall b. b -> (a,b) f :: forall c. T c f = ... Here, we want only 'c' to scope over the RHS of f. The renamer ensures that... but we must also take care that we freshly instantiate the expanded type signature (forall c b. b -> (c,b)) before checking f's RHS, so that we don't get false sharing between uses of T.
-
- 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)
-
- 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!
-
- 02 Dec, 2004 1 commit
-
-
simonpj authored
Sorry for the fact that there are overlapping three commits in here... 1. Make -fno-monomorphism-restriction and -fno-implicit-prelude reversible, like other flags 2. Fix a wibble in the new ImportAvails story, in RnNames.mkExportAvails 3. Fix a Template Haskell bug that meant that top-level names created with newName were not made properly unique.
-
- 11 Nov, 2004 1 commit
-
-
simonpj authored
--------------------------------- Buglet in the handling of unlifted bindings --------------------------------- Unlifted bindings, like let I# v = ... in ... can't be generalised. In teh transition to GADTs I introduced a bug that accidentally discarded some necessary dictionary bindings. This commit fixes it by moving the test for unlifted bindings to a much earlier point in tcBindWithSigs, which seems a lot cleaner to me.
-
- 01 Oct, 2004 1 commit
-
-
panne authored
Layout rule again...
-
- 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).
-
- 19 Jul, 2004 1 commit
-
-
simonpj authored
Comments only
-
- 06 May, 2004 1 commit
-
-
simonpj authored
Better location info
-
- 30 Dec, 2003 1 commit
-
-
simonpj authored
---------------------------- Re-do kind inference (again) ---------------------------- [WARNING: interface file binary representation has (as usual) changed slightly; recompile your libraries!] Inspired by the lambda-cube, for some time GHC has used type Kind = Type That is, kinds were represented by the same data type as types. But GHC also supports unboxed types and unboxed tuples, and these complicate the kind system by requiring a sub-kind relationship. Notably, an unboxed tuple is acceptable as the *result* of a function but not as an *argument*. So we have the following setup: ? / \ / \ ?? (#) / \ * # where * [LiftedTypeKind] means a lifted type # [UnliftedTypeKind] means an unlifted type (#) [UbxTupleKind] means unboxed tuple ?? [ArgTypeKind] is the lub of *,# ? [OpenTypeKind] means any type at all In particular: error :: forall a:?. String -> a (->) :: ?? -> ? -> * (\(x::t) -> ...) Here t::?? (i.e. not unboxed tuple) All this has beome rather difficult to accommodate with Kind=Type, so this commit splits the two. * Kind is a distinct type, defined in types/Kind.lhs * IfaceType.IfaceKind disappears: we just re-use Kind.Kind * TcUnify.unifyKind is a distinct unifier for kinds * TyCon no longer needs KindCon and SuperKindCon variants * TcUnify.zapExpectedType takes an expected Kind now, so that in TcPat.tcMonoPatBndr we can express that the bound variable must have an argTypeKind (??). The big change is really that kind inference is much more systematic and well behaved. In particular, a kind variable can unify only with a "simple kind", which is built from * and (->). This deals neatly with awkward questions about how we can combine sub-kinding with type inference. Lots of small consequential changes, especially to the kind-checking plumbing in TcTyClsDecls. (We played a bit fast and loose before, and now we have to be more honest, in particular about how kind inference works for type synonyms. They can have kinds like (* -> #), so This cures two long-standing SourceForge bugs * 753777 (tcfail115.hs), which used erroneously to pass, but crashed in the code generator type T a = Int -> (# Int, Int #) f :: T a -> T a f t = \x -> case t x of r -> r * 753780 (tc167.hs), which used erroneously to fail f :: (->) Int# Int# Still, the result is not entirely satisfactory. In particular * The error message from tcfail115 is pretty obscure * SourceForge bug 807249 (Instance match failure on openTypeKind) is not fixed. Alas.
-
- 17 Dec, 2003 1 commit
-
-
simonpj authored
----------------------------------------------------- Fix a subtle loop in the context-reduction machinery ---------------------------------------------------- This bug was provoked by a recent change: when trying to prove a constraint C, TcSimplify.reduce now adds C to the database before trying to prove C, thus building recursive dictionaries. Two bugs a) If we add C's superclasses (which we were) we can now build a bogusly-recursive dictionary (see Note [SUPERCLASS-LOOP]). Solution: in reduce, add C only (via addIrred NoSCs) and then later use addWanted to add its definition plus SCs. b) Since we can have recursive definitions, the superclass-loop handling machinery (findAllDeps) must carry its visited-set with it (which it was not doing before) The main file is TcSimplify; but I modified a bunch of others to take advantage of new function extendVarSetList
-
- 10 Dec, 2003 1 commit
-
-
simonmar authored
Add accurate source location annotations to HsSyn ------------------------------------------------- Every syntactic entity in HsSyn is now annotated with a SrcSpan, which details the exact beginning and end points of that entity in the original source file. All honest compilers should do this, and it was about time GHC did the right thing. The most obvious benefit is that we now have much more accurate error messages; when running GHC inside emacs for example, the cursor will jump to the exact location of an error, not just a line somewhere nearby. We haven't put a huge amount of effort into making sure all the error messages are accurate yet, so there could be some tweaking still needed, although the majority of messages I've seen have been spot-on. Error messages now contain a column number in addition to the line number, eg. read001.hs:25:10: Variable not in scope: `+#' To get the full text span info, use the new option -ferror-spans. eg. read001.hs:25:10-11: Variable not in scope: `+#' I'm not sure whether we should do this by default. Emacs won't understand the new error format, for one thing. In a more elaborate editor setting (eg. Visual Studio), we can arrange to actually highlight the subexpression containing an error. Eventually this information will be used so we can find elements in the abstract syntax corresponding to text locations, for performing high-level editor functions (eg. "tell me the type of this expression I just highlighted"). Performance of the compiler doesn't seem to be adversely affected. Parsing is still quicker than in 6.0.1, for example. Implementation: This was an excrutiatingly painful change to make: both Simon P.J. and myself have been working on it for the last three weeks or so. The basic changes are: - a new datatype SrcSpan, which represents a beginning and end position in a source file. - To reduce the pain as much as possible, we also defined: data Located e = L SrcSpan e - Every datatype in HsSyn has an equivalent Located version. eg. type LHsExpr id = Located (HsExpr id) and pretty much everywhere we used to use HsExpr we now use LHsExpr. Believe me, we thought about this long and hard, and all the other options were worse :-) Additional changes/cleanups we made at the same time: - The abstract syntax for bindings is now less arcane. MonoBinds and HsBinds with their built-in list constructors have gone away, replaced by HsBindGroup and HsBind (see HsSyn/HsBinds.lhs). - The various HsSyn type synonyms have now gone away (eg. RdrNameHsExpr, RenamedHsExpr, and TypecheckedHsExpr are now HsExpr RdrName, HsExpr Name, and HsExpr Id respectively). - Utilities over HsSyn are now collected in a new module HsUtils. More stuff still needs to be moved in here. - MachChar now has a real Char instead of an Int. All GHC versions that can compile GHC now support 32-bit Chars, so this was a simplification.
-
- 21 Oct, 2003 1 commit
-
-
simonpj authored
1. A tiresome change to HsType, to keep a record of whether or not the HsForAll was originally explicitly-quantified. This is solely so that the type checker can print out messages that show the source code the programmer wrote. Tiresome but easy. 2. Improve reporting of kind errors.
-
- 09 Oct, 2003 1 commit
-
-
simonpj authored
------------------------- GHC heart/lung transplant ------------------------- This major commit changes the way that GHC deals with importing types and functions defined in other modules, during renaming and typechecking. On the way I've changed or cleaned up numerous other things, including many that I probably fail to mention here. Major benefit: GHC should suck in many fewer interface files when compiling (esp with -O). (You can see this with -ddump-rn-stats.) It's also some 1500 lines of code shorter than before. ** So expect bugs! I can do a 3-stage bootstrap, and run ** the test suite, but you may be doing stuff I havn't tested. ** Don't update if you are relying on a working HEAD. In particular, (a) External Core and (b) GHCi are very little tested. But please, please DO test this version! ------------------------ Big things ------------------------ Interface files, version control, and importing declarations ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ * There is a totally new data type for stuff that lives in interface files: Original names IfaceType.IfaceExtName Types IfaceType.IfaceType Declarations (type,class,id) IfaceSyn.IfaceDecl Unfoldings IfaceSyn.IfaceExpr (Previously we used HsSyn for type/class decls, and UfExpr for unfoldings.) The new data types are in iface/IfaceType and iface/IfaceSyn. They are all instances of Binary, so they can be written into interface files. Previous engronkulation concering the binary instance of RdrName has gone away -- RdrName is not an instance of Binary any more. Nor does Binary.lhs need to know about the ``current module'' which it used to, which made it specialised to GHC. A good feature of this is that the type checker for source code doesn't need to worry about the possibility that we might be typechecking interface file stuff. Nor does it need to do renaming; we can typecheck direct from IfaceSyn, saving a whole pass (module TcIface) * Stuff from interface files is sucked in *lazily*, rather than being eagerly sucked in by the renamer. Instead, we use unsafeInterleaveIO to capture a thunk for the unfolding of an imported function (say). If that unfolding is every pulled on, TcIface will scramble over the unfolding, which may in turn pull in the interface files of things mentioned in the unfolding. The External Package State is held in a mutable variable so that it can be side-effected by this lazy-sucking-in process (which may happen way later, e.g. when the simplifier runs). In effect, the EPS is a kind of lazy memo table, filled in as we suck things in. Or you could think of it as a global symbol table, populated on demand. * This lazy sucking is very cool, but it can lead to truly awful bugs. The intent is that updates to the symbol table happen atomically, but very bad things happen if you read the variable for the table, and then force a thunk which updates the table. Updates can get lost that way. I regret this subtlety. One example of the way it showed up is that the top level of TidyPgm (which updates the global name cache) to be much more disciplined about those updates, since TidyPgm may itself force thunks which allocate new names. * Version numbering in interface files has changed completely, fixing one major bug with ghc --make. Previously, the version of A.f changed only if A.f's type and unfolding was textually different. That missed changes to things that A.f's unfolding mentions; which was fixed by eagerly sucking in all of those things, and listing them in the module's usage list. But that didn't work with --make, because they might have been already sucked in. Now, A.f's version changes if anything reachable from A.f (via interface files) changes. A module with unchanged source code needs recompiling only if the versions of any of its free variables changes. [This isn't quite right for dictionary functions and rules, which aren't mentioned explicitly in the source. There are extensive comments in module MkIface, where all version-handling stuff is done.] * We don't need equality on HsDecls any more (because they aren't used in interface files). Instead we have a specialised equality for IfaceSyn (eqIfDecl etc), which uses IfaceEq instead of Bool as its result type. See notes in IfaceSyn. * The horrid bit of the renamer that tried to predict what instance decls would be needed has gone entirely. Instead, the type checker simply sucks in whatever instance decls it needs, when it needs them. Easy! Similarly, no need for 'implicitModuleFVs' and 'implicitTemplateHaskellFVs' etc. Hooray! Types and type checking ~~~~~~~~~~~~~~~~~~~~~~~ * Kind-checking of types is far far tidier (new module TcHsTypes replaces the badly-named TcMonoType). Strangely, this was one of my original goals, because the kind check for types is the Right Place to do type splicing, but it just didn't fit there before. * There's a new representation for newtypes in TypeRep.lhs. Previously they were represented using "SourceTypes" which was a funny compromise. Now they have their own constructor in the Type datatype. SourceType has turned back into PredType, which is what it used to be. * Instance decl overlap checking done lazily. Consider instance C Int b instance C a Int These were rejected before as overlapping, because when seeking (C Int Int) one couldn't tell which to use. But there's no problem when seeking (C Bool Int); it can only be the second. So instead of checking for overlap when adding a new instance declaration, we check for overlap when looking up an Inst. If we find more than one matching instance, we see if any of the candidates dominates the others (in the sense of being a substitution instance of all the others); and only if not do we report an error. ------------------------ Medium things ------------------------ * The TcRn monad is generalised a bit further. It's now based on utils/IOEnv.lhs, the IO monad with an environment. The desugarer uses the monad too, so that anything it needs can get faulted in nicely. * Reduce the number of wired-in things; in particular Word and Integer are no longer wired in. The latter required HsLit.HsInteger to get a Type argument. The 'derivable type classes' data types (:+:, :*: etc) are not wired in any more either (see stuff about derivable type classes below). * The PersistentComilerState is now held in a mutable variable in the HscEnv. Previously (a) it was passed to and then returned by many top-level functions, which was painful; (b) it was invariably accompanied by the HscEnv. This change tidies up top-level plumbing without changing anything important. * Derivable type classes are treated much more like 'deriving' clauses. Previously, the Ids for the to/from functions lived inside the TyCon, but now the TyCon simply records their existence (with a simple boolean). Anyone who wants to use them must look them up in the environment. This in turn makes it easy to generate the to/from functions (done in types/Generics) using HsSyn (like TcGenDeriv for ordinary derivings) instead of CoreSyn, which in turn means that (a) we don't have to figure out all the type arguments etc; and (b) it'll be type-checked for us. Generally, the task of generating the code has become easier, which is good for Manuel, who wants to make it more sophisticated. * A Name now says what its "parent" is. For example, the parent of a data constructor is its type constructor; the parent of a class op is its class. This relationship corresponds exactly to the Avail data type; there may be other places we can exploit it. (I made the change so that version comparison in interface files would be a bit easier; but in fact it tided up other things here and there (see calls to Name.nameParent). For example, the declaration pool, of declararations read from interface files, but not yet used, is now keyed only by the 'main' name of the declaration, not the subordinate names. * New types OccEnv and OccSet, with the usual operations. OccNames can be efficiently compared, because they have uniques, thanks to the hashing implementation of FastStrings. * The GlobalRdrEnv is now keyed by OccName rather than RdrName. Not only does this halve the size of the env (because we don't need both qualified and unqualified versions in the env), but it's also more efficient because we can use a UniqFM instead of a FiniteMap. Consequential changes to Provenance, which has moved to RdrName. * External Core remains a bit of a hack, as it was before, done with a mixture of HsDecls (so that recursiveness and argument variance is still inferred), and IfaceExprs (for value declarations). It's not thoroughly tested. ------------------------ Minor things ------------------------ * DataCon fields dcWorkId, dcWrapId combined into a single field dcIds, that is explicit about whether the data con is a newtype or not. MkId.mkDataConWorkId and mkDataConWrapId are similarly combined into MkId.mkDataConIds * Choosing the boxing strategy is done for *source* type decls only, and hence is now in TcTyDecls, not DataCon. * WiredIn names are distinguished by their n_sort field, not by their location, which was rather strange * Define Maybes.mapCatMaybes :: (a -> Maybe b) -> [a] -> [b] and use it here and there * Much better pretty-printing of interface files (--show-iface) Many, many other small things. ------------------------ File changes ------------------------ * New iface/ subdirectory * Much of RnEnv has moved to iface/IfaceEnv * MkIface and BinIface have moved from main/ to iface/ * types/Variance has been absorbed into typecheck/TcTyDecls * RnHiFiles and RnIfaces have vanished entirely. Their work is done by iface/LoadIface * hsSyn/HsCore has gone, replaced by iface/IfaceSyn * typecheck/TcIfaceSig has gone, replaced by iface/TcIface * typecheck/TcMonoType has been renamed to typecheck/TcHsType * basicTypes/Var.hi-boot and basicTypes/Generics.hi-boot have gone altogether
-
- 24 Sep, 2003 1 commit
-
-
simonmar authored
The concensus seems to be that 'with' should go away now, after its customary period of deprecation. Hugs has already removed it, so we're following suit.
-
- 20 Sep, 2003 1 commit
-
-
ross authored
Re-arrange the interface to TcMatches to allow typechecking of case commands (part of arrow notation): * replace the export of the internal tcGRHSs with a more specific tcGRHSsPat for checking PatMonoBinds. * generalize match contexts in the same way as stmt contexts, to include a typechecker for the bodies of alts. This should probably be reviewed, but I hope it can make it into STABLE after a while.
-
- 16 Apr, 2003 1 commit
-
-
simonpj authored
---------------------------------- Use the Infer/Check idea for typechecking higher-rank types ---------------------------------- The main idea is that data Expected ty = Infer (TcRef ty) | Check ty tcMonoExpr :: Expr -> Expected TcRhoType -> TcM Expra This "Expected" type tells tcMonoExpr whether it's doing inference or checking. It replaces the "HoleTv" flavour of type variable. This actually leads to slightly more lines of code, but it's much clearer, and the new type distinctions showed up several subtle bugs in the previous implementation. It all arose out of writing the prototype implementation for the paper. Error messages wibble around a little bit. I'm not quite certain why! But the changes look like improvements to me.
-
- 26 Feb, 2003 1 commit
-
-
simonpj authored
---------------------------------- Improve higher-rank type inference ---------------------------------- Yanling Wang pointed out that if we have f = \ (x :: forall a. a->a). x it would be reasonable to expect that type inference would get the "right" rank-2 type for f. She also found that the plausible definition f :: (forall a. a->a) = \x -> x acutally failed to type check. This commit fixes up TcBinds.tcMonoBinds so that it does a better job. The main idea is that there are three cases to consider in a function binding: a) 'f' has a separate type signature In this case, we know f's type everywhere b) The binding is recursive, and there is no type sig In this case we must give f a monotype in its RHS c) The binding is non-recursive, and there is no type sig Then we do not need to add 'f' to the envt, and can simply infer a type for the RHS, which may be higher ranked.
-
- 21 Feb, 2003 2 commits
- 06 Jan, 2003 1 commit
-
-
simonpj authored
Small extra tc-trace
-
- 28 Nov, 2002 1 commit
-
-
simonpj authored
------------------------------- A day's work to improve error messages ------------------------------- 1. Indicate when the cause of the error is likely to be the monomorpism restriction, and identify the offending variables. This involves mainly tcSimplifyTop and its error generation. 2. Produce much better kind error messages. No more ../alonzo/DiGraph.hs:40: Couldn't match `* -> *' against `Type bx' Expected kind: * -> * Inferred kind: Type bx When checking that `DiGraph n' is a type It took a surprisingly long time to get the details right.
-
- 23 Oct, 2002 1 commit
-
-
simonpj authored
------------------------------------------------ Allow implicit-parameter bindings anywhere that a normal binding group is allowed. ------------------------------------------------ That is, you can have implicit parameters * in a let binding * in a where clause (but then you can't have non-implicit ones as well) * in a let group in a list comprehension or monad do-notation The implementation is simple: just add IPBinds to the allowable forms of HsBinds, and remove the HsWith expression form altogether. (It now comes in via the HsLet form.) It'a a nice generalisation really. Needs a bit of documentation, which I'll do next.
-