summaryrefslogtreecommitdiff
path: root/compiler/parser/Parser.y.pp
Commit message (Collapse)AuthorAgeFilesLines
...
* Keep track of explicit kinding in HsTyVarBndr; plus fix Trac #3845simonpj@microsoft.com2010-02-101-8/+6
| | | | | | | | | | | | | | | | | | | | To print HsTypes correctly we should remember whether the Kind on a HsTyVarBndr came from type inference, or was put there by the user. See Note [Printing KindedTyVars] in HsTypes. So instead of changing a UserTyVar to a KindedTyVar during kind checking, we simply add a PostTcKind to the UserTyVar. The change was provoked by Trac #3830, although other changes mean that #3830 gets a diferent and better error message now. So this patch is simply doing the Right Thing for the future. This patch also fixes Trac #3845, which was caused by a *type splice* not remembering the free *term variables* mentioned in it. Result was that we build a 'let' when it should have been 'letrec'. Hence a new FreeVars field in HsSpliceTy. While I was at it, I got rid of HsSpliceTyOut and use a PostTcKind on HsSpliceTy instead, just like on the UserTyVar.
* Several TH/quasiquote changessimonpj@microsoft.com2010-02-101-7/+11
| | | | | | | | | | | | | | | | | | | | | | a) Added quasi-quote forms for declarations types e.g. f :: [$qq| ... |] b) Allow Template Haskell pattern quotes (but not splices) e.g. f x = [p| Int -> $x |] c) Improve pretty-printing for HsPat to remove superfluous parens. (This isn't TH related really, but it affects some of the same code.) A consequence of (a) is that when gathering and grouping declarations in RnSource.findSplice, we must expand quasiquotes as we do so. Otherwise it's all fairly straightforward. I did a little bit of refactoring in TcSplice. User-manual changes still to come.
* Make view patterns right-associatesimonpj@microsoft.com2010-01-061-1/+1
| | | | | | So that you can write f (v1 -> v2 -> pat)
* Comments onlysimonpj@microsoft.com2010-01-051-5/+6
|
* Substantial improvements to coercion optimisationsimonpj@microsoft.com2010-01-041-1/+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.
* Columns now start at 1, as lines already didIan Lynagh2009-11-271-1/+1
| | | | Also corrected a couple of line 0's to line 1
* The Big INLINE Patch: totally reorganise way that INLINE pragmas worksimonpj@microsoft.com2009-10-291-8/+8
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch has been a long time in gestation and has, as a result, accumulated some extra bits and bobs that are only loosely related. I separated the bits that are easy to split off, but the rest comes as one big patch, I'm afraid. Note that: * It comes together with a patch to the 'base' library * Interface file formats change slightly, so you need to recompile all libraries The patch is mainly giant tidy-up, driven in part by the particular stresses of the Data Parallel Haskell project. I don't expect a big performance win for random programs. Still, here are the nofib results, relative to the state of affairs without the patch Program Size Allocs Runtime Elapsed -------------------------------------------------------------------------------- Min -12.7% -14.5% -17.5% -17.8% Max +4.7% +10.9% +9.1% +8.4% Geometric Mean +0.9% -0.1% -5.6% -7.3% The +10.9% allocation outlier is rewrite, which happens to have a very delicate optimisation opportunity involving an interaction of CSE and inlining (see nofib/Simon-nofib-notes). The fact that the 'before' case found the optimisation is somewhat accidental. Runtimes seem to go down, but I never kno wwhether to really trust this number. Binary sizes wobble a bit, but nothing drastic. The Main Ideas are as follows. InlineRules ~~~~~~~~~~~ When you say {-# INLINE f #-} f x = <rhs> you intend that calls (f e) are replaced by <rhs>[e/x] So we should capture (\x.<rhs>) in the Unfolding of 'f', and never meddle with it. Meanwhile, we can optimise <rhs> to our heart's content, leaving the original unfolding intact in Unfolding of 'f'. So the representation of an Unfolding has changed quite a bit (see CoreSyn). An INLINE pragma gives rise to an InlineRule unfolding. Moreover, it's only used when 'f' is applied to the specified number of arguments; that is, the number of argument on the LHS of the '=' sign in the original source definition. For example, (.) is now defined in the libraries like this {-# INLINE (.) #-} (.) f g = \x -> f (g x) so that it'll inline when applied to two arguments. If 'x' appeared on the left, thus (.) f g x = f (g x) it'd only inline when applied to three arguments. This slightly-experimental change was requested by Roman, but it seems to make sense. Other associated changes * Moving the deck chairs in DsBinds, which processes the INLINE pragmas * In the old system an INLINE pragma made the RHS look like (Note InlineMe <rhs>) The Note switched off optimisation in <rhs>. But it was quite fragile in corner cases. The new system is more robust, I believe. In any case, the InlineMe note has disappeared * The workerInfo of an Id has also been combined into its Unfolding, so it's no longer a separate field of the IdInfo. * Many changes in CoreUnfold, esp in callSiteInline, which is the critical function that decides which function to inline. Lots of comments added! * exprIsConApp_maybe has moved to CoreUnfold, since it's so strongly associated with "does this expression unfold to a constructor application". It can now do some limited beta reduction too, which Roman found was an important. Instance declarations ~~~~~~~~~~~~~~~~~~~~~ It's always been tricky to get the dfuns generated from instance declarations to work out well. This is particularly important in the Data Parallel Haskell project, and I'm now on my fourth attempt, more or less. There is a detailed description in TcInstDcls, particularly in Note [How instance declarations are translated]. Roughly speaking we now generate a top-level helper function for every method definition in an instance declaration, so that the dfun takes a particularly stylised form: dfun a d1 d2 = MkD (op1 a d1 d2) (op2 a d1 d2) ...etc... In fact, it's *so* stylised that we never need to unfold a dfun. Instead ClassOps have a special rewrite rule that allows us to short-cut dictionary selection. Suppose dfun :: Ord a -> Ord [a] d :: Ord a Then compare (dfun a d) --> compare_list a d in one rewrite, without first inlining the 'compare' selector and the body of the dfun. To support this a) ClassOps have a BuiltInRule (see MkId.dictSelRule) b) DFuns have a special form of unfolding (CoreSyn.DFunUnfolding) which is exploited in CoreUnfold.exprIsConApp_maybe Implmenting all this required a root-and-branch rework of TcInstDcls and bits of TcClassDcl. Default methods ~~~~~~~~~~~~~~~ If you give an INLINE pragma to a default method, it should be just as if you'd written out that code in each instance declaration, including the INLINE pragma. I think that it now *is* so. As a result, library code can be simpler; less duplication. The CONLIKE pragma ~~~~~~~~~~~~~~~~~~ In the DPH project, Roman found cases where he had p n k = let x = replicate n k in ...(f x)...(g x).... {-# RULE f (replicate x) = f_rep x #-} Normally the RULE would not fire, because doing so involves (in effect) duplicating the redex (replicate n k). A new experimental modifier to the INLINE pragma, {-# INLINE CONLIKE replicate #-}, allows you to tell GHC to be prepared to duplicate a call of this function if it allows a RULE to fire. See Note [CONLIKE pragma] in BasicTypes Join points ~~~~~~~~~~~ See Note [Case binders and join points] in Simplify Other refactoring ~~~~~~~~~~~~~~~~~ * I moved endPass from CoreLint to CoreMonad, with associated jigglings * Better pretty-printing of Core * The top-level RULES (ones that are not rules for locally-defined things) are now substituted on every simplifier iteration. I'm not sure how we got away without doing this before. This entails a bit more plumbing in SimplCore. * The necessary stuff to serialise and deserialise the new info across interface files. * Something about bottoming floats in SetLevels Note [Bottoming floats] * substUnfolding has moved from SimplEnv to CoreSubs, where it belongs -------------------------------------------------------------------------------- Program Size Allocs Runtime Elapsed -------------------------------------------------------------------------------- anna +2.4% -0.5% 0.16 0.17 ansi +2.6% -0.1% 0.00 0.00 atom -3.8% -0.0% -1.0% -2.5% awards +3.0% +0.7% 0.00 0.00 banner +3.3% -0.0% 0.00 0.00 bernouilli +2.7% +0.0% -4.6% -6.9% boyer +2.6% +0.0% 0.06 0.07 boyer2 +4.4% +0.2% 0.01 0.01 bspt +3.2% +9.6% 0.02 0.02 cacheprof +1.4% -1.0% -12.2% -13.6% calendar +2.7% -1.7% 0.00 0.00 cichelli +3.7% -0.0% 0.13 0.14 circsim +3.3% +0.0% -2.3% -9.9% clausify +2.7% +0.0% 0.05 0.06 comp_lab_zift +2.6% -0.3% -7.2% -7.9% compress +3.3% +0.0% -8.5% -9.6% compress2 +3.6% +0.0% -15.1% -17.8% constraints +2.7% -0.6% -10.0% -10.7% cryptarithm1 +4.5% +0.0% -4.7% -5.7% cryptarithm2 +4.3% -14.5% 0.02 0.02 cse +4.4% -0.0% 0.00 0.00 eliza +2.8% -0.1% 0.00 0.00 event +2.6% -0.0% -4.9% -4.4% exp3_8 +2.8% +0.0% -4.5% -9.5% expert +2.7% +0.3% 0.00 0.00 fem -2.0% +0.6% 0.04 0.04 fft -6.0% +1.8% 0.05 0.06 fft2 -4.8% +2.7% 0.13 0.14 fibheaps +2.6% -0.6% 0.05 0.05 fish +4.1% +0.0% 0.03 0.04 fluid -2.1% -0.2% 0.01 0.01 fulsom -4.8% +9.2% +9.1% +8.4% gamteb -7.1% -1.3% 0.10 0.11 gcd +2.7% +0.0% 0.05 0.05 gen_regexps +3.9% -0.0% 0.00 0.00 genfft +2.7% -0.1% 0.05 0.06 gg -2.7% -0.1% 0.02 0.02 grep +3.2% -0.0% 0.00 0.00 hidden -0.5% +0.0% -11.9% -13.3% hpg -3.0% -1.8% +0.0% -2.4% ida +2.6% -1.2% 0.17 -9.0% infer +1.7% -0.8% 0.08 0.09 integer +2.5% -0.0% -2.6% -2.2% integrate -5.0% +0.0% -1.3% -2.9% knights +4.3% -1.5% 0.01 0.01 lcss +2.5% -0.1% -7.5% -9.4% life +4.2% +0.0% -3.1% -3.3% lift +2.4% -3.2% 0.00 0.00 listcompr +4.0% -1.6% 0.16 0.17 listcopy +4.0% -1.4% 0.17 0.18 maillist +4.1% +0.1% 0.09 0.14 mandel +2.9% +0.0% 0.11 0.12 mandel2 +4.7% +0.0% 0.01 0.01 minimax +3.8% -0.0% 0.00 0.00 mkhprog +3.2% -4.2% 0.00 0.00 multiplier +2.5% -0.4% +0.7% -1.3% nucleic2 -9.3% +0.0% 0.10 0.10 para +2.9% +0.1% -0.7% -1.2% paraffins -10.4% +0.0% 0.20 -1.9% parser +3.1% -0.0% 0.05 0.05 parstof +1.9% -0.0% 0.00 0.01 pic -2.8% -0.8% 0.01 0.02 power +2.1% +0.1% -8.5% -9.0% pretty -12.7% +0.1% 0.00 0.00 primes +2.8% +0.0% 0.11 0.11 primetest +2.5% -0.0% -2.1% -3.1% prolog +3.2% -7.2% 0.00 0.00 puzzle +4.1% +0.0% -3.5% -8.0% queens +2.8% +0.0% 0.03 0.03 reptile +2.2% -2.2% 0.02 0.02 rewrite +3.1% +10.9% 0.03 0.03 rfib -5.2% +0.2% 0.03 0.03 rsa +2.6% +0.0% 0.05 0.06 scc +4.6% +0.4% 0.00 0.00 sched +2.7% +0.1% 0.03 0.03 scs -2.6% -0.9% -9.6% -11.6% simple -4.0% +0.4% -14.6% -14.9% solid -5.6% -0.6% -9.3% -14.3% sorting +3.8% +0.0% 0.00 0.00 sphere -3.6% +8.5% 0.15 0.16 symalg -1.3% +0.2% 0.03 0.03 tak +2.7% +0.0% 0.02 0.02 transform +2.0% -2.9% -8.0% -8.8% treejoin +3.1% +0.0% -17.5% -17.8% typecheck +2.9% -0.3% -4.6% -6.6% veritas +3.9% -0.3% 0.00 0.00 wang -6.2% +0.0% 0.18 -9.8% wave4main -10.3% +2.6% -2.1% -2.3% wheel-sieve1 +2.7% -0.0% +0.3% -0.6% wheel-sieve2 +2.7% +0.0% -3.7% -7.5% x2n1 -4.1% +0.1% 0.03 0.04 -------------------------------------------------------------------------------- Min -12.7% -14.5% -17.5% -17.8% Max +4.7% +10.9% +9.1% +8.4% Geometric Mean +0.9% -0.1% -5.6% -7.3%
* Tidy up the parsing of comprehensions and improve locationssimonpj@microsoft.com2009-10-281-27/+20
| | | | While I was dealing with 'rec' statements I did this tidy-up
* White space onlysimonpj@microsoft.com2009-09-301-1/+1
|
* Three improvements to Template Haskell (fixes #3467)simonpj@microsoft.com2009-09-101-8/+8
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch implements three significant improvements to Template Haskell. Declaration-level splices with no "$" ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ This change simply allows you to omit the "$(...)" wrapper for declaration-level TH splices. An expression all by itself is not legal, so we now treat it as a TH splice. Thus you can now say data T = T1 | T2 deriveMyStuff ''T where deriveMyStuff :: Name -> Q [Dec] This makes a much nicer interface for clients of libraries that use TH: no scary $(deriveMyStuff ''T). Nested top-level splices ~~~~~~~~~~~~~~~~~~~~~~~~ Previously TH would reject this, saying that splices cannot be nested: f x = $(g $(h 'x)) But there is no reason for this not to work. First $(h 'x) is run, yielding code <blah> that is spliced instead of the $(h 'x). Then (g <blah>) is typechecked and run, yielding code that replaces the $(g ...) splice. So this simply lifts the restriction. Fix Trac #3467: non-top-level type splices ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ It appears that when I added the ability to splice types in TH programs, I failed to pay attention to non-top-level splices -- that is, splices inside quotatation brackets. This patch fixes the problem. I had to modify HsType, so there's a knock-on change to Haddock. Its seems that a lot of lines of code has changed, but almost all the new lines are comments! General tidying up ~~~~~~~~~~~~~~~~~~ As a result of thinking all this out I re-jigged the data type ThStage, which had far too many values before. And I wrote a nice state transition diagram to make it all precise; see Note [Template Haskell state diagram] in TcSplice Lots more refactoring in TcSplice, resulting in significantly less code. (A few more lines, but actually less code -- the rest is comments.) I think the result is significantly cleaner.
* Refactor the parsing of data type declarationssimonpj@microsoft.com2009-09-081-17/+17
| | | | | | | | | | | | | | This is a minor change to the parser that tidies it up a bit, and allows us to parse data T :: * data S :: * -> * just like data T data S a
* remove Haddock-lexing/parsing/renaming from GHCIsaac Dupree2009-08-261-42/+25
|
* Move the standalone-deriving flag test from parser to renamersimonpj@microsoft.com2009-08-251-1/+1
| | | | | | This is just a tiny refactoring. In general, we're trying to get rid of parser errors in favour of later, more civlised, errors.
* Wibbles to field-label punssimonpj@microsoft.com2009-08-211-1/+1
|
* Add support for multi-line deprecated pragmas; trac #3303Ian Lynagh2009-08-121-6/+14
|
* Turn group into a special_id when TransformListComp is onMax Bolingbroke2009-07-171-0/+11
|
* Remove old 'foreign import dotnet' codeSimon Marlow2009-07-271-6/+4
| | | | It still lives in darcs, if anyone wants to revive it sometime.
* Add tuple sections as a new featuresimonpj@microsoft.com2009-07-231-10/+27
| | | | | | | | | | | | | | | | This patch adds tuple sections, so that (x,,z) means \y -> (x,y,z) Thanks for Max Bolinbroke for doing the hard work. In the end, instead of using two constructors in HsSyn, I used just one (still called ExplicitTuple) whose arguments can be Present (LHsExpr id) or Missing PostTcType While I was at it, I did a bit of refactoring too.
* New syntax for GADT-style record declarations, and associated refactoringsimonpj@microsoft.com2009-07-021-148/+69
| | | | | | | | | | | | | | | | | | | | | | | The main purpose of this patch is to fix Trac #3306, by fleshing out the syntax for GADT-style record declraations so that you have a context in the type. The new form is data T a where MkT :: forall a. Eq a => { x,y :: !a } -> T a See discussion on the Trac ticket. The old form is still allowed, but give a deprecation warning. When we remove the old form we'll also get rid of the one reduce/reduce error in the grammar. Hurrah! While I was at it, I failed as usual to resist the temptation to do lots of refactoring. The parsing of data/type declarations is now much simpler and more uniform. Less code, less chance of errors, and more functionality. Took longer than I planned, though. ConDecl has record syntax, but it was not being used consistently, so I pushed that through the compiler.
* Lexing and parsing for "foreign import prim"Duncan Coutts2009-06-091-0/+3
| | | | | We only allow simple function label imports, not the normal complicated business with "wrapper" "dynamic" or data label "&var" imports.
* Deprecate the threadsafe kind of foreign importDuncan Coutts2009-06-111-2/+2
|
* Fix Trac #3013: multiple constructors in a GADT declsimonpj@microsoft.com2009-05-281-6/+10
| | | | | | | | | Makes GADT syntax consistent by allowing multiple constructors to be given a single signature data T wehre A, B :: T C :: Int -> t
* Template Haskell: allow type splicessimonpj@microsoft.com2009-05-271-0/+4
| | | | | | | | | | | | | | | | | | | | | At last! Trac #1476 and #3177 This patch extends Template Haskell by allowing splices in types. For example f :: Int -> $(burble 3) A type splice should work anywhere a type is expected. This feature has been long requested, and quite a while ago I'd re-engineered the type checker to make it easier, but had never got around to finishing the job. With luck, this does it. There's a ToDo in the HsSpliceTy case of RnTypes.rnHsType, where I am not dealing properly with the used variables; but that's awaiting the refactoring of the way we report unused names.
* Hide warnings from alex/happy sourcesIan Lynagh2009-05-141-1/+1
|
* Require a bang pattern when unlifted types are where/let bound; #3182Ian Lynagh2009-04-241-1/+1
| | | | | For now we only get a warning, rather than an error, because the alex and happy templates don't follow the new rules yet.
* Fix my previous patch about type parsingDavid Waern2009-04-181-19/+0
| | | | I forgot to record some additional changes.
* Simplify the type grammarDavid Waern2009-04-171-16/+18
| | | | | | | | | | | Simon P-J suggested the following simplifications in #3097: * Allow nested foralls in `ctype` just like in `ctypedoc`. * Use `gentype` rather than `type` in the LHS of type declarations. * Inline `type` in `ctype`. * Rename `gentype` to `type`. This patch does this. Also, the equivalent thing is done for documented types.
* Fix Trac #3155: better error message when -XRankNTypes is omittedsimonpj@microsoft.com2009-04-091-0/+5
| | | | | | | | | | | | | | | | | | | | | This patch sligtly re-adjusts the way in which the syntax of types is handled: * In the lexer, '.' and '*' are always accepted in types (previously it was conditional). This things can't mean anything else in H98, which is the only reason for doing things conditionally in the lexer. * As a result '.' in types is never treated as an operator. Instead, lacking a 'forall' keyword, it turns into a plain parse error. * Test for -XKindSignatures in the renamer when processing a) type variable bindings b) types with sigs (ty :: kind-sig) * Make -XKindSignatures be implied by -XTypeFamilies Previously this was buried in the conditonal lexing of '*'
* Comments only; record remarks about removing 'type' nonterminalsimonpj@microsoft.com2009-04-021-11/+37
|
* Allow Haddock comments in type synonymsDavid Waern2009-03-311-22/+22
| | | | | | | | | | | | | | | | | | | | | | | | | | | | We now use `ctypedoc` instead of `ctype` for type synonyms. `ctypedoc` was previously only used for top-level type signatures. This change means that type synonyms now can contain comments, just like top-level type signatures. Note: * I've modified `ctypedoc` so it allows implicit parameters and equational constraints, just like ctype. * Since `ctypedoc` allows nested foralls, we now allow that in type synonyms. * I have inlined some productions into gentypedoc so that there is now a non-doc version of every production with a 'doc' suffix. (Stylistic change only, which should make the code easier to follow). * It would have been nice to simplify the grammar by unifying `ctype` and ctypedoc` into one production, allowing comments on types everywhere (and rejecting them after parsing, where necessary). This is however not possible since it leads to ambiguity. The reason is the support for comments on record fields: > data R = R { field :: Int -- ^ comment on the field } If we allow comments on types here, it's not clear if the comment applies to 'field' or to 'Int'. So we must use `ctype` to describe the type.
* Add the notion of "constructor-like" Ids for rule-matchingsimonpj@microsoft.com2009-03-181-3/+7
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch adds an optional CONLIKE modifier to INLINE/NOINLINE pragmas, {-# NOINLINE CONLIKE [1] f #-} The effect is to allow applications of 'f' to be expanded in a potential rule match. Example {-# RULE "r/f" forall v. r (f v) = f (v+1) #-} Consider the term let x = f v in ..x...x...(r x)... Normally the (r x) would not match the rule, because GHC would be scared about duplicating the redex (f v). However the CONLIKE modifier says to treat 'f' like a constructor in this situation, and "look through" the unfolding for x. So (r x) fires, yielding (f (v+1)). The main changes are: - Syntax - The inlinePragInfo field of an IdInfo has a RuleMatchInfo component, which records whether or not the Id is CONLIKE. Of course, this needs to be serialised in interface files too. - The occurrence analyser (OccAnal) and simplifier (Simplify) treat CONLIKE thing like constructors, by ANF-ing them - New function coreUtils.exprIsExpandable is like exprIsCheap, but additionally spots applications of CONLIKE functions - A CoreUnfolding has a field that caches exprIsExpandable - The rule matcher consults this field. See Note [Expanding variables] in Rules.lhs. On the way I fixed a lurking variable bug in the way variables are expanded. See Note [Do not expand locally-bound variables] in Rule.lhs. I also did a bit of reformatting and refactoring in Rules.lhs, so the module has more lines changed than are really different.
* Add (a) CoreM monad, (b) new Annotations featuresimonpj@microsoft.com2008-10-301-0/+9
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch, written by Max Bolingbroke, does two things 1. It adds a new CoreM monad (defined in simplCore/CoreMonad), which is used as the top-level monad for all the Core-to-Core transformations (starting at SimplCore). It supports * I/O (for debug printing) * Unique supply * Statistics gathering * Access to the HscEnv, RuleBase, Annotations, Module The patch therefore refactors the top "skin" of every Core-to-Core pass, but does not change their functionality. 2. It adds a completely new facility to GHC: Core "annotations". The idea is that you can say {#- ANN foo (Just "Hello") #-} which adds the annotation (Just "Hello") to the top level function foo. These annotations can be looked up in any Core-to-Core pass, and are persisted into interface files. (Hence a Core-to-Core pass can also query the annotations of imported things.) Furthermore, a Core-to-Core pass can add new annotations (eg strictness info) of its own, which can be queried by importing modules. The design of the annotation system is somewhat in flux. It's designed to work with the (upcoming) dynamic plug-ins mechanism, but is meanwhile independently useful. Do not merge to 6.10!
* add -XNewQualifiedOperators (Haskell' qualified operator syntax)Simon Marlow2008-09-221-7/+11
|
* Add -XPackageImports, new syntax for package-qualified importsSimon Marlow2008-08-051-2/+6
| | | | | | | | | | | | | | | | | Now you can say import "network" Network.Socket and get Network.Socket from package "network", even if there are multiple Network.Socket modules in scope from different packages and/or the current package. This is not really intended for general use, it's mainly so that we can build backwards-compatible versions of packages, where we need to be able to do module GHC.Base (module New.GHC.Base) where import "base" GHC.Base as New.GHC.Base
* Fix Trac #2490: sections should be parenthesisedsimonpj@microsoft.com2008-08-121-6/+17
| | | | | | | | | | When I added bang patterns I had to slightly generalise where the parser would recognise sections. See Note [Parsing sections] in parser.y.pp. I forgot to check that ordinary H98 sections obey the original rules. This patch adds the check.
* Add a WARNING pragmaIan Lynagh2008-07-201-18/+33
|
* Change pragma order to stop GHC 6.4 getting confusedIan Lynagh2008-07-101-7/+7
|
* Move more flags from the Makefile into pragmasIan Lynagh2008-07-101-0/+8
|
* Make part of the parser a bit stricterIan Lynagh2008-05-021-4/+4
|
* Fix some space-wasting in the ParserIan Lynagh2008-05-021-1/+1
| | | | (fst x, snd x) => x
* Fix an error if an SCC name contains a space; fixes trac #2071Ian Lynagh2008-04-271-2/+10
|
* Add 123## literals for Word#Ian Lynagh2008-04-231-0/+3
|
* (F)SLIT -> (f)sLit in ParserIan Lynagh2008-04-121-23/+20
|
* Make the parser a bit stricterIan Lynagh2008-02-181-1/+1
|
* Parser tweakIan Lynagh2008-01-251-1/+1
|
* A couple more parser tweaksIan Lynagh2008-01-251-1/+1
|
* Make comb[234] strictIan Lynagh2008-01-241-4/+6
|
* Strictness tweaksIan Lynagh2008-01-241-3/+8
|
* Get a bit of sharingIan Lynagh2008-01-241-2/+3
|
* Make sL strict in /both/ arguments to LIan Lynagh2008-01-241-1/+1
|