[GHC] #8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining ------------------------------------+------------------------------------- Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- I just remembered an old idea I put to the GHC user's list [http://www .mail-archive.com/glasgow-haskell-users@haskell.org/msg22119.html here], and thought I should present it here. As I understand it GHC inlines inlines only after a function is fully applied with respect to the syntactic left-hand side, so in order to control inlining and sharing, we sometimes see strange things like: {{{ {-# INLINE foo #-} foo :: a -> b -> c foo a = \b -> ... }}} It would be nice to be able to define the function syntactically in the way that's the most clear (e.g. in pointfree style, etc.) and specify at what point to inline something like this: {{{ foo :: a -> {-# INLINE #-} b -> c foo a b = ... -- or: foo = ... }}} ...which tells the compiler to inline after applying the arguments to the left of the pragma, and GHC would do whatever trivial (I assume?) eta- conversion was required. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): I know; the current story for inlining is a compromise. If people really want the expressiveness, I'd prefer to do so by changing the existing INLINE pragma. Something like {{{ {-# INLINE f (arity 2) #-} }}} or {{{ {-# INLINE (f _ _) #-} }}} I don't see this as very high priority, but (everyone) please chime in if you care. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by WrenThornton): * cc: wren@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by YitzGale): * cc: gale@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by lelf): * cc: me@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by Ptharien's Flame): * cc: alexanderaltman@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by basvandijk): * cc: v.dijk.bas@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by ekmett): This would make a big difference in the readability of the lens code. We have an opn issue to move more of our arguments to the right of the = to get more agressive inlining, but it makes a few hundred functions harder to read. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by ekmett): * cc: ekmett@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): Thanks. Can I encourage the other cc folks to say what their use-case is, as Edward has done? A plain "cc" says "I'm interested", but doesn't directly support the claim that it's an important or useful feature. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by ekmett): Replying to [comment:9 simonpj]:
PS: Edward, could you offer a couple of concrete examples?
This issue I mentioned is up on github at https://github.com/ekmett/lens/issues/183 We have a lot of code like {{{ over l f = runIdentity #. l (Identity #. f) }}} In that you can read (#.) as if it were (.), but if we switch it to {{{ over l = \f -> runIdentity #. l (Identity #. f) }}} then GHC can inline it better in a call like {{{ foo :: (a -> b) -> [a] -> [b] foo = over mapped }}} For reference: {{{ mapped f = Identity #. fmap (runIdentity #. f) }}} Unfortunately, this means that the 'f' argument isn't in scope for where clauses, etc. which makes a lot of function implementations a lot uglier when they have more structure than this trivial example. {{{ scanr1Of l f = snd . mapAccumROf l step Nothing where step Nothing a = (Just a, a) step (Just s) a = let r = f a s in (Just r, r) }}} There because f is referenced in the where clause step becomes explicitly parameterized on f, so we wind up having to either plumb the f argument in to step or we have to define step inside of a let clause inside of the lambda that takes f cluttering things up considerably. You can find dozens of examples by skimming through http://hackage.haskell.org/packages/archive/lens/3.9.0.2/doc/html/src /Control-Lens-Traversal.html#mapMOf or http://hackage.haskell.org/packages/archive/lens/3.9.0.2/doc/html/src /Control-Lens-Fold.html#foldrOf Almost any combinator with a name that ends in "Of" which currently takes more than one argument on the left hand side of the equal sign is a candidate. Our current plan is to just bite the bullet and move all the code around to get better inlining, because we've found it makes an difference in quality of the resulting core. -Edward -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): OK. Any thoughts about concrete syntax? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by basvandijk):
Can I encourage the other cc folks to say what their use-case is
I remember that by eta abstracting the definitions in [http://hackage.haskell.org/packages/archive/vector/0.10.0.1/doc/html /Data-Vector-Generic.html Data.Vector.Generic] I could really speedup the [https://github.com/basvandijk/vector- bytestring/blob/master/bench/bench.hs benchmarks] in `vector-bytestring`. If there's some nice syntax to make eta conversion easier it would be cheaper to make this change. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): Copied from #8508. After trying a simple test, I noticed some strange performance results from stylistic changes to the code. For example, {{{#!haskell import qualified Data.Vector.Unboxed as U {-# INLINE f #-} f :: U.Vector Int -> U.Vector Int -> U.Vector Int f = U.zipWith (+) -- version 1 --f x = U.zipWith (+) x -- version 2 --f x = (U.zipWith (+) x) . id -- version 3 --f x y = U.zipWith (+) x y -- version 4 main = do let iters = 100 dim = 221184 y = U.replicate dim 0 :: U.Vector Int let ans = iterate (f y) y !! iters putStr $ (show $ U.foldl1' (+) ans) }}} Versions 1 and 2 of `f` run in 1.6 seconds, while versions 3 and 4 run in 0.09 seconds (with vector-0.10.9.1 and GHC 7.6.2, compiling with -O2). According to an answer on the Vector trac (link below), this problem is because GHC only inlines on saturated function applications. Is there any way to expand the cases when GHC inlines to avoid having coding style affect performance? * [https://github.com/haskell/vector/issues/4 Vector Trac] -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): No great difficulty to implement something here, if y'all can converge on a syntax. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by carter): simon, you're forgetting version 5! : {{{ f = \ x y -> ( U.zipWith (+) x y) }}} I think thats the "maximally inlining" way to define that procedure. Its also how i'm writing quite a bit of my performance sensitive code, because a) this way inlining is independent of using it point free or not b) it saturates all the functions in the body of the procedure c) the way the end user uses the code won't impact when / if inlining happens :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by crockeea): * cc: ecrockett0@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------ Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by ihameed): * cc: idhameed@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8099: Alternate syntax for indicating when a function is "fully applied" for purposes of inlining -------------------------------------+------------------------------------- Reporter: jberryman | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining 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 mpickering): * keywords: => Inlining -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8099#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC