- 20 Apr, 2011 1 commit
-
-
Simon Peyton Jones authored
In RnBinds.rnValBindsRHS I had (sig_dus `plusDU` bind_dus) when it should be (bind_dus `plusDU` sig_dus) So the fix is easy.
-
- 19 Apr, 2011 1 commit
-
-
simonpj authored
-
- 02 Apr, 2011 1 commit
-
-
batterseapower authored
We collect variables introduced by the {...} part of a let-like record wildcard pattern and do not warn if the user then doesn't actually use them.
-
- 22 Dec, 2010 1 commit
-
-
simonpj@microsoft.com authored
For a long time an 'mdo' expression has had a SyntaxTable attached to it. However, we're busy deprecating SyntaxTables in favour of rebindable syntax attached to individual Stmts, and MDoExpr was totally inconsistent with DoExpr in this regard. This patch tidies it all up. Now there's no SyntaxTable on MDoExpr, and 'modo' is generally handled much more like 'do'. There is resulting small change in behaviour: now MonadFix is required only if you actually *use* recursion in mdo. This seems consistent with the implicit dependency analysis that is done for mdo. Still to do: * Deal with #4148 (this patch is on the way) * Get rid of the last remaining SyntaxTable on HsCmdTop
-
- 07 Oct, 2010 1 commit
-
-
simonpj@microsoft.com authored
This big-ish patch arranges that if an Id 'f' is * Type-class overloaded f :: Ord a => [a] -> [a] * Defined with an INLINABLE pragma {-# INLINABLE f #-} * Exported from its defining module 'D' then in any module 'U' that imports D 1. Any call of 'f' at a fixed type will generate (a) a specialised version of f in U (b) a RULE that rewrites unspecialised calls to the specialised on e.g. if the call is (f Int dOrdInt xs) then the specialiser will generate $sfInt :: [Int] -> [Int] $sfInt = <code for f, imported from D, specialised> {-# RULE forall d. f Int d = $sfInt #-} 2. In addition, you can give an explicit {-# SPECIALISE -#} pragma for the imported Id {-# SPECIALISE f :: [Bool] -> [Bool] #-} This too generates a local specialised definition, and the corresponding RULE The new RULES are exported from module 'U', so that any module importing U will see the specialised versions of 'f', and will not re-specialise them. There's a flag -fwarn-auto-orphan that warns you if the auto-generated RULES are orphan rules. It's not in -Wall, mainly to avoid lots of error messages with existing packages. Main implementation changes - A new flag on a CoreRule to say if it was auto-generated. This is persisted across interface files, so there's a small change in interface file format. - Quite a bit of fiddling with plumbing, to get the {-# SPECIALISE #-} pragmas for imported Ids. In particular, a new field tgc_imp_specs in TcGblEnv, to keep the specialise pragmas for imported Ids between the typechecker and the desugarer. - Some new code (although surprisingly little) in Specialise, to deal with calls of imported Ids
-
- 18 Sep, 2010 1 commit
-
-
Ian Lynagh authored
and remove the temporary DOpt class workaround.
-
- 13 Sep, 2010 1 commit
-
-
simonpj@microsoft.com authored
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.
-
- 24 Jul, 2010 1 commit
-
-
Ian Lynagh authored
-
- 14 Jun, 2010 1 commit
-
-
simonpj@microsoft.com authored
-
- 25 May, 2010 1 commit
-
-
simonpj@microsoft.com authored
This patch fixes Trac #4056, by a) tidying up the treatment of default method names b) removing the 'module' argument to newTopSrcBinder The details aren't that interesting, but the result is much tidier. The original bug was a 'nameModule' panic, caused by trying to find the module of a top-level name. But TH quotes generate Internal top-level names that don't have a module, and that is generally a good thing. Fixing that in turn led to the default-method refactoring, which also makes the Name for a default method be handled in the same way as other derived names, generated in BuildTyCl via a call newImplicitBinder. Hurrah.
-
- 06 May, 2010 1 commit
-
-
simonpj@microsoft.com authored
The tcg_dus field used to contain *uses* of type and class decls, but not *defs*. That was inconsistent, and it really went wrong for Template Haskell bracket. What happened was that foo = [d| data A = A f :: A -> A f x = x |] would find a "use" of A when processing the top level of the module, which in turn led to a mkUsageInfo panic in MkIface. The cause was the fact that the tcg_dus for the nested quote didn't have defs for A.
-
- 12 Apr, 2010 1 commit
-
-
simonpj@microsoft.com authored
In fixing this I did the usual little bit of refactoring
-
- 04 Mar, 2010 1 commit
-
-
simonpj@microsoft.com authored
This one was bigger than I anticipated! The problem was that were were gathering the binders from a pattern before renaming -- but with record wild-cards we don't know what variables are bound by C {..} until after the renamer has filled in the "..". So this patch does the following * Change all the collect-X-Binders functions in HsUtils so that they expect to only be called *after* renaming. That means they don't need to return [Located id] but just [id]. Which turned out to be a very worthwhile simplification all by itself. * Refactor the renamer, and in ptic RnExpr.rnStmt, so that it doesn't need to use collectLStmtsBinders on pre-renamed Stmts. * This in turn required me to understand how GroupStmt and TransformStmts were renamed. Quite fiddly. I rewrote most of it; result is much shorter. * In doing so I flattened HsExpr.GroupByClause into its parent GroupStmt, with trivial knock-on effects in other files. Blargh.
-
- 07 Jan, 2010 1 commit
-
-
simonpj@microsoft.com authored
More on Trac #597
-
- 05 Nov, 2009 1 commit
-
-
simonpj@microsoft.com authored
In fixing this bug (to do with record puns), I had the usual rush of blood to the head, and I did quite a bit of refactoring in the way that duplicate/shadowed names are reported. I think the result is shorter as well as clearer. In one place I found it convenient for the renamer to use the ErrCtxt carried in the monad. (The renamer used not to have such a context, but years ago the typechecker and renamer monads became one, so now it does.) So now it's availble if you want it in future.
-
- 20 Aug, 2009 2 commits
-
-
simonpj@microsoft.com authored
-
simonpj@microsoft.com authored
* Make C { A.a } work with punning, expanding to C { A.a = a } * Make it so that, with -fwarn-unused-matches, f (C {..}) = x does not complain about the bindings introduced by the "..". * Make -XRecordWildCards implies -XDisambiguateRecordFields. * Overall refactoring of RnPat, which had become very crufty. In particular, there is now a monad, CpsRn, private to RnPat, which deals with the cps-style plumbing. This is why so many lines of RnPat have changed. * Refactor the treatment of renaming of record fields into two passes - rnHsRecFields1, used both for patterns and expressions, which expands puns, wild-cards - a local renamer in RnPat for fields in patterns - a local renamer in RnExpr for fields in construction and update This make it all MUCH easier to understand * Improve documentation of record puns, wildcards, and disambiguation
-
- 24 Jul, 2009 1 commit
-
-
Ian Lynagh authored
-
- 02 Jan, 2009 1 commit
-
-
simonpj@microsoft.com authored
This biggish patch addresses Trac #2670. The main effect is to make record selectors into ordinary functions, whose unfoldings appear in interface files, in contrast to their previous existence as magic "implicit Ids". This means that the usual machinery of optimisation, analysis, and inlining applies to them, which was failing before when the selector was somewhat complicated. (Which it can be when strictness annotations, unboxing annotations, and GADTs are involved.) The change involves the following points * Changes in Var.lhs to the representation of Var. Now a LocalId can have an IdDetails as well as a GlobalId. In particular, the information that an Id is a record selector is kept in the IdDetails. While compiling the current module, the record selector *must* be a LocalId, so that it participates properly in compilation (free variables etc). This led me to change the (hidden) representation of Var, so that there is now only one constructor for Id, not two. * The IdDetails is persisted into interface files, so that an importing module can see which Ids are records selectors. * In TcTyClDecls, we generate the record-selector bindings in renamed, but not typechecked form. In this way, we can get the typechecker to add all the types and so on, which is jolly helpful especially when GADTs or type families are involved. Just like derived instance declarations. This is the big new chunk of 180 lines of code (much of which is commentary). A call to the same function, mkAuxBinds, is needed in TcInstDcls for associated types. * The typechecker therefore has to pin the correct IdDetails on to the record selector, when it typechecks it. There was a neat way to do this, by adding a new sort of signature to HsBinds.Sig, namely IdSig. This contains an Id (with the correct Name, Type, and IdDetails); the type checker uses it as the binder for the final binding. This worked out rather easily. * Record selectors are no longer "implicit ids", which entails changes to IfaceSyn.ifaceDeclSubBndrs HscTypes.implicitTyThings TidyPgm.getImplicitBinds (These three functions must agree.) * MkId.mkRecordSelectorId is deleted entirely, some 300+ lines (incl comments) of very error prone code. Happy days. * A TyCon no longer contains the list of record selectors: algTcSelIds is gone The renamer is unaffected, including the way that import and export of record selectors is handled. Other small things * IfaceSyn.ifaceDeclSubBndrs had a fragile test for whether a data constructor had a wrapper. I've replaced that with an explicit flag in the interface file. More robust I hope. * I renamed isIdVar to isId, which touched a few otherwise-unrelated files.
-
- 27 Oct, 2008 1 commit
-
-
simonpj@microsoft.com authored
In fixing #2713, this patch also eliminates two almost-unused functions from RnEnv (lookupBndr and lookupBndr_maybe). The net lines of code is prety much unchanged, but more of them are comments!
-
- 03 Oct, 2008 2 commits
-
-
simonpj@microsoft.com authored
-
simonpj@microsoft.com authored
This patch fixes a dirty hack (the fake ThFake module), which in turn was causing Trac #2632. The new scheme is that the top-level binders in a TH [d| ... |] decl splice get Internal names. That breaks a previous invariant that things like TyCons always have External names, but these TyCons are never long-lived; they live only long enough to typecheck the TH quotation; the result is discarded. So it seems cool. Nevertheless -- Template Haskell folk: please test your code. The testsuite is OK but it's conceivable that I've broken something in TH. Let's see.
-
- 04 Sep, 2008 1 commit
-
-
Ian Lynagh authored
-
- 30 Aug, 2008 2 commits
-
-
Ian Lynagh authored
-
Ian Lynagh authored
-
- 11 Aug, 2008 1 commit
-
-
simonpj@microsoft.com authored
See the comments with Trac #2431. This patch makes an empty HsCase acceptable to the renamer onwards. If you want to accept empty case in Haskell source there's a little more to do: the ticket lists the remaining tasks.
-
- 31 Jul, 2008 1 commit
-
-
batterseapower authored
-
- 20 Jul, 2008 1 commit
-
-
Thomas Schilling authored
-
- 04 Jun, 2008 1 commit
-
-
simonpj@microsoft.com authored
We have not supported "result type signatures" for some time, but using one in the wrong way caused a crash. This patch tidies it up.
-
- 20 May, 2008 1 commit
-
-
simonpj@microsoft.com authored
Refactoring reduces code and improves error messages
-
- 03 May, 2008 1 commit
-
-
Ian Lynagh authored
-
- 12 Apr, 2008 1 commit
-
-
Ian Lynagh authored
-
- 10 Apr, 2008 1 commit
-
-
simonpj@microsoft.com authored
-
- 04 Apr, 2008 1 commit
-
-
simonpj@microsoft.com authored
This patch fixes a rather tiresome issue, namely the fact that a TH declaration quote *shadows* bindings in outer scopes: f g = [d| f :: Int f = g g :: Int g = 4 |] Here, the outer bindings for 'f' (top-level) and 'g' (local) are shadowed, and the inner bindings for f,g should not be reported as duplicates. (Remember they are top-level bindings.) The actual bug was that we'd forgotten to delete 'g' from the LocalRdrEnv, so the type sig for 'g' was binding to the outer 'g' not the inner one.
-
- 03 Apr, 2008 1 commit
-
-
simonpj@microsoft.com authored
There's a bit of a hack RnBinds.rnValBindsAndThen, documented in Note [Unused binding hack]. But the hack was over brutal before, and produced unnecssarily bad (absence of) warnings. This patch does a bit of refactoring; and fixes the bug in rnValBindsAndThen.
-
- 29 Mar, 2008 1 commit
-
-
Ian Lynagh authored
Modules that need it import it themselves instead.
-
- 07 Feb, 2008 1 commit
-
-
Ian Lynagh authored
These fix these failures: break008(ghci) break009(ghci) break026(ghci) ghci.prog009(ghci) ghci025(ghci) print007(ghci) prog001(ghci) prog002(ghci) prog003(ghci) at least some of which have this symptom: Exception: expectJust prune
-
- 17 Jan, 2008 1 commit
-
-
twanvl authored
-
- 18 Jan, 2008 1 commit
-
-
simonpj@microsoft.com authored
This patch adds quasi-quotation, as described in "Nice to be Quoted: Quasiquoting for Haskell" (Geoffrey Mainland, Haskell Workshop 2007) Implemented by Geoffrey and polished by Simon. Overview ~~~~~~~~ The syntax for quasiquotation is very similar to the existing Template haskell syntax: [$q| stuff |] where 'q' is the "quoter". This syntax differs from the paper, by using a '$' rather than ':', to avoid clashing with parallel array comprehensions. The "quoter" is a value of type Language.Haskell.TH.Quote.QuasiQuoter, which contains two functions for quoting expressions and patterns, respectively. quote = Language.Haskell.TH.Quote.QuasiQuoter quoteExp quotePat quoteExp :: String -> Language.Haskell.TH.ExpQ quotePat :: String -> Language.Haskell.TH.PatQ TEXT is passed unmodified to the quoter. The context of the quasiquotation statement determines which of the two quoters is called: if the quasiquotation occurs in an expression context, quoteExp is called, and if it occurs in a pattern context, quotePat is called. The result of running the quoter on its arguments is spliced into the program using Template Haskell's existing mechanisms for splicing in code. Note that although Template Haskell does not support pattern brackets, with this patch binding occurrences of variables in patterns are supported. Quoters must also obey the same stage restrictions as Template Haskell; in particular, in this example quote may not be defined in the module where it is used as a quasiquoter, but must be imported from another module. Points to notice ~~~~~~~~~~~~~~~~ * The whole thing is enabled with the flag -XQuasiQuotes * There is an accompanying patch to the template-haskell library. This involves one interface change: currentModule :: Q String is replaced by location :: Q Loc where Loc is a data type defined in TH.Syntax thus: data Loc = Loc { loc_filename :: String , loc_package :: String , loc_module :: String , loc_start :: CharPos , loc_end :: CharPos } type CharPos = (Int, Int) -- Line and character position So you get a lot more info from 'location' than from 'currentModule'. The location you get is the location of the splice. This works in Template Haskell too of course, and lets a TH program generate much better error messages. * There's also a new module in the template-haskell package called Language.Haskell.TH.Quote, which contains support code for the quasi-quoting feature. * Quasi-quote splices are run *in the renamer* because they can build *patterns* and hence the renamer needs to see the output of running the splice. This involved a bit of rejigging in the renamer, especially concerning the reporting of duplicate or shadowed names. (In fact I found and removed a few calls to checkDupNames in RnSource that are redundant, becuase top-level duplicate decls are handled in RnNames.)
-
- 13 Dec, 2007 1 commit
-
-
simonpj@microsoft.com authored
As well as fixing the immediate problem (Trac #1972) this patch does a signficant simplification and refactoring of pattern renaming. Fewer functions, fewer parameters passed....it's all good. But it took much longer than I expected to figure out. The most significant change is that the NameMaker type does *binding* as well as *making* and, in the matchNameMaker case, checks for unused bindings as well. This is much tider. (No need to merge to the 6.8 branch, but no harm either.)
-