summaryrefslogtreecommitdiff
path: root/testsuite/tests/patsyn/should_fail/all.T
Commit message (Collapse)AuthorAgeFilesLines
* Don't zap to Any; error insteadRichard Eisenberg2020-01-121-0/+1
| | | | | | | | | This changes GHC's treatment of so-called Naughty Quantification Candidates to issue errors, instead of zapping to Any. Close #16775. No new test cases, because existing ones cover this well.
* More sensible SrcSpans for recursive pattern synonym errors (#16900)Ryan Scott2019-07-051-0/+1
| | | | | | | | Attach the `SrcSpan` of the first pattern synonym binding involved in the recursive group when throwing the corresponding error message, similarly to how it is done for type synonyms. Fixes #16900.
* Treat kind/type variables identically, demolish FKTVVladislav Zavialov2019-02-271-1/+0
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Implements GHC Proposal #24: .../ghc-proposals/blob/master/proposals/0024-no-kind-vars.rst Fixes Trac #16334, Trac #16315 With this patch, scoping rules for type and kind variables have been unified: kind variables no longer receieve special treatment. This simplifies both the language and the implementation. User-facing changes ------------------- * Kind variables are no longer implicitly quantified when an explicit forall is used: p :: Proxy (a :: k) -- still accepted p :: forall k a. Proxy (a :: k) -- still accepted p :: forall a. Proxy (a :: k) -- no longer accepted In other words, now we adhere to the "forall-or-nothing" rule more strictly. Related function: RnTypes.rnImplicitBndrs * The -Wimplicit-kind-vars warning has been deprecated. * Kind variables are no longer implicitly quantified in constructor declarations: data T a = T1 (S (a :: k) | forall (b::k). T2 (S b) -- no longer accepted data T (a :: k) = T1 (S (a :: k) | forall (b::k). T2 (S b) -- still accepted Related function: RnTypes.extractRdrKindSigVars * Implicitly quantified kind variables are no longer put in front of other variables: f :: Proxy (a :: k) -> Proxy (b :: j) f :: forall k j (a :: k) (b :: j). Proxy a -> Proxy b -- old order f :: forall k (a :: k) j (b :: j). Proxy a -> Proxy b -- new order This is a breaking change for users of TypeApplications. Note that we still respect the dpendency order: 'k' before 'a', 'j' before 'b'. See "Ordering of specified variables" in the User's Guide. Related function: RnTypes.rnImplicitBndrs * In type synonyms and type family equations, free variables on the RHS are no longer implicitly quantified unless used in an outermost kind annotation: type T = Just (Nothing :: Maybe a) -- no longer accepted type T = Just Nothing :: Maybe (Maybe a) -- still accepted The latter form is a workaround due to temporary lack of an explicit quantification method. Ideally, we would write something along these lines: type T @a = Just (Nothing :: Maybe a) Related function: RnTypes.extractHsTyRdrTyVarsKindVars * Named wildcards in kinds are fixed (Trac #16334): x :: (Int :: _t) -- this compiles, infers (_t ~ Type) Related function: RnTypes.partition_nwcs Implementation notes -------------------- * One of the key changes is the removal of FKTV in RnTypes: - data FreeKiTyVars = FKTV { fktv_kis :: [Located RdrName] - , fktv_tys :: [Located RdrName] } + type FreeKiTyVars = [Located RdrName] We used to keep track of type and kind variables separately, but now that they are on equal footing when it comes to scoping, we can put them in the same list. * extract_lty and family are no longer parametrized by TypeOrKind, as we now do not distinguish kind variables from type variables. * PatSynExPE and the related Note [Pattern synonym existentials do not scope] have been removed (Trac #16315). With no implicit kind quantification, we can no longer trigger the error. * reportFloatingKvs and the related Note [Free-floating kind vars] have been removed. With no implicit kind quantification, we can no longer trigger the error.
* Finish fix for #14880.Tobias Dammers2018-10-281-1/+0
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | The real change that fixes the ticket is described in Note [Naughty quantification candidates] in TcMType. Fixing this required reworking candidateQTyVarsOfType, the function that extracts free variables as candidates for quantification. One consequence is that we now must be more careful when quantifying: any skolems around must be quantified manually, and quantifyTyVars will now only quantify over metavariables. This makes good sense, as skolems are generally user-written and are listed in the AST. As a bonus, we now have more control over the ordering of such skolems. Along the way, this commit fixes #15711 and refines the fix to #14552 (by accepted a program that was previously rejected, as we can now accept that program by zapping variables to Any). This commit also does a fair amount of rejiggering kind inference of datatypes. Notably, we now can skip the generalization step in kcTyClGroup for types with CUSKs, because we get the kind right the first time. This commit also thus fixes #15743 and #15592, which both concern datatype kind generalisation. (#15591 is also very relevant.) For this aspect of the commit, see Note [Required, Specified, and Inferred in types] in TcTyClsDecls. Test cases: dependent/should_fail/T14880{,-2}, dependent/should_fail/T15743[cd] dependent/should_compile/T15743{,e} ghci/scripts/T15743b polykinds/T15592 dependent/should_fail/T15591[bc] ghci/scripts/T15591
* Solve equalities in a pattern signatureSimon Peyton Jones2018-10-241-0/+1
| | | | | | | | Trac #15694 showed that we were forgetting to solve the equalities of a pattern signature until too late. Result: WARNINGs and a panic: "Type-correct unfilled coercion hole"
* Fail fast on pattern synonymsSimon Peyton Jones2018-10-041-0/+2
| | | | | | | | | | | | | We were recovering too eagerly from errors in pattern-synonym type inference, leading to a cascade of confusing follow up errors (Trac #15685, #15692). The underlying issue is that a pattern synonym should have a closed, fixed type, with no unification variables in it. But it wasn't! Fixing this made me change the interface to simplifyInfer slightly. Instead of /emitting/ a residual implication constraint, it now /returns/ it, so that the caller can decide what to do.
* Do not mark CoVars as dead in the occur-analSimon Peyton Jones2018-10-041-0/+1
| | | | | | | | For years we have been marking CoVars as dead, becuase we don't gather occurrence info from types. This is obviously wrong and caused Trac #15695. See Note [Do not mark CoVars as dead] in OccurAnal.
* Fix error recovery for pattern synonymsSimon Peyton Jones2018-06-251-1/+1
| | | | | | | | | As Trac #15289 showed, we were carrying on after a type error in a pattern synonym, and then crashing. This patch improves error handling for pattern synonyms. I also moved a bit of code from TcBinds into TcPatSyn, which helpfully narrows the API.
* testsuite: Add broken test for #15289Ben Gamari2018-06-191-0/+1
| | | | | The stderr output is merely a guess at what we should expect, but currently this is certainly broken.
* Allow as-patterns in unidirectional patttern synonymsSimon Peyton Jones2018-03-211-1/+1
| | | | | | | | | | | | | | This patch implements GHC Proposal #94, described here https://github.com/ghc-proposals/ghc-proposals/pull/94 The effect is simply to lift a totally-undocumented restriction to unidirecional pattern synonyms, namely that they can't have as-patterns or n+k patterns. The fix is easy: just remove the checks. I also took the opportunity to improve the manual entry for the semantics of pattern matching for pattern synonyms.
* Pass -dsuppress-uniques when running T14507Ryan Scott2018-01-221-1/+1
| | | | | Not doing so resulted in different uniques being printed on different environments, as shown in #14703.
* Fix another obscure pattern-synonym crashSimon Peyton Jones2018-01-051-0/+1
| | | | | | | | | This one, discovered by Iceland Jack (Trac #14507), shows that a pattern-bound coercion can show up in the argument type(s) of the matcher of a pattern synonym. The error message isn't great, but at least we now rightly reject the program.
* Fix deep, dark corner of pattern synonymsSimon Peyton Jones2018-01-041-0/+1
| | | | | | | | Trac #14552 showed a very obscure case where we can't infer a good pattern-synonym type. The error message is horrible, but at least we no longer crash and burn.
* Fix scoping of pattern-synonym existentialsSimon Peyton Jones2017-12-181-0/+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.
* Temporary fix to Trac #14380Simon Peyton Jones2017-10-241-0/+1
| | | | | | | | This fix replaces an utterly bogus error message with a decent one, rejecting a pattern synonym with a list pattern and rebindable syntax. Not hard to fix properly, but I'm going to wait for a willing volunteer and/or more user pressure.
* Disallow bang/lazy patterns in the RHSes of implicitly bidirectional patsynsRyan Scott2017-09-021-0/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Summary: GHC was allowing implicitly bidirectional pattern synonyms with bang patterns and irrefutable patterns in the RHS, like so: ```lang=haskell pattern StrictJust a = Just !a ``` This has multiple problems: 1. `Just !a` isn't a valid expression, so it feels strange to allow it in an implicitly bidirectional pattern synonym. 2. `StrictJust` doesn't provide the strictness properties one would expect from a strict constructor. (One could imagine a design where the `StrictJust` builder infers a bang pattern for its pattern variable, but accomplishing this inference in a way that accounts for all possible patterns on the RHS, including other pattern synonyms, is somewhat awkward, so we do not pursue this design.) We nip these issues in the bud by simply disallowing bang/irrefutable patterns on the RHS. Test Plan: make test TEST="T14112 unidir" Reviewers: simonpj, austin, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie GHC Trac Issues: #14112 Differential Revision: https://phabricator.haskell.org/D3896
* Fix #14114 by checking for duplicate vars on pattern synonym RHSesRyan Scott2017-08-221-0/+1
| | | | | | | | | | | | | | | | | | | | | | | | Summary: Because we weren't checking for duplicate variables on the right-hand sides of pattern synonyms, bogus definitions like this one passed the renamer: ```lang=haskell pattern Foo a <- (a,a) ``` Luckily, the fix is simple. Test Plan: make test TEST=T14114 Reviewers: mpickering, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #14114 Differential Revision: https://phabricator.haskell.org/D3866
* Only use locally bound variables in pattern synonym declarationsMatthew Pickering2017-03-271-0/+1
| | | | | | | | | | | | | | | | | | | | Summary: We were using the unconstrainted `lookupOccRn` function which looked up any variable in scope. Instead we only want to consider variables brought into scope by renaming the pattern on the RHS. A few more changes to make reporting of unbound names suggest the correct things. Fixes #13470 Reviewers: simonpj, austin, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3377
* Don't allow orphan COMPLETE pragmas (#13349)Reid Barton2017-03-021-0/+1
| | | | | | | | | | | | | | | We might support them properly in the future, but for now it's simpler to disallow them. Test Plan: validate Reviewers: mpickering, austin, bgamari, simonpj Reviewed By: mpickering, simonpj Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D3243
* Update levity polymorphismRichard Eisenberg2017-01-191-0/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This commit implements the proposal in https://github.com/ghc-proposals/ghc-proposals/pull/29 and https://github.com/ghc-proposals/ghc-proposals/pull/35. Here are some of the pieces of that proposal: * Some of RuntimeRep's constructors have been shortened. * TupleRep and SumRep are now parameterized over a list of RuntimeReps. * This means that two types with the same kind surely have the same representation. Previously, all unboxed tuples had the same kind, and thus the fact above was false. * RepType.typePrimRep and friends now return a *list* of PrimReps. These functions can now work successfully on unboxed tuples. This change is necessary because we allow abstraction over unboxed tuple types and so cannot always handle unboxed tuples specially as we did before. * We sometimes have to create an Id from a PrimRep. I thus split PtrRep * into LiftedRep and UnliftedRep, so that the created Ids have the right strictness. * The RepType.RepType type was removed, as it didn't seem to help with * much. * The RepType.repType function is also removed, in favor of typePrimRep. * I have waffled a good deal on whether or not to keep VoidRep in TyCon.PrimRep. In the end, I decided to keep it there. PrimRep is *not* represented in RuntimeRep, and typePrimRep will never return a list including VoidRep. But it's handy to have in, e.g., ByteCodeGen and friends. I can imagine another design choice where we have a PrimRepV type that is PrimRep with an extra constructor. That seemed to be a heavier design, though, and I'm not sure what the benefit would be. * The last, unused vestiges of # (unliftedTypeKind) have been removed. * There were several pretty-printing bugs that this change exposed; * these are fixed. * We previously checked for levity polymorphism in the types of binders. * But we also must exclude levity polymorphism in function arguments. This is hard to check for, requiring a good deal of care in the desugarer. See Note [Levity polymorphism checking] in DsMonad. * In order to efficiently check for levity polymorphism in functions, it * was necessary to add a new bit of IdInfo. See Note [Levity info] in IdInfo. * It is now safe for unlifted types to be unsaturated in Core. Core Lint * is updated accordingly. * We can only know strictness after zonking, so several checks around * strictness in the type-checker (checkStrictBinds, the check for unlifted variables under a ~ pattern) have been moved to the desugarer. * Along the way, I improved the treatment of unlifted vs. banged * bindings. See Note [Strict binds checks] in DsBinds and #13075. * Now that we print type-checked source, we must be careful to print * ConLikes correctly. This is facilitated by a new HsConLikeOut constructor to HsExpr. Particularly troublesome are unlifted pattern synonyms that get an extra void# argument. * Includes a submodule update for haddock, getting rid of #. * New testcases: typecheck/should_fail/StrictBinds typecheck/should_fail/T12973 typecheck/should_run/StrictPats typecheck/should_run/T12809 typecheck/should_fail/T13105 patsyn/should_fail/UnliftedPSBind typecheck/should_fail/LevPolyBounded typecheck/should_compile/T12987 typecheck/should_compile/T11736 * Fixed tickets: #12809 #12973 #11736 #13075 #12987 * This also adds a test case for #13105. This test case is * "compile_fail" and succeeds, because I want the testsuite to monitor the error message. When #13105 is fixed, the test case will compile cleanly.
* Reshuffle levity polymorphism checks.Richard Eisenberg2016-12-171-0/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | Previously, GHC checked for bad levity polymorphism to the left of all arrows in data constructors. This was wrong, as reported in #12911 (where an example is also shown). The solution is to check each individual argument for bad levity polymorphism. Thus the check has been moved from TcValidity to TcTyClsDecls. A similar situation exists with pattern synonyms, also fixed here. This patch also nabs #12819 while I was in town. Test cases: typecheck/should_compile/T12911, patsyn/should_fail/T12819 Test Plan: ./validate Reviewers: simonpj, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2783 GHC Trac Issues: #12819, #12911
* Treat duplicate pattern synonym signatures as an errorSeraphime Kirkovski2016-07-041-0/+1
| | | | | | | | | | | | | | | | | | | | | | | Fixes issue T12165 by banning duplicate pattern synonyms signatures. This seems to me the best solution because: 1) it is coherent with the way we treat other duplicate signatures 2) the typechecker currently doesn't try to apply a second signature to a pattern to see if it matches, probably because it assumes there is no more than one signature per object. Test Plan: ./validate Reviewers: goldfire, austin, mpickering, bgamari Reviewed By: mpickering, bgamari Subscribers: mpickering, thomie Differential Revision: https://phabricator.haskell.org/D2361 GHC Trac Issues: #12165
* Add `PatSynSigSkol` and modify `PatSynCtxt`Rik Steenkamp2016-03-241-0/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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
* Improve pattern synonym error messages (add `PatSynOrigin`)Rik Steenkamp2016-02-251-0/+1
| | | | | | | | | | | | | | | | | | Adds a new data constructor `PatSynOrigin Bool Name` to the `CtOrigin` data type. This allows for better error messages when the origin of a wanted constraint is a pattern synonym declaration. Fixes T10873. Reviewers: mpickering, simonpj, austin, thomie, bgamari Reviewed By: simonpj, thomie, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1866 GHC Trac Issues: #10873
* Make warning names more consistentManav Rathi2016-02-251-1/+1
| | | | | | | | | | | | | | | | | | | | | | | | | | | | - Replace "Sigs" with "Signatures" in WarningFlag data constructors. - Replace "PatSyn" with "PatternSynonym" in WarningFlag data constructors. - Deprecate "missing-local-sigs" in favor of "missing-local-signatures". - Deprecate "missing-exported-sigs" in favor of "missing-exported-signatures". - Deprecate "missing-pat-syn-signatures" in favor of "missing-pattern-synonym-signatures". - Replace "ddump-strsigs" with "ddump-str-signatures" These complete the tasks that were explicitly mentioned in #11583 Test Plan: Executed `ghc --show-options` and verified that the flags were changed as expected. Reviewers: svenpanne, austin, bgamari Reviewed By: austin, bgamari Subscribers: mpickering, thomie Differential Revision: https://phabricator.haskell.org/D1939 GHC Trac Issues: #11583
* Rename missing-pat-syn-sigs to missing-pat-syn-signaturesMatthew Pickering2016-02-151-1/+1
|
* Update tests for Trac #11039Simon Peyton Jones2015-12-231-1/+2
|
* Add a pattern-syn form of PromotionErrSimon Peyton Jones2015-12-231-0/+1
| | | | | | | | | | The main change is to add PatSynPE to PromotionErr, so that when we get an ill-staged use of a pattern synonym we get a civilised error message. We were already doing this in half-baked form in tcValBinds, but this patch tidies up the impl (which previously used a hack rather than APromotionErr), and does it in tcTyClsInstDecls too.
* Revert "Allow as-patterns in pattern synonym declarations."Simon Peyton Jones2015-12-231-1/+0
| | | | | | | | | | I'm reverting this until we agree a design. See comment:5 in Trac #9793. Incidentally the reference to Trac #9739 in the reverted patch is bogus; it shold have said #9793. This reverts commit 44640af7afa1a01ff2e2357f7c1436b4804866fc.
* Allow as-patterns in pattern synonym declarations.Matthew Pickering2015-12-201-0/+1
| | | | | | | | | | | | | | | | | | | | | We can allow them if they contain no free variables. This patch just allows them in one direction and not to be used as builders as the original ticket suggests. Test Plan: ./validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1666 GHC Trac Issues:  #9739 Conflicts: testsuite/tests/patsyn/should_fail/all.T
* Disallow empty where bindings in pattern synonym declarations.Matthew Pickering2015-12-201-0/+1
| | | | | | | | | | | | Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1665 GHC Trac Issues: #10426
* Implement -fwarn-missing-pat-syn-sigsMatthew Pickering2015-12-121-0/+1
| | | | | | | | | | | | | | | | | | | | | | | This adds a warning when a pattern synonym is not accompanied by a signature in the style of `-fwarn-missing-sigs`. It is turned on by -Wall. If the user specifies, `-fwarn-missing-exported-signatures` with `-fwarn-missing-pat-syn-sigs` then it will only warn when the pattern synonym is exported. Test Plan: ./validate Reviewers: hvr, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1596 GHC Trac Issues: #11053
* Associate pattern synonyms with types in module exportsMatthew Pickering2015-11-111-0/+8
| | | | | | | | | | | | | | | | | | | | | | This patch implements #10653. It adds the ability to bundle pattern synonyms with type constructors in export lists so that users can treat pattern synonyms more like data constructors. Updates haddock submodule. Test Plan: ./validate Reviewers: goldfire, austin, bgamari Reviewed By: bgamari Subscribers: simonpj, gridaphobe, thomie Differential Revision: https://phabricator.haskell.org/D1258 GHC Trac Issues: #10653
* Add failing test for #11039Matthew Pickering2015-10-301-0/+1
| | | | | | | | | | Reviewers: austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1406 GHC Trac Issues: #11039
* Record pattern synonymsMatthew Pickering2015-10-291-1/+8
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | 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-0/+1
| | | | | | | | | | | | | | 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.
* Don't require PatternSynonyms language extension to just use pattern synonymsDr. ERDI Gergo2014-11-271-1/+0
| | | | (see #9838)
* If pattern synonym is bidirectional and its type is some unboxed type T#,Dr. ERDI Gergo2014-11-131-0/+1
| | | | | generate a worker function of type Void# -> T#, and redirect the wrapper (via a compulsory unfolding) to the worker. Fixes #9732.
* Binding things matched by an unboxed pattern synonym should require a bangDr. ERDI Gergo2014-11-131-1/+1
|
* Tweak the error message for pattern synonym methods,Dr. ERDI Gergo2014-11-021-1/+2
| | | | since they are disallowed both in class and instance declarations
* rnMethodBind: reject pattern synonyms in instance definitions (fixes #9705)Dr. ERDI Gergo2014-11-011-0/+1
|
* Add fake entries into the global kind environment for pattern synonyms.Dr. ERDI Gergo2014-06-211-0/+2
| | | | | | This is needed to give meaningful error messages (instead of internal panics) when a program tries to lift a pattern synonym into a kind. (fixes T9161)
* Split off pattern synonym definition checking from pattern inversionDr. ERDI Gergo2014-04-101-0/+1
|
* Require PatternSynonyms language flag when encountering a use of pattern synonymDr. ERDI Gergo2014-04-061-0/+1
| | | | (#8961)
* Issue an error for pattern synonyms defined in a local scope (#8757)Dr. ERDI Gergo2014-02-091-0/+1
| | | | | This also fixes the internal crash when using pattern synonyms in GHCi (#8749)
* Implement pattern synonymsDr. ERDI Gergo2014-01-201-0/+3
This patch implements Pattern Synonyms (enabled by -XPatternSynonyms), allowing y ou to assign names to a pattern and abstract over it. The rundown is this: * Named patterns are introduced by the new 'pattern' keyword, and can be either *unidirectional* or *bidirectional*. A unidirectional pattern is, in the simplest sense, simply an 'alias' for a pattern, where the LHS may mention variables to occur in the RHS. A bidirectional pattern synonym occurs when a pattern may also be used in expression context. * Unidirectional patterns are declared like thus: pattern P x <- x:_ The synonym 'P' may only occur in a pattern context: foo :: [Int] -> Maybe Int foo (P x) = Just x foo _ = Nothing * Bidirectional patterns are declared like thus: pattern P x y = [x, y] Here, P may not only occur as a pattern, but also as an expression when given values for 'x' and 'y', i.e. bar :: Int -> [Int] bar x = P x 10 * Patterns can't yet have their own type signatures; signatures are inferred. * Pattern synonyms may not be recursive, c.f. type synonyms. * Pattern synonyms are also exported/imported using the 'pattern' keyword in an import/export decl, i.e. module Foo (pattern Bar) where ... Note that pattern synonyms share the namespace of constructors, so this disambiguation is required as a there may also be a 'Bar' type in scope as well as the 'Bar' pattern. * The semantics of a pattern synonym differ slightly from a typical pattern: when using a synonym, the pattern itself is matched, followed by all the arguments. This means that the strictness differs slightly: pattern P x y <- [x, y] f (P True True) = True f _ = False g [True, True] = True g _ = False In the example, while `g (False:undefined)` evaluates to False, `f (False:undefined)` results in undefined as both `x` and `y` arguments are matched to `True`. For more information, see the wiki: https://ghc.haskell.org/trac/ghc/wiki/PatternSynonyms https://ghc.haskell.org/trac/ghc/wiki/PatternSynonyms/Implementation Reviewed-by: Simon Peyton Jones <simonpj@microsoft.com> Signed-off-by: Austin Seipp <austin@well-typed.com>