Implicit reboxing of unboxed tuple in let-patterns

Dear all, I discovered the hard way, yesterday, that lazy let pattern matching is allowed on unboxed tuples. And that it implicitly reboxes the pattern. Here is how the manual describes it, from the relevant section https://downloads.haskell.org/ghc/latest/docs/html/users_guide/glasgow_exts.... : You can have an unboxed tuple in a pattern binding, thus f x = let (# p,q #) = h x in ..body.. If the types of p and q are not unboxed, the resulting binding is lazy like any other Haskell pattern binding. The above example desugars like this: f x = let t = case h x of { (# p,q #) -> (p,q) } p = fst t q = snd t in ..body.. Indeed, the bindings can even be recursive. Notice how h x is lazily bound, hence won’t necessarily be run when body is forced. as opposed to if I had written, for instance, let u = hxin ..body.. My question is: are we happy with this? I did find this extremely surprising. If I’m using unboxed tuples, it’s because I want to guarantee to myself a strict, unboxed behaviour. But a very subtle syntactic detail seems to break this expectation for me. My expectation would be that I would need to explicitly rebox things before they get lazy again. I find that this behaviour invites trouble. But you may disagree. Let me know!

Have you tried using do notation for bindings you want to keep strict, with
Eg the identity monad? That doesn’t address the design critique but gives
you a path forward ?
I do agree that the semantics / default recursivity Of let bindings can be
inappropriate for non recursive code , but would any other non uniform
semantics or optimization be safe?
On Fri, Aug 28, 2020 at 9:05 AM Spiwack, Arnaud
Dear all,
I discovered the hard way, yesterday, that lazy let pattern matching is allowed on unboxed tuples. And that it implicitly reboxes the pattern.
Here is how the manual describes it, from the relevant section https://downloads.haskell.org/ghc/latest/docs/html/users_guide/glasgow_exts.... :
You can have an unboxed tuple in a pattern binding, thus
f x = let (# p,q #) = h x in ..body..
If the types of p and q are not unboxed, the resulting binding is lazy like any other Haskell pattern binding. The above example desugars like this:
f x = let t = case h x of { (# p,q #) -> (p,q) }
p = fst t
q = snd t
in ..body..
Indeed, the bindings can even be recursive.
Notice how h x is lazily bound, hence won’t necessarily be run when body is forced. as opposed to if I had written, for instance,
let u = hx
in ..body..
My question is: are we happy with this? I did find this extremely surprising. If I’m using unboxed tuples, it’s because I want to guarantee to myself a strict, unboxed behaviour. But a very subtle syntactic detail seems to break this expectation for me. My expectation would be that I would need to explicitly rebox things before they get lazy again.
I find that this behaviour invites trouble. But you may disagree. Let me know!
_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org

Hi Carter,
We are using let !(#x,y#) = … actually. Having the strict behaviour is not
particularly difficult. You can even use case … of (#x, y#) ->… directly,
it’s not too bad. My complaint, as it were, is solely about the potential
for mistakes.
On Fri, Aug 28, 2020 at 3:20 PM Carter Schonwald
Have you tried using do notation for bindings you want to keep strict, with Eg the identity monad? That doesn’t address the design critique but gives you a path forward ?
I do agree that the semantics / default recursivity Of let bindings can be inappropriate for non recursive code , but would any other non uniform semantics or optimization be safe?
On Fri, Aug 28, 2020 at 9:05 AM Spiwack, Arnaud
wrote: Dear all,
I discovered the hard way, yesterday, that lazy let pattern matching is allowed on unboxed tuples. And that it implicitly reboxes the pattern.
Here is how the manual describes it, from the relevant section https://downloads.haskell.org/ghc/latest/docs/html/users_guide/glasgow_exts.... :
You can have an unboxed tuple in a pattern binding, thus
f x = let (# p,q #) = h x in ..body..
If the types of p and q are not unboxed, the resulting binding is lazy like any other Haskell pattern binding. The above example desugars like this:
f x = let t = case h x of { (# p,q #) -> (p,q) }
p = fst t
q = snd t
in ..body..
Indeed, the bindings can even be recursive.
Notice how h x is lazily bound, hence won’t necessarily be run when body is forced. as opposed to if I had written, for instance,
let u = hx
in ..body..
My question is: are we happy with this? I did find this extremely surprising. If I’m using unboxed tuples, it’s because I want to guarantee to myself a strict, unboxed behaviour. But a very subtle syntactic detail seems to break this expectation for me. My expectation would be that I would need to explicitly rebox things before they get lazy again.
I find that this behaviour invites trouble. But you may disagree. Let me know!
_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org

Arnaud,
I have dealt with this in the past and find the laziness extremely
counterintuitive and never wanted. Every time I have let-bound an unboxed
tuple, I have never wanted that boxing to occur. Perhaps there is a good
reason this is the case but I wish it would change.
On Fri, Aug 28, 2020, 08:26 Spiwack, Arnaud
Hi Carter,
We are using let !(#x,y#) = … actually. Having the strict behaviour is not particularly difficult. You can even use case … of (#x, y#) ->… directly, it’s not too bad. My complaint, as it were, is solely about the potential for mistakes.
On Fri, Aug 28, 2020 at 3:20 PM Carter Schonwald < carter.schonwald@gmail.com> wrote:
Have you tried using do notation for bindings you want to keep strict, with Eg the identity monad? That doesn’t address the design critique but gives you a path forward ?
I do agree that the semantics / default recursivity Of let bindings can be inappropriate for non recursive code , but would any other non uniform semantics or optimization be safe?
On Fri, Aug 28, 2020 at 9:05 AM Spiwack, Arnaud
wrote: Dear all,
I discovered the hard way, yesterday, that lazy let pattern matching is allowed on unboxed tuples. And that it implicitly reboxes the pattern.
Here is how the manual describes it, from the relevant section https://downloads.haskell.org/ghc/latest/docs/html/users_guide/glasgow_exts.... :
You can have an unboxed tuple in a pattern binding, thus
f x = let (# p,q #) = h x in ..body..
If the types of p and q are not unboxed, the resulting binding is lazy like any other Haskell pattern binding. The above example desugars like this:
f x = let t = case h x of { (# p,q #) -> (p,q) }
p = fst t
q = snd t
in ..body..
Indeed, the bindings can even be recursive.
Notice how h x is lazily bound, hence won’t necessarily be run when body is forced. as opposed to if I had written, for instance,
let u = hx
in ..body..
My question is: are we happy with this? I did find this extremely surprising. If I’m using unboxed tuples, it’s because I want to guarantee to myself a strict, unboxed behaviour. But a very subtle syntactic detail seems to break this expectation for me. My expectation would be that I would need to explicitly rebox things before they get lazy again.
I find that this behaviour invites trouble. But you may disagree. Let me know!
_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

I’ve been pointed to https://github.com/ghc-proposals/ghc-proposals/pull/35 where this was debated a few years ago. With much of the same arguments as today. Simon Marlow said making an unboxed tuple binding lazy by default seems to be intuitively the
wrong choice. I guarantee I would get tripped up by this! Giving unboxed tuples an implicit bang seems reasonable to me.
I can share that I got tripped by it. And so were other members of my team.
That being said, Richard seemed to feel rather strongly about this one.
Richard, do you still agree with your then position that let (#x, y#) = …
being a lazy pattern (hence implicitly boxes the pair) is the right
semantics?
On Fri, Aug 28, 2020 at 8:26 PM chessai
Arnaud,
I have dealt with this in the past and find the laziness extremely counterintuitive and never wanted. Every time I have let-bound an unboxed tuple, I have never wanted that boxing to occur. Perhaps there is a good reason this is the case but I wish it would change.
On Fri, Aug 28, 2020, 08:26 Spiwack, Arnaud
wrote: Hi Carter,
We are using let !(#x,y#) = … actually. Having the strict behaviour is not particularly difficult. You can even use case … of (#x, y#) ->… directly, it’s not too bad. My complaint, as it were, is solely about the potential for mistakes.
On Fri, Aug 28, 2020 at 3:20 PM Carter Schonwald < carter.schonwald@gmail.com> wrote:
Have you tried using do notation for bindings you want to keep strict, with Eg the identity monad? That doesn’t address the design critique but gives you a path forward ?
I do agree that the semantics / default recursivity Of let bindings can be inappropriate for non recursive code , but would any other non uniform semantics or optimization be safe?
On Fri, Aug 28, 2020 at 9:05 AM Spiwack, Arnaud
wrote: Dear all,
I discovered the hard way, yesterday, that lazy let pattern matching is allowed on unboxed tuples. And that it implicitly reboxes the pattern.
Here is how the manual describes it, from the relevant section https://downloads.haskell.org/ghc/latest/docs/html/users_guide/glasgow_exts.... :
You can have an unboxed tuple in a pattern binding, thus
f x = let (# p,q #) = h x in ..body..
If the types of p and q are not unboxed, the resulting binding is lazy like any other Haskell pattern binding. The above example desugars like this:
f x = let t = case h x of { (# p,q #) -> (p,q) }
p = fst t
q = snd t
in ..body..
Indeed, the bindings can even be recursive.
Notice how h x is lazily bound, hence won’t necessarily be run when body is forced. as opposed to if I had written, for instance,
let u = hx
in ..body..
My question is: are we happy with this? I did find this extremely surprising. If I’m using unboxed tuples, it’s because I want to guarantee to myself a strict, unboxed behaviour. But a very subtle syntactic detail seems to break this expectation for me. My expectation would be that I would need to explicitly rebox things before they get lazy again.
I find that this behaviour invites trouble. But you may disagree. Let me know!
_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

I haven't used unboxed tuples enough to perhaps feel the pain, but on paper the current design makes sense to me. The laziness of the binding is suppose to have to do with the runtime rep of the binding itself, not any enclosing pattern. For example take {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE MagicHash #-} import GHC.Base data Foo = Foo Int# Int# main = pure () where Foo x y = Foo undefined undefined This program will fail even though x and y are unused. While this principle may not match how this stuff is used in practice, the alternative of making the strictness of the bindings depend on more than their runtime reps seems less-local / more ad-hoc to me. John On 8/31/20 10:34 AM, Spiwack, Arnaud wrote:
I’ve been pointed to https://github.com/ghc-proposals/ghc-proposals/pull/35 where this was debated a few years ago. With much of the same arguments as today.
Simon Marlow said
making an unboxed tuple binding lazy by default seems to be intuitively the wrong choice. I guarantee I would get tripped up by this! Giving unboxed tuples an implicit bang seems reasonable to me.
I can share that I got tripped by it. And so were other members of my team.
That being said, Richard seemed to feel rather strongly about this one. Richard, do you still agree with your then position that |let (#x, y#) = …| being a lazy pattern (hence implicitly boxes the pair) is the right semantics?
On Fri, Aug 28, 2020 at 8:26 PM chessai
mailto:chessai1996@gmail.com> wrote: Arnaud,
I have dealt with this in the past and find the laziness extremely counterintuitive and never wanted. Every time I have let-bound an unboxed tuple, I have never wanted that boxing to occur. Perhaps there is a good reason this is the case but I wish it would change.
On Fri, Aug 28, 2020, 08:26 Spiwack, Arnaud
mailto:arnaud.spiwack@tweag.io> wrote: Hi Carter,
We are using |let !(#x,y#) = …| actually. Having the strict behaviour is not particularly difficult. You can even use |case … of (#x, y#) ->…| directly, it’s not too bad. My complaint, as it were, is solely about the potential for mistakes.
On Fri, Aug 28, 2020 at 3:20 PM Carter Schonwald
mailto:carter.schonwald@gmail.com> wrote: Have you tried using do notation for bindings you want to keep strict, with Eg the identity monad? That doesn’t address the design critique but gives you a path forward ?
I do agree that the semantics / default recursivity Of let bindings can be inappropriate for non recursive code , but would any other non uniform semantics or optimization be safe?
On Fri, Aug 28, 2020 at 9:05 AM Spiwack, Arnaud
mailto:arnaud.spiwack@tweag.io> wrote: Dear all,
I discovered the hard way, yesterday, that lazy let pattern matching is allowed on unboxed tuples. And that it implicitly reboxes the pattern.
Here is how the manual describes it, from the relevant section https://downloads.haskell.org/ghc/latest/docs/html/users_guide/glasgow_exts....:
You can have an unboxed tuple in a pattern binding, thus
|f x = let (# p,q #) = h x in ..body.. |
If the types of |p| and |q| are not unboxed, the resulting binding is lazy like any other Haskell pattern binding. The above example desugars like this:
|f x = let t = case h x of { (# p,q #) -> (p,q) } p = fst t q = snd t in ..body.. |
Indeed, the bindings can even be recursive.
Notice how |h x| is lazily bound, hence won’t necessarily be run when |body| is forced. as opposed to if I had written, for instance,
|let u = hx in ..body.. |
My question is: are we happy with this? I did find this extremely surprising. If I’m using unboxed tuples, it’s because I want to guarantee to myself a strict, unboxed behaviour. But a very subtle syntactic detail seems to break this expectation for me. My expectation would be that I would need to explicitly rebox things before they get lazy again.
I find that this behaviour invites trouble. But you may disagree. Let me know!
_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org mailto:ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org mailto:ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

On Aug 31, 2020, at 10:34 AM, Spiwack, Arnaud
wrote: That being said, Richard seemed to feel rather strongly about this one. Richard, do you still agree with your then position that let (#x, y#) = … being a lazy pattern (hence implicitly boxes the pair) is the right semantics?
I admit I don't feel as strongly any more. My argument in that thread was from the standpoint of a language designer: there is really no reason, a priori, for an unboxed-tuple binding to be strict. What controls strictness is whether the bound variables are of unlifted type. However, I'm currently in more sympathy with language users, who (for whatever reason) seem to think that bindings with #s in them should be strict. (I have this intuition myself, even though it's not quite warranted on technical grounds.) What do we think of
pattern Unl x y = (# x, y #)
ex1, ex2 :: () ex1 = let Unl x y = Unl undefined undefined in () ex2 = let Unl x y = undefined in ()
? Today, both ex1 and ex2 evaluate to (). If we were to change the specification here, would we consider any unlifted-type pattern (where the type of the pattern itself is unlifted, independent of the type of any of its bound variables) to be banged? Or would it be a super-special case for unboxed tuples? Richard

I admit I don't feel as strongly any more. My argument in that thread was from the standpoint of a language designer: there is really no reason, a priori, for an unboxed-tuple binding to be strict. What controls strictness is whether the bound variables are of unlifted type. However, I'm currently in more sympathy with language users, who (for whatever reason) seem to think that bindings with #s in them should be strict. (I have this intuition myself, even though it's not quite warranted on technical grounds.)
A middle ground could be to not allow unbanged patterns for unboxed tuples. Since they currently exist, we could also simply emit a warning, saying: “this is probably not what you want, do add an exclamation mark”.
What do we think of
pattern Unl x y = (# x, y #)
ex1, ex2 :: () ex1 = let Unl x y = Unl undefined undefined in () ex2 = let Unl x y = undefined in ()
? Today, both ex1 and ex2 evaluate to (). If we were to change the specification here, would we consider any unlifted-type pattern (where the type of the pattern itself is unlifted, independent of the type of any of its bound variables) to be banged? Or would it be a super-special case for unboxed tuples?
Ooh… pattern synonyms for unboxed tuple. I must confess that I don't know what the semantics of these ought to be. It does look like an interesting can of worms. How do they currently desugar?

On Sep 2, 2020, at 9:39 AM, Spiwack, Arnaud
wrote: Ooh… pattern synonyms for unboxed tuple. I must confess that I don't know what the semantics of these ought to be. It does look like an interesting can of worms. How do they currently desugar?
Right now, there is one rule: if the type of any variable bound in the pattern is unlifted, then the pattern is an unlifter-var pattern and is strict. The pattern must be banged, unless the bound variable is not nested. This rule is consistent across all features. This thread is suggesting to add a special case -- one that seems to match intuition, but it's still a special case. And my question is: should the special case be for unboxed tuples? or should the special case be for any pattern whose overall type is unlifted? Richard

This thread is suggesting to add a special case -- one that seems to match intuition, but it's still a special case. And my question is: should the special case be for unboxed tuples? or should the special case be for any pattern whose overall type is unlifted?
My intuition would be: for all unlifted types. I'd submit that the distinction between lazy and strict pattern-matching doesn't really make a ton of sense for unlifted types. To implement lazy pattern-matching on an unlifted type, one has to actually indirect through another type, which I find deeply suspicious. That being said Right now, there is one rule: if the type of any variable bound in the
pattern is unlifted, then the pattern is an unlifter-var pattern and is strict. The pattern must be banged, unless the bound variable is not nested. This rule is consistent across all features.
I realise that there are a lot of subtil details to get right to specify pattern-matching. Or at the very least, that it's difficult to come up with a straightforward specification which is as clear as the one above. I'm wondering though: have there been discussions which led to the above rule, or did it just come to be, mostly informally? (and if there have been explicit discussions, are they recorded somewhere?)

Hi, Right now, there is one rule: if the type of any variable bound in the
pattern is unlifted, then the pattern is an unlifter-var pattern and is strict.
I think the intuition I followed so far was "bindings with unlifted *RHS* are strict". So if I take a program in a strict language with Haskell syntax (Idris with a different syntax, not like -XStrict) and replace all types with their unlifted counterparts (which should be possible once we have -XUnliftedDatatypes), then I get exactly the same semantics in GHC Haskell. I find this property very useful. As a special case that means that any binders of unlifted type are bound strictly, if only for uniformity with simple variable bindings. I think my intuition is different to Richard's rule only for the "unlifted constructor match with nested lifted-only variable matches" case. Sebastian Am Do., 3. Sept. 2020 um 14:48 Uhr schrieb Spiwack, Arnaud < arnaud.spiwack@tweag.io>:
This thread is suggesting to add a special case -- one that seems to match
intuition, but it's still a special case. And my question is: should the special case be for unboxed tuples? or should the special case be for any pattern whose overall type is unlifted?
My intuition would be: for all unlifted types. I'd submit that the distinction between lazy and strict pattern-matching doesn't really make a ton of sense for unlifted types. To implement lazy pattern-matching on an unlifted type, one has to actually indirect through another type, which I find deeply suspicious.
That being said
Right now, there is one rule: if the type of any variable bound in the
pattern is unlifted, then the pattern is an unlifter-var pattern and is strict. The pattern must be banged, unless the bound variable is not nested. This rule is consistent across all features.
I realise that there are a lot of subtil details to get right to specify pattern-matching. Or at the very least, that it's difficult to come up with a straightforward specification which is as clear as the one above.
I'm wondering though: have there been discussions which led to the above rule, or did it just come to be, mostly informally? (and if there have been explicit discussions, are they recorded somewhere?) _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Right now, there is one rule: if the type of any variable bound in the
pattern is unlifted, then the pattern is an unlifter-var pattern and is strict.
I think the intuition I followed so far was "bindings with unlifted *RHS* are strict".
This is a very different rule indeed! And one which gives a strict semantic to the initial offender. But there are holes in it: if I `let (x, y) = blah in …` and `x` is at an unlifted type, the pattern _needs_ to be strict (this is solved by the current rule as described by Richard) despite the rhs being at a lifted type. That's because binding `x` forces the pattern anyway, by definition. There are questions about nested patterns, as well. What about `let (U x, y) = blah in …`, where `U` is some unlifted type. Is the nested `U x` pattern strict? or is it lazy? There is no corresponding right-hand side. This is all a tad tricky, I must say.

On Sep 3, 2020, at 12:10 PM, Spiwack, Arnaud
wrote: This is all a tad tricky, I must say.
... which is one of the reasons I originally wanted one simple rule. I'm not now saying I was in the right, but it is an attractive resting point for this discussion. To be clear, I don't think there's going to be any concrete action here without a proposal, so perhaps once this thread finds a resting point different than the status quo, someone will have to write it up. Richard

How about the following rule: unlifted patterns are always strict (i.e.,
you desugar them as if they had an explicit `!`). A pattern is
"unlifted" if the type it examines is unlifted. Seems simple enough and,
I think, it would do what most folks would expect.
I guess a more explicit option would be to make it an error to use a lazy
pattern on an unlifted type, and require programmers to manually add the
`!` but I am not sure that gains much, and is more work in the compiler.
-Iavor
On Thu, Sep 3, 2020 at 10:38 AM Richard Eisenberg
On Sep 3, 2020, at 12:10 PM, Spiwack, Arnaud
wrote: This is all a tad tricky, I must say.
... which is one of the reasons I originally wanted one simple rule. I'm not now saying I was in the right, but it is an attractive resting point for this discussion.
To be clear, I don't think there's going to be any concrete action here without a proposal, so perhaps once this thread finds a resting point different than the status quo, someone will have to write it up.
Richard _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

On Sep 3, 2020, at 1:51 PM, Iavor Diatchki
wrote: How about the following rule: unlifted patterns are always strict (i.e., you desugar them as if they had an explicit `!`). A pattern is "unlifted" if the type it examines is unlifted. Seems simple enough and, I think, it would do what most folks would expect.
I don't think it's this simple. For example:
data X = MkX Int#
a = let MkX 3# = undefined in () b = let MkX z = undefined in () c = let MkX _ = undefined in () d = let MkX {} = undefined in () e = let _ :: X = undefined in ()
Which of these diverge? e definitely converges, as X is lifted. b definitely diverges, because it binds z, a variable of an unlifted type, to a component of a diverging computation. In GHC today, all the cases other than b converge. Iavor suggests that a should diverge: 3# is a pattern of an unlifted type. What about c? What about d? Very unclear to me. Note that banging the pattern nested inside the MkX does not change the behavior (in GHC today) for any of the cases where this makes sense to do so. Richard
I guess a more explicit option would be to make it an error to use a lazy pattern on an unlifted type, and require programmers to manually add the `!` but I am not sure that gains much, and is more work in the compiler.
-Iavor
On Thu, Sep 3, 2020 at 10:38 AM Richard Eisenberg
mailto:rae@richarde.dev> wrote: On Sep 3, 2020, at 12:10 PM, Spiwack, Arnaud
mailto:arnaud.spiwack@tweag.io> wrote: This is all a tad tricky, I must say.
... which is one of the reasons I originally wanted one simple rule. I'm not now saying I was in the right, but it is an attractive resting point for this discussion.
To be clear, I don't think there's going to be any concrete action here without a proposal, so perhaps once this thread finds a resting point different than the status quo, someone will have to write it up.
Richard _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org mailto:ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Yeah, I think these are nice examples that illustrate some of the
problems with the current behavior of GHC. For example, I think it is
weird that `b` non-terminates, but `c` does, because `z` is not used. I
would expect those to be equivalent.
My preference would be to use the simple rule I mentioned before, but
change how bang patterns work in pattern bindings. In particular, I think
writing a bang pattern should constitute a use of the banged value. I
think two equivalent ways to specify this is to say that a) writing a
nested bang pattern implicitly adds bangs to the enclosing patterns, or I
think equivalently b) writing `!p` is the same as writing `x@p` and adding
`seq x` the same way we do for simple `!x = e` definitions
With this interpretation, all but `e` would diverge, which matches my
intuition of how unboxed types should work.
-Iavor
On Thu, Sep 3, 2020 at 11:02 AM Richard Eisenberg
On Sep 3, 2020, at 1:51 PM, Iavor Diatchki
wrote: How about the following rule: unlifted patterns are always strict (i.e., you desugar them as if they had an explicit `!`). A pattern is "unlifted" if the type it examines is unlifted. Seems simple enough and, I think, it would do what most folks would expect.
I don't think it's this simple. For example:
data X = MkX Int#
a = let MkX 3# = undefined in () b = let MkX z = undefined in () c = let MkX _ = undefined in () d = let MkX {} = undefined in () e = let _ :: X = undefined in ()
Which of these diverge? e definitely converges, as X is lifted. b definitely diverges, because it binds z, a variable of an unlifted type, to a component of a diverging computation.
In GHC today, all the cases other than b converge.
Iavor suggests that a should diverge: 3# is a pattern of an unlifted type. What about c? What about d? Very unclear to me.
Note that banging the pattern nested inside the MkX does not change the behavior (in GHC today) for any of the cases where this makes sense to do so.
Richard
I guess a more explicit option would be to make it an error to use a lazy pattern on an unlifted type, and require programmers to manually add the `!` but I am not sure that gains much, and is more work in the compiler.
-Iavor
On Thu, Sep 3, 2020 at 10:38 AM Richard Eisenberg
wrote: On Sep 3, 2020, at 12:10 PM, Spiwack, Arnaud
wrote: This is all a tad tricky, I must say.
... which is one of the reasons I originally wanted one simple rule. I'm not now saying I was in the right, but it is an attractive resting point for this discussion.
To be clear, I don't think there's going to be any concrete action here without a proposal, so perhaps once this thread finds a resting point different than the status quo, someone will have to write it up.
Richard _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

I guess a more explicit option would be to make it an error to use a lazy pattern on an unlifted type, and require programmers to manually add the `!` but I am not sure that gains much, and is more work in the compiler.
Not being used to deal with unlifted types, this would be my preferred
option. Having the meaning of let change depending on the levity of the
type is a good opportunity for confusion.
Cheers,
Facundo
On Thu, Sep 3, 2020 at 3:43 PM Iavor Diatchki
Yeah, I think these are nice examples that illustrate some of the problems with the current behavior of GHC. For example, I think it is weird that `b` non-terminates, but `c` does, because `z` is not used. I would expect those to be equivalent.
My preference would be to use the simple rule I mentioned before, but change how bang patterns work in pattern bindings. In particular, I think writing a bang pattern should constitute a use of the banged value. I think two equivalent ways to specify this is to say that a) writing a nested bang pattern implicitly adds bangs to the enclosing patterns, or I think equivalently b) writing `!p` is the same as writing `x@p` and adding `seq x` the same way we do for simple `!x = e` definitions
With this interpretation, all but `e` would diverge, which matches my intuition of how unboxed types should work.
-Iavor
On Thu, Sep 3, 2020 at 11:02 AM Richard Eisenberg
wrote: On Sep 3, 2020, at 1:51 PM, Iavor Diatchki
wrote: How about the following rule: unlifted patterns are always strict (i.e., you desugar them as if they had an explicit `!`). A pattern is "unlifted" if the type it examines is unlifted. Seems simple enough and, I think, it would do what most folks would expect.
I don't think it's this simple. For example:
data X = MkX Int#
a = let MkX 3# = undefined in () b = let MkX z = undefined in () c = let MkX _ = undefined in () d = let MkX {} = undefined in () e = let _ :: X = undefined in ()
Which of these diverge? e definitely converges, as X is lifted. b definitely diverges, because it binds z, a variable of an unlifted type, to a component of a diverging computation.
In GHC today, all the cases other than b converge.
Iavor suggests that a should diverge: 3# is a pattern of an unlifted type. What about c? What about d? Very unclear to me.
Note that banging the pattern nested inside the MkX does not change the behavior (in GHC today) for any of the cases where this makes sense to do so.
Richard
I guess a more explicit option would be to make it an error to use a lazy pattern on an unlifted type, and require programmers to manually add the `!` but I am not sure that gains much, and is more work in the compiler.
-Iavor
On Thu, Sep 3, 2020 at 10:38 AM Richard Eisenberg
wrote: On Sep 3, 2020, at 12:10 PM, Spiwack, Arnaud
wrote: This is all a tad tricky, I must say.
... which is one of the reasons I originally wanted one simple rule. I'm not now saying I was in the right, but it is an attractive resting point for this discussion.
To be clear, I don't think there's going to be any concrete action here without a proposal, so perhaps once this thread finds a resting point different than the status quo, someone will have to write it up.
Richard _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________
ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Not saying it's the best option, but it is an idea: Perhaps the behaviour
could stay the same, but the proposed behaviour could sit behind a language
pragma? I myself would always enable that pragma.
On Thu, Sep 3, 2020, 13:59 Domínguez, Facundo
I guess a more explicit option would be to make it an error to use a lazy pattern on an unlifted type, and require programmers to manually add the `!` but I am not sure that gains much, and is more work in the compiler.
Not being used to deal with unlifted types, this would be my preferred option. Having the meaning of let change depending on the levity of the type is a good opportunity for confusion.
Cheers, Facundo
On Thu, Sep 3, 2020 at 3:43 PM Iavor Diatchki
wrote: Yeah, I think these are nice examples that illustrate some of the problems with the current behavior of GHC. For example, I think it is weird that `b` non-terminates, but `c` does, because `z` is not used. I would expect those to be equivalent.
My preference would be to use the simple rule I mentioned before, but change how bang patterns work in pattern bindings. In particular, I think writing a bang pattern should constitute a use of the banged value. I think two equivalent ways to specify this is to say that a) writing a nested bang pattern implicitly adds bangs to the enclosing patterns, or I think equivalently b) writing `!p` is the same as writing `x@p` and adding `seq x` the same way we do for simple `!x = e` definitions
With this interpretation, all but `e` would diverge, which matches my intuition of how unboxed types should work.
-Iavor
On Thu, Sep 3, 2020 at 11:02 AM Richard Eisenberg
wrote: On Sep 3, 2020, at 1:51 PM, Iavor Diatchki
wrote: How about the following rule: unlifted patterns are always strict (i.e., you desugar them as if they had an explicit `!`). A pattern is "unlifted" if the type it examines is unlifted. Seems simple enough and, I think, it would do what most folks would expect.
I don't think it's this simple. For example:
data X = MkX Int#
a = let MkX 3# = undefined in () b = let MkX z = undefined in () c = let MkX _ = undefined in () d = let MkX {} = undefined in () e = let _ :: X = undefined in ()
Which of these diverge? e definitely converges, as X is lifted. b definitely diverges, because it binds z, a variable of an unlifted type, to a component of a diverging computation.
In GHC today, all the cases other than b converge.
Iavor suggests that a should diverge: 3# is a pattern of an unlifted type. What about c? What about d? Very unclear to me.
Note that banging the pattern nested inside the MkX does not change the behavior (in GHC today) for any of the cases where this makes sense to do so.
Richard
I guess a more explicit option would be to make it an error to use a lazy pattern on an unlifted type, and require programmers to manually add the `!` but I am not sure that gains much, and is more work in the compiler.
-Iavor
On Thu, Sep 3, 2020 at 10:38 AM Richard Eisenberg
wrote: On Sep 3, 2020, at 12:10 PM, Spiwack, Arnaud
wrote: This is all a tad tricky, I must say.
... which is one of the reasons I originally wanted one simple rule. I'm not now saying I was in the right, but it is an attractive resting point for this discussion.
To be clear, I don't think there's going to be any concrete action here without a proposal, so perhaps once this thread finds a resting point different than the status quo, someone will have to write it up.
Richard _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________
ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Iavor:
Yeah, I think these are nice examples that illustrate some of the problems
with the current behavior of GHC. For example, I think it is weird that b
non-terminates, but c does, because z is not used. I would expect those to
be equivalent.
What about if I rewrite all these patterns as
data X = MkX Int#
a = let ~(MkX 3#) = undefined in ()b = let ~(MkX z) = undefined in ()c
= let ~(MkX _) = undefined in ()d = let ~(MkX {}) = undefined in ()e =
let ~(_ :: X) = undefined in ()
Do you still expect c to diverge?
On Thu, Sep 3, 2020 at 9:04 PM chessai
Not saying it's the best option, but it is an idea: Perhaps the behaviour could stay the same, but the proposed behaviour could sit behind a language pragma? I myself would always enable that pragma.
On Thu, Sep 3, 2020, 13:59 Domínguez, Facundo
wrote: I guess a more explicit option would be to make it an error to use a lazy pattern on an unlifted type, and require programmers to manually add the `!` but I am not sure that gains much, and is more work in the compiler.
Not being used to deal with unlifted types, this would be my preferred option. Having the meaning of let change depending on the levity of the type is a good opportunity for confusion.
Cheers, Facundo
On Thu, Sep 3, 2020 at 3:43 PM Iavor Diatchki
wrote: Yeah, I think these are nice examples that illustrate some of the problems with the current behavior of GHC. For example, I think it is weird that `b` non-terminates, but `c` does, because `z` is not used. I would expect those to be equivalent.
My preference would be to use the simple rule I mentioned before, but change how bang patterns work in pattern bindings. In particular, I think writing a bang pattern should constitute a use of the banged value. I think two equivalent ways to specify this is to say that a) writing a nested bang pattern implicitly adds bangs to the enclosing patterns, or I think equivalently b) writing `!p` is the same as writing `x@p` and adding `seq x` the same way we do for simple `!x = e` definitions
With this interpretation, all but `e` would diverge, which matches my intuition of how unboxed types should work.
-Iavor
On Thu, Sep 3, 2020 at 11:02 AM Richard Eisenberg
wrote: On Sep 3, 2020, at 1:51 PM, Iavor Diatchki
wrote: How about the following rule: unlifted patterns are always strict (i.e., you desugar them as if they had an explicit `!`). A pattern is "unlifted" if the type it examines is unlifted. Seems simple enough and, I think, it would do what most folks would expect.
I don't think it's this simple. For example:
data X = MkX Int#
a = let MkX 3# = undefined in () b = let MkX z = undefined in () c = let MkX _ = undefined in () d = let MkX {} = undefined in () e = let _ :: X = undefined in ()
Which of these diverge? e definitely converges, as X is lifted. b definitely diverges, because it binds z, a variable of an unlifted type, to a component of a diverging computation.
In GHC today, all the cases other than b converge.
Iavor suggests that a should diverge: 3# is a pattern of an unlifted type. What about c? What about d? Very unclear to me.
Note that banging the pattern nested inside the MkX does not change the behavior (in GHC today) for any of the cases where this makes sense to do so.
Richard
I guess a more explicit option would be to make it an error to use a lazy pattern on an unlifted type, and require programmers to manually add the `!` but I am not sure that gains much, and is more work in the compiler.
-Iavor
On Thu, Sep 3, 2020 at 10:38 AM Richard Eisenberg
wrote: On Sep 3, 2020, at 12:10 PM, Spiwack, Arnaud
wrote: This is all a tad tricky, I must say.
... which is one of the reasons I originally wanted one simple rule. I'm not now saying I was in the right, but it is an attractive resting point for this discussion.
To be clear, I don't think there's going to be any concrete action here without a proposal, so perhaps once this thread finds a resting point different than the status quo, someone will have to write it up.
Richard _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________
ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Yes
On Fri, Sep 4, 2020 at 2:29 AM Spiwack, Arnaud
Iavor:
Yeah, I think these are nice examples that illustrate some of the problems with the current behavior of GHC. For example, I think it is weird that b non-terminates, but c does, because z is not used. I would expect those to be equivalent.
What about if I rewrite all these patterns as
data X = MkX Int# a = let ~(MkX 3#) = undefined in ()b = let ~(MkX z) = undefined in ()c = let ~(MkX _) = undefined in ()d = let ~(MkX {}) = undefined in ()e = let ~(_ :: X) = undefined in ()
Do you still expect c to diverge?
On Thu, Sep 3, 2020 at 9:04 PM chessai
wrote: Not saying it's the best option, but it is an idea: Perhaps the behaviour could stay the same, but the proposed behaviour could sit behind a language pragma? I myself would always enable that pragma.
On Thu, Sep 3, 2020, 13:59 Domínguez, Facundo
wrote: I guess a more explicit option would be to make it an error to use a lazy pattern on an unlifted type, and require programmers to manually add the `!` but I am not sure that gains much, and is more work in the compiler.
Not being used to deal with unlifted types, this would be my preferred option. Having the meaning of let change depending on the levity of the type is a good opportunity for confusion.
Cheers, Facundo
On Thu, Sep 3, 2020 at 3:43 PM Iavor Diatchki
wrote: Yeah, I think these are nice examples that illustrate some of the problems with the current behavior of GHC. For example, I think it is weird that `b` non-terminates, but `c` does, because `z` is not used. I would expect those to be equivalent.
My preference would be to use the simple rule I mentioned before, but change how bang patterns work in pattern bindings. In particular, I think writing a bang pattern should constitute a use of the banged value. I think two equivalent ways to specify this is to say that a) writing a nested bang pattern implicitly adds bangs to the enclosing patterns, or I think equivalently b) writing `!p` is the same as writing `x@p` and adding `seq x` the same way we do for simple `!x = e` definitions
With this interpretation, all but `e` would diverge, which matches my intuition of how unboxed types should work.
-Iavor
On Thu, Sep 3, 2020 at 11:02 AM Richard Eisenberg
wrote: On Sep 3, 2020, at 1:51 PM, Iavor Diatchki
wrote: How about the following rule: unlifted patterns are always strict (i.e., you desugar them as if they had an explicit `!`). A pattern is "unlifted" if the type it examines is unlifted. Seems simple enough and, I think, it would do what most folks would expect.
I don't think it's this simple. For example:
data X = MkX Int#
a = let MkX 3# = undefined in () b = let MkX z = undefined in () c = let MkX _ = undefined in () d = let MkX {} = undefined in () e = let _ :: X = undefined in ()
Which of these diverge? e definitely converges, as X is lifted. b definitely diverges, because it binds z, a variable of an unlifted type, to a component of a diverging computation.
In GHC today, all the cases other than b converge.
Iavor suggests that a should diverge: 3# is a pattern of an unlifted type. What about c? What about d? Very unclear to me.
Note that banging the pattern nested inside the MkX does not change the behavior (in GHC today) for any of the cases where this makes sense to do so.
Richard
I guess a more explicit option would be to make it an error to use a lazy pattern on an unlifted type, and require programmers to manually add the `!` but I am not sure that gains much, and is more work in the compiler.
-Iavor
On Thu, Sep 3, 2020 at 10:38 AM Richard Eisenberg
wrote: On Sep 3, 2020, at 12:10 PM, Spiwack, Arnaud
wrote: This is all a tad tricky, I must say.
... which is one of the reasons I originally wanted one simple rule. I'm not now saying I was in the right, but it is an attractive resting point for this discussion.
To be clear, I don't think there's going to be any concrete action here without a proposal, so perhaps once this thread finds a resting point different than the status quo, someone will have to write it up.
Richard _______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________
ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

On Fri, Sep 4, 2020 at 5:47 PM Iavor Diatchki
Interesting. Thanks. Personally, I don’t really know how to resolve the tension between the outer pattern saying: I *really* want to be lazy; and uniformity with the unlifted-variable-binding case. The point about b b = let ~(MkX z) = undefined in () Is that it *cannot* do anything else than force the pattern. Because b is an unlifted variable, it doesn’t contain a thunk. In other words, we can read it as the pattern being lazy, but it being immediately forced. Pretty much as in: let (x,y) = undefined in x `seq` () My intuition would be that let (x, (# #)) = (1, undefined) in () converges, while let (x, (# #)) = (1, undefined) in x `seq` () diverges. But I’m not exactly sure how to explain this rule succinctly. And I’m not sure it would be quite as intuitive to anybody. For starters, it seems to depart significantly from Iavor’s intuition.
participants (8)
-
Carter Schonwald
-
chessai
-
Domínguez, Facundo
-
Iavor Diatchki
-
John Cotton Ericson
-
Richard Eisenberg
-
Sebastian Graf
-
Spiwack, Arnaud