#4428: Local functions lose their unfoldings
---------------------------------+------------------------------------------
Reporter: rl | Owner:
Type: bug | Status: merge
Priority: normal | Milestone: 7.0.2
Component: Compiler | Version: 7.1
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: Runtime performance bug
---------------------------------+------------------------------------------
Comment(by rl):
Replying to [comment:7 simonpj]:
> Now suppose you wrote that in the first place. Well then, the `{-#
INLINE[0] local #-}` says "in phase 0 please inline `local`, replacing it
with the original (unoptimised) RHS. And that's exactly what happens.
Actually, didn't we say `{-# INLINE[0] local #-}` means: "in phase 0
please inline `local`, replacing it with the RHS it would have right
before phase 0"? I was under the impression that GHC would inline into
unfoldings as long as it didn't affect phasing. Has that changed?
Anyway, the biggest problem is that local `INLINE` functions are optimised
twice (the rhs and the unfolding after it's been inlined) and usually the
rhs is just thrown away so it's completely wasted work. For DPH/vector
programs, this leads to significantly longer compile times. And
compilation of such programs is quite slow even without this problem.
I'm not sure if there is a reason for local `INLINE` functions to ever
have an unfolding that is different from their rhs. I can't think of any
situation where this makes a difference semantically.
> Without understanding more clearly what you are trying to achieve I
don't think I can help much more. Maybe an example showing how you are
exploiting these nested inlinings?
Here is an example from vector:
{{{
-- | Map a monadic function over a 'Stream'
mapM :: Monad m => (a -> m b) -> Stream m a -> Stream m b
{-# INLINE [1] mapM #-}
mapM f (Stream step s n) = Stream step' s n
where
{-# INLINE [0] step' #-}
step' s = do
r <- step s
case r of
Yield x s' -> liftM (`Yield` s') (f x)
Skip s' -> return (Skip s')
Done -> return Done
}}}
We want to inline `step'` late because doing it early can introduce join
points which affect other optimisations (well, perhaps not this particular
`step'` but certainly more complex ones). But we want to make sure that it
does get inlined eventually. So we say `INLINE [0]`.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4428#comment:8>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs