[GHC] #13340: Core top-level bindings no longer deduplicated

#13340: Core top-level bindings no longer deduplicated -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This module {{{#!hs module Two where f :: Int -> Int f n = n + 1 + 1 g :: Int -> Int g n = n + 1 + 1 }}} used to (in 8.0) optimize to a definition of `g` plus `f = g`. The Common sub-expression phase noticed `f` and `g` were equal. That doesn't happen any more in HEAD and we end up with two copies of the code. The Common sub-expression pass apparently still runs, it just doesn't succeed in removing one of the bindings. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13340 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13340: Core top-level bindings no longer deduplicated -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): I guess this probably has to do with #11781, but it seems a bit silly that we can't handle this case. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13340#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13340: Core top-level bindings no longer deduplicated -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Even this case doesn't get deduplicated: {{{#!hs f x = x g x = x }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13340#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13340: Core top-level bindings no longer deduplicated -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: 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 bgamari): * priority: high => highest -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13340#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13340: Core top-level bindings no longer deduplicated -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: 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 rwbarton): * priority: highest => high Comment: This does get deduplicated though: {{{#!hs f = 0 :: Int g = 0 :: Int }}} so it's not totally broken. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13340#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13340: Core top-level bindings no longer deduplicated -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: 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 rwbarton): * priority: high => highest -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13340#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13340: Core top-level bindings no longer deduplicated -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): It must be related to the new `Note [CSE for stable unfoldings]` as `f` and `g` get stable unfoldings in the cases in which CSE does not work and vanilla unfoldings in the case in which CSE does work. I have no idea why the unfoldings for `f` and `g` would ever be stable, though, reading the documentation for `InlineStable`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13340#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13340: Core top-level bindings no longer deduplicated
-------------------------------------+-------------------------------------
Reporter: rwbarton | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone: 8.2.1
Component: Compiler | Version: 8.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13340: Core top-level bindings no longer deduplicated -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
I have no idea why the unfoldings for f and g would ever be stable
It's done by `certainlyWillInline`. See `Note [Don't w/w inline small non-loop-breaker things]` in `WorkWrap`. I'd be happy to have a better way, but this is not terrible. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13340#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13340: Core top-level bindings no longer deduplicated -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I realised the following two things. * If we wanted to distinguish between stable-unfoldings created by user- specified INLINE pragmas, from those created by `WorkWrap` (see `Note [Don't w/w inline small non-loop-breaker things] there), we can do so. The former has `inl_spec = Inline` in its `InlinePragma`; the latter has `inl_spec = EmptyInlineSpec`. * But re-reading the note {{{ Note [CSE for stable unfoldings] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider {-# Unf = Stable (\pq. build blah) #-} foo = x Here 'foo' has a stable unfolding, but its (optimised) RHS is trivial. (Turns out that this actually happens for the enumFromTo method of the Integer instance of Enum in GHC.Enum.) Then we obviously do NOT want to extend the substitution with (foo->x)! See similar SimplUtils Note [Stable unfoldings and postInlineUnconditionally]. Nor do we want to change the reverse mapping. Suppose we have {-# Unf = Stable (\pq. build blah) #-} foo = <expr> bar = <expr> There could conceivably be merit in rewriting the RHS of bar: bar = foo but now bar's inlining behaviour will change, and importing modules might see that. So it seems dodgy and we don't do it. }}} suppose both `foo` and `bar` have a stable-unfolding, and they are identical. That's exactly the situation in the examples above. Then it'd be fine to replace `bar` by `foo`. I think we should try the second of these. Not hard I think. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13340#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13340: Core top-level bindings no longer deduplicated -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Strangely enough this test appears to be unexpectedly passing as of 701256df88c61a2eee4cf00a59e61ef76a57b4b4. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13340#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13340: Core top-level bindings no longer deduplicated -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Simon, it looks like you implemented the first bullet point in your comment above in 55efc9718b520ef354e32c15c4b49cdfecce412f "Combine identical case alternatives in CSE", though the old version is commented out. {{{#!diff +noCSE :: InId -> Bool +noCSE id = not (isAlwaysActive (idInlineActivation id)) + -- See Note [CSE for INLINE and NOINLINE] + || isAnyInlinePragma (idInlinePragma id) + --isStableUnfolding (idUnfolding id) + -- See Note [CSE for stable unfoldings] + || isJoinId id + -- See Note [CSE for join points?] }}} Did you mean to commit this in this form? It did fix the test associated to this ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13340#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13340: Core top-level bindings no longer deduplicated -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): So I did! I was fixing a whole bunch of things, noted this problem, fixed it, and forgot. Then when building the patch sequence I accidentally swept this into the equal-alts patch. I think it'll do fine as-is. Could you add language in `Note [CSE for stable unfoldings]` to explain the use of `isAnyInlinePragma`; and point to this ticket? And delete the commented-out `isStableUnfolding`. Thanks Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13340#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13340: Core top-level bindings no longer deduplicated -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: 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 bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13340#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13340: Core top-level bindings no longer deduplicated
-------------------------------------+-------------------------------------
Reporter: rwbarton | Owner: (none)
Type: bug | Status: closed
Priority: highest | Milestone: 8.2.1
Component: Compiler | Version: 8.1
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari
participants (1)
-
GHC