[commit: ghc] wip/ww-noinline: Always do the worker/wrapper split for NOINLINEs (70ebc57)

git at git.haskell.org git at git.haskell.org
Tue Feb 19 14:13:59 UTC 2019


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/ww-noinline
Link       : http://ghc.haskell.org/trac/ghc/changeset/70ebc57eddc0951128184482aabe30fb84aada70/ghc

>---------------------------------------------------------------

commit 70ebc57eddc0951128184482aabe30fb84aada70
Author: Sebastian Graf <sebastian.graf at kit.edu>
Date:   Tue Feb 19 13:52:11 2019 +0100

    Always do the worker/wrapper split for NOINLINEs
    
    Trac #10069 revealed that small NOINLINE functions didn't get split
    into worker and wrapper. This was due to `certainlyWillInline`
    saying that any unfoldings with a guidance of `UnfWhen` inline
    unconditionally. That isn't the case for NOINLINE functions, so we
    catch this case earlier now.
    
    Fixes #10069.


>---------------------------------------------------------------

70ebc57eddc0951128184482aabe30fb84aada70
 compiler/coreSyn/CoreUnfold.hs                       | 13 ++++++-------
 testsuite/tests/stranal/should_compile/T10069.hs     | 11 +++++++++++
 testsuite/tests/stranal/should_compile/T10069.stderr |  1 +
 testsuite/tests/stranal/should_compile/all.T         |  1 +
 4 files changed, 19 insertions(+), 7 deletions(-)

diff --git a/compiler/coreSyn/CoreUnfold.hs b/compiler/coreSyn/CoreUnfold.hs
index 3ac35c9..9bb6231 100644
--- a/compiler/coreSyn/CoreUnfold.hs
+++ b/compiler/coreSyn/CoreUnfold.hs
@@ -1118,13 +1118,14 @@ smallEnoughToInline _ _
 ----------------
 
 certainlyWillInline :: DynFlags -> IdInfo -> Maybe Unfolding
--- Sees if the unfolding is pretty certain to inline
--- If so, return a *stable* unfolding for it, that will always inline
+-- ^ Sees if the unfolding is pretty certain to inline.
+-- If so, return a *stable* unfolding for it, that will always inline.
 certainlyWillInline dflags fn_info
   = case unfoldingInfo fn_info of
       CoreUnfolding { uf_tmpl = e, uf_guidance = g }
-        | loop_breaker -> Nothing       -- Won't inline, so try w/w
-        | otherwise    -> do_cunf e g   -- Depends on size, so look at that
+        | loop_breaker                 -- Loop breakers and NOINLINEs
+        || noinline    -> Nothing      -- won't inline, so try w/w
+        | otherwise    -> do_cunf e g  -- Depends on size, so look at that
 
       DFunUnfolding {} -> Just fn_unf  -- Don't w/w DFuns; it never makes sense
                                        -- to do so, and even if it is currently a
@@ -1134,6 +1135,7 @@ certainlyWillInline dflags fn_info
 
   where
     loop_breaker = isStrongLoopBreaker (occInfo fn_info)
+    noinline     = inlinePragmaSpec (inlinePragInfo fn_info) == NoInline
     fn_unf       = unfoldingInfo fn_info
 
     do_cunf :: CoreExpr -> UnfoldingGuidance -> Maybe Unfolding
@@ -1148,9 +1150,6 @@ certainlyWillInline dflags fn_info
         --    See Note [certainlyWillInline: INLINABLE]
     do_cunf expr (UnfIfGoodArgs { ug_size = size, ug_args = args })
       | not (null args)  -- See Note [certainlyWillInline: be careful of thunks]
-      , case inlinePragmaSpec (inlinePragInfo fn_info) of
-          NoInline -> False -- NOINLINE; do not say certainlyWillInline!
-          _        -> True  -- INLINE, INLINABLE, or nothing
       , not (isBottomingSig (strictnessInfo fn_info))
               -- Do not unconditionally inline a bottoming functions even if
               -- it seems smallish. We've carefully lifted it out to top level,
diff --git a/testsuite/tests/stranal/should_compile/T10069.hs b/testsuite/tests/stranal/should_compile/T10069.hs
new file mode 100644
index 0000000..f93eaf5
--- /dev/null
+++ b/testsuite/tests/stranal/should_compile/T10069.hs
@@ -0,0 +1,11 @@
+module T10069 where
+
+data C = C !Int !Int
+
+{-# NOINLINE c1 #-}
+c1 :: C -> Int
+c1 (C _ c) = c
+
+{-# NOINLINE fc #-}
+fc :: C -> Int
+fc c = c1 c +  c1 c
diff --git a/testsuite/tests/stranal/should_compile/T10069.stderr b/testsuite/tests/stranal/should_compile/T10069.stderr
new file mode 100644
index 0000000..97c255a
--- /dev/null
+++ b/testsuite/tests/stranal/should_compile/T10069.stderr
@@ -0,0 +1 @@
+T10069.$wc1 [InlPrag=NOINLINE] :: GHC.Prim.Int# -> GHC.Prim.Int#
diff --git a/testsuite/tests/stranal/should_compile/all.T b/testsuite/tests/stranal/should_compile/all.T
index c94065b..3cff3c7 100644
--- a/testsuite/tests/stranal/should_compile/all.T
+++ b/testsuite/tests/stranal/should_compile/all.T
@@ -48,3 +48,4 @@ test('T13077a', normal, compile, [''])
 test('T15627',  [ grep_errmsg(r'(wmutVar|warray).*Int#') ], compile, ['-dppr-cols=200 -ddump-simpl'])
 
 test('T16029', normal, makefile_test, [])
+test('T10069',  [ grep_errmsg(r'(wc1).*Int#$') ], compile, ['-dppr-cols=200 -ddump-simpl'])



More information about the ghc-commits mailing list