summaryrefslogtreecommitdiff
path: root/compiler/main/GHC.hs
Commit message (Collapse)AuthorAgeFilesLines
...
* Export CoreModule(..) (#5698)Simon Marlow2011-12-141-2/+5
|
* Allow full constraint solving under a for-all (Trac #5595)Simon Peyton Jones2011-12-051-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The main idea is that when we unify forall a. t1 ~ forall a. t2 we get constraints from unifying t1~t2 that mention a. We are producing a coercion witnessing the equivalence of the for-alls, and inside *that* coercion we need bindings for the solved constraints arising from t1~t2. We didn't have way to do this before. The big change is that here's a new type TcEvidence.TcCoercion, which is much like Coercion.Coercion except that there's a slot for TcEvBinds in it. This has a wave of follow-on changes. Not deep but broad. * New module TcEvidence, which now contains the HsWrapper TcEvBinds, EvTerm etc types that used to be in HsBinds * The typechecker works exclusively in terms of TcCoercion. * The desugarer converts TcCoercion to Coercion * The main payload is in TcUnify.unifySigmaTy. This is the function that had a gross hack before, but is now beautiful. * LCoercion is gone! Hooray. Many many fiddly changes in conssequence. But it's nice.
* Track #included files for recompilation checking (#4900, #3589)Simon Marlow2011-11-181-4/+7
| | | | | | | | | | This was pretty straightforward: collect the filenames in the lexer, and add them in to the tcg_dependent_files list that the typechecker collects. Note that we still don't get #included files in the ghc -M output. Since we don't normally lex the whole file in ghc -M, this same mechanism can't be used directly.
* New kind-polymorphic coreJose Pedro Magalhaes2011-11-111-2/+2
| | | | | | | | | This big patch implements a kind-polymorphic core for GHC. The current implementation focuses on making sure that all kind-monomorphic programs still work in the new core; it is not yet guaranteed that kind-polymorphic programs (using the new -XPolyKinds flag) will work. For more information, see http://haskell.org/haskellwiki/GHC/Kinds
* Use -fwarn-tabs when validatingIan Lynagh2011-11-041-0/+7
| | | | | We only use it for "compiler" sources, i.e. not for libraries. Many modules have a -fno-warn-tabs kludge for now.
* Make a new type synonym CoreProgram = [CoreBind]Simon Peyton Jones2011-09-231-1/+1
| | | | | | | | | | | and comment its invariants in Note [CoreProgram] in CoreSyn I'm not totally convinced that CoreProgram is the right name (perhaps CoreTopBinds might better), but it is useful to have a clue that you are looking at the top-level bindings. This is only a matter of a type synonym change; no deep refactoring here.
* move AvailInfo and related things into its own moduleSimon Marlow2011-09-211-2/+2
|
* Add support for all top-level declarations to GHCiSimon Marlow2011-09-211-13/+19
| | | | | | | | | | | | | | | | This is work mostly done by Daniel Winograd-Cort during his internship at MSR Cambridge, with some further refactoring by me. This commit adds support to GHCi for most top-level declarations that can be used in Haskell source files. Class, data, newtype, type, instance are all supported, as are Type Family-related declarations. The current set of declarations are shown by :show bindings. As with variable bindings, entities bound by newer declarations shadow earlier ones. Tests are in testsuite/tests/ghci/scripts/ghci039--ghci054. Documentation to follow.
* Implement -XConstraintKindMax Bolingbroke2011-09-061-3/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Basically as documented in http://hackage.haskell.org/trac/ghc/wiki/KindFact, this patch adds a new kind Constraint such that: Show :: * -> Constraint (?x::Int) :: Constraint (Int ~ a) :: Constraint And you can write *any* type with kind Constraint to the left of (=>): even if that type is a type synonym, type variable, indexed type or so on. The following (somewhat related) changes are also made: 1. We now box equality evidence. This is required because we want to give (Int ~ a) the *lifted* kind Constraint 2. For similar reasons, implicit parameters can now only be of a lifted kind. (?x::Int#) => ty is now ruled out 3. Implicit parameter constraints are now allowed in superclasses and instance contexts (this just falls out as OK with the new constraint solver) Internally the following major changes were made: 1. There is now no PredTy in the Type data type. Instead GHC checks the kind of a type to figure out if it is a predicate 2. There is now no AClass TyThing: we represent classes as TyThings just as a ATyCon (classes had TyCons anyway) 3. What used to be (~) is now pretty-printed as (~#). The box constructor EqBox :: (a ~# b) -> (a ~ b) 4. The type LCoercion is used internally in the constraint solver and type checker to represent coercions with free variables of type (a ~ b) rather than (a ~# b)
* Some minor wibbling in printing source locationsSimon Peyton Jones2011-09-021-1/+1
| | | | | | | | | | | I found that an imported instance was getting printed with <no location info>. Fixing this pushed me into a bit more refactoring than I intended, but it's all small aesthetic stuff, nothing fundamental. Caused some error message to change as a result. I removed pprDefnLoc from the GHC API because it doesn't seem to be used. Name.pprNamedefnLoc and pprDefinedAt are probably more useful anyway.
* export HscEnvSimon Marlow2011-08-261-1/+1
|
* Make pprTyThingInContenxt handle associated types rightSimon Peyton Jones2011-08-221-1/+1
| | | | | | Just as we want to display a data constructor as part of its parent data type declaration, so with associated types. This was simply missing before.
* Refactor to replace hscGetModuleExports by hscGetModuleInterfaceSimon Peyton Jones2011-08-031-26/+6
| | | | I also tidied up the interfaces for LoadIface to be a bit simpler
* tiny cleanupSimon Marlow2011-08-031-3/+5
|
* Refactor the imports of InteractiveContextSimon Peyton Jones2011-08-021-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | Instead of two fields ic_toplev_scope :: [Module] ic_imports :: [ImportDecl RdrName] we now just have one ic_imports :: [InteractiveImport] with the auxiliary data type data InteractiveImport = IIDecl (ImportDecl RdrName) -- Bring the exports of a particular module -- (filtered by an import decl) into scope | IIModule Module -- Bring into scope the entire top-level envt of -- of this module, including the things imported -- into it. This makes lots of code less confusing. No change in behaviour. It's preparatory to fixing Trac #5147. While I was at I also * Cleaned up the handling of the "implicit" Prelude import by adding a ideclImplicit field to ImportDecl. This significantly reduces plumbing in the handling of the implicit Prelude import * Used record notation consistently for ImportDecl
* Fix #481: use a safe recompilation check when Template Haskell isSimon Marlow2011-07-201-0/+5
| | | | | | | | | | | | | | | | being used. We now track whether a module used any TH splices in the ModIface (and at compile time in the TcGblEnv and ModGuts). If a module used TH splices last time it was compiled, then we ignore the results of the normal recompilation check and recompile anyway, *unless* the module is "stable" - that is, none of its dependencies (direct or indirect) have changed. The stability test is pretty important - otherwise ghc --make would always recompile TH modules even if nothing at all had changed, but it does require some extra plumbing to get this information from GhcMake into HscMain. test in driver/recomp009
* note that we don't understand a comment (#5249)Simon Marlow2011-07-201-0/+2
|
* defaultErrorHandler now only takes LogActionIan Lynagh2011-07-031-6/+6
| | | | | | | | | It used to take a whole DynFlags, but that meant we had to create a DynFlags with (panic "No settings") for settings, as we didn't have any real settings. Now we just pass the LogAction, which is all that it actually needed. The default is exported from DynFlags as defaultLogAction.
* Restore home-package-plugin functionalityMax Bolingbroke2011-06-301-1/+1
|
* SafeHaskell: Restore comment although we don't know what it means.David Terei2011-06-171-1/+8
| | | | | | | | Comment was removed as I thought it was incorrect now with code changes but Simon M thinks my interpretation of the comment was incorrect. He isn't sure what the comment is refereeing to either though! So have restored comment and created trac #5249 to track fixing this at some point.
* SafeHaskell: Add ':issafe' cmd to GHCi that displays module safety infoDavid Terei2011-06-171-20/+32
|
* SafeHaskell: Disable certain ghc extensions in Safe.David Terei2011-06-171-0/+5
| | | | | | | | | | This patch disables the use of some GHC extensions in Safe mode and also the use of certain flags. Some are disabled completely while others are only allowed on the command line and not in source PRAGMAS. We also check that Safe imports are indeed importing a Safe or Trustworthy module.
* Follow Src{Loc,Span} changes in other parts of the treeIan Lynagh2011-06-091-2/+2
|
* Refactor SrcLoc and SrcSpanIan Lynagh2011-06-091-30/+36
| | | | | | | | | | | | | | | The "Unhelpful" cases are now in a separate type. This allows us to improve various things, e.g.: * Most of the panic's in SrcLoc are now gone * The Lexer now works with RealSrcSpans rather than SrcSpans, i.e. it knows that it has real locations and thus can assume that the line number etc really exists * Some of the more suspicious cases are no longer necessary, e.g. we no longer need this case in advanceSrcLoc: advanceSrcLoc loc _ = loc -- Better than nothing More improvements can probably be made, e.g. tick locations can probably use RealSrcSpans too.
* add commentSimon Marlow2011-06-041-0/+4
|
* Merge remote branch 'origin/master' into ghc-new-coSimon Peyton Jones2011-04-301-2/+2
|\ | | | | | | | | | | | | | | Conflicts: compiler/typecheck/TcErrors.lhs compiler/typecheck/TcSMonad.lhs compiler/typecheck/TcType.lhs compiler/types/TypeRep.lhs
| * Initialise Settings before DynFlagsIan Lynagh2011-04-221-2/+1
| | | | | | | | | | | | Stops us having to temporarily have a panic in the DynFlags. We still need a panic in the DynFlags used for the top-level error handler, though.
| * Split off a Settings type from DynFlagsIan Lynagh2011-04-221-1/+2
| |
* | This BIG PATCH contains most of the work for the New Coercion RepresentationSimon Peyton Jones2011-04-191-4/+3
|/ | | | | | | | | | | | | | See the paper "Practical aspects of evidence based compilation in System FC" * Coercion becomes a data type, distinct from Type * Coercions become value-level things, rather than type-level things, (although the value is zero bits wide, like the State token) A consequence is that a coerion abstraction increases the arity by 1 (just like a dictionary abstraction) * There is a new constructor in CoreExpr, namely Coercion, to inject coercions into terms
* Change the way module initialisation is done (#3252, #4417)Simon Marlow2011-04-121-5/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Previously the code generator generated small code fragments labelled with __stginit_M for each module M, and these performed whatever initialisation was necessary for that module and recursively invoked the initialisation functions for imported modules. This appraoch had drawbacks: - FFI users had to call hs_add_root() to ensure the correct initialisation routines were called. This is a non-standard, and ugly, API. - unless we were using -split-objs, the __stginit dependencies would entail linking the whole transitive closure of modules imported, whether they were actually used or not. In an extreme case (#4387, #4417), a module from GHC might be imported for use in Template Haskell or an annotation, and that would force the whole of GHC to be needlessly linked into the final executable. So now instead we do our initialisation with C functions marked with __attribute__((constructor)), which are automatically invoked at program startup time (or DSO load-time). The C initialisers are emitted into the stub.c file. This means that every time we compile with -prof or -hpc, we now get a stub file, but thanks to #3687 that is now invisible to the user. There are some refactorings in the RTS (particularly for HPC) to handle the fact that initialisers now get run earlier than they did before. The __stginit symbols are still generated, and the hs_add_root() function still exists (but does nothing), for backwards compatibility.
* :script file scripts in GHCi #1363Vivian McPhail2011-02-261-1/+2
| | | | | | | | | This patch adds the script command in GHCi A file is read and executed as a series of GHCi commands. Execution terminates on the first error. The filename and line number are included in the error.
* Split main/GHC into GHC and GhcMakesimonpj@microsoft.com2011-01-251-1454/+58
| | | | | | | | | | | | | | | | | | | There are two things going on in main/GHC.hs. * It's the root module of the GHC package * It contains lots of stuff for --make It is also gigantic (2.7k lines) This patch splits it into two * GHC.hs is the root module for the GHC package (1.3k lines) * GhcMake.hs contains the stuff for --make (1.4k lines) Happily the functional split divided it almost exactly in half. This is a pure refactoring. There should be no behavioural change.
* Move imports around (no change in behaviour)simonpj@microsoft.com2011-01-101-4/+4
|
* Replace uses of the old try function with the new oneIan Lynagh2010-12-181-2/+2
|
* Fix bug #3165 (:history throws irrefutable pattern failed)pepeiborra@gmail.com2010-11-151-1/+1
| | | | | | | | | I ran across this bug and took the time to fix it, closing a long time due TODO in InteractiveEval.hs Instead of looking around to find the enclosing declaration of a tick, this patch makes use of the information already collected during the coverage desugaring phase
* Refactoring and tidyup of HscMain and related things (also fix #1666)Simon Marlow2010-10-271-216/+173
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | While trying to fix #1666 (-Werror aborts too early) I decided to some tidyup in GHC/DriverPipeline/HscMain. - The GhcMonad overloading is gone from DriverPipeline and HscMain now. GhcMonad is now defined in a module of its own, and only used in the top-level GHC layer. DriverPipeline and HscMain use the plain IO monad and take HscEnv as an argument. - WarnLogMonad is gone. printExceptionAndWarnings is now called printException (the old name is deprecated). Session no longer contains warnings. - HscMain has its own little monad that collects warnings, and also plumbs HscEnv around. The idea here is that warnings are collected while we're in HscMain, but on exit from HscMain (any function) we check for warnings and either print them (via log_action, so IDEs can still override the printing), or turn them into an error if -Werror is on. - GhcApiCallbacks is gone, along with GHC.loadWithLogger. Thomas Schilling told me he wasn't using these, and I don't see a good reason to have them. - there's a new pure API to the parser (suggestion from Neil Mitchell): parser :: String -> DynFlags -> FilePath -> Either ErrorMessages (WarningMessages, Located (HsModule RdrName))
* Remove GHC.extendGlobalRdrScope, GHC.extendGlobalTypeScopesimonpj@microsoft.com2010-10-131-31/+0
| | | | | | | | | | | | | | These functions were added by Tue Apr 18 03:36:06 BST 2006 Lemmih <lemmih@gmail.com> * Make the initial rdr and type scope available in the ghc-api The are extremely dubious, because they extend the Rdr and Type env for every compilation. The right thing to do is to use the InteractiveContext for temporary extensions. So far as we know, no one uses them. And if they are being used it's probably a mistake. So we're backing them out.
* Add separate functions for querying DynFlag and ExtensionFlag optionsIan Lynagh2010-09-181-2/+2
| | | | and remove the temporary DOpt class workaround.
* Remove (most of) the FiniteMap wrapperIan Lynagh2010-09-141-12/+16
| | | | | | | | We still have insertList, insertListWith, deleteList which aren't in Data.Map, and foldRightWithKey which works around the fold(r)WithKey addition and deprecation.
* Super-monster patch implementing the new typechecker -- at lastsimonpj@microsoft.com2010-09-131-2/+3
| | | | | | | | | This major patch implements the new OutsideIn constraint solving algorithm in the typecheker, following our JFP paper "Modular type inference with local assumptions". Done with major help from Dimitrios Vytiniotis and Brent Yorgey.
* Expose the functions haddock needs even when haddock is disabled; #3558Ian Lynagh2010-07-311-2/+11
|
* trac #2362 (full import syntax in ghci)amsay@amsay.net2010-06-251-1/+1
| | | | 'import' syntax is seperate from ':module' syntax
* fix the home_imps filter to allow for 'import "this" <module>'Simon Marlow2010-06-211-1/+4
| | | | | In the PackageImports extension, import "this" means "import from the current package".
* Fix Trac #4127: build GlobalRdrEnv in GHCi correctlysimonpj@microsoft.com2010-06-151-1/+1
| | | | | | | GHCi was building its GlobalRdrEnv wrongly, so that the gre_par field was bogus. That in turn fooled the renamer. The fix is easy: use the right function! Namely, call RnNames.gresFromAvail rather than availsToNameSet.
* Use UserInterrupt rather than our own Interrupted exception (#4100)Simon Marlow2010-06-021-1/+1
|
* Improve printing of TyThings; fixes Trac #4087simonpj@microsoft.com2010-05-251-2/+2
|
* Remove LazyUniqFM; fixes trac #3880Ian Lynagh2010-03-201-3/+2
|
* catch SIGHUP and SIGTERM and raise an exception (#3656)Simon Marlow2010-01-271-3/+1
|
* Do some recompilation avoidance in GHC.loadModuleSimon Marlow2010-01-121-7/+17
| | | | | | | | | | | GHC.loadModule compiles a module after it has been parsed and typechecked explicity. If we are compiling to object code and there is a valid object file already on disk, then we can skip the compilation step. This is useful in Haddock, when processing a package that uses Template Haskell and hence needs actual compilation, and the package has already been compiled. As usual, the recomp avoidance can be disabled with -fforce-recomp.
* Substantial improvements to coercion optimisationsimonpj@microsoft.com2010-01-041-2/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | The main purpose of this patch is to add a bunch of new rules to the coercion optimiser. They are documented in the (revised) Appendix of the System FC paper. Some code has moved about: - OptCoercion is now a separate module, mainly because it now uses tcMatchTy, which is defined in Unify, so OptCoercion must live higehr up in the hierarchy - Functions that manipulate Kinds has moved from Type.lhs to Coercion.lhs. Reason: the function typeKind now needs to call coercionKind. And in any case, a Kind is a flavour of Type, so it builds on top of Type; indeed Coercions and Kinds are both flavours of Type. This change required fiddling with a number of imports, hence the one-line changes to otherwise-unrelated modules - The representation of CoTyCons in TyCon has changed. Instead of an extensional representation (a kind checker) there is now an intensional representation (namely TyCon.CoTyConDesc). This was needed for one of the new coercion optimisations.