summaryrefslogtreecommitdiff
path: root/compiler/deSugar/DsMeta.hs
Commit message (Collapse)AuthorAgeFilesLines
* Typos in commentsGabor Greif2016-11-291-2/+2
|
* Handle types w/ type variables in signatures inside patterns (DsMeta)Mikhail Vorozhtsov2016-11-051-8/+6
| | | | | | | | | | | | | | | | | | The comment indicated that scoping of type variables was a large problem but Simon fixed it in e21e13fb52b99b14770cc5857df57bbcc9c85102. Thus, we can implement repP for signatures very easily in the usual way now. Reviewers: goldfire, simonpj, austin, bgamari Reviewed By: simonpj Subscribers: mpickering, simonpj, thomie Differential Revision: https://phabricator.haskell.org/D2490 GHC Trac Issues: #12164
* Implement deriving strategiesRyan Scott2016-09-301-19/+38
| | | | | | | | | | | | | | | | | | | | | | | | | | | Allows users to explicitly request which approach to `deriving` to use via keywords, e.g., ``` newtype Foo = Foo Bar deriving Eq deriving stock Ord deriving newtype Show ``` Fixes #10598. Updates haddock submodule. Test Plan: ./validate Reviewers: hvr, kosmikus, goldfire, alanz, bgamari, simonpj, austin, erikd, simonmar Reviewed By: alanz, bgamari, simonpj Subscribers: thomie, mpickering, oerjan Differential Revision: https://phabricator.haskell.org/D2280 GHC Trac Issues: #10598
* Template Haskell support for TypeApplicationsRyan Scott2016-08-291-0/+6
| | | | | | | | | | | | | | | | Summary: Fixes #12530. Test Plan: make test TEST=12530 Reviewers: austin, bgamari, hvr, goldfire Reviewed By: goldfire Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2472 GHC Trac Issues: #12530
* Template Haskell support for unboxed sumsRyan Scott2016-08-231-0/+29
| | | | | | | | | | | | | | | | | | | | | | | This adds new constructors `UnboxedSumE`, `UnboxedSumT`, and `UnboxedSumP` to represent unboxed sums in Template Haskell. One thing you can't currently do is, e.g., `reify ''(#||#)`, since I don't believe unboxed sum type/data constructors can be written in prefix form. I will look at fixing that as part of #12514. Fixes #12478. Test Plan: make test TEST=T12478_{1,2,3} Reviewers: osa1, goldfire, austin, bgamari Reviewed By: goldfire, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2448 GHC Trac Issues: #12478
* Support SCC pragmas in declaration contextÖmer Sinan Ağacan2016-07-201-2/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Not having SCCs at the top level is becoming annoying real quick. For simplest cases, it's possible to do this transformation: f x y = ... => f = {-# SCC f #-} \x y -> ... However, it doesn't work when there's a `where` clause: f x y = <t is in scope> where t = ... => f = {-# SCC f #-} \x y -> <t is out of scope> where t = ... Or when we have a "equation style" definition: f (C1 ...) = ... f (C2 ...) = ... f (C3 ...) = ... ... (usual solution is to rename `f` to `f'` and define a new `f` with a `SCC`) This patch implements support for SCC annotations in declaration contexts. This is now a valid program: f x y = ... where g z = ... {-# SCC g #-} {-# SCC f #-} Test Plan: This passes slow validate (no new failures added). Reviewers: goldfire, mpickering, austin, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: simonmar, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2407
* Have addModFinalizer expose the local type environment.Facundo Domínguez2016-07-061-0/+1
| | | | | | | | | | | | | | | | | | | | | | Summary: This annotates the splice point with 'HsSpliced ref e' where 'e' is the result of the splice. 'ref' is a reference that the typechecker will fill with the local type environment. The finalizer then reads the ref and uses the local type environment, which causes 'reify' to find local variables when run in the finalizer. Test Plan: ./validate Reviewers: simonpj, simonmar, bgamari, austin, goldfire Reviewed By: goldfire Subscribers: simonmar, thomie, mboes Differential Revision: https://phabricator.haskell.org/D2286 GHC Trac Issues: #11832
* Allow one type signature for multiple pattern synonymsMatthew Pickering2016-07-011-1/+1
| | | | | | | | | This makes pattern synonym signatures more consistent with normal type signatures. Updates haddock submodule. Differential Revision: https://phabricator.haskell.org/D2083
* Improve typechecking of let-bindingsSimon Peyton Jones2016-06-131-7/+7
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This major commit was initially triggered by #11339, but it spiraled into a major review of the way in which type signatures for bindings are handled, especially partial type signatures. On the way I fixed a number of other bugs, namely #12069 #12033 #11700 #11339 #11670 The main change is that I completely reorganised the way in which type signatures in bindings are handled. The new story is in TcSigs Note [Overview of type signatures]. Some specific: * Changes in the data types for signatures in TcRnTypes: TcIdSigInfo and new TcIdSigInst * New module TcSigs deals with typechecking type signatures and pragmas. It contains code mostly moved from TcBinds, which is already too big * HsTypes: I swapped the nesting of HsWildCardBndrs and HsImplicitBndsrs, so that the wildcards are on the oustide not the insidde in a LHsSigWcType. This is just a matter of convenient, nothing deep. There are a host of other changes as knock-on effects, and it all took FAR longer than I anticipated :-). But it is a significant improvement, I think. Lots of error messages changed slightly, some just variants but some modest improvements. New tests * typecheck/should_compile * SigTyVars: a scoped-tyvar test * ExPat, ExPatFail: existential pattern bindings * T12069 * T11700 * T11339 * partial-sigs/should_compile * T12033 * T11339a * T11670 One thing to check: * Small change to output from ghc-api/landmines. Need to check with Alan Zimmerman
* Merge MatchFixity and HsMatchContextAlan Zimmerman2016-06-061-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | Summary: MatchFixity was introduced to facilitate use of API Annotations. HsMatchContext does the same thing with more detail, but is chased through all over the place to provide context when processing a Match. Since we already have MatchFixity in the Match, it may as well provide the full context. updates submodule haddock Test Plan: ./validate Reviewers: austin, goldfire, bgamari Subscribers: thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2271 GHC Trac Issues: #12105 (cherry picked from commit 306ecad591951521ac3f5888ca8be85bf749d271)
* Add TH support for pattern synonyms (fixes #8761)Dominik Bollmann2016-05-121-12/+117
| | | | | | | | | | | | | | | | | | This commit adds Template Haskell support for pattern synonyms as requested by trac ticket #8761. Test Plan: ./validate Reviewers: thomie, jstolarek, osa1, RyanGlScott, mpickering, austin, goldfire, bgamari Reviewed By: goldfire, bgamari Subscribers: rdragon Differential Revision: https://phabricator.haskell.org/D1940 GHC Trac Issues: #8761
* StaticPointers: Allow closed vars in the static form.Facundo Domínguez2016-05-021-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: With this patch closed variables are allowed regardless of whether they are bound at the top level or not. The FloatOut pass is always performed. When optimizations are disabled, only expressions that go to the top level are floated. Thus, the applications of the StaticPtr data constructor are always floated. The CoreTidy pass makes sure the floated applications appear in the symbol table of object files. It also collects the floated bindings and inserts them in the static pointer table. The renamer does not check anymore if free variables appearing in the static form are top-level. Instead, the typechecker looks at the tct_closed flag to decide if the free variables are closed. The linter checks that applications of StaticPtr only occur at the top of top-level bindings after the FloatOut pass. The field spInfoName of StaticPtrInfo has been removed. It used to contain the name of the top-level binding that contains the StaticPtr application. However, this information is no longer available when the StaticPtr is constructed, as the binding name is determined now by the FloatOut pass. Test Plan: ./validate Reviewers: goldfire, simonpj, austin, hvr, bgamari Reviewed By: simonpj Subscribers: thomie, mpickering, mboes Differential Revision: https://phabricator.haskell.org/D2104 GHC Trac Issues: #11656
* SCC analysis for instances as well as types/classesSimon Peyton Jones2016-04-201-3/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | This big patch is in pursuit of Trac #11348. It is largely the work of Alex Veith (thank you!), with some follow-up simplification and refactoring from Simon PJ. The main payload is described in RnSource Note [Dependency analysis of type, class, and instance decls] which is pretty detailed. * There is a new data type HsDecls.TyClGroup, for a strongly connected component of type/class/instance/role decls. The hs_instds field of HsGroup disappears, in consequence This forces some knock-on changes, including a minor haddock submodule update Smaller, weakly-related things * I found that both the renamer and typechecker were building an identical env for RoleAnnots, so I put common code for RoleAnnotEnv in RnEnv. * I found that tcInstDecls1 had very clumsy error handling, so I put it together into TcInstDcls.doClsInstErrorChecks
* Add TemplateHaskell support for Overlapping pragmasIavor S. Diatchki2016-04-171-4/+25
| | | | | | | | | | Reviewers: hvr, goldfire, austin, RyanGlScott, bgamari Reviewed By: RyanGlScott, bgamari Subscribers: RyanGlScott, thomie Differential Revision: https://phabricator.haskell.org/D2118
* Fix #11797.Richard Eisenberg2016-04-121-6/+7
| | | | | | | DsMeta curiously omitted quantified tyvars in certain circumstances. This patch means it doesn't. Test case: th/T11797
* Fix suggestions for unbound variables (#11680)Jason Eisenberg2016-04-101-2/+2
| | | | | | | | | | | | | | | | | | | | | | | | | When the typechecker generates the error message for an out-of-scope variable, it now uses the GlobalRdrEnv with respect to which the variable is unbound, not the GlobalRdrEnv which is available at the time the error is reported. Doing so ensures we do not provide suggestions which themselves are out-of-scope (because they are bound in a later inter-splice group). Nonetheless, we do note in the error message if an unambiguous, exact match to the out-of-scope variable is found in a later inter-splice group, and we specify where that match is not in scope. Test Plan: ./validate Reviewers: goldfire, austin, bgamari Reviewed By: goldfire Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2000 GHC Trac Issues: #11680
* Refactor in TcMatchesSimon Peyton Jones2016-03-311-1/+1
| | | | | | | | | | * Move the several calls of tauifyMultipleMatches into tcMatches, so that it can be called only once, and the invariants are clearer * I discovered in doing this that HsLamCase had a redundant and tiresome argument, so I removed it. That in turn allowed some modest but nice code simplification
* Fix #11648.Richard Eisenberg2016-03-141-6/+13
| | | | | | | | | | | | We now check that a CUSK is really a CUSK and issue an error if it isn't. This also involves more solving and zonking in kcHsTyVarBndrs, which was the outright bug reported in #11648. Test cases: polykinds/T11648{,b} This updates the haddock submodule. [skip ci]
* Refactor visible type application.Richard Eisenberg2016-03-141-2/+2
| | | | | | | | | | | | | This replaces the old HsType and HsTypeOut constructors with HsAppType and HsAppTypeOut, leading to some simplification. (This refactoring addresses #11329.) This also fixes #11456, which stumbled over HsType (which is not an expression). test case: ghci/scripts/T11456 [skip ci]
* Refactor the typechecker to use ExpTypes.Richard Eisenberg2016-01-271-5/+5
| | | | | | | | | | | | | | | | | | | | | The idea here is described in [wiki:Typechecker]. Briefly, this refactor keeps solid track of "synthesis" mode vs "checking" in GHC's bidirectional type-checking algorithm. When in synthesis mode, the expected type is just an IORef to write to. In addition, this patch does a significant reworking of RebindableSyntax, allowing much more freedom in the types of the rebindable operators. For example, we can now have `negate :: Int -> Bool` and `(>>=) :: m a -> (forall x. a x -> m b) -> m b`. The magic is in tcSyntaxOp. This addresses tickets #11397, #11452, and #11458. Tests: typecheck/should_compile/{RebindHR,RebindNegate,T11397,T11458} th/T11452
* Replace calls to `ptext . sLit` with `text`Jan Stolarek2016-01-181-1/+1
| | | | | | | | | | | | | | | | | | | | Summary: In the past the canonical way for constructing an SDoc string literal was the composition `ptext . sLit`. But for some time now we have function `text` that does the same. Plus it has some rules that optimize its runtime behaviour. This patch takes all uses of `ptext . sLit` in the compiler and replaces them with calls to `text`. The main benefits of this patch are clener (shorter) code and less dependencies between module, because many modules now do not need to import `FastString`. I don't expect any performance benefits - we mostly use SDocs to report errors and it seems there is little to be gained here. Test Plan: ./validate Reviewers: bgamari, austin, goldfire, hvr, alanz Subscribers: goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1784
* Work SourceText in for all integer literalsAlan Zimmerman2016-01-161-6/+6
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Certain syntactic elements have integers in them, such as fixity specifications, SPECIALISE pragmas and so on. The lexer will accept mult-radix literals, with arbitrary leading zeros in these. Bring in a SourceText field to each affected AST element to capture the original literal text for use with API Annotations. Affected hsSyn elements are ``` -- See note [Pragma source text] data Activation = NeverActive | AlwaysActive | ActiveBefore SourceText PhaseNum -- Active only *strictly before* this phase | ActiveAfter SourceText PhaseNum -- Active in this phase and later deriving( Eq, Data, Typeable ) -- Eq used in comparing rules in HsDecls data Fixity = Fixity SourceText Int FixityDirection -- Note [Pragma source text] deriving (Data, Typeable) ``` and ``` | HsTickPragma -- A pragma introduced tick SourceText -- Note [Pragma source text] in BasicTypes (StringLiteral,(Int,Int),(Int,Int)) -- external span for this tick ((SourceText,SourceText),(SourceText,SourceText)) -- Source text for the four integers used in the span. -- See note [Pragma source text] in BasicTypes (LHsExpr id) ``` Updates haddock submodule Test Plan: ./validate Reviewers: goldfire, bgamari, austin Reviewed By: bgamari Subscribers: thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1781 GHC Trac Issues: #11430
* Fix #11405.Richard Eisenberg2016-01-151-0/+1
| | | | | | | This adds a new variant of AbsBinds that is used solely for bindings with a type signature. This allows for a simpler desugaring that does not produce the bogus output that tripped up Core Lint in ticket #11405. Should make other desugarings simpler, too.
* Fix Template Haskell's handling of infix GADT constructorsRyanGlScott2016-01-081-2/+4
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This is the second (and hopefully last) fix needed to make TH handle GADTs properly (after D1465). This Diff addresses some issues with infix GADT constructors, specifically: * Before, you could not determine if a GADT constructor was declared infix because TH did not give you the ability to determine if there is a //user-specified// fixity declaration for that constructor. The return type of `reifyFixity` was changed to `Maybe Fixity` so that it yields `Just` the fixity is there is a fixity declaration, and `Nothing` otherwise (indicating it has `defaultFixity`). * `DsMeta`/`Convert` were changed so that infix GADT constructors are turned into `GadtC`, not `InfixC` (which should be reserved for Haskell98 datatype declarations). * Some minor fixes to the TH pretty-printer so that infix GADT constructors will be parenthesized in GADT signatures. Fixes #11345. Test Plan: ./validate Reviewers: goldfire, austin, bgamari, jstolarek Reviewed By: jstolarek Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1744 GHC Trac Issues: #11345
* Change Template Haskell representation of GADTs.Jan Stolarek2016-01-061-17/+7
| | | | | | | | | | | | | | | Previous representation of GADTs in TH was not expressive enough to express possible GADT return types. See #11341 Test Plan: ./validate Reviewers: goldfire, austin, bgamari Subscribers: thomie, RyanGlScott Differential Revision: https://phabricator.haskell.org/D1738 GHC Trac Issues: #11341
* Comments and white spaceSimon Peyton Jones2015-12-231-3/+3
|
* Refactor named wildcards (again)Simon Peyton Jones2015-12-221-7/+0
| | | | | | | | | | | | | | | | | | | | | | | | | | Michal's work on #10982, #11098, refactored the handling of named wildcards by making them more like ordinary type variables. This patch takes the same idea to its logical conclusion, resulting in a much tidier, tighter implementation. Read Note [The wildcard story for types] in HsTypes. Changes: * Named wildcards are ordinary type variables, throughout * HsType no longer has a data constructor for named wildcards (was NamedWildCard in HsWildCardInfo). Named wildcards are simply HsTyVars * Similarly named wildcards disappear from Template Haskell * I refactored RnTypes to avoid polluting LocalRdrEnv with something as narrow as named wildcards. Instead the named wildcard set is carried in RnTyKiEnv. There is a submodule update for Haddock.
* Rework Template Haskell's handling of strictnessRyanGlScott2015-12-221-13/+22
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | Currently, Template Haskell's treatment of strictness is not enough to cover all possible combinations of unpackedness and strictness. In addition, it isn't equipped to deal with new features (such as `-XStrictData`) which can change a datatype's fields' strictness during compilation. To address this, I replaced TH's `Strict` datatype with `SourceUnpackedness` and `SourceStrictness` (which give the programmer a more complete toolkit to configure a datatype field's strictness than just `IsStrict`, `IsLazy`, and `Unpack`). I also added the ability to reify a constructor fields' strictness post-compilation through the `reifyConStrictness` function. Fixes #10697. Test Plan: ./validate Reviewers: simonpj, goldfire, bgamari, austin Reviewed By: goldfire, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1603 GHC Trac Issues: #10697
* Add proper GADTs support to Template HaskellJan Stolarek2015-12-211-203/+143
| | | | | | | | | | | | | | | | Until now GADTs were supported in Template Haskell by encoding them using normal data types. This patch adds proper support for representing GADTs in TH. Test Plan: T10828 Reviewers: goldfire, austin, bgamari Subscribers: thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1465 GHC Trac Issues: #10828
* Use Cxt for deriving clauses in TH (#10819)Ben Gamari2015-12-141-14/+14
| | | | | | | | | | | | | | | | | | | | | | | Summary: Deriving clauses in the TH representations of data, newtype, data instance, and newtype instance declarations previously were just [Name], which didn't allow for more complex derived classes, eg. multi-parameter typeclasses. This switches out [Name] for Cxt, representing the derived classes as types instead of names. Test Plan: validate Reviewers: goldfire, spinda, austin Reviewed By: goldfire, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1202 GHC Trac Issues: #10819
* Add kind equalities to GHC.Richard Eisenberg2015-12-111-48/+45
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This implements the ideas originally put forward in "System FC with Explicit Kind Equality" (ICFP'13). There are several noteworthy changes with this patch: * We now have casts in types. These change the kind of a type. See new constructor `CastTy`. * All types and all constructors can be promoted. This includes GADT constructors. GADT pattern matches take place in type family equations. In Core, types can now be applied to coercions via the `CoercionTy` constructor. * Coercions can now be heterogeneous, relating types of different kinds. A coercion proving `t1 :: k1 ~ t2 :: k2` proves both that `t1` and `t2` are the same and also that `k1` and `k2` are the same. * The `Coercion` type has been significantly enhanced. The documentation in `docs/core-spec/core-spec.pdf` reflects the new reality. * The type of `*` is now `*`. No more `BOX`. * Users can write explicit kind variables in their code, anywhere they can write type variables. For backward compatibility, automatic inference of kind-variable binding is still permitted. * The new extension `TypeInType` turns on the new user-facing features. * Type families and synonyms are now promoted to kinds. This causes trouble with parsing `*`, leading to the somewhat awkward new `HsAppsTy` constructor for `HsType`. This is dispatched with in the renamer, where the kind `*` can be told apart from a type-level multiplication operator. Without `-XTypeInType` the old behavior persists. With `-XTypeInType`, you need to import `Data.Kind` to get `*`, also known as `Type`. * The kind-checking algorithms in TcHsType have been significantly rewritten to allow for enhanced kinds. * The new features are still quite experimental and may be in flux. * TODO: Several open tickets: #11195, #11196, #11197, #11198, #11203. * TODO: Update user manual. Tickets addressed: #9017, #9173, #7961, #10524, #8566, #11142. Updates Haddock submodule.
* Refactor ConDeclAlan Zimmerman2015-12-071-21/+77
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The ConDecl type in HsDecls is an uneasy compromise. For the most part, HsSyn directly reflects the syntax written by the programmer; and that gives just the right "pegs" on which to hang Alan's API annotations. But ConDecl doesn't properly reflect the syntax of Haskell-98 and GADT-style data type declarations. To be concrete, here's a draft new data type ```lang=hs data ConDecl name | ConDeclGADT { con_names :: [Located name] , con_type :: LHsSigType name -- The type after the ‘::’ , con_doc :: Maybe LHsDocString } | ConDeclH98 { con_name :: Located name , con_qvars :: Maybe (LHsQTyVars name) -- User-written forall (if any), and its implicit -- kind variables -- Non-Nothing needs -XExistentialQuantification , con_cxt :: Maybe (LHsContext name) -- ^ User-written context (if any) , con_details :: HsConDeclDetails name -- ^ Arguments , con_doc :: Maybe LHsDocString -- ^ A possible Haddock comment. } deriving (Typeable) ``` Note that For GADTs, just keep a type. That's what the user writes. NB:HsType can represent records on the LHS of an arrow: { x:Int,y:Bool} -> T con_qvars and con_cxt are both Maybe because they are both optional (the forall and the context of an existential data type For ConDeclGADT the type variables of the data type do not scope over the con_type; whereas for ConDeclH98 they do scope over con_cxt and con_details. Updates haddock submodule. Test Plan: ./validate Reviewers: simonpj, erikd, hvr, goldfire, austin, bgamari Subscribers: erikd, goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1558 GHC Trac Issues: #11028
* Refactor treatment of wildcardsSimon Peyton Jones2015-12-011-72/+112
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch began as a modest refactoring of HsType and friends, to clarify and tidy up exactly where quantification takes place in types. Although initially driven by making the implementation of wildcards more tidy (and fixing a number of bugs), I gradually got drawn into a pretty big process, which I've been doing on and off for quite a long time. There is one compiler performance regression as a result of all this, in perf/compiler/T3064. I still need to look into that. * The principal driving change is described in Note [HsType binders] in HsType. Well worth reading! * Those data type changes drive almost everything else. In particular we now statically know where (a) implicit quantification only (LHsSigType), e.g. in instance declaratios and SPECIALISE signatures (b) implicit quantification and wildcards (LHsSigWcType) can appear, e.g. in function type signatures * As part of this change, HsForAllTy is (a) simplified (no wildcards) and (b) split into HsForAllTy and HsQualTy. The two contructors appear when and only when the correponding user-level construct appears. Again see Note [HsType binders]. HsExplicitFlag disappears altogether. * Other simplifications - ExprWithTySig no longer needs an ExprWithTySigOut variant - TypeSig no longer needs a PostRn name [name] field for wildcards - PatSynSig records a LHsSigType rather than the decomposed pieces - The mysterious 'GenericSig' is now 'ClassOpSig' * Renamed LHsTyVarBndrs to LHsQTyVars * There are some uninteresting knock-on changes in Haddock, because of the HsSyn changes I also did a bunch of loosely-related changes: * We already had type synonyms CoercionN/CoercionR for nominal and representational coercions. I've added similar treatment for TcCoercionN/TcCoercionR mkWpCastN/mkWpCastN All just type synonyms but jolly useful. * I record-ised ForeignImport and ForeignExport * I improved the (poor) fix to Trac #10896, by making TcTyClsDecls.checkValidTyCl recover from errors, but adding a harmless, abstract TyCon to the envt if so. * I did some significant refactoring in RnEnv.lookupSubBndrOcc, for reasons that I have (embarrassingly) now totally forgotten. It had to do with something to do with import and export Updates haddock submodule.
* ApiAnnotations: Make all RdrName occurences LocatedAlan Zimmerman2015-11-231-20/+20
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | At the moment the API Annotations can only be used on the ParsedSource, as there are changes made to the RenamedSource that prevent it from being used to round trip source code. It is possible to build a map from every Located Name in the RenamedSource from its location to the Name, which can then be used when resolved names are required when changing the ParsedSource. However, there are instances where the identifier is not located, specifically (GHC.VarPat name) (GHC.HsVar name) (GHC.UserTyVar name) (GHC.HsTyVar name) Replace each of the name types above with (Located name) Updates the haddock submodule. Test Plan: ./validate Reviewers: austin, goldfire, bgamari Reviewed By: bgamari Subscribers: goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1512 GHC Trac Issues: #11019
* Refactor HsExpr.RecordCon, RecordUpdSimon Peyton Jones2015-11-181-2/+2
| | | | | | | | | | | | | | This follows Matthew's patch making pattern synoyms work with records. This patch - replaces the (PostTc id [FieldLabel]) field of RecordCon with (PostTc id ConLike) - record-ises both RecordCon and RecordUpd, which both have quite a lot of fields. No change in behaviour
* Implement OverloadedLabelsAdam Gundry2015-11-171-0/+1
| | | | | | | | | | | | | | See https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/OverloadedLabels for the big picture. Reviewers: goldfire, simonpj, austin, hvr, bgamari Reviewed By: simonpj, bgamari Subscribers: kosmikus, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1331
* APIAnnotations:add Locations in hsSyn for layoutAlan Zimmerman2015-11-131-16/+19
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: At the moment ghc-exactprint, which uses the GHC API Annotations to provide a framework for roundtripping Haskell source code with optional AST edits, has to implement a horrible workaround to manage the points where layout needs to be captured. These are MatchGroup HsDo HsCmdDo HsLet LetStmt HsCmdLet GRHSs To provide a more natural representation, the contents subject to layout rules need to be wrapped in a SrcSpan. This commit does this. Trac ticket #10250 Test Plan: ./validate Reviewers: hvr, goldfire, bgamari, austin, mpickering Reviewed By: mpickering Subscribers: thomie, mpickering Differential Revision: https://phabricator.haskell.org/D1370 GHC Trac Issues: #10250
* Remove PatSynBuilderIdMatthew Pickering2015-11-071-1/+1
| | | | | | | | | | | | | | | | | Summary: It was only used to pass field labels between the typechecker and desugarer. Instead we add an extra field the RecordCon to carry this information. Reviewers: austin, goldfire, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1443 GHC Trac Issues: #11057
* Disambiguate record selectors by type signatureAdam Gundry2015-10-301-1/+5
| | | | | | | | | | | | | | | This makes DuplicateRecordFields more liberal in when it will accept ambiguous record selectors, making use of type information in a similar way to updates. See Note [Disambiguating record fields] for more details. I've also refactored how record updates are disambiguated. Test Plan: New and amended tests in overloadedrecflds Reviewers: simonpj, goldfire, bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1391
* Record pattern synonymsMatthew Pickering2015-10-291-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch implements an extension to pattern synonyms which allows user to specify pattern synonyms using record syntax. Doing so generates appropriate selectors and update functions. === Interaction with Duplicate Record Fields === The implementation given here isn't quite as general as it could be with respect to the recently-introduced `DuplicateRecordFields` extension. Consider the following module: {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE PatternSynonyms #-} module Main where pattern S{a, b} = (a, b) pattern T{a} = Just a main = do print S{ a = "fst", b = "snd" } print T{ a = "a" } In principle, this ought to work, because there is no ambiguity. But at the moment it leads to a "multiple declarations of a" error. The problem is that pattern synonym record selectors don't do the same name mangling as normal datatypes when DuplicateRecordFields is enabled. They could, but this would require some work to track the field label and selector name separately. In particular, we currently represent datatype selectors in the third component of AvailTC, but pattern synonym selectors are just represented as Avails (because they don't have a corresponding type constructor). Moreover, the GlobalRdrElt for a selector currently requires it to have a parent tycon. (example due to Adam Gundry) === Updating Explicitly Bidirectional Pattern Synonyms === Consider the following ``` pattern Silly{a} <- [a] where Silly a = [a, a] f1 = a [5] -- 5 f2 = [5] {a = 6} -- currently [6,6] ``` === Fixing Polymorphic Updates === They were fixed by adding these two lines in `dsExpr`. This might break record updates but will be easy to fix. ``` + ; let req_wrap = mkWpTyApps (mkTyVarTys univ_tvs) - , pat_wrap = idHsWrapper } +, pat_wrap = req_wrap } ``` === Mixed selectors error === Note [Mixed Record Field Updates] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider the following pattern synonym. data MyRec = MyRec { foo :: Int, qux :: String } pattern HisRec{f1, f2} = MyRec{foo = f1, qux=f2} This allows updates such as the following updater :: MyRec -> MyRec updater a = a {f1 = 1 } It would also make sense to allow the following update (which we reject). updater a = a {f1 = 1, qux = "two" } ==? MyRec 1 "two" This leads to confusing behaviour when the selectors in fact refer the same field. updater a = a {f1 = 1, foo = 2} ==? ??? For this reason, we reject a mixture of pattern synonym and normal record selectors in the same update block. Although of course we still allow the following. updater a = (a {f1 = 1}) {foo = 2} > updater (MyRec 0 "str") MyRec 2 "str"
* Add typed holes support in Template Haskell.Jan Stolarek2015-10-161-5/+19
| | | | | Fixes #10267. Typed holes in typed Template Haskell currently don't work. See #10945 and #10946.
* Implement DuplicateRecordFieldsAdam Gundry2015-10-161-5/+20
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This implements DuplicateRecordFields, the first part of the OverloadedRecordFields extension, as described at https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/DuplicateRecordFields This includes fairly wide-ranging changes in order to allow multiple records within the same module to use the same field names. Note that it does *not* allow record selector functions to be used if they are ambiguous, and it does not have any form of type-based disambiguation for selectors (but it does for updates). Subsequent parts will make overloading selectors possible using orthogonal extensions, as described on the wiki pages. This part touches quite a lot of the codebase, and requires changes to several GHC API datatypes in order to distinguish between field labels (which may be overloaded) and selector function names (which are always unique). The Haddock submodule has been adapted to compile with the GHC API changes, but it will need further work to properly support modules that use the DuplicateRecordFields extension. Test Plan: New tests added in testsuite/tests/overloadedrecflds; these will be extended once the other parts are implemented. Reviewers: goldfire, bgamari, simonpj, austin Subscribers: sjcjoosten, haggholm, mpickering, bgamari, tibbe, thomie, goldfire Differential Revision: https://phabricator.haskell.org/D761
* Rename package key to unit ID, and installed package ID to component ID.Edward Z. Yang2015-10-141-1/+1
| | | | | | Comes with Haddock submodule update. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>
* Allow TH quoting of assoc type defaults.Richard Eisenberg2015-09-201-10/+19
| | | | This fixes #10811.
* ApplicativeDo transformationSimon Marlow2015-09-171-1/+1
| | | | | | | | | | | | | | | | Summary: This is an implementation of the ApplicativeDo proposal. See the Note [ApplicativeDo] in RnExpr for details on the current implementation, and the wiki page https://ghc.haskell.org/trac/ghc/wiki/ApplicativeDo for design notes. Test Plan: validate Reviewers: simonpj, goldfire, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D729
* Injective type familiesJan Stolarek2015-09-031-56/+124
| | | | | | | | | | | | | | | | | | | For details see #6018, Phab:D202 and the wiki page: https://ghc.haskell.org/trac/ghc/wiki/InjectiveTypeFamilies This patch also wires-in Maybe data type and updates haddock submodule. Test Plan: ./validate Reviewers: simonpj, goldfire, austin, bgamari Subscribers: mpickering, bgamari, alanz, thomie, goldfire, simonmar, carter Differential Revision: https://phabricator.haskell.org/D202 GHC Trac Issues: #6018
* Implementation of StrictData language extensionAdam Sandberg Eriksson2015-07-271-6/+6
| | | | | | | | | | | | | | | | | | | | | | | | | | | | This implements the `StrictData` language extension, which lets the programmer default to strict data fields in datatype declarations on a per-module basis. Specification and motivation can be found at https://ghc.haskell.org/trac/ghc/wiki/StrictPragma This includes a tricky parser change due to conflicts regarding `~` in the type level syntax: all ~'s are parsed as strictness annotations (see `strict_mark` in Parser.y) and then turned into equality constraints at the appropriate places using `RdrHsSyn.splitTilde`. Updates haddock submodule. Test Plan: Validate through Harbormaster. Reviewers: goldfire, austin, hvr, simonpj, tibbe, bgamari Reviewed By: simonpj, tibbe, bgamari Subscribers: lelf, simonpj, alanz, goldfire, thomie, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D1033 GHC Trac Issues: #8347
* Do not treat prim and javascript imports as C imports in TH and QQLuite Stegeman2015-07-201-3/+5
| | | | | | | | | | | | Reviewers: austin, hvr, goldfire, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1070 GHC Trac Issues: #10638
* Support wild cards in TH splicesThomas Winant2015-07-201-7/+28
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | - Declaration splices: partial type signatures are fully supported in TH declaration splices. For example, the wild cards in the example below will unify with `Eq a` and `a -> a -> Bool`, as expected: ``` [d| foo :: _ => _ foo x y = x == y |] ``` - Expression splices: anonymous and named wild cards are supported in expression signatures, but extra-constraints wild cards aren't. Just as is the case for regular expression signatures. ``` [e | Just True :: _a _ |] ``` - Typed expression splices: the same wildcards as in (untyped) expression splices are supported. - Pattern splices: TH doesn't support type signatures in pattern splices, consequently, partial type signatures aren't supported either. - Type splices: partial type signatures are only partially supported in type splices, specifically: only anonymous wild cards are allowed. So `[t| _ |]`, `[t| _ -> Maybe _ |]` will work, but `[t| _ => _ |]` or `[| _a |]` won't (without `-XNamedWildCards`, the latter will work as the named wild card is treated as a type variable). Normally, named wild cards are collected before renaming a (partial) type signature. However, TH type splices are run during renaming, i.e. after the initial traversal, leading to out of scope errors for named wild cards. We can't just extend the initial traversal to collect the named wild cards in TH type splices, as we'd need to expand them, which is supposed to happen only once, during renaming. Similarly, the extra-constraints wild card is handled right before renaming too, and is therefore also not supported in a TH type splice. Another reason not to support extra-constraints wild cards in TH type splices is that a single signature can contain many TH type splices, whereas it mustn't contain more than one extra-constraints wild card. Enforcing would this be hard the way things are currently organised. Anonymous wild cards pose no problem, because they start without names and are given names during renaming. These names are collected right after renaming. The names generated for anonymous wild cards in TH type splices will thus be collected as well. With a more invasive refactoring of the renaming, partial type signatures could be fully supported in TH type splices. As only anonymous wild cards have been requested so far, these small changes satisfying this request will do for now. Also don't forget that a TH declaration splices support all kinds of wild cards. - Extra-constraints wild cards were silently ignored in expression and pattern signatures, appropriate error messages are now generated. Test Plan: run new tests Reviewers: austin, goldfire, adamgundry, bgamari Reviewed By: goldfire, adamgundry, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1048 GHC Trac Issues: #10094, #10548
* Handle Char#, Addr# in TH quasiquoter (fixes #10620)RyanGlScott2015-07-171-0/+13
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | DsMeta does not attempt to handle quasiquoted Char# or Addr# values, which causes expressions like `$([| 'a'# |])` or `$([| "abc"# |])` to fail with an `Exotic literal not (yet) handled by Template Haskell` error. To fix this, the API of `template-haskell` had to be changed so that `Lit` now has an extra constructor `CharPrimL` (a `StringPrimL` constructor already existed, but it wasn't used). In addition, `DsMeta` has to manipulate `CoreExpr`s directly that involve `Word8`s. In order to do this, `Word8` had to be added as a wired-in type to `TysWiredIn`. Actually converting from `HsCharPrim` and `HsStringPrim` to `CharPrimL` and `StringPrimL`, respectively, is pretty straightforward after that, since both `HsCharPrim` and `CharPrimL` use `Char` internally, and `HsStringPrim` uses a `ByteString` internally, which can easily be converted to `[Word8]`, which is what `StringPrimL` uses. Reviewers: goldfire, austin, simonpj, bgamari Reviewed By: simonpj, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1054 GHC Trac Issues: #10620