summaryrefslogtreecommitdiff
path: root/compiler/deSugar/DsMeta.hs
Commit message (Collapse)AuthorAgeFilesLines
* 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
* Refactor wild card renamingThomas Winant2015-06-091-1/+6
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: Refactor wild card error reporting * Merge `HsWildcardTy` and `HsNamedWildcardTy` into one constructor `HsWildCardTy` with as field the new type `HsWildCardInfo`, which has two constructors: `AnonWildCard` and `NamedWildCard`. * All partial type checks are removed from `RdrHsSyn.hs` and are now done during renaming in order to report better error messages. When wild cards are allowed in a type, the new function `rnLHsTypeWithWildCards` (or `rnHsSigTypeWithWildCards`) should be used. This will bring the named wild cards into scope before renaming them. When this is not done, renaming will trigger "Unexpected wild card..." errors. Unfortunately, this has to be done separately for anonymous wild cards because they are given a fresh name during renaming, so they will not cause an out-of-scope error. They are handled in `tc_hs_type`, as a special case of a lookup that fails. The previous opt-out approach is replaced with an opt-in approach. No more panics because of forgotten checks! * `[t| _ |]` isn't caught by the above two checks, so it is currently handled by a special case. The error message (generated in the `DsM` monad) doesn't provide as much context information as the other cases. * Instead of three (!) functions that walk `HsType`, there is now only one pure function called `collectWildCards`. * Alternative approach: catch all unwanted wild cards in `rnHsTyKi` by looking at the `HsDocContext`. This will reduce the number of places to catch unwanted wild cards form three to one, and make the error messages more uniform, albeit less informative, as the error context for renaming is not as informative as the one for type checking. A new constructor of `HsDocContext` will be required for pattern synonyms signatures. Small problem: currently type-class type signatures can't be distinguished from type signatures using the `HsDocContext`. This requires an update to the Haddock submodule. Test Plan: validate Reviewers: goldfire, simonpj, austin Reviewed By: simonpj Subscribers: bgamari, thomie, goldfire Differential Revision: https://phabricator.haskell.org/D613 GHC Trac Issues: #10098
* ApiAnnotations : strings in warnings do not return SourceTextAlan Zimmerman2015-06-011-5/+7
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. This patch now deals with all remaining instances of getSTRING to bring in a SourceText for each. This updates the haddock submodule as well, for the AST change. Test Plan: ./validate Reviewers: hvr, austin, goldfire Reviewed By: austin Subscribers: bgamari, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D907 GHC Trac Issues: #10313
* Refactor tuple constraintsSimon Peyton Jones2015-05-181-837/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Make tuple constraints be handled by a perfectly ordinary type class, with the component constraints being the superclasses: class (c1, c2) => (c2, c2) This change was provoked by #10359 inability to re-use a given tuple constraint as a whole #9858 confusion between term tuples and constraint tuples but it's generally a very nice simplification. We get rid of - In Type, the TuplePred constructor of PredTree, and all the code that dealt with TuplePreds - In TcEvidence, the constructors EvTupleMk, EvTupleSel See Note [How tuples work] in TysWiredIn. Of course, nothing is ever entirely simple. This one proved quite fiddly. - I did quite a bit of renaming, which makes this patch touch a lot of modules. In partiuclar tupleCon -> tupleDataCon. - I made constraint tuples known-key rather than wired-in. This is different to boxed/unboxed tuples, but it proved awkward to have all the superclass selectors wired-in. Easier just to use the standard mechanims. - While I was fiddling with known-key names, I split the TH Name definitions out of DsMeta into a new module THNames. That meant that the known-key names can all be gathered in PrelInfo, without causing module loops. - I found that the parser was parsing an import item like T( .. ) as a *data constructor* T, and then using setRdrNameSpace to fix it. Stupid! So I changed the parser to parse a *type constructor* T, which means less use of setRdrNameSpace. I also improved setRdrNameSpace to behave better on Exact Names. Largely on priciple; I don't think it matters a lot. - When compiling a data type declaration for a wired-in thing like tuples (,), or lists, we don't really need to look at the declaration. We have the wired-in thing! And not doing so avoids having to line up the uniques for data constructor workers etc. See Note [Declarations for wired-in things] - I found that FunDeps.oclose wasn't taking superclasses into account; easily fixed. - Some error message refactoring for invalid constraints in TcValidity - Haddock needs to absorb the change too; so there is a submodule update
* Revert multiple commitsAustin Seipp2015-05-141-3/+837
| | | | | | | | | | | | | | | | | | | | This reverts multiple commits from Simon: - 04a484eafc9eb9f8774b4bdd41a5dc6c9f640daf Test Trac #10359 - a9ccd37add8315e061c02e5bf26c08f05fad9ac9 Test Trac #10403 - c0aae6f699cbd222d826d0b8d78d6cb3f682079e Test Trac #10248 - eb6ca851f553262efe0824b8dcbe64952de4963d Make the "matchable-given" check happen first - ca173aa30467a0b1023682d573fcd94244d85c50 Add a case to checkValidTyCon - 51cbad15f86fca1d1b0e777199eb1079a1b64d74 Update haddock submodule - 6e1174da5b8e0b296f5bfc8b39904300d04eb5b7 Separate transCloVarSet from fixVarSet - a8493e03b89f3b3bfcdb6005795de050501f5c29 Fix imports in HscMain (stage2) - a154944bf07b2e13175519bafebd5a03926bf105 Two wibbles to fix the build - 5910a1bc8142b4e56a19abea104263d7bb5c5d3f Change in capitalisation of error msg - 130e93aab220bdf14d08028771f83df210da340b Refactor tuple constraints - 8da785d59f5989b9a9df06386d5bd13f65435bc0 Delete commented-out line These break the build by causing Haddock to fail mysteriously when trying to examine GHC.Prim it seems.
* Refactor tuple constraintsSimon Peyton Jones2015-05-131-837/+3
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Make tuple constraints be handled by a perfectly ordinary type class, with the component constraints being the superclasses: class (c1, c2) => (c2, c2) This change was provoked by #10359 inability to re-use a given tuple constraint as a whole #9858 confusion between term tuples and constraint tuples but it's generally a very nice simplification. We get rid of - In Type, the TuplePred constructor of PredTree, and all the code that dealt with TuplePreds - In TcEvidence, the constructors EvTupleMk, EvTupleSel See Note [How tuples work] in TysWiredIn. Of course, nothing is ever entirely simple. This one proved quite fiddly. - I did quite a bit of renaming, which makes this patch touch a lot of modules. In partiuclar tupleCon -> tupleDataCon. - I made constraint tuples known-key rather than wired-in. This is different to boxed/unboxed tuples, but it proved awkward to have all the superclass selectors wired-in. Easier just to use the standard mechanims. - While I was fiddling with known-key names, I split the TH Name definitions out of DsMeta into a new module THNames. That meant that the known-key names can all be gathered in PrelInfo, without causing module loops. - I found that the parser was parsing an import item like T( .. ) as a *data constructor* T, and then using setRdrNameSpace to fix it. Stupid! So I changed the parser to parse a *type constructor* T, which means less use of setRdrNameSpace. I also improved setRdrNameSpace to behave better on Exact Names. Largely on priciple; I don't think it matters a lot. - When compiling a data type declaration for a wired-in thing like tuples (,), or lists, we don't really need to look at the declaration. We have the wired-in thing! And not doing so avoids having to line up the uniques for data constructor workers etc. See Note [Declarations for wired-in things] - I found that FunDeps.oclose wasn't taking superclasses into account; easily fixed. - Some error message refactoring for invalid constraints in TcValidity
* Revert "API Annotations : add Locations in hsSyn were layout occurs"Austin Seipp2015-05-061-19/+16
| | | | | | | This reverts commit fb54b2c11cc7f2cfbafa35b6a1819d7443aa5494. As Alan pointed out, this will make cherry picking a lot harder until 7.10.2, so lets back it out until after the release.
* API Annotations : add Locations in hsSyn were layout occursAlan Zimmerman2015-05-061-16/+19
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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 Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D815 GHC Trac Issues: #10250
* Permit empty closed type familiesAdam Gundry2015-05-041-6/+8
| | | | | | | | | | | | | | | | | | | Fixes #9840 and #10306, and includes an alternative resolution to #8028. This permits empty closed type families, and documents them in the user guide. It updates the Haddock submodule to support the API change. Test Plan: Added `indexed-types/should_compile/T9840` and updated `indexed-types/should_fail/ClosedFam4` and `th/T8028`. Reviewers: austin, simonpj, goldfire Reviewed By: goldfire Subscribers: bgamari, jstolarek, thomie, goldfire Differential Revision: https://phabricator.haskell.org/D841 GHC Trac Issues: #9840, #10306
* Refactor the handling of quasi-quotesSimon Peyton Jones2015-02-101-5/+10
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | As Trac #10047 points out, a quasi-quotation [n|...blah...|] is supposed to behave exactly like $(n "...blah..."). But it doesn't! This was outright wrong: quasiquotes were being run even inside brackets. Now that TH supports both typed and untyped splices, a quasi-quote is properly regarded as a particular syntax for an untyped splice. But apart from that they should be treated the same. So this patch refactors the handling of quasiquotes to do just that. The changes touch quite a lot of files, but mostly in a routine way. The biggest changes by far are in RnSplice, and more minor changes in TcSplice. These are the places where there was real work to be done. Everything else is routine knock-on changes. * No more QuasiQuote forms in declarations, expressions, types, etc. So we get rid of these data constructors * HsBinds.QuasiQuoteD * HsExpr.HsSpliceE * HsPat.QuasiQuotePat * HsType.HsQuasiQuoteTy * We get rid of the HsQuasiQuote type altogether * Instead, we augment the HsExpr.HsSplice type to have three consructors, for the three types of splice: * HsTypedSplice * HsUntypedSplice * HsQuasiQuote There are some related changes in the data types in HsExpr near HsSplice. Specifically: PendingRnSplice, PendingTcSplice, UntypedSpliceFlavour. * In Hooks, we combine rnQuasiQuoteHook and rnRnSpliceHook into one. A smaller, clearer interface. * We have to update the Haddock submodule, to accommodate the hsSyn changes
* API Annotations tweaks.Alan Zimmerman2015-01-161-28/+33
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: HsTyLit now has SourceText Update documentation of HsSyn to reflect which annotations are attached to which element. Ensure that the parser always keeps HsSCC and HsTickPragma values, to be ignored in the desugar phase if not needed Bringing in SourceText for pragmas Add Location in NPlusKPat Add Location in FunDep Make RecCon payload Located Explicitly add AnnVal to RdrName where it is compound Add Location in IPBind Add Location to name in IEThingAbs Add Maybe (Located id,Bool) to Match to track fun_id,infix This includes converting Match into a record and adding a note about why the fun_id needs to be replicated in the Match. Add Location in KindedTyVar Sort out semi-colons for parsing - import statements - stmts - decls - decls_cls - decls_inst This updates the haddock submodule. Test Plan: ./validate Reviewers: hvr, austin, goldfire, simonpj Reviewed By: simonpj Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D538
* Improve HsBangSimon Peyton Jones2015-01-081-3/+3
| | | | | | | | | | | | Provoked by questions from Johan - Improve comments, fix misleading stuff - Add commented synonyms for HsSrcBang, HsImplBang, and use them throughout - Rename HsUserBang to HsSrcBang - Rename dataConStrictMarks to dataConSrcBangs dataConRepBangs to dataConImplBangs This renaming affects Haddock in a trivial way, hence submodule update
* Fix dll-split problem with patch 'Make Core Lint check for locally-bound ↵Simon Peyton Jones2014-12-151-9/+9
| | | | | | | | | | | | | | | | | | | | | GlobalId' The trouble was that my changes made a lot more files transitively link with DynFlags, which is the root module for the revolting Windows dll-split stuff. Anyway this patch fixes it, in a good way: - Make GHC/Hooks *not* import DsMonad, because DsMonad imports too much other stuff (notably tcLookup variants). Really, Hooks depends only on *types* not *code*. - To do this I need the DsM type, and the types it depends on, not to be part of DsMonad. So I moved it to TcRnTypes, which is where the similar pieces for the TcM and IfM monads live. - We can then delete DsMonad.hs-boot - There are a bunch of knock-on change, of no great significance
* Implement -XStaticValuesFacundo Domínguez2014-12-091-3/+6
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: As proposed in [1], this extension introduces a new syntactic form `static e`, where `e :: a` can be any closed expression. The static form produces a value of type `StaticPtr a`, which works as a reference that programs can "dereference" to get the value of `e` back. References are like `Ptr`s, except that they are stable across invocations of a program. The relevant wiki pages are [2, 3], which describe the motivation/ideas and implementation plan respectively. [1] Jeff Epstein, Andrew P. Black, and Simon Peyton-Jones. Towards Haskell in the cloud. SIGPLAN Not., 46(12):118–129, September 2011. ISSN 0362-1340. [2] https://ghc.haskell.org/trac/ghc/wiki/StaticPointers [3] https://ghc.haskell.org/trac/ghc/wiki/StaticPointers/ImplementationPlan Authored-by: Facundo Domínguez <facundo.dominguez@tweag.io> Authored-by: Mathieu Boespflug <m@tweag.io> Authored-by: Alexander Vershilov <alexander.vershilov@tweag.io> Test Plan: `./validate` Reviewers: hvr, simonmar, simonpj, austin Reviewed By: simonpj, austin Subscribers: qnikst, bgamari, mboes, carter, thomie, goldfire Differential Revision: https://phabricator.haskell.org/D550 GHC Trac Issues: #7015
* Implement Partial Type SignaturesThomas Winant2014-11-281-5/+5
| | | | | | | | | | | | | | | | | | | | Summary: Add support for Partial Type Signatures, i.e. holes in types, see: https://ghc.haskell.org/trac/ghc/wiki/PartialTypeSignatures This requires an update to the Haddock submodule. Test Plan: validate Reviewers: austin, goldfire, simonpj Reviewed By: simonpj Subscribers: thomie, Iceland_jack, dominique.devriese, simonmar, carter, goldfire Differential Revision: https://phabricator.haskell.org/D168 GHC Trac Issues: #9478
* Capture original source for literalsAlan Zimmerman2014-11-211-20/+20
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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-41/+59
| | | | | | | | | | | | | | | | | | | | | | | | | 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
* Make calling conventions in template haskell Syntax.hs consistent with those ↵Luite Stegeman2014-11-191-24/+33
| | | | | | | | | | | | | | | | | | in ghc ForeignCall.hs this impliments #9703 from ghc trac Test Plan: still needs tests Reviewers: cmsaperstein, ekmett, goldfire, austin Reviewed By: goldfire, austin Subscribers: goldfire, thomie, carter, simonmar Differential Revision: https://phabricator.haskell.org/D353 GHC Trac Issues: #9703