[GHC] #14112: bang patterns on pattern synonyms? (left vs right hand sides)
GHC
ghc-devs at haskell.org
Mon Aug 14 20:40:26 UTC 2017
#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
More information about the ghc-tickets
mailing list