summaryrefslogtreecommitdiff
path: root/compiler/basicTypes/PatSyn.hs
Commit message (Collapse)AuthorAgeFilesLines
* Modules: Core (#13009)Sylvain Henry2020-03-161-484/+0
| | | | Update submodule: haddock
* compiler: Qualify imports of Data.ListBen Gamari2020-02-081-1/+1
|
* Ensure that coreView/tcView are able to inlineBen Gamari2019-11-131-0/+1
| | | | | | | | | | | | | | | | | | | | Previously an import cycle between Type and TyCoRep meant that several functions in TyCoRep ended up SOURCE import coreView. This is quite unfortunate as coreView is intended to be fused into a larger pattern match and not incur an extra call. Fix this with a bit of restructuring: * Move the functions in `TyCoRep` which depend upon things in `Type` into `Type` * Fold contents of `Kind` into `Type` and turn `Kind` into a simple wrapper re-exporting kind-ish things from `Type` * Clean up the redundant imports that popped up as a result Closes #17441. Metric Decrease: T4334
* Encode shape information in `PmOracle`Sebastian Graf2019-09-161-0/+14
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Previously, we had an elaborate mechanism for selecting the warnings to generate in the presence of different `COMPLETE` matching groups that, albeit finely-tuned, produced wrong results from an end user's perspective in some cases (#13363). The underlying issue is that at the point where the `ConVar` case has to commit to a particular `COMPLETE` group, there's not enough information to do so and the status quo was to just enumerate all possible complete sets nondeterministically. The `getResult` function would then pick the outcome according to metrics defined in accordance to the user's guide. But crucially, it lacked knowledge about the order in which affected clauses appear, leading to the surprising behavior in #13363. In !1010 we taught the term oracle to reason about literal values a variable can certainly not take on. This MR extends that idea to `ConLike`s and thereby fixes #13363: Instead of committing to a particular `COMPLETE` group in the `ConVar` case, we now split off the matching constructor incrementally and record the newly covered case as a refutable shape in the oracle. Whenever the set of refutable shapes covers any `COMPLETE` set, the oracle recognises vacuosity of the uncovered set. This patch goes a step further: Since at this point the information in value abstractions is merely a cut down representation of what the oracle knows, value abstractions degenerate to a single `Id`, the semantics of which is determined by the oracle state `Delta`. Value vectors become lists of `[Id]` given meaning to by a single `Delta`, value set abstractions (of which the uncovered set is an instance) correspond to a union of `Delta`s which instantiate the same `[Id]` (akin to models of formula). Fixes #11528 #13021, #13363, #13965, #14059, #14253, #14851, #15753, #17096, #17149 ------------------------- Metric Decrease: ManyAlternatives T11195 -------------------------
* Properly trim IdInfos of DFunIds and PatSyns in TidyPgmÖmer Sinan Ağacan2019-06-191-3/+3
| | | | | | | | | | | Not doing this right caused #16608. We now properly trim IdInfos of DFunIds and PatSyns. Some further refactoring done by SPJ. Two regression tests T16608_1 and T16608_2 added. Fixes #16608
* Update Trac ticket URLs to point to GitLabRyan Scott2019-03-151-1/+1
| | | | | This moves all URL references to Trac tickets to their corresponding GitLab counterparts.
* Add AnonArgFlag to FunTySimon Peyton Jones2019-02-231-2/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The big payload of this patch is: Add an AnonArgFlag to the FunTy constructor of Type, so that (FunTy VisArg t1 t2) means (t1 -> t2) (FunTy InvisArg t1 t2) means (t1 => t2) The big payoff is that we have a simple, local test to make when decomposing a type, leading to many fewer calls to isPredTy. To me the code seems a lot tidier, and probably more efficient (isPredTy has to take the kind of the type). See Note [Function types] in TyCoRep. There are lots of consequences * I made FunTy into a record, so that it'll be easier when we add a linearity field, something that is coming down the road. * Lots of code gets touched in a routine way, simply because it pattern matches on FunTy. * I wanted to make a pattern synonym for (FunTy2 arg res), which picks out just the argument and result type from the record. But alas the pattern-match overlap checker has a heart attack, and either reports false positives, or takes too long. In the end I gave up on pattern synonyms. There's some commented-out code in TyCoRep that shows what I wanted to do. * Much more clarity about predicate types, constraint types and (in particular) equality constraints in kinds. See TyCoRep Note [Types for coercions, predicates, and evidence] and Note [Constraints in kinds]. This made me realise that we need an AnonArgFlag on AnonTCB in a TyConBinder, something that was really plain wrong before. See TyCon Note [AnonTCB InivsArg] * When building function types we must know whether we need VisArg (mkVisFunTy) or InvisArg (mkInvisFunTy). This turned out to be pretty easy in practice. * Pretty-printing of types, esp in IfaceType, gets tidier, because we were already recording the (->) vs (=>) distinction in an ad-hoc way. Death to IfaceFunTy. * mkLamType needs to keep track of whether it is building (t1 -> t2) or (t1 => t2). See Type Note [mkLamType: dictionary arguments] Other minor stuff * Some tidy-up in validity checking involving constraints; Trac #16263
* Coercion Quantificationningning2018-09-151-5/+5
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch corresponds to #15497. According to https://ghc.haskell.org/trac/ghc/wiki/DependentHaskell/Phase2, we would like to have coercion quantifications back. This will allow us to migrate (~#) to be homogeneous, instead of its current heterogeneous definition. This patch is (lots of) plumbing only. There should be no user-visible effects. An overview of changes: - Both `ForAllTy` and `ForAllCo` can quantify over coercion variables, but only in *Core*. All relevant functions are updated accordingly. - Small changes that should be irrelevant to the main task: 1. removed dead code `mkTransAppCo` in Coercion 2. removed out-dated Note Computing a coercion kind and roles in Coercion 3. Added `Eq4` in Note Respecting definitional equality in TyCoRep, and updated `mkCastTy` accordingly. 4. Various updates and corrections of notes and typos. - Haddock submodule needs to be changed too. Acknowledgments: This work was completed mostly during Ningning Xie's Google Summer of Code, sponsored by Google. It was advised by Richard Eisenberg, supported by NSF grant 1704041. Test Plan: ./validate Reviewers: goldfire, simonpj, bgamari, hvr, erikd, simonmar Subscribers: RyanGlScott, monoidal, rwbarton, carter GHC Trac Issues: #15497 Differential Revision: https://phabricator.haskell.org/D5054
* Typo in commentsGabor Greif2018-05-231-1/+1
|
* Fix scoping of pattern-synonym existentialsSimon Peyton Jones2017-12-181-1/+1
| | | | | | | | This patch fixes Trac #14998, where we eventually decided that the existential type variables of the signature of a pattern synonym should not scope over the pattern synonym. See Note [Pattern synonym existentials do not scope] in TcPatSyn.
* compiler: introduce custom "GhcPrelude" PreludeHerbert Valerio Riedel2017-09-191-0/+2
| | | | | | | | | | | | | | | | | | This switches the compiler/ component to get compiled with -XNoImplicitPrelude and a `import GhcPrelude` is inserted in all modules. This is motivated by the upcoming "Prelude" re-export of `Semigroup((<>))` which would cause lots of name clashes in every modulewhich imports also `Outputable` Reviewers: austin, goldfire, bgamari, alanz, simonmar Reviewed By: bgamari Subscribers: goldfire, rwbarton, thomie, mpickering, bgamari Differential Revision: https://phabricator.haskell.org/D3989
* A bunch of typofixesGabor Greif2017-07-311-1/+1
|
* Fix instantiation of pattern synonymsSimon Peyton Jones2017-07-281-8/+46
| | | | | | | | | | In Check.hs (pattern match ovelap checking) we to figure out the instantiation of a pattern synonym from the type of the pattern. We were doing this utterly wrongly. Trac #13768 demonstrated this bogosity. The fix is easy; and is described in PatSyn.hs Note [Pattern synonym result type]
* Use lengthIs and friends in more placesRyan Scott2017-06-021-2/+2
| | | | | | | | | | | | | | | | | | | | | | | | | | While investigating #12545, I discovered several places in the code that performed length-checks like so: ``` length ts == 4 ``` This is not ideal, since the length of `ts` could be much longer than 4, and we'd be doing way more work than necessary! There are already a slew of helper functions in `Util` such as `lengthIs` that are designed to do this efficiently, so I found every place where they ought to be used and did just that. I also defined a couple more utility functions for list length that were common patterns (e.g., `ltLength`). Test Plan: ./validate Reviewers: austin, hvr, goldfire, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: goldfire, rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3622
* Disambiguate two Notes with identical namesRyan Scott2016-12-211-2/+2
| | | | | | It turns out there were two Notes in the GHC codebase named [Pattern synonym signatures]. To avoid confusion, I gave one Note a slightly different name.
* Expanded abbreviations in Haddock documentationBen Gamari2016-08-051-1/+2
| | | | | | | | | | | This adds notes to the Haddock documentation for various core datatypes expanding abbreviations. Reviewers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D2406 GHC Trac Issues: #12405
* Major patch to introduce TyConBinderSimon Peyton Jones2016-06-151-4/+4
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Before this patch, following the TypeInType innovations, each TyCon had two lists: - tyConBinders :: [TyBinder] - tyConTyVars :: [TyVar] They were in 1-1 correspondence and contained overlapping information. More broadly, there were many places where we had to pass around this pair of lists, instead of a single list. This commit tidies all that up, by having just one list of binders in a TyCon: - tyConBinders :: [TyConBinder] The new data types look like this: Var.hs: data TyVarBndr tyvar vis = TvBndr tyvar vis data VisibilityFlag = Visible | Specified | Invisible type TyVarBinder = TyVarBndr TyVar VisibilityFlag TyCon.hs: type TyConBinder = TyVarBndr TyVar TyConBndrVis data TyConBndrVis = NamedTCB VisibilityFlag | AnonTCB TyCoRep.hs: data TyBinder = Named TyVarBinder | Anon Type Note that Var.TyVarBdr has moved from TyCoRep and has been made polymorphic in the tyvar and visiblity fields: type TyVarBinder = TyVarBndr TyVar VisibilityFlag -- Used in ForAllTy type TyConBinder = TyVarBndr TyVar TyConBndrVis -- Used in TyCon type IfaceForAllBndr = TyVarBndr IfaceTvBndr VisibilityFlag type IfaceTyConBinder = TyVarBndr IfaceTvBndr TyConBndrVis -- Ditto, in interface files There are a zillion knock-on changes, but everything arises from these types. It was a bit fiddly to get the module loops to work out right! Some smaller points ~~~~~~~~~~~~~~~~~~~ * Nice new functions TysPrim.mkTemplateKiTyVars TysPrim.mkTemplateTyConBinders which help you make the tyvar binders for dependently-typed TyCons. See comments with their definition. * The change showed up a bug in TcGenGenerics.tc_mkRepTy, where the code was making an assumption about the order of the kind variables in the kind of GHC.Generics.(:.:). I fixed this; see TcGenGenerics.mkComp.
* Re-add FunTy (big patch)Simon Peyton Jones2016-06-151-23/+19
| | | | | | | | | | | | | | | | | | | | | | With TypeInType Richard combined ForAllTy and FunTy, but that was often awkward, and yielded little benefit becuase in practice the two were always treated separately. This patch re-introduces FunTy. Specfically * New type data TyVarBinder = TvBndr TyVar VisibilityFlag This /always/ has a TyVar it. In many places that's just what what we want, so there are /lots/ of TyBinder -> TyVarBinder changes * TyBinder still exists: data TyBinder = Named TyVarBinder | Anon Type * data Type = ForAllTy TyVarBinder Type | FunTy Type Type | .... There are a LOT of knock-on changes, but they are all routine. The Haddock submodule needs to be updated too
* Remove Ord PatSynBartosz Nitka2016-06-091-7/+0
| | | | | | It's implemented in terms of Unique which is nondeterministic GHC Trac: #4012
* Remove 'deriving Typeable' statementsRyan Scott2016-05-241-3/+1
| | | | | | | | | | | | | | | | | Summary: Deriving `Typeable` has been a no-op since GHC 7.10, and now that we require 7.10+ to build GHC, we can remove all the redundant `deriving Typeable` statements in GHC. Test Plan: ./validate Reviewers: goldfire, austin, hvr, bgamari Reviewed By: austin, hvr, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2260
* SpellingGabor Greif2016-05-241-1/+1
|
* Reduce use of instances in hs-boot filesSimon Peyton Jones2016-04-201-2/+3
| | | | | | | | | | | | | | | Several things here * GHC no longer allows user-written Typeable instances, so remove them from hs-boot files. * Generally, reduce the use of instances in hs-boot files. They are hard to track. Mainly this involves using pprType, pprKind etc instead of just ppr. There were a lot of instances in hs-boot files that weren't needed at all. * Take TyThing out of Eq; it was used in exactly one place (in InteractiveEval), and equality is too big a hammer for that.
* Improve printing of pattern synonym typesRik Steenkamp2016-04-021-12/+15
| | | | | | | | | | | | | | | | | | | | | Add the function `pprPatSynType :: PatSyn -> SDoc` for printing pattern synonym types, and remove the ambiguous `patSynType` function. Also, the types in a `PatSyn` are now tidy. Haddock submodule updated to reflect the removal of `patSynType` by mpickering. Fixes: #11213. Reviewers: goldfire, simonpj, austin, mpickering, bgamari Reviewed By: simonpj, mpickering Subscribers: bollmann, simonpj, thomie Differential Revision: https://phabricator.haskell.org/D1896 GHC Trac Issues: #11213
* A raft of comments about TyBindersSimon Peyton Jones2016-03-251-10/+15
| | | | | | | | I had a conversation with Richard about TyBinders and VisibilityFlags. This patch adds a lot of comments to explain what is going on. I feel much more secure now. Richard please check.
* Add `PatSynSigSkol` and modify `PatSynCtxt`Rik Steenkamp2016-03-241-0/+15
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | As the type of a pattern synonym cannot in general be represented by a value of type Type, we cannot use a value `SigSkol (PatSynCtxt n) (Check ty)` to represent the signature of a pattern synonym (this causes incorrect signatures to be printed in error messages). Therefore we now represent it by a value `PatSynSigSkol n` (instead of incorrect signatures we simply print no explicit signature). Furthermore, we rename `PatSynCtxt` to `PatSynBuilderCtxt`, and use `SigSkol (PatSynBuilderCtxt n) (Check ty)` to represent the type of a bidirectional pattern synonym when used in an expression context. Before, this type was represented by a value `SigSkol (PatSynCtxt n) (Check ty)`, which caused incorrect error messages. Also, in `mk_dict_err` of `typecheck\TcErrors.hs` we now distinguish between all enclosing implications and "useful" enclosing implications, for better error messages concerning pattern synonyms. See `Note [Useful implications]`. See the Phabricator page for examples. Reviewers: mpickering, goldfire, simonpj, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1967 GHC Trac Issues: #11667
* Track specified/invisible more carefully.Richard Eisenberg2016-03-211-6/+19
| | | | | | | | | | | | | | In particular, this allows correct tracking of specified/invisible for variables in Haskell98 data constructors and in pattern synonyms. GADT-syntax constructors are harder, and are left until #11721. This was all inspired by Simon's comments to my fix for #11512, which this subsumes. Test case: ghci/scripts/TypeAppData [skip ci] (The test case fails because of an unrelated problem fixed in the next commit.)
* Address #11471 by putting RuntimeRep in kinds.wip/runtime-repRichard Eisenberg2016-02-241-2/+2
| | | | | | | | | | | | | | | | | | | | | See Note [TYPE] in TysPrim. There are still some outstanding pieces in #11471 though, so this doesn't actually nail the bug. This commit also contains a few performance improvements: * Short-cut equality checking of nullary type syns * Compare types before kinds in eqType * INLINE coreViewOneStarKind * Store tycon binders separately from kinds. This resulted in a ~10% performance improvement in compiling the Cabal package. No change in functionality other than performance. (This affects the interface file format, though.) This commit updates the haddock submodule.
* Fix typosRik Steenkamp2016-02-161-4/+4
| | | | | | | | | | Reviewers: bgamari, austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1915
* Replace calls to `ptext . sLit` with `text`Jan Stolarek2016-01-181-3/+2
| | | | | | | | | | | | | | | | | | | | 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
* Implement scoped type variables in pattern synonymsSimon Peyton Jones2016-01-181-2/+2
| | | | | | | | This fixes Trac #11351. The implementation is pretty simple, happily. I took the opportunity to re-order the prov/req context in builder-ids, which was confusingly backwards.
* Visible type applicationRichard Eisenberg2015-12-241-3/+3
| | | | | | | | | | | | | This re-working of the typechecker algorithm is based on the paper "Visible type application", by Richard Eisenberg, Stephanie Weirich, and Hamidhasan Ahmed, to be published at ESOP'16. This patch introduces -XTypeApplications, which allows users to say, for example `id @Int`, which has type `Int -> Int`. See the changes to the user manual for details. This patch addresses tickets #10619, #5296, #10589.
* Fix typechecking for pattern synonym signaturesSimon Peyton Jones2015-12-221-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Various tickets have revealed bad shortcomings in the typechecking of pattern type synonyms. Discussed a lot in (the latter part of) Trac #11224. This patch fixes the most complex issues: - Both parser and renamer now treat pattern synonyms as an ordinary LHsSigType. Nothing special. Hooray. - tcPatSynSig (now in TcPatSyn) typechecks the signature, and decomposes it into its pieces. See Note [Pattern synonym signatures] - tcCheckPatSyn has had a lot of refactoring. See Note [Checking against a pattern signature] The result is a lot tidier and more comprehensible. Plus, it actually works! NB: this patch doesn't actually address the precise target of #11224, namely "inlining pattern synonym does not preserve semantics". That's an unrelated bug, with a separate patch. ToDo: better documentation in the user manual Test Plan: Validate Reviewers: austin, hvr, goldfire Subscribers: goldfire, mpickering, thomie, simonpj Differential Revision: https://phabricator.haskell.org/D1685 GHC Trac Issues: #11224
* Add kind equalities to GHC.Richard Eisenberg2015-12-111-5/+7
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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.
* Record pattern synonymsMatthew Pickering2015-10-291-12/+39
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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"
* Pattern synonyms: swap provided/requiredSimon Peyton Jones2015-10-281-3/+42
| | | | | | | | | | | | | | This patch swaps the order of provided and required constraints in a pattern signature, so it now goes pattern P :: req => prov => t1 -> ... tn -> res_ty See the long discussion in Trac #10928. I think I have found all the places, but I could have missed something particularly in comments. There is a Haddock changes; so a submodule update.
* Remove dead function patSynTyDetailsSimon Peyton Jones2015-10-161-9/+1
| | | | | And that allows us to remove the nasty import of HsBinds, which has no business in this module.
* Use a new $b prefix for pattern synonym builder names, instead of re-using ↵Dr. ERDI Gergo2014-12-201-6/+6
| | | | $W from wrappers
* compiler: de-lhs basicTypes/Austin Seipp2014-12-031-0/+345
Signed-off-by: Austin Seipp <austin@well-typed.com>