summaryrefslogtreecommitdiff
path: root/compiler/rename/RnPat.lhs
Commit message (Collapse)AuthorAgeFilesLines
* compiler: de-lhs rename/Austin Seipp2014-12-031-751/+0
| | | | Signed-off-by: Austin Seipp <austin@well-typed.com>
* Capture original source for literalsAlan Zimmerman2014-11-211-5/+6
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Make HsLit and OverLitVal have original source strings, for source to source conversions using the GHC API This is part of the ongoing AST Annotations work, as captured in https://ghc.haskell.org/trac/ghc/wiki/GhcAstAnnotations and https://ghc.haskell.org/trac/ghc/ticket/9628#comment:28 The motivations for the literals is as follows ```lang=haskell x,y :: Int x = 0003 y = 0x04 s :: String s = "\x20" c :: Char c = '\x20' d :: Double d = 0.00 blah = x where charH = '\x41'# intH = 0004# wordH = 005## floatH = 3.20# doubleH = 04.16## x = 1 ``` Test Plan: ./sh validate Reviewers: simonpj, austin Reviewed By: simonpj, austin Subscribers: thomie, goldfire, carter, simonmar Differential Revision: https://phabricator.haskell.org/D412 GHC Trac Issues: #9628
* AST changes to prepare for API annotations, for #9628Alan Zimmerman2014-11-211-16/+16
| | | | | | | | | | | | | | | | | | | | | | | | | Summary: AST changes to prepare for API annotations Add locations to parts of the AST so that API annotations can then be added. The outline of the whole process is captured here https://ghc.haskell.org/trac/ghc/wiki/GhcAstAnnotations This change updates the haddock submodule. Test Plan: sh ./validate Reviewers: austin, simonpj, Mikolaj Reviewed By: simonpj, Mikolaj Subscribers: thomie, goldfire, carter Differential Revision: https://phabricator.haskell.org/D426 GHC Trac Issues: #9628
* Fix #9824 by not warning about unused matches in pattern quotes.Richard Eisenberg2014-11-211-0/+3
|
* Fix #1476 by making splice patterns work.Richard Eisenberg2014-11-211-4/+6
| | | | | | | | | Unfortunately, splice patterns in brackets still do not work because we don't run splices in brackets. Without running a pattern splice, we can't know what variables it binds, so we're stuck. This is still a substantial improvement, and it may be the best we can do. Still must document new behavior.
* Fix Trac #9815Simon Peyton Jones2014-11-211-4/+10
| | | | | | | | | | | Dot-dot record-wildcard notation is simply illegal for constructors without any named fields, but that was neither documented nor checked. This patch does so - Make the check in RnPat - Add test T9815 - Fix CmmLayoutStack which was using the illegal form (!) - Document in user manual
* PostTcType replaced with TypeAnnotAlan Zimmerman2014-09-061-6/+11
| | | | | | | | | | | | | | | | | | | | | Summary: This is a first step toward allowing generic traversals of the AST without 'landmines', by removing the `panic`s located throughout `placeHolderType`, `placeHolderKind` & co. See more on the discussion at https://www.mail-archive.com/ghc-devs@haskell.org/msg05564.html (This also makes a corresponding update to the `haddock` submodule.) Test Plan: `sh validate` and new tests pass. Reviewers: austin, simonpj, goldfire Reviewed By: austin, simonpj, goldfire Subscribers: edsko, Fuuzetsu, thomasw, holzensp, goldfire, simonmar, relrod, ezyang, carter Projects: #ghc Differential Revision: https://phabricator.haskell.org/D157
* Typos in commentsGabor Greif2014-08-291-1/+1
|
* Two buglets in record wild-cards (Trac #9436 and #9437)Simon Peyton Jones2014-08-251-9/+24
| | | | | | | of named fields, whereas the code in RnPat.rnHsRecFields is much better set up to do so. Both easily fixed.
* Fix egregious instantiation bug in matchOneConLike (fixing Trac #9023)Simon Peyton Jones2014-06-051-1/+1
| | | | | | | | | | | | | | | We simply weren't giving anything like the right instantiating types to patSynInstArgTys in matchOneConLike. To get these instantiating types would have involved matching the result type of the pattern synonym with the pattern type, which is tiresome. So instead I changed ConPatOut so that instead of recording the type of the *whole* pattern (in old field pat_ty), it not records the *instantiating* types (in new field pat_arg_tys). Then we canuse TcHsSyn.conLikeResTy to get the pattern type when needed. There are lots of knock-on incidental effects, but they mostly made the code simpler, so I'm happy.
* Add LANGUAGE pragmas to compiler/ source filesHerbert Valerio Riedel2014-05-151-6/+1
| | | | | | | | | | | | | | | | | | In some cases, the layout of the LANGUAGE/OPTIONS_GHC lines has been reorganized, while following the convention, to - place `{-# LANGUAGE #-}` pragmas at the top of the source file, before any `{-# OPTIONS_GHC #-}`-lines. - Moreover, if the list of language extensions fit into a single `{-# LANGUAGE ... -#}`-line (shorter than 80 characters), keep it on one line. Otherwise split into `{-# LANGUAGE ... -#}`-lines for each individual language extension. In both cases, try to keep the enumeration alphabetically ordered. (The latter layout is preferable as it's more diff-friendly) While at it, this also replaces obsolete `{-# OPTIONS ... #-}` pragma occurences by `{-# OPTIONS_GHC ... #-}` pragmas.
* Issue an error for pattern synonyms defined in a local scope (#8757)Dr. ERDI Gergo2014-02-091-0/+5
| | | | | This also fixes the internal crash when using pattern synonyms in GHCi (#8749)
* Squash some spelling issuesGabor Greif2014-01-261-2/+2
|
* Implement pattern synonymsDr. ERDI Gergo2014-01-201-6/+20
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch implements Pattern Synonyms (enabled by -XPatternSynonyms), allowing y ou to assign names to a pattern and abstract over it. The rundown is this: * Named patterns are introduced by the new 'pattern' keyword, and can be either *unidirectional* or *bidirectional*. A unidirectional pattern is, in the simplest sense, simply an 'alias' for a pattern, where the LHS may mention variables to occur in the RHS. A bidirectional pattern synonym occurs when a pattern may also be used in expression context. * Unidirectional patterns are declared like thus: pattern P x <- x:_ The synonym 'P' may only occur in a pattern context: foo :: [Int] -> Maybe Int foo (P x) = Just x foo _ = Nothing * Bidirectional patterns are declared like thus: pattern P x y = [x, y] Here, P may not only occur as a pattern, but also as an expression when given values for 'x' and 'y', i.e. bar :: Int -> [Int] bar x = P x 10 * Patterns can't yet have their own type signatures; signatures are inferred. * Pattern synonyms may not be recursive, c.f. type synonyms. * Pattern synonyms are also exported/imported using the 'pattern' keyword in an import/export decl, i.e. module Foo (pattern Bar) where ... Note that pattern synonyms share the namespace of constructors, so this disambiguation is required as a there may also be a 'Bar' type in scope as well as the 'Bar' pattern. * The semantics of a pattern synonym differ slightly from a typical pattern: when using a synonym, the pattern itself is matched, followed by all the arguments. This means that the strictness differs slightly: pattern P x y <- [x, y] f (P True True) = True f _ = False g [True, True] = True g _ = False In the example, while `g (False:undefined)` evaluates to False, `f (False:undefined)` results in undefined as both `x` and `y` arguments are matched to `True`. For more information, see the wiki: https://ghc.haskell.org/trac/ghc/wiki/PatternSynonyms https://ghc.haskell.org/trac/ghc/wiki/PatternSynonyms/Implementation Reviewed-by: Simon Peyton Jones <simonpj@microsoft.com> Signed-off-by: Austin Seipp <austin@well-typed.com>
* A raft of changes driven by Trac #8540Simon Peyton Jones2013-11-221-4/+4
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The root cause of #8450 is that the new Template Haskell story, with the renamer doing more of the work of Template Haskell, wasn't dealing correctly with the keepAlive problem. Consider g = ..blah... f = [| g |] Then f's RHS refers to g's name but not to g, so g was being discarded as dead code. Fixing this sucked me into a deep swamp of understanding how all the moving parts of hte new Template Haskell fit together, leading to a large collection of related changes and better documentation. Specifically: * Instead of putting the TH level of a binder in the LocalRdrEnv, there is now a separate field tcl_th_bndrs :: NameEnv (TopLevelFlag, ThLevel) in the TcLclEnv, which records for each binder a) whether it is syntactically a top-level binder or not b) its TH level This deals uniformly with top-level and non-top-level binders, which was previously dealt with via greviously-delicate meddling with Internal and External Names. Much better. * As a result I could remove the tct_level field of ATcId. * There are consequential changes in TcEnv too, which must also extend the level bindings. Again, more clarity. I renamed TcEnv.tcExtendTcTyThingEnv to tcExtendKindEnv2, since it's only used during kind inference, for (AThing kind) and APromotionErr; and that is relevant to whether we want to extend the tcl_th_bndrs field (no). * I de-crufted the code in RnEnv.extendGlobalRdrEnv, by getting rid of the qual_gre code which said "Seems like 5 times as much work as it deserves!". Instead, RdrName.pickGREs makes the Internal names shadow External ones. * I moved the checkThLocalName cross-stage test to finishHsVar; previously we weren't doing the test at all in the OpApp case! * Quite a few changes (shortening the code) in the cross-stage checking code in TcExpr and RnSplice, notably to move the keepAlive call to the renamer One leftover piece: * In TcEnv I removed tcExtendGhciEnv and refactored tcExtendGlobalTyVars; this is really related to the next commit, but it was too hard to disentangle.
* Tidy up the error messages we get from TH in stage1 (Trac #8312)Simon Peyton Jones2013-11-061-10/+1
| | | | | | Instead of panic-ing we now give a sensible message. There is quite a bit of refactoring here too, removing several #ifdef GHCI things
* Fix Trac #8448Simon Peyton Jones2013-10-231-3/+11
| | | | | | We weren't dealing with built-in syntax; data constructors that are built-in syntax (only [] actually) don't appear in the GlobalRdrEnv
* Add support for pattern splices.Geoffrey Mainland2013-10-041-2/+12
|
* Globally replace "hackage.haskell.org" with "ghc.haskell.org"Simon Marlow2013-10-011-1/+1
|
* Give language pragma suggestions without -XJoachim Breitner2013-09-141-4/+4
| | | | for easier copy'n'paste. This fixes: #3647
* Fix AMP warnings.Austin Seipp2013-09-111-6/+13
| | | | | Authored-by: David Luposchainsky <dluposchainsky@gmail.com> Signed-off-by: Austin Seipp <austin@well-typed.com>
* Fix #7918Edsko de Vries2013-09-031-2/+3
|
* Detabify RnPat.lhsAustin Seipp2013-08-281-107/+106
| | | | Signed-off-by: Austin Seipp <aseipp@pobox.com>
* Implement -XNumDecimals (#7266)Austin Seipp2013-08-281-3/+16
| | | | | | | | | | | | | | | | | Under -XNumDecimals, it's possible to specify an integer literal using compact "floating point" syntax for any floating literal constant which also happens to be an integer. This lets us write 1.2e6 :: Integer instead of: 1200000 :: Integer This also makes some amendments to the users guide. Authored-by: Shachaf Ben-Kiki <shachaf@gmail.com> Signed-off-by: Austin Seipp <aseipp@pobox.com>
* Fix type variable scoping in nested pattern type signatures (#7827)Patrick Palka2013-04-121-2/+11
|
* Add OverloadedLists, allowing list syntax to be overloadedSimon Peyton Jones2013-02-141-5/+16
| | | | | | | | | | | | | | | | | | | | | | | This work was all done by Achim Krause <achim.t.krause@gmail.com> George Giorgidze <giorgidze@gmail.com> Weijers Jeroen <jeroen.weijers@uni-tuebingen.de> It allows list syntax, such as [a,b], [a..b] and so on, to be overloaded so that it works for a variety of types. The design is described here: http://hackage.haskell.org/trac/ghc/wiki/OverloadedLists Eg. you can use it for maps, so that [(1,"foo"), (4,"bar")] :: Map Int String The main changes * The ExplicitList constructor of HsExpr gets witness field * Ditto ArithSeq constructor * Ditto the ListPat constructor of HsPat Everything else flows from this.
* Do not treat a constructor in a *pattern* as a *use* of that constructorSimon Peyton Jones2012-10-291-2/+18
| | | | | | | | | | | | | | | | | | | | | | | | Occurrences in terms are uses, in patterns they are not. In this way we get unused-constructor warnings from modules like this module M( f, g, T ) where data T = T1 | T2 Bool f x = T2 x g T1 = True g (T2 x) = x Here a T1 value cannot be constructed, so we can warn. The use in a pattern doesn't count. See Note [Patterns are not uses] in RnPat. Interestingly this change exposed three module in GHC itself that had unused constructors, which I duly removed: * ghc/Main.hs * compiler/ghci/ByteCodeAsm * compiler/nativeGen/PPC/RegInfo Their changes are in this patch.
* This big patch re-factors the way in which arrow-syntax is handledSimon Peyton Jones2012-10-031-2/+2
| | | | | | | | | | | | | | | | | | | | | | All the work was done by Dan Winograd-Cort. The main thing is that arrow comamnds now have their own data type HsCmd (defined in HsExpr). Previously it was punned with the HsExpr type, which was jolly confusing, and made it hard to do anything arrow-specific. To make this work, we now parameterise * MatchGroup * Match * GRHSs, GRHS * StmtLR and friends over the "body", that is the kind of thing they enclose. This "body" parameter can be instantiated to either LHsExpr or LHsCmd respectively. Everything else is really a knock-on effect; there should be no change (yet!) in behaviour. But it should be a sounder basis for fixing bugs.
* Don't warn about defining deprecated class methodsIan Lynagh2012-09-231-1/+1
| | | | | We only warn when the method is used, not when it is defined as part of an instance.
* Complain if we use a tuple tycon or data-con that is too bigSimon Peyton Jones2012-06-071-10/+0
| | | | | Previously (Trac #6148) we were only complaining for the distfix syntax (a,b,c).
* Change how macros like ASSERT are definedIan Lynagh2012-06-051-1/+1
| | | | | By using Haskell's debugIsOn rather than CPP's "#ifdef DEBUG", we don't need to kludge things to keep the warning checker happy etc.
* Refactor LHsTyVarBndrs to fix Trac #6081Simon Peyton Jones2012-05-111-2/+2
| | | | | | | | | | | | | | | This is really a small change, but it touches a lot of files quite significantly. The real goal is to put the implicitly-bound kind variables of a data/class decl in the right place, namely on the LHsTyVarBndrs type, which now looks like data LHsTyVarBndrs name = HsQTvs { hsq_kvs :: [Name] , hsq_tvs :: [LHsTyVarBndr name] } This little change made the type checker neater in a number of ways, but it was fiddly to push through the changes.
* Fix Trac #5892: a coding errorsSimon Peyton Jones2012-03-041-4/+4
| | | | | | | | | | We had a lazy pattern gres@(gre:_) = blah and then a test for (null gres). But I'd forgotten that a demand for *any* of variables in the pattern matches *all* of the variables in the entire pattern. So the test for (null gres) was matching the cons, which defeats the purpose.
* Hurrah! This major commit adds support for scoped kind variables,Simon Peyton Jones2012-03-021-12/+9
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | which (finally) fills out the functionality of polymorphic kinds. It also fixes numerous bugs. Main changes are: Renaming stuff ~~~~~~~~~~~~~~ * New type in HsTypes: data HsBndrSig sig = HsBSig sig [Name] which is used for type signatures in patterns, and kind signatures in types. So when you say f (x :: [a]) = x ++ x or data T (f :: k -> *) (x :: *) = MkT (f x) the signatures in both cases are a HsBndrSig. * The [Name] in HsBndrSig records the variables bound by the pattern, that is 'a' in the first example, 'k' in the second, and nothing in the third. The renamer initialises the field. * As a result I was able to get rid of RnHsSyn.extractHsTyNames :: LHsType Name -> NameSet and its friends altogether. Deleted the entire module! This led to some knock-on refactoring; in particular the type renamer now returns the free variables just like the term renamer. Kind-checking types: mainly TcHsType ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ A major change is that instead of kind-checking types in two passes, we now do one. Under the old scheme, the first pass did kind-checking and (hackily) annotated the HsType with the inferred kinds; and the second pass desugared the HsType to a Type. But now that we have kind variables inside types, the first pass (TcHsType.tc_hs_type) can go straight to Type, and zonking will squeeze out any kind unification variables later. This is much nicer, but it was much more fiddly than I had expected. The nastiest corner is this: it's very important that tc_hs_type uses lazy constructors to build the returned type. See Note [Zonking inside the knot] in TcHsType. Type-checking type and class declarations: mainly TcTyClsDecls ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ I did tons of refactoring in TcTyClsDecls. Simpler and nicer now. Typechecking bindings: mainly TcBinds ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ I rejigged (yet again) the handling of type signatures in TcBinds. It's a bit simpler now. The main change is that tcTySigs goes right through to a TcSigInfo in one step; previously it was split into two, part here and part later. Unsafe coercions ~~~~~~~~~~~~~~~~ Usually equality coercions have exactly the same kind on both sides. But we do allow an *unsafe* coercion between Int# and Bool, say, used in case error Bool "flah" of { True -> 3#; False -> 0# } --> (error Bool "flah") |> unsafeCoerce Bool Int# So what is the instantiation of (~#) here? unsafeCoerce Bool Int# :: (~#) ??? Bool Int# I'm using OpenKind here for now, but it's un-satisfying that the lhs and rhs of the ~ don't have precisely the same kind. More minor ~~~~~~~~~~ * HsDecl.TySynonym has its free variables attached, which makes the cycle computation in TcTyDecls.mkSynEdges easier. * Fixed a nasty reversed-comparison bug in FamInstEnv: @@ -490,7 +490,7 @@ lookup_fam_inst_env' match_fun one_sided ie fam tys n_tys = length tys extra_tys = drop arity tys (match_tys, add_extra_tys) - | arity > n_tys = (take arity tys, \res_tys -> res_tys ++ extra_tys) + | arity < n_tys = (take arity tys, \res_tys -> res_tys ++ extra_tys) | otherwise = (tys, \res_tys -> res_tys)
* Make RnEnv.lookupBindGroupOcc work on Orig RdrNamesSimon Peyton Jones2011-12-231-1/+1
| | | | | | | | Such names can come from Template Haskell; see Trac #5700 Easily fixed, happily. I also renamed lookupSubBndr to lookupSubBndrOcc, which is more descriptive.
* New kind-polymorphic coreJose Pedro Magalhaes2011-11-111-3/+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.
* Fix Trac #5592: unused-import warnings with dot-dot notationSimon Peyton Jones2011-11-021-21/+27
| | | | A subtle interaction between two complicate features!
* Implement -XConstraintKindMax Bolingbroke2011-09-061-7/+7
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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)
* Fix Trac #5372: a panic caused by over-eager error recoverySimon Peyton Jones2011-08-031-23/+36
|
* Improve semantics of wild-card expansion (fixes #5334)Simon Peyton Jones2011-07-201-17/+40
| | | | | | | | | When expanding the {..} stuff in an *expression*, take account of which variables are in scope. I updated the documentation, and in doing so found that part of the previously-documented semantics wasn't implemented (namely the stuff about fields in scope), so I fixed that too.
* Re-do (again) the handling of binders in Template HaskellSimon Peyton Jones2011-06-161-6/+9
| | | | | | | | | | See the long Note [Binders in Template Haskell] in Convert.lhs which explains it all. This patch fixes Trac #5037. The key change is that NameU binders (ones made up by newName in Template Haskell, and by TH quotations) now make Exact RdrNames again, rather than making RdrNames with heavily encoded OccNames like x[03cv]. (This encoding is what was making #5037 fail.)
* Remove HsNumTy and TypePati.Jose Pedro Magalhaes2011-05-041-4/+0
| | | | They belonged to the old generic deriving mechanism, so they can go. Adapted a lot of code as a consequence.
* Remove use of lambda with a refutable patternsimonpj@microsoft.com2010-09-231-1/+1
|
* Add separate functions for querying DynFlag and ExtensionFlag optionsIan Lynagh2010-09-181-6/+6
| | | | and remove the temporary DOpt class workaround.
* Separate the language flags from the other DynFlag'sIan Lynagh2010-07-241-1/+1
|
* Refactor (again) the handling of default methodssimonpj@microsoft.com2010-05-251-10/+9
| | | | | | | | | | | | | | | | | | 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.
* Fix Trac #3943: incorrect unused-variable warningsimonpj@microsoft.com2010-04-121-2/+12
| | | | In fixing this I did the usual little bit of refactoring
* Refactor part of the renamer to fix Trac #3901simonpj@microsoft.com2010-03-041-1/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | 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.
* Several TH/quasiquote changessimonpj@microsoft.com2010-02-101-27/+8
| | | | | | | | | | | | | | | | | | | | | | 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.