[GHC] #14688: Note [Lone variables] leads to missing a case-of-case opportunity

#14688: Note [Lone variables] leads to missing a case-of-case opportunity -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 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: -------------------------------------+------------------------------------- After the simplifier, my program ends up in the following state. {{{ foo = \f s -> let x = case s of { T1 a b -> a :> b :> Nil } in fmap (\v -> case x of { _v1 :> vs -> T1 v (case vs of {v2 :> _ -> v2}) }) (f (case x of {v1 :> _ -> v1})) }}} Now if I understand `Note [Lone variables]` correctly, `x` is NOT inlined into the call sites, no matter what I do as `x` is work-free. However, this is bad as if we were to inline `x` we get a case-of-case opportunity. {{{ => Inline foo = \f s -> let x = case s of { T1 a b -> a :> b :> Nil } in fmap (\v -> case (case s of { T1 a b -> a :> b :> Nil }) of { _v1 :> vs -> T1 v (case vs of {v2 :> _ -> v2}) }) (f (case x of {v1 :> _ -> v1})) => case of case foo = \f s -> let x = case s of { T1 a b -> a :> b :> Nil } in fmap (\v -> case s of { T1 a b -> case (a :> b :> Nil) of { _v1 :> vs -> T1 v (case vs of {v2 :> _ -> v2}) }) (f (case x of {v1 :> _ -> v1})) => case of known constructor foo = \f s -> let x = case s of { T1 a b -> a :> b :> Nil } in fmap (\v -> case s of { T1 a b -> T1 v b}) (f (case x of {v1 :> _ -> v1})) => Same for the other branch foo = \f s -> fmap (\v -> case s of { T1 a b -> T1 v b}) (case s of T1 a b -> a) }}} Which no longer mentions the intermediate representation. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14688 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14688: Note [Lone variables] leads to missing a case-of-case opportunity -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 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): Crumbs, you are right. Looking at the `Note [Lone variables]` I see {{{ Fundamentally such contexts should not encourage inlining because the context can ``see'' the unfolding of the variable (e.g. case or a RULE) so there's no gain. If the thing is bound to a value. ... So the non-inlining of lone_variables should only apply if the unfolding is regarded as cheap; because that is when exprIsConApp_maybe looks through the unfolding. Hence the "&& is_wf" in the InlineRule branch. }}} But actually `exprIsConApp_maybe` uses `expandUnfolding_maybe` to look through the unfolding, which in turn uses the `uf_expandable` field of the unfolding, not the `uf_is_work_free` field. Conclusion: the test in `interesting_call` in `tryUnfolding` (at `Note [Lone variable]`) should not test `is_wf` but rather `is_exp`. That's an extremely simple, local change. Can you try it? I think it'll fix your problem. If it does, could you do a nofib comparison, before and after? Thanks. This looks promising. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14688#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14688: Note [Lone variables] leads to missing a case-of-case opportunity -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 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 mpickering): I tried to get to the bottom of what was going on here this afternoon. Here's a nice self-contained program now. https://gist.github.com/mpickering/37b7119561e825ba895ac2b014d178d7 `foo` is the example from the original ticket. `x` is not work-free or expandable. `foo2` is a modified example where `x` is work-free and expandable but still doesn't get inlined even with the modified test (changing `is_wf` to `is_exp`). 1. Something is definitely wrong in `tryUnfolding` as if `lone_variable` then either `some_benefit` or `is_wf` is going to be `False` so it won't get inlined. (Case 1: `is_wf` is False; trivial, Case 2: `is_wf` is True then `not (lone_variable && is_wf)` will be `False` and hence `some_benefit` is `False`.) 2. Changing it to `is_exp` doesn't help `foo2` as `x` is reported to be expandable as well as work-free. 3. Using a GADT means that GHC concludes that the `x` binding is no longer expandable or work-free which I found very surprising. Adding the type index shouldn't affect the optimiser like this? 4. Changing the call to `is_exp` doesn't look like it would work anyway as there is no case for `Case` in `expandUnfolding_maybe` and so it will still return `Nothing`. Have you got any more hints Simon :) ? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14688#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14688: Note [Lone variables] leads to missing a case-of-case opportunity -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 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): Huh. I really don't think case-expressions should be expandable. I think that's an unintentional consequences of sharing `exprIsCheapX`. This patch makes both `foo` and `foo2` behave well. Would you like to do a full nofib run? {{{ diff --git a/compiler/coreSyn/CoreArity.hs b/compiler/coreSyn/CoreArity.hs index 945cad6..538648d 100644 --- a/compiler/coreSyn/CoreArity.hs +++ b/compiler/coreSyn/CoreArity.hs @@ -514,9 +514,9 @@ getBotArity _ = Nothing mk_cheap_fn :: DynFlags -> CheapAppFun -> CheapFun mk_cheap_fn dflags cheap_app | not (gopt Opt_DictsCheap dflags) - = \e _ -> exprIsCheapX cheap_app e + = \e _ -> exprIsCheapX True cheap_app e | otherwise - = \e mb_ty -> exprIsCheapX cheap_app e + = \e mb_ty -> exprIsCheapX True cheap_app e || case mb_ty of Nothing -> False Just ty -> isDictLikeTy ty diff --git a/compiler/coreSyn/CoreUnfold.hs b/compiler/coreSyn/CoreUnfold.hs index c459fd2..f30aca6 100644 --- a/compiler/coreSyn/CoreUnfold.hs +++ b/compiler/coreSyn/CoreUnfold.hs @@ -1241,8 +1241,8 @@ tryUnfolding dflags id lone_variable = True | otherwise = case cont_info of - CaseCtxt -> not (lone_variable && is_wf) -- Note [Lone variables] - ValAppCtxt -> True -- Note [Cast then apply] + CaseCtxt -> not (lone_variable && is_exp) -- Note [Lone variables] + ValAppCtxt -> True -- Note [Cast then apply] RuleArgCtxt -> uf_arity > 0 -- See Note [Unfold info lazy contexts] DiscArgCtxt -> uf_arity > 0 -- RhsCtxt -> uf_arity > 0 -- diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index 5e32dc6..c99e05f 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -1131,18 +1131,18 @@ in this (which it previously was): -} -------------------- +exprIsWorkFree :: CoreExpr -> Bool -- See Note [exprIsWorkFree] +exprIsWorkFree = exprIsCheapX True isWorkFreeApp + exprIsCheap :: CoreExpr -> Bool -exprIsCheap = exprIsCheapX isCheapApp +exprIsCheap = exprIsCheapX True isCheapApp exprIsExpandable :: CoreExpr -> Bool -- See Note [exprIsExpandable] -exprIsExpandable = exprIsCheapX isExpandableApp - -exprIsWorkFree :: CoreExpr -> Bool -- See Note [exprIsWorkFree] -exprIsWorkFree = exprIsCheapX isWorkFreeApp +exprIsExpandable = exprIsCheapX False isExpandableApp -------------------- -exprIsCheapX :: CheapAppFun -> CoreExpr -> Bool -exprIsCheapX ok_app e +exprIsCheapX :: Bool -> CheapAppFun -> CoreExpr -> Bool +exprIsCheapX ok_case ok_app e = ok e where ok e = go 0 e @@ -1153,7 +1153,8 @@ exprIsCheapX ok_app e go _ (Type {}) = True go _ (Coercion {}) = True go n (Cast e _) = go n e - go n (Case scrut _ _ alts) = ok scrut && + go n (Case scrut _ _ alts) = ok_case && + ok scrut && and [ go n rhs | (_,_,rhs) <- alts ] go n (Tick t e) | tickishCounts t = False | otherwise = go n e }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14688#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14688: Note [Lone variables] leads to missing a case-of-case opportunity -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 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 mpickering): Nofib results, so generally reduced allocations but very little change overall. {{{ -------------------------------------------------------------------------------- Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- CS 0.0% 0.0% 0.183 0.183 0.0% CSD 0.0% 0.0% -0.1% -0.1% 0.0% FS 0.0% 0.0% +0.4% +0.5% 0.0% S 0.0% 0.0% -0.4% -0.5% 0.0% VS 0.0% 0.0% +0.3% +0.3% 0.0% VSD 0.0% 0.0% 0.009 0.009 0.0% VSM 0.0% 0.0% -0.4% -0.4% 0.0% anna +0.0% +0.3% 0.062 0.062 0.0% ansi 0.0% 0.0% 0.000 0.000 0.0% atom 0.0% 0.0% 0.175 0.175 0.0% awards -0.0% -0.2% 0.000 0.000 0.0% banner 0.0% 0.0% 0.000 0.000 0.0% bernouilli 0.0% 0.0% 0.095 0.095 0.0% binary-trees 0.0% 0.0% -0.0% +0.0% 0.0% boyer 0.0% 0.0% 0.022 0.022 0.0% boyer2 +0.0% 0.0% 0.004 0.004 0.0% bspt +0.0% -0.1% 0.004 0.004 0.0% cacheprof 0.0% -0.0% -0.1% -0.1% 0.0% calendar 0.0% 0.0% 0.000 0.000 0.0% cichelli 0.0% 0.0% 0.043 0.043 0.0% circsim 0.0% 0.0% +0.3% +0.3% 0.0% clausify 0.0% 0.0% 0.020 0.020 0.0% comp_lab_zift -0.0% -0.0% 0.105 0.105 0.0% compress 0.0% 0.0% 0.073 0.073 0.0% compress2 +0.1% -0.7% 0.077 0.077 -4.0% constraints 0.0% 0.0% +0.2% +0.2% 0.0% cryptarithm1 0.0% 0.0% -0.1% +0.1% 0.0% cryptarithm2 0.0% 0.0% 0.004 0.004 0.0% cse 0.0% 0.0% 0.001 0.001 0.0% digits-of-e1 0.0% 0.0% +0.0% +0.0% 0.0% digits-of-e2 0.0% 0.0% -0.3% -0.3% 0.0% eliza +0.0% -2.4% 0.000 0.000 0.0% event 0.0% 0.0% 0.083 0.083 0.0% exact-reals -0.0% 0.0% +2.7% +2.6% 0.0% exp3_8 0.0% 0.0% 0.132 0.132 0.0% expert 0.0% 0.0% 0.000 0.000 0.0% fannkuch-redux 0.0% 0.0% -1.7% -1.7% 0.0% fasta 0.0% 0.0% -0.5% -0.5% 0.0% fem +0.0% -0.0% 0.013 0.013 0.0% fft 0.0% 0.0% 0.019 0.019 0.0% fft2 0.0% 0.0% 0.027 0.027 0.0% fibheaps 0.0% 0.0% 0.014 0.014 0.0% fish 0.0% 0.0% 0.006 0.006 0.0% fluid +0.0% +0.1% 0.004 0.004 0.0% fulsom +0.1% -13.3% 0.158 0.158 +190.0% gamteb 0.0% 0.0% 0.023 0.023 0.0% gcd 0.0% 0.0% 0.024 0.024 0.0% gen_regexps 0.0% 0.0% 0.000 0.000 0.0% genfft 0.0% 0.0% 0.018 0.018 0.0% gg +0.0% -0.1% 0.005 0.005 0.0% grep 0.0% 0.0% 0.000 0.000 0.0% hidden +0.0% 0.0% -4.2% -4.2% 0.0% hpg 0.0% 0.0% 0.048 0.048 0.0% ida +0.0% +0.3% 0.052 0.052 0.0% infer 0.0% 0.0% 0.029 0.029 0.0% integer 0.0% 0.0% -0.4% -0.4% 0.0% integrate 0.0% 0.0% 0.070 0.070 0.0% k-nucleotide 0.0% 0.0% +4.9% +4.9% 0.0% kahan 0.0% 0.0% 0.195 0.195 0.0% knights 0.0% 0.0% 0.002 0.002 0.0% lambda 0.0% 0.0% +0.3% +0.3% 0.0% last-piece 0.0% 0.0% +0.6% +0.6% 0.0% lcss 0.0% 0.0% -0.3% -0.4% 0.0% life 0.0% 0.0% 0.136 0.136 0.0% lift +0.0% -0.1% 0.001 0.001 0.0% linear 0.0% 0.0% +0.2% +0.2% 0.0% listcompr 0.0% 0.0% 0.056 0.056 0.0% listcopy 0.0% 0.0% 0.060 0.060 0.0% maillist 0.0% 0.0% 0.035 0.035 +1.9% mandel 0.0% 0.0% 0.040 0.040 0.0% mandel2 0.0% 0.0% 0.002 0.002 0.0% mate +0.0% -5.2% -3.2% -3.2% 0.0% minimax 0.0% 0.0% 0.001 0.001 0.0% mkhprog 0.0% 0.0% 0.001 0.001 0.0% multiplier 0.0% 0.0% 0.056 0.056 0.0% n-body 0.0% 0.0% -0.5% -0.5% 0.0% nucleic2 0.0% 0.0% 0.046 0.046 0.0% para -0.0% 0.0% 0.165 0.166 0.0% paraffins 0.0% 0.0% 0.064 0.064 0.0% parser +0.0% -0.0% 0.015 0.015 0.0% parstof +0.0% -0.0% 0.003 0.003 0.0% pic 0.0% 0.0% 0.004 0.004 0.0% pidigits 0.0% 0.0% +0.2% +0.1% 0.0% power 0.0% 0.0% 0.196 0.196 0.0% pretty +0.0% -2.8% 0.000 0.000 0.0% primes 0.0% 0.0% 0.040 0.040 0.0% primetest 0.0% 0.0% 0.061 0.061 0.0% prolog 0.0% 0.0% 0.001 0.001 0.0% puzzle 0.0% 0.0% 0.070 0.070 0.0% queens 0.0% 0.0% 0.008 0.008 0.0% reptile -0.0% -0.0% 0.006 0.006 0.0% reverse-complem 0.0% 0.0% 0.064 0.063 0.0% rewrite +0.1% -0.0% 0.010 0.010 0.0% rfib 0.0% 0.0% 0.009 0.009 0.0% rsa 0.0% 0.0% 0.014 0.014 0.0% scc 0.0% 0.0% 0.000 0.000 0.0% sched 0.0% 0.0% 0.011 0.011 0.0% scs +0.0% -0.0% +3.1% +3.1% 0.0% simple +0.1% -0.2% 0.112 0.112 0.0% solid +0.1% +0.0% 0.074 0.074 0.0% sorting 0.0% 0.0% 0.001 0.001 0.0% spectral-norm 0.0% 0.0% -0.7% -0.7% 0.0% sphere +0.0% -0.0% 0.029 0.029 0.0% symalg 0.0% 0.0% 0.005 0.005 0.0% tak 0.0% 0.0% 0.006 0.006 0.0% transform 0.0% 0.0% 0.192 0.192 0.0% treejoin -0.0% -0.0% 0.076 0.076 0.0% typecheck 0.0% 0.0% 0.141 0.141 0.0% veritas +0.2% -1.0% 0.001 0.001 0.0% wang +0.0% -1.6% 0.055 0.055 0.0% wave4main 0.0% 0.0% 0.156 0.156 0.0% wheel-sieve1 0.0% 0.0% -0.2% -0.2% 0.0% wheel-sieve2 +0.0% -0.0% 0.115 0.115 0.0% x2n1 0.0% 0.0% 0.001 0.001 0.0% -------------------------------------------------------------------------------- Min -0.0% -13.3% -4.2% -4.2% -4.0% Max +0.2% +0.3% +4.9% +4.9% +190.0% Geometric Mean +0.0% -0.2% -0.0% -0.0% +0.9% }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14688#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14688: Note [Lone variables] leads to missing a case-of-case opportunity -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 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): That's great! Let's go for it. The patch could probably do with a note to explain the significance of the changes. I'm happy to write them. Do you want to commit or shall I? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14688#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14688: Note [Lone variables] leads to missing a case-of-case opportunity -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 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 mpickering): You can go ahead and commit once the note is written so it's all together. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14688#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14688: Note [Lone variables] leads to missing a case-of-case opportunity
-------------------------------------+-------------------------------------
Reporter: mpickering | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.2
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 Simon Peyton Jones

#14688: Note [Lone variables] leads to missing a case-of-case opportunity -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 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 simonpj): * status: new => closed * resolution: => fixed Comment: Thanks Matthew -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14688#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC