[GHC] #10744: Allow oneShot to work with unboxed types

#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Currently `oneShot` requires that both the argument type and the return type of the given function have the kind `*`. It would be nice if I could use unlifted types there. The following program demonstrates this: {{{#!hs {-# LANGUAGE MagicHash #-} module Foo where import GHC.Exts import GHC.Magic f0 :: Int -> Int f0 = oneShot $ \n -> n -- OK f1 :: Int# -> Int f1 = oneShot $ \n# -> I# n# -- Error, the argument type is unlifted f2 :: Int -> Int# f2 = oneShot $ \(I# n#) -> n# -- Error, the result type is unlifted }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by nomeata): * cc: nomeata (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Out of curiosity: How are you using `oneShot`? We added it to make foldl list fusion more reliable, but never actually had a case where it would be better than Call Arity, so I am very interested in examples of effective uses of `oneShot`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by akio): I use it in the fast-builder package [1], which aims to be a ByteString builder implementation that is significantly faster than the standard one. The main Builder type looks like this {{{#!hs type Builder = DataSink -> State -> State data DataSink = -- abstract data State = -- abstract -- | Builder concatenation. (<>) :: Builder -> Builder -> Builder a <> b = \sink s = b sink (a sink s) -- | Primitive builder. int :: Int -> Builder int = -- implementation omitted. }}} As an example, the user may write code like this to serialize a list of Ints: {{{#!hs serialize :: [Int] -> Builder serialize list = int (length list) <> foldr (<>) mempty (map int list) }}} For `serialize` to work efficiently, I really want it to have the arity of 3. However, simply inlining `int` and `(<>)` only gives {{{#!hs serialize = \list -> let len = length list in \sink s -> ... }}} So it gets arity 1, which means it has to allocate a lambda and then call it. By default GHC doesn't eta-expand `serialize` because it wants to avoid evaluating `length` multiple times. However, I want GHC to produce better code in the assumption that the resulting Builder will be used at most once, because using the same Builder multiple times is usually a bad idea anyway (you should instead turn it into a ByteString and use that ByteString multiple times). I express this preference by inserting calls to `oneShot` into the definitions of `(<>)`, `int`, etc. The current type of `oneShot` means `State` has to be a lifted type. Ideally I'd like to use something like `(# Addr#, Addr#, State# RealWorld #)`. [1]: http://hackage.haskell.org/package/fast-builder -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Hmm, I am not sure if this is a valid use of `oneShot` if you cannot guarantee that the Builder will be used only once, as GHC and the runtime (probably) relies on the annotation to be correct, and you might get crashes at runtime. If everything is inlined enough the existing arity analyses might be able to eta-expand `serialize`, but that’s probably not reliably enough. But nevertheless, the feature request is of course valid. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by akio): Replying to [comment:4 nomeata]:
Hmm, I am not sure if this is a valid use of `oneShot` if you cannot guarantee that the Builder will be used only once, as GHC and the runtime (probably) relies on the annotation to be correct, and you might get crashes at runtime.
Oh, I didn't know this, thank you for pointing it out. I had hoped that it worked the same way as the state hack, which does not cause a crash even if the assumption is violated and the IO action is used multiple times. If this is not a valid use of `oneShot`, I don't have real uses that involve unlifted types. I'm happy to close this ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Wait wait! I’m just saying that at the moment, I cannot guarantee that it is safe. It is possible that it is safe after all (and I really need to investigate and document that). And if not, it might be possible to make it safe, now that we have a real use case! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by akio): Ah sorry, I had misinterpreted your comment. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): I think it'd be fine to allow `oneShot` to accept unboxed types; just a matter of using `openAlphaTyVar` etc in `MkId.oneShot`. Give it a try and submit a patch. Moreover, the worst that can happen if you mis-use it, by applying it to a function that is called many times, is that computation may be repeated. For example {{{ f xs y = let x = expensive_fn y in map (oneShot (\v. x+v)) xs }}} The `oneShot` claims (falsely unless `xs` has length at most one) that `(\v. x+v)` is called at most once. So GHC will move the call to `expensive_fn` inside the lambda thus: {{{ f xs y = map (oneShot (\v. expensive_fn y + v)) xs }}} That will work just fine, but it'll call `expensive_fn` once per element of `xs`. So, no seg-faults at least! It would be good if someone felt like extending the Haddock comments for `GHC.Magic.oneShot` to explain this. Thanks Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Simon, I am worried that due to a wrong annotation here, a thunk is marked as single entry that is not really single entry, and I can imagine that bad things can happen then. But if you think that this cannot happen, then I’d be relieved, and akio can go forwared using `oneShot`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Simon, I am worried that due to a wrong annotation here, a thunk is marked as single entry that is not really single entry, and I can imagine
#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Replying to [comment:9 nomeata]: that bad things can happen then. But if you think that this cannot happen, then I’d be relieved, and akio can go forwared using `oneShot`. Yes, this is what happened in #10414 and #10218. Suppose in my example in comment:8 that GHC does ''not'' float the `let x` thunk into the lambda for some reason. Then it might instead be marked single-entry. So we get {{{ f xs y = let x[single-entry] = expensive_fn y in map (oneShot (\v. x+v)) xs }}} The bad thing in #10414 and #10218 was that, with eager black-holing, `x` was blackholed, so that the second time it was entered we got `<<loop>>`. But the fix in ticket:10414#comment:29 switches off eager-blackholing for single-entry thunks, so it'll all be fine. So, because of that, I think we are good. Mind you, if we implement the sanity check in #10613, you might get failures reported due to bogus `oneShot` claims. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Interestingly, I cannot even make GHC mark such a thunk as a `\s` closure in the STG output (which is what we are looking for, right?). Anyways, I’ll prepare a patch to make `oneShot` open-kinded, and also update the docs. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature request | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1136 -------------------------------------+------------------------------------- Changes (by nomeata): * status: new => patch * differential: => Phab:D1136 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1136 -------------------------------------+------------------------------------- Changes (by nomeata): * status: patch => closed * resolution: => fixed Comment: Voila, akio. Hack away! And let me know if `oneShot` makes a difference for your use case, I’d like to report on it in my thesis, which marginally mentions `oneShot` as well. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1136 -------------------------------------+------------------------------------- Comment (by nomeata): Darn, wrong ticket number in commit message. This is fixed in changeset:92f35cd9829db7555397aa3dc8cd243d17694fee -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1136 -------------------------------------+------------------------------------- Comment (by akio): Thank you very much for implementing this! Replying to [comment:13 nomeata]:
Voila, akio. Hack away! And let me know if `oneShot` makes a difference for your use case, I’d like to report on it in my thesis, which marginally mentions `oneShot` as well.
In one of my benchmarks (serializing JSON), `oneShot` improves performance by 50%. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10744: Allow oneShot to work with unboxed types -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: feature request | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1136 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * failure: None/Unknown => Runtime performance bug * milestone: => 8.0.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10744#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC