[GHC] #14112: bang patterns on pattern synonyms? (left vs right hand sides)

#14112: bang patterns on pattern synonyms? (left vs right hand sides) -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I'm trying to define my own fancy strict maybe types, and so i've written some pattern synonyms to wrap them up. imagine my surprise when i find i can write bang patterns on the *right* hand side, but not the left hand! {{{ data MyMaybe a = JustC a | NothingC pattern MyJust :: a -> MyMaybe a -- pattern MyJust !a = JustC a -- this fails pattern MyJust a = JustC !a -- this is fine }}} is this deliberate or a leakage of how desugaring works? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14112 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14112: bang patterns on pattern synonyms? (left vs right hand sides) -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => PatternSynonyms Comment: I'm not surprised that putting bang patterns on the left-hand side of a pattern synonyms doesn't work. After all, the left-hand side simply binds pattern variables. No more, no less. I am surprised, however, that putting bang patterns on the //right//-hand side does work. Especially since the right-hand sides of simply bidirectional pattern synonyms are supposed to be valid expressions, and `JustC !a` certainly doesn't feel like one. Curiously, the users' guide documentation is quite silent about the relationship between simply bidirectional pattern synonyms and bang patterns. To fix this quandary, we could either: 1. Disallow bang patterns entirely on the right-hand sides of simply bidirectional pattern synonyms (like we do with wildcard patterns and view patterns). 2. Document the current behavior as expected. `JustC !a` is bit strange- looking from an expression standpoint, but at the same time, it does work and accomplishes a useful task, so perhaps we shouldn't throw the baby out with the bathwater. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14112#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14112: bang patterns on pattern synonyms? (left vs right hand sides)
-------------------------------------+-------------------------------------
Reporter: carter | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1
Resolution: | Keywords:
| PatternSynonyms
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by carter):
well, my first question is: how do i validate that this bang pattern?
i've looked at the core this generates, and it looks like im only getting
strictness when i'm matching on the `Just`
and not when i'm using it as a constructor!
or maybe i'm not reading the Just constructor code correclty
{{{
-- RHS size: {terms: 5, types: 9, coercions: 0, joins: 0/0}
$bJust1_r1wL
:: forall a. a -> Data.Unboxed.Maybe.R:MaybeLiftedRepa a
[GblId, Arity=1, Caf=NoCafRefs]
$bJust1_r1wL
= \ (@ a_a1zx) (a1_a1xs :: a_a1zx) ->
break<5>(a1_a1xs)
Data.Unboxed.Maybe.MaybeSum
@ a_a1zx
(GHC.Prim.(#_|#)
@ 'LiftedRep @ ('TupleRep '[]) @ a_a1zx @ (# #) a1_a1xs)
}}}
plus the casing encoding
{{{
-- RHS size: {terms: 17, types: 31, coercions: 2, joins: 0/0}
Data.Unboxed.Maybe.$mJust
:: forall (r :: TYPE rep) a.
Maybe a -> (a -> r) -> (Void# -> r) -> r
[GblId, Arity=3]
Data.Unboxed.Maybe.$mJust
= \ (@ (rep_a1zm :: RuntimeRep))
(@ (r_a1zn :: TYPE rep_a1zm))
(@ a_a1xr)
(scrut_a1zo :: Maybe a_a1xr)
(cont_a1zp :: a_a1xr -> r_a1zn)
_ [Occ=Dead] ->
break<2>(scrut_a1zo,cont_a1zp)
case scrut_a1zo
`cast` (Data.Unboxed.Maybe.D:R:MaybeLiftedRepa0[0]

#14112: bang patterns on pattern synonyms? (left vs right hand sides) -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: mpickering (added) Comment: Ah, now this is interesting. You've noted that there is a semantic difference between implicitly bidirectional pattern synonyms with bang patterns and explicitly bidirectional synonyms with bang patterns. Consider these definitions: {{{#!hs {-# LANGUAGE BangPatterns #-} {-# LANGUAGE PatternSynonyms #-} module Bug where data Pair a = MkPair a a pattern MyPair1 x y <- MkPair !x !y where MyPair1 !x !y = MkPair x y pattern MyPair2 x y = MkPair !x !y }}} The expression: {{{#!hs let MkPair x y = MyPair1 "a" undefined in putStrLn x }}} throws an exception. However, the expression: {{{#!hs let MkPair x y = MyPair2 "a" undefined in putStrLn x }}} simply prints `a`. This asymmetry does feel quite unsavory to me. While we could just disallow `pattern MyPair2 x y = MkPair !x !y` entirely to avoid this, it doesn't feel like a very satisfactory solution, since defining an implicitly bidirectional pattern synonym with bang patterns feels like something useful that GHC should be able to do. So the question becomes: should we change the semantics of `pattern MyPair2 x y = MkPair !x !y` so that the `MyPair2` builder expression becomes strict in its arguments? But it's a bit weird to have bang patterns on the RHS of something determine the strictness of its binding sites on the LHS. Alternatively, we could change the syntax of implicitly bidirectional pattern synonyms to allow `pattern MyPair2 !x !y = ...`. This would bring it more in-line with explicitly bidirectional pattern synonyms, where there are two sets of binding sites: the pattern variable binders in `pattern MyPair1 x y`, as well as the builder expression's bound variables in `where MyPair1 !x !y`. Notice that you can only give bang patterns to the latter set of bound variables. Implicitly bidirectional pattern synonyms combine these two sets of bound variables into one, so perhaps we should allow bang patterns on the LHS of implicit synonyms to bring it up to par with explicit ones. An interesting consequence of this second design choice is that you could have varying combinations of strictness. For instance, all four of these could co-exist: {{{#!hs pattern Foo1 x = MkFoo1 x -- Lazy in builder and pattern pattern Foo2 !x = MkFoo2 x -- Strict in builder, lazy in pattern pattern Foo3 x = MkFoo3 !x -- Lazy in builder, strict in pattern pattern Foo4 !x = MkFoo4 !x -- Strict in builder and pattern }}} Perhaps this is the better solution, since now implicitly bidirectional pattern synonyms would be equally as expressive as explicit ones vis à vis strictness. The downside is that we'd be endorsing a design that allows RHSes that aren't valid expressions, but I think this is a small price to pay for the increased expressiveness. I'm cc'ing Matthew, since I'd be curious to hear what his thoughts are on the matter. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14112#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14112: bang patterns on pattern synonyms? (left vs right hand sides) -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Actually, I want to take back my proposal in comment:3. My idea relies on the ability to put "bang patterns" on variable binders, which is something that simply isn't possible anywhere else. (We could change the pattern variable binders to be proper patterns and only allow them to be variables or variables adorned with bangs, but that would be an exceedingly strange design.) In light of this, I would suggest that we endorse explicitly bidirectional pattern synonyms as the only way to achieve a "two-way" strict pattern synonym. That is: {{{#!hs pattern MyPair1 x y <- MkPair !x !y where MyPair1 !x !y = MkPair x y }}} Therefore, the fact that you can currently do this: {{{#!hs pattern MyJust a = JustC !a }}} Should be treated as a bug. `JustC !a` makes no sense as an expression, and moreover, it doesn't even give the strictness behavior that you'd expect, as discovered in comment:2. Does that sound agreeable, carter? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14112#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14112: bang patterns on pattern synonyms? (left vs right hand sides) -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Ryan has it right. The syntax is {{{ pattern P x y z = <pattern> }}} Hence bangs are allowed. For the implicitly-bidirectional case we have to turn the `<pattern>` into an expression. Currently, that conversion simply discards the bangs, which is the behaviour you are seeing. Silently ignoring the bangs is arguably rather undesirable. (The conversion also silently ignores a `~`, but that's probably correct behaviour.) It would make more sense to do one of these: A. Reject an implicitly-bidirectional pattern with bangs, on the grounds that it's not invertible (like view patterns, say); suggest using an explicitly-bidirectional pattern instead. B. Auto-generate the bang'd definition that Ryan writes above. {{{ MkPair1 !x !y = MkPair x y }}} That is, in the `ImplicitBidirectional` case, if we see `!x` in the pattern, use a `!x`, instead of `x` as the argument pattern of the builder. I think I prefer (B). It's easy to implement: see `mk_match_group` in `TcPatSyn.tcPatSynBuilderBind` . You'd need to alter `tcPatToExpr` to return the banged variables. (Ignore bangs on constructors e.g. `Just !(Just x)`; they are no-ops.) Don't forget to specify all this in the user manual. Volunteers? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14112#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14112: bang patterns on pattern synonyms? (left vs right hand sides) -------------------------------------+------------------------------------- Reporter: carter | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * owner: (none) => RyanGlScott * milestone: => 8.4.1 Comment: The only reason I don't favor (B) is because it's not always clear how you'd translate bang patterns on the RHS of an implicitly bidirectional pattern synonym to bang patterns for the builder arguments. For example, how would this be desugared? {{{#!hs pattern Foo a = Just !(Just a) }}} The only sensible thing I could envision here would be to silently ignore the bang pattern, but that makes me just as uncomfortable as it does you. I'd be willing to implement option (A). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14112#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14112: bang patterns on pattern synonyms? (left vs right hand sides) -------------------------------------+------------------------------------- Reporter: carter | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): As I say, bang on data constructors are always no-ops. They are ignored in patterns too! So it's fine. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14112#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14112: bang patterns on pattern synonyms? (left vs right hand sides) -------------------------------------+------------------------------------- Reporter: carter | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): That was perhaps a poor example. Here's an example that is less clear: {{{#!hs pattern Foo f a = Just !(f a) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14112#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14112: bang patterns on pattern synonyms? (left vs right hand sides) -------------------------------------+------------------------------------- Reporter: carter | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): They might be ignored for data constructors, yes. But what about pattern synonyms? For instance, we have that: {{{ λ> pattern Id a = a λ> let f (Id _) = "foo" λ> f undefined "foo" λ> let g !(Id _) = "bar" λ> g undefined "*** Exception: Prelude.undefined CallStack (from HasCallStack): error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err undefined, called at <interactive>:19:3 in interactive:Ghci9 }}} That is to say, bang patterns aren't no-ops for //every// conlike, as they matter in the presence of pattern synonyms. This awkwardly melds with implicitly bidirectional pattern synonyms, since if you define this: {{{ λ> pattern Foo a = Just !(Id a) λ> case Foo undefined of Just _ -> "wat" "wat" λ> case Just undefined of Foo _ -> "wat" "*** Exception: Prelude.undefined CallStack (from HasCallStack): error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err undefined, called at <interactive>:22:11 in interactive:Ghci11 }}} Notice that the bang pattern doesn't kick in when `Foo` is used as an expression, only as a pattern. In order to make a `Foo` expression strict as a pattern, you'd have to dig underneath the `Id` pattern synonym to figure out whether //its// bindings are strict or not. All of this sounds terribly fiddly in contrast to option (A), which is simple to describe, implement, and even gives nice error messages. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14112#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14112: bang patterns on pattern synonyms? (left vs right hand sides) -------------------------------------+------------------------------------- Reporter: carter | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carter): so what i'm sensing is the point that normal / "strict" data types are only strict on construction, but lazy on matching (except perhaps when dealing with unpacked/unboxed style internal tricks eg mapping Int to Int# etc). In contrast, we have here a way that can express lazy construction and strict matching? am i missing something? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14112#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14112: bang patterns on pattern synonyms? (left vs right hand sides) -------------------------------------+------------------------------------- Reporter: carter | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
But what about pattern synonyms?
That's an excellent point, one that I had not considered. The right thing to do would probably be to `seq` on the sub-pattern thus {{{ pattern P x = Just !(Id x) }}} would give rise to a builder thus {{{ P x = let !a = Id x in Just a }}} In short, when converting from pattern to expression, let!-bind the expressions gotten from converting each banged sub-pattern. But now I grant you that the cost/benefit ratio is less attractive. I'm happy with A. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14112#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14112: bang patterns on pattern synonyms? (left vs right hand sides) -------------------------------------+------------------------------------- Reporter: carter | Owner: RyanGlScott Type: bug | Status: patch Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3896 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D3896 Comment: I've implemented (A) in Phab:D3896. Replying to [comment:10 carter]:
so what i'm sensing is the point that
normal / "strict" data types are only strict on construction, but lazy on matching (except perhaps when dealing with unpacked/unboxed style internal tricks eg mapping Int to Int# etc).
In contrast, we have here a way that can express lazy construction and strict matching?
am i missing something?
I'd summarize the point by saying that if you were to hypothetically allow an implicitly bidirectional pattern synonym with a bang pattern in the RHS, you'd want both the pattern and the builder expression to be strict. However, in practice GHC was making the pattern strict, but not the builder. We pondered whether it would be possible to desugar a builder that figured out the right strictness, but this turns out to be an awkward thing to do in the presence of other pattern synonyms in the RHS. It's much easier to simply disallow bang patterns in the RHS altogether, since this avoids the need to explain away a special syntactic rule that only applies for expressions in implicitly bidirectional pattern synonyms. (In Phab:D3896, I've tailored the error message so that if you do try typing something like `data StrictJust a = Just !a`, it recommends using an explicitly bidirectional pattern synonym instead.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14112#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14112: bang patterns on pattern synonyms? (left vs right hand sides)
-------------------------------------+-------------------------------------
Reporter: carter | Owner: RyanGlScott
Type: bug | Status: patch
Priority: normal | Milestone: 8.4.1
Component: Compiler | Version: 8.2.1
Resolution: | Keywords:
| PatternSynonyms
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3896
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#14112: bang patterns on pattern synonyms? (left vs right hand sides) -------------------------------------+------------------------------------- Reporter: carter | Owner: RyanGlScott Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | patsyn/should_fail/T14112 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3896 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * testcase: => patsyn/should_fail/T14112 * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14112#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC