
#13143: NOINLINE and worker/wrapper -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 made several errors. First, here's a better test {{{ {-# NOINLINE f #-} f :: Int -> a f x = error (show x) g :: Bool -> Bool -> Int -> Int g True True p = f p g False True p = p + 1 g b False p = g b True p }}} I've made `g` recursive to guarantee a w/w split. And I've given it a type signature to avoid the overloading. With HEAD we get {{{ $wg_s2kz [InlPrag=[0], Occ=LoopBreaker] :: Bool -> Bool -> GHC.Prim.Int# -> GHC.Prim.Int# $wg_s2kz = \ (w_s2kp :: Bool) (w_s2kq :: Bool) (ww_s2ku :: GHC.Prim.Int#) -> case w_s2kp of { False -> case w_s2kq of { False -> $wg_s2kz GHC.Types.False GHC.Types.True ww_s2ku; True -> GHC.Prim.+# ww_s2ku 1# }; True -> case w_s2kq of { False -> $wg_s2kz GHC.Types.True GHC.Types.True ww_s2ku; True -> case f @ Int (GHC.Types.I# ww_s2ku) of wild_00 { } } } }}} Note the re-boxing of the argument `(I# ww_s2ku)`, in the call to `f`. Second, here is a patch that does the job {{{ diff --git a/compiler/coreSyn/CoreUnfold.hs b/compiler/coreSyn/CoreUnfold.hs index f7e4265..efae22c 100644 --- a/compiler/coreSyn/CoreUnfold.hs +++ b/compiler/coreSyn/CoreUnfold.hs @@ -54,7 +54,7 @@ import DataCon import Literal import PrimOp import IdInfo -import BasicTypes ( Arity ) +import BasicTypes ( Arity, InlineSpec(..), inlinePragmaSpec ) import Type import PrelNames import TysPrim ( realWorldStatePrimTy ) @@ -997,6 +997,9 @@ 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 , let arity = length args , size - (10 * (arity + 1)) <= ufUseThreshold dflags = Just (fn_unf { uf_src = InlineStable diff --git a/compiler/stranal/WorkWrap.hs b/compiler/stranal/WorkWrap.hs index d50bb22..9a0ccc5 100644 --- a/compiler/stranal/WorkWrap.hs +++ b/compiler/stranal/WorkWrap.hs @@ -283,12 +283,6 @@ tryWW :: DynFlags -- if two, then a worker and a -- wrapper. tryWW dflags fam_envs is_rec fn_id rhs - | isNeverActive inline_act - -- No point in worker/wrappering if the thing is never inlined! - -- Because the no-inline prag will prevent the wrapper ever - -- being inlined at a call site. - = return [ (new_fn_id, rhs) ] - | Just stable_unf <- certainlyWillInline dflags fn_info = return [ (fn_id `setIdUnfolding` stable_unf, rhs) ] -- See Note [Don't w/w INLINE things] @@ -305,7 +299,6 @@ tryWW dflags fam_envs is_rec fn_id rhs where fn_info = idInfo fn_id - inline_act = inlinePragmaActivation (inlinePragInfo fn_info) (wrap_dmds, res_info) = splitStrictSig (strictnessInfo fn_info) new_fn_id = zapIdUsedOnceInfo (zapIdUsageEnvInfo fn_id) }}} There are two components * Remove the `isNeverActtive` branch in `tryWW`, as described above * Make `certainlyWillInline` return `False` for any NOINLINE thing. I hadn't realised that this would be necessary but it's obviously true that a NOINLINE thing shouldn't reply `True` to `certainlyWillInline`. Now we get no re-boxing in the example. Would you like to try that? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13143#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler