
#13143: NOINLINE and worker/wrapper -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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: -------------------------------------+------------------------------------- Currently we do no worker/wrapper on a NOINLINE thing. In `WorkWrap`: {{{ 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. }}} But if we have, say, {{{ {-# NOINLINE f #-} f (x,y) = error (show x) g True p = f p g False p = snd p + 1 }}} then strictness analysis will discover `f` is strict, and `g`, but ''because `f` has no wrapper'', the worker for `g` will rebox the thing. So we get {{{ f (x,y) = error (show x) $wg b x y = let p = (x,y) -- Yikes! Reboxing! in case b of True -> f p False -> y + 1 g b p = case p of (x,y) -> $wg b x y }}} Now, in this case the reboxing will float into the `True` branch, an so the allocation will only happen on the error path. But it won't float inwards if there are multiple branches that call `(f p)`, so the reboxing will happen on every call of `g`. Disaster. Solution: do worker/wrapper even on NOINLINE things; but move the NOINLINE pragma to the worker. --------------------------- This actually happens! In `GHC.Arr` we have {{{ {-# NOINLINE indexError #-} indexError :: Show a => (a,a) -> a -> String -> b indexError rng i tp = error (...) index b i | inRange b i = unsafeIndex b i | otherwise = indexError b i "Char" }}} The `inRange` generates multiple alternatives, which the `indexError` is duplicated into, and exactly this phenomenon takes place. Eric (gridaphobe) offered this standalone example {{{ module Err where tabulate :: (Int -> a) -> (Int, Int) -> [Int] tabulate f (l,u) = array (l,u) [l..u] {-# INLINE array #-} array :: (Int, Int) -> [Int] -> [Int] array (l,u) is = [index (l,u) i | i <- is] {-# INLINE index #-} index :: (Int, Int) -> Int -> Int index b@(l,h) i | l <= i && i < h = 0 | otherwise = indexError b i 0 {-# NOINLINE indexError #-} indexError :: (Int, Int) -> Int -> Int -> b indexError rng i tp = error (show rng) }}} Compile this with GHC 8, and shudder at the terrible code we get for `$wtabulate`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13143 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler