[GHC] #13422: INLINE CONLIKE sometimes fails to inline

#13422: INLINE CONLIKE sometimes fails to inline -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: #7206 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I got surprisingly poor results from the `cheapBuild` experiment (see #7206), so I decided to try a simple example. {{{#!hs foo :: Int -> Int foo n = s + p where nums = [1..n] s = sum nums p = product nums }}} The idea is that we want `nums` to inline into `s` and `p`; the lost sharing is unimportant. Unfortunately, this didn't fuse. I got {{{ -- RHS size: {terms: 44, types: 31, coercions: 0, joins: 2/3} $wfoo :: Int# -> Int# $wfoo = \ (ww_s2HT :: Int#) -> let { nums_s2Gq :: [Int] nums_s2Gq = eftInt 1# ww_s2HT } in joinrec { $wgo_s2HP :: [Int] -> Int# -> Int# $wgo_s2HP (w_s2HJ :: [Int]) (ww1_s2HN :: Int#) = case w_s2HJ of { [] -> joinrec { $wgo1_s2HI :: [Int] -> Int# -> Int# $wgo1_s2HI (w1_s2HC :: [Int]) (ww2_s2HG :: Int#) = case w1_s2HC of { [] -> +# ww1_s2HN ww2_s2HG; : y_a2F9 ys_a2Fa -> case y_a2F9 of { I# y1_a2Gf -> jump $wgo1_s2HI ys_a2Fa (*# ww2_s2HG y1_a2Gf) } }; } in jump $wgo1_s2HI nums_s2Gq 1#; : y_a2F9 ys_a2Fa -> case y_a2F9 of { I# y1_a2EX -> jump $wgo_s2HP ys_a2Fa (+# ww1_s2HN y1_a2EX) } }; } in jump $wgo_s2HP nums_s2Gq 0# -- RHS size: {terms: 10, types: 4, coercions: 0, joins: 0/0} foo :: Int -> Int foo = \ (w_s2HQ :: Int) -> case w_s2HQ of { I# ww1_s2HT -> case $wfoo ww1_s2HT of ww2_s2HX { __DEFAULT -> I# ww2_s2HX } } }}} I verified that `cheapBuild` actually appeared (in `-dverbose-core2core`), but it didn't fuse, and ultimately inlined. Interestingly, forcing the argument manually fixed the problem: {{{#!hs foo :: Int -> Int foo !n = s + p where nums = [1..n] s = sum nums p = product nums }}} produces {{{#!hs $wfoo :: Int# -> Int# $wfoo = \ (ww_s2Ia :: Int#) -> case tagToEnum# (># 1# ww_s2Ia) of { False -> joinrec { $wgo_s2I6 :: Int# -> Int# -> Int# $wgo_s2I6 (w_s2I0 :: Int#) (ww1_s2I4 :: Int#) = case tagToEnum# (==# w_s2I0 ww_s2Ia) of { False -> jump $wgo_s2I6 (+# w_s2I0 1#) (+# ww1_s2I4 w_s2I0); True -> let { x_X2Fz :: Int# x_X2Fz = +# ww1_s2I4 w_s2I0 } in joinrec { $wgo1_s2HY :: Int# -> Int# -> Int# $wgo1_s2HY (w1_s2HS :: Int#) (ww2_s2HW :: Int#) = case tagToEnum# (==# w1_s2HS ww_s2Ia) of { False -> jump $wgo1_s2HY (+# w1_s2HS 1#) (*# ww2_s2HW w1_s2HS); True -> +# x_X2Fz (*# ww2_s2HW w1_s2HS) }; } in jump $wgo1_s2HY 1# 1# }; } in jump $wgo_s2I6 1# 0#; True -> 1# } }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13422 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13422: INLINE CONLIKE sometimes fails to inline -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Can you describe how I can reproduce this? Thanks Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13422#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13422: INLINE CONLIKE sometimes fails to inline -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Reproduction instructions: Clone the `wip/cheapBuild` branch. Compile the following file: {{{#!hs module Ischeap where import Data.List foo :: Int -> Int foo n = s + p where nums = [1..n] s = sum nums p = product nums }}} using `ghc-stage2` with `-O2 -ddump-simpl`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13422#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13422: INLINE CONLIKE sometimes fails to inline -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I've quickly looked at this and it seems that one crucial difference is that when `n` is banged the first phase simplifier considers it to be a `ValueArg` as it has a conlike unfolding, whereas without it is merely ` TrivialArg`. At first simplification proceeds similarly in both cases, * `$fEnumInt_$cenumFromTo` * `sum` is inlined (the unfolding of which contains a `foldl`). It is interesting to note that the list argument is considered to be a `ValueArg` with the bang, but a `TrivialArg` without. * `foldl` is inlined * `$fNumInt_$cfromInteger` is inlined This is where the two programs diverge. While the `fold/cheapBuild` rule fires in the banged case, it fails to fire on the unbanged program. After that point, things obviously proceed much differently. While `cheapBuild` itself is eventually inlined in the unbanged version, it the fusion rule never fires. This is rather curious since, * the desugared core is identical between the banged and unbanged case * the performed inlinings are identical -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13422#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13422: INLINE CONLIKE sometimes fails to inline -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Here's the reason. We get {{{ let xs = case n of I# n1 -> cheapBuild blah in ...(foldr k z xs)...(foldr k2 z2 xs)... }}} So the `cheapBuild` is hidden behind that `case n` and the `foldr/cheapBuild` rule does not fire. The problem comes from {{{ instance Enum Int where ... enumFromTo (I# x) (I# y) = eftInt x y }}} So `[1..n]` desugars into `(case n of I# n' -> eftInt 1# n')`. This doesn't hurt normal foldr/build because if we see {{{ foldr k z (case n of I# n' -> build blah) }}} we know that `foldr` is strict and so float the case outwards. This doesn't happen with the `cheapBuild` stuff since the producer and consumer are further apart. But the solution is, I think, easy: move the evaluation of n into `eftInt`. So we have {{{ instance Enum Int where ... enumFromTo x y = eftInt x y }}} Now `eftInt` takes boxed `Ints` but it can evaluate them just fine. I've pushed a patch to `wip/cheap-build`, and it works just fine. '''However''': * It needs a serious note (steal the text above) * Other uses of `cheapBuild` need similar treatment. So the commit needs work. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13422#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13422: INLINE CONLIKE sometimes fails to inline -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): I think this ticket can be closed. This ticket was about an improvement to the idea described in #7206, and comment:4 fixes this. I've rebased the cheap-build branch (not pushed to GHC's git repo as force pushes are not allowed, see it here: https://github.com/osa1/ghc/tree/cheap-build), applied idea in comment:4, and verified that it works on `Int`, `Word` and `Char` enumerations. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13422#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13422: INLINE CONLIKE sometimes fails to inline -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: Lovely. Thanks Omer! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13422#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC