- 04 Jul, 2006 2 commits
-
-
Simon Marlow authored
-
Simon Marlow authored
-
- 18 Apr, 2006 1 commit
-
-
David Himmelstrup authored
-
- 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.
-
- 06 Apr, 2006 1 commit
-
-
David Himmelstrup authored
-
- 10 Mar, 2006 1 commit
-
-
David Himmelstrup authored
Use the lexer to parse OPTIONS, LANGUAGE and INCLUDE pragmas. This gives us greater flexibility and far better error messages. However, I had to make a few quirks: * The token parser is written manually since Happy doesn't like lexer errors (we need to extract options before the buffer is passed through 'cpp'). Still better than manually parsing a String, though. * The StringBuffer API has been extended so files can be read in blocks. I also made a new field in ModSummary called ms_hspp_opts which stores the updated DynFlags. Oh, and I took the liberty of moving 'getImports' into HeaderInfo together with 'getOptions'.
-
- 02 Mar, 2006 2 commits
-
-
Simon Marlow authored
-
Simon Marlow authored
-
- 06 Jan, 2006 1 commit
-
-
simonmar authored
Add support for UTF-8 source files GHC finally has support for full Unicode in source files. Source files are now assumed to be UTF-8 encoded, and the full range of Unicode characters can be used, with classifications recognised using the implementation from Data.Char. This incedentally means that only the stage2 compiler will recognise Unicode in source files, because I was too lazy to port the unicode classifier code into libcompat. Additionally, the following synonyms for keywords are now recognised: forall symbol (U+2200) forall right arrow (U+2192) -> left arrow (U+2190) <- horizontal ellipsis (U+22EF) .. there are probably more things we could add here. This will break some source files if Latin-1 characters are being used. In most cases this should result in a UTF-8 decoding error. Later on if we want to support more encodings (perhaps with a pragma to specify the encoding), I plan to do it by recoding into UTF-8 before parsing. Internally, there were some pretty big changes: - FastStrings are now stored in UTF-8 - Z-encoding has been moved right to the back end. Previously we used to Z-encode every identifier on the way in for simplicity, and only decode when we needed to show something to the user. Instead, we now keep every string in its UTF-8 encoding, and Z-encode right before printing it out. To avoid Z-encoding the same string multiple times, the Z-encoding is cached inside the FastString the first time it is requested. This speeds up the compiler - I've measured some definite improvement in parsing at least, and I expect compilations overall to be faster too. It also cleans up a lot of cruft from the OccName interface. Z-encoding is nicely hidden inside the Outputable instance for Names & OccNames now. - StringBuffers are UTF-8 too, and are now represented as ForeignPtrs. - I've put together some test cases, not by any means exhaustive, but there are some interesting UTF-8 decoding error cases that aren't obvious. Also, take a look at unicode001.hs for a demo.
-
- 22 Jul, 2005 1 commit
-
-
simonpj authored
MERGE TO STABLE Fix a long-standing bug in dependency tracking. If you have import M( x ) then you must recompile if M's export list changes, because it might no longer export x. Until now we have only done that if the import was import M I can't think why this bug has lasted so long. Thanks to Ian Lynagh for pointing it out.
-
- 21 Jun, 2005 1 commit
-
-
simonmar authored
Relax the restrictions on conflicting packages. This should address many of the traps that people have been falling into with the current package story. Now, a local module can shadow a module in an exposed package, as long as the package is not otherwise required by the program. GHC checks for conflicts when it knows the dependencies of the module being compiled. Also, we now check for module conflicts in exposed packages only when importing a module: if an import can be satisfied from multiple packages, that's an error. It's not possible to prevent GHC from starting by installing packages now (unless you install another base package). It seems to be possible to confuse GHCi by having a local module shadowing a package module that goes away and comes back again. I think it's nearly right, but strange happenings have been observed. I'll try to merge this into the STABLE branch.
-
- 24 May, 2005 1 commit
-
-
simonmar authored
isObjectLinkable: don't return True for an empty linkable
-
- 17 May, 2005 3 commits
-
-
simonmar authored
Improve source locations on error messages from the downsweep. We now keep track of SrcSpans from import declarations, so we can report a proper source location for unknown imports (this improves on the previous hacky solution of keeping track of the filename that contained the original import declaration). ModSummary now contains (Located Module) for each import instead of Module.
-
simonmar authored
More commentary
-
simonmar authored
expand comment
-
- 16 May, 2005 1 commit
-
-
simonmar authored
Implement -x <suffix> flag to override the suffix of a filename for the purposes of determinig how it should be compiled. The usage is similar to gcc, except that we just use a suffix rather than a name for the language. eg. ghc -c -x hs hello.blah will pretend hello.blah is a .hs file. Another possible use is -x hspp, which skips preprocessing. This works for one-shot compilation, --make, GHCi, and ghc -e. The original idea was to make it possible to use runghc on a file that doesn't end in .hs, so changes to runghc will follow. Also, I made it possible to specify .c files and other kinds of files on the --make command line; these will be compiled to objects as normal and linked into the final executable. GHC API change: I had to extend the Target type to include an optional start phase, and also GHC.guessTarget now takes a (Maybe Phase) argument. I thought this would be half an hour, in fact it took half a day, and I still haven't documented it. Sigh.
-
- 05 May, 2005 1 commit
-
-
simonpj authored
Make it so that you can deprecate a data constructor. Previously {-# DEPRECATED T "no" #-} referred only to the type or class T. Now it refers to the data constructor T as well, just like in fixity declarations. There's no way to deprecate the data constructor T without also deprecating the type T, alas. Same problem in fixity decls. Main problem is coming up with a suitable concrete syntax to do so. We could consider merging this to the STABLE branch. NB: Sven, the manual fixes are not XML-valideated! I'm at home.
-
- 28 Apr, 2005 2 commits
-
-
simonpj authored
Re-plumb the connections between TidyPgm and the various code generators. There's a new type, CgGuts, to mediate this, which has the happy effect that ModGuts can die earlier. The non-O route still isn't quite right, because default methods are being lost. I'm working on it.
-
simonpj authored
This big commit does several things at once (aeroplane hacking) which change the format of interface files. So you'll need to recompile your libraries! 1. The "stupid theta" of a newtype declaration ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Retain the "stupid theta" in a newtype declaration. For some reason this was being discarded, and putting it back in meant changing TyCon and IfaceSyn slightly. 2. Overlap flags travel with the instance ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Arrange that the ability to support overlap and incoherence is a property of the *instance declaration* rather than the module that imports the instance decl. This allows a library writer to define overlapping instance decls without the library client having to know. The implementation is that in an Instance we store the overlap flag, and preseve that across interface files 3. Nuke the "instnce pool" and "rule pool" ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ A major tidy-up and simplification of the way that instances and rules are sucked in from interface files. Up till now an instance decl has been held in a "pool" until its "gates" (a set of Names) are in play, when the instance is typechecked and added to the InstEnv in the ExternalPackageState. This is complicated and error-prone; it's easy to suck in too few (and miss an instance) or too many (and thereby be forced to suck in its type constructors, etc). Now, as we load an instance from an interface files, we put it straight in the InstEnv... but the Instance we put in the InstEnv has some Names (the "rough-match" names) that can be used on lookup to say "this Instance can't match". The detailed dfun is only read lazily, and the rough-match thing meansn it is'nt poked on until it has a chance of being needed. This simply continues the successful idea for Ids, whereby they are loaded straightaway into the TypeEnv, but their TyThing is a lazy thunk, not poked on until the thing is looked up. Just the same idea applies to Rules. On the way, I made CoreRule and Instance into full-blown records with lots of info, with the same kind of key status as TyCon or DataCon or Class. And got rid of IdCoreRule altogether. It's all much more solid and uniform, but it meant touching a *lot* of modules. 4. Allow instance decls in hs-boot files ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Allowing instance decls in hs-boot files is jolly useful, becuase in a big mutually-recursive bunch of data types, you want to give the instances with the data type declarations. To achieve this * The hs-boot file makes a provisional name for the dict-fun, something like $fx9. * When checking the "mother module", we check that the instance declarations line up (by type) and generate bindings for the boot dfuns, such as $fx9 = $f2 where $f2 is the dfun generated by the mother module * In doing this I decided that it's cleaner to have DFunIds get their final External Name at birth. To do that they need a stable OccName, so I have an integer-valued dfun-name-supply in the TcM monad. That keeps it simple. This feature is hardly tested yet. 5. Tidy up tidying, and Iface file generation ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ main/TidyPgm now has two entry points: simpleTidyPgm is for hi-boot files, when typechecking only (not yet implemented), and potentially when compiling without -O. It ignores the bindings, and generates a nice small TypeEnv. optTidyPgm is the normal case: compiling with -O. It generates a TypeEnv rich in IdInfo MkIface.mkIface now only generates a ModIface. A separate procedure, MkIface.writeIfaceFile, writes the file out to disk.
-
- 13 Apr, 2005 1 commit
-
-
simonmar authored
- checkModule is back, and now returns a ModuleInfo - added: modInfoTopLevelScope :: [Name] modInfoExports :: [Name] - in order to implement modInfoExports, ModDetails now contains md_exports::NameSet.
-
- 31 Mar, 2005 2 commits
-
-
simonmar authored
More hacking on the GHC API to get it into shape for VS - load now takes a LoadHowMuch argument, which is either LoadAllTargets LoadUpTo Module LoadDependenciesOf Module which should be self-explanatory. LoadDependenciesOf might go away in the future, it's necessary at the moment because it is used in the implementation of: - checkModule :: Session -> Module -> MessageHandler -> IO CheckResult which is currently the only way to get at the parsed & typechecked abstract syntax for a module.
-
simonmar authored
Tweaks to get the GHC sources through Haddock. Doesn't quite work yet, because Haddock complains about the recursive modules. Haddock needs to understand SOURCE imports (it can probably just ignore them as a first attempt).
-
- 30 Mar, 2005 1 commit
-
-
simonmar authored
Add support for partial reloads in the GHC API. This is mainly for VS: when editing a file you don't want to continually reload the entire project whenever the current file changes, you want to reload up to and including the current file only. However, you also want to retain any other modules in the session that are still stable. I added a variant of :reload in GHCi to test this. You can say ':reload M' to reload up to module M only. This will bring M up to date, and throw away any invalidated modules from the session.
-
- 24 Mar, 2005 1 commit
-
-
simonmar authored
Cleanup the upsweep strategy in GHC.load. Now it's hopefully clearer how we decide what modules to recompile, and which are "stable" (not even looked at) during a reload. See the comments for details. Also, I've taken some trouble to explicitly prune out things that aren't required before a reload, which should reduce the memory requirements for :reload in GHCi. Currently I believe it keeps most of the old program until the reload is complete, now it shouldn't require any extra memory.
-
- 22 Mar, 2005 1 commit
-
-
simonmar authored
A start on the GHC API: Flesh out the GHC module so that it can replace CompManager. Now, the clients that used CompManager consume the GHC API instead (namely Main, DriverMkDepend, and InteractiveUI). Main is significantly cleaner as a result. The interface needs more work: in particular, getInfo returns results in the form of IfaceDecls but we want to use full HsSyn and Id/DataCon/Class across the boundary instead. The interfaces for inspecting loaded modules are not yet implemented.
-
- 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
ghc --make should check for a module graph that contains a hs-boot file with no corresponding parent module Merge to STABLE
-
- 14 Feb, 2005 1 commit
-
-
simonmar authored
Put the GlobalRdrEnv back into the ModIface, so it gets preserved when we reload a module without recompiling it.
-
- 27 Jan, 2005 2 commits
-
-
simonpj authored
Make sure that the interactive context can see home-package instances; I forgot to do this when making tcRnModule find the appropriate intances (TcRnDriver rev 1.91) This was causing SourceForge [ghc-Bugs-1106171].
-
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.
-
- 18 Jan, 2005 1 commit
-
-
simonpj authored
------------------------ Reorganisation of hi-boot files ------------------------ The main point of this commit is to arrange that in the Compilation Manager's dependendency graph, hi-boot files are proper nodes. This is important to make sure that we compile everything in the right order. It's a step towards hs-boot files. * The fundamental change is that CompManager.ModSummary has a new field, ms_boot :: IsBootInterface I also tided up CompManager a bit. No change to the Basic Plan. ModSummary is now exported abstractly from CompManager (was concrete) * Hi-boot files now have import declarations. The idea is they are compulsory, so that the dependency analyser can find them * I changed an invariant: the Compilation Manager used to ensure that hscMain was given a HomePackageTable only for the modules 'below' the one being compiled. This was really only important for instances and rules, and it was a bit inconvenient. So I moved the filter to the compiler itself: see HscTypes.hptInstances and hptRules. * Module Packages.hs now defines data PackageIdH = HomePackage -- The "home" package is the package -- curently being compiled | ExtPackage PackageId -- An "external" package is any other package It was just a Maybe type before, so this makes it a bit clearer. * I tried to add a bit better location info to the IfM monad, so that errors in interfaces come with a slightly more helpful error message. See the if_loc field in TcRnTypes --- and follow-on consequences * Changed Either to Maybes.MaybeErr in a couple of places (more perspicuous)
-
- 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)
-
- 26 Nov, 2004 1 commit
-
-
simonmar authored
Further integration with the new package story. GHC now supports pretty much everything in the package proposal. - GHC now works in terms of PackageIds (<pkg>-<version>) rather than just package names. You can still specify package names without versions on the command line, as long as the name is unambiguous. - GHC understands hidden/exposed modules in a package, and will refuse to import a hidden module. Also, the hidden/eposed status of packages is taken into account. - I had to remove the old package syntax from ghc-pkg, backwards compatibility isn't really practical. - All the package.conf.in files have been rewritten in the new syntax, and contain a complete list of modules in the package. I've set all the versions to 1.0 for now - please check your package(s) and fix the version number & other info appropriately. - New options: -hide-package P sets the expose flag on package P to False -ignore-package P unregisters P for this compilation For comparison, -package P sets the expose flag on package P to True, and also causes P to be linked in eagerly. -package-name is no longer officially supported. Unofficially, it's a synonym for -ignore-package, which has more or less the same effect as -package-name used to. Note that a package may be hidden and yet still be linked into the program, by virtue of being a dependency of some other package. To completely remove a package from the compiler's internal database, use -ignore-package. The compiler will complain if any two packages in the transitive closure of exposed packages contain the same module. You *must* use -ignore-package P when compiling modules for package P, if package P (or an older version of P) is already registered. The compiler will helpfully complain if you don't. The fptools build system does this. - Note: the Cabal library won't work yet. It still thinks GHC uses the old package config syntax. Internal changes/cleanups: - The ModuleName type has gone away. Modules are now just (a newtype of) FastStrings, and don't contain any package information. All the package-related knowledge is in DynFlags, which is passed down to where it is needed. - DynFlags manipulation has been cleaned up somewhat: there are no global variables holding DynFlags any more, instead the DynFlags are passed around properly. - There are a few less global variables in GHC. Lots more are scheduled for removal. - -i is now a dynamic flag, as are all the package-related flags (but using them in {-# OPTIONS #-} is Officially Not Recommended). - make -j now appears to work under fptools/libraries/. Probably wouldn't take much to get it working for a whole build.
-
- 01 Oct, 2004 2 commits
-
-
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.
-
simonpj authored
----------------------------------- Do simple checking on hi-boot files ----------------------------------- This commit arranges that, when compiling A.hs, we compare the types we infer with those in A.hi-boot, if the latter exists. (Or, more accurately, if anything A.hs imports in turn imports A.hi-boot, directly or indirectly.) This has been on the to-do list forever.
-
- 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).
-
- 26 Aug, 2004 1 commit
-
-
simonpj authored
------------------------------- Print built-in sytax right ------------------------------- Built-in syntax, like (:) and [], is not "in scope" via the GlobalRdrEnv in the usual way. When we print it out, we should also print it in unqualified form, even though it's not in the environment. I've finally bitten the (not very big) bullet, and added to Name the information about whether or not a name is one of these built-in ones. That entailed changing the calls to mkWiredInName, but those are exactly the places where you have to decide whether it's built-in or not, which is fine. Built-in syntax => It's a syntactic form, not "in scope" (e.g. []) Wired-in thing => The thing (Id, TyCon) is fully known to the compiler, not read from an interface file. E.g. Bool, True, Int, Float, and many others All built-in syntax is for wired-in things.
-
- 16 Aug, 2004 1 commit
-
-
simonpj authored
------------------------------- Add instance information to :i Get rid of the DeclPool ------------------------------- 1. Add instance information to :info command. GHCi now prints out which instances a type or class belongs to, when you use :i 2. Tidy up printing of unqualified names in user output. Previously Outputable.PrintUnqualified was type PrintUnqualified = Name -> Bool but it's now type PrintUnqualified = ModuleName -> OccName -> Bool This turns out to be tidier even for Names, and it's now also usable when printing IfaceSyn stuff in GHCi, eliminating a grevious hack. 3. On the way to doing this, Simon M had the great idea that we could get rid of the DeclPool holding pen, which held declarations read from interface files but not yet type-checked. We do this by eagerly populating the TypeEnv with thunks what, when poked, do the type checking. This is just a logical continuation of lazy import mechanism we've now had for some while. The InstPool and RulePool still exist, but I plan to get rid of them in the same way. The new scheme does mean that more rules get sucked in than before, because previously the TypeEnv was used to mean "this thing was needed" and hence to control which rules were sucked in. But now the TypeEnv is populated more eagerly => more rules get sucked in. However this problem will go away when I get rid of the Inst and Rule pools. I should have kept these changes separate, but I didn't. Change (1) affects mainly TcRnDriver, HscMain, CompMan, InteractiveUI whereas change (3) is more wide ranging.
-
- 06 May, 2004 1 commit
-
-
simonpj authored
Use IfaceDeprecs synonym
-
- 24 Feb, 2004 1 commit
-
-
simonpj authored
--------------------------------------- Record dependency on Template Haskell package --------------------------------------- An unforseen consequence of making the Template Haskell package separate is that we need to record dependency on the package, even if no TH module is imported. So we carry round (another) mutable variable tcg_th_used in the tyepchecker monad, and zap it when $(...) and [| ... |] are used. I did a little tidy-up and documentation in ListSetOps too
-