Implicit reboxing of unboxed tuple in let-patterns

John Cotton Ericson John.Ericson at Obsidian.Systems
Mon Aug 31 17:48:55 UTC 2020


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 <chessai1996 at gmail.com 
> <mailto:chessai1996 at 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
>     <arnaud.spiwack at tweag.io <mailto:arnaud.spiwack at 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
>         <carter.schonwald at gmail.com
>         <mailto:carter.schonwald at 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
>             <arnaud.spiwack at tweag.io <mailto:arnaud.spiwack at 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.html#extension-UnboxedTuples>:
>
>
>
>
>
>                     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 at haskell.org <mailto:ghc-devs at haskell.org>
>
>                 http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>         _______________________________________________
>         ghc-devs mailing list
>         ghc-devs at haskell.org <mailto:ghc-devs at haskell.org>
>         http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20200831/c71b9741/attachment-0001.html>


More information about the ghc-devs mailing list