#4428: Local functions lose their unfoldings
--------------------------------------+-------------------------------------
Reporter: rl | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 7.0.2
Component: Compiler | Version: 7.1
Resolution: | Keywords:
Testcase: | Blockedby:
Difficulty: | Os: Unknown/Multiple
Blocking: | Architecture: Unknown/Multiple
Failure: Runtime performance bug |
--------------------------------------+-------------------------------------
Comment(by simonpj):
> Perhaps we shouldn't optimise local functions with `INLINE[n]` until
phase n? That way, we avoid duplicating work if they get inlined in that
phase.
I suppose that would be possible, but it would be very odd, because they'd
miss out on rules and inlinings that only apply earlier than phase n. So
you'd lose the claim that you get just as good optimisation of the
function with INLINE(n) as you do without.
I'm still don't really understand your application for all this
complexity, and without understanding it it's hard to suggest solutions.
You seem to be doing essentially no fusion etc until phase 0. So why not
write this?
{{{
mapM :: Monad m => (a -> m b) -> Stream m a -> Stream m b
{-# INLINE [1] mapM #-}
mapM f (Stream step s n) = Stream (step' step f) s n
{-# INLINE [0] step' #-}
step' step f s
= do r <- step s
case r of
Yield x s' -> liftM (`Yield` s') (f x)
Skip s' -> return (Skip s')
Done -> return Done
}}}
I'm still puzzled why the slow down is so great. After all, the template
rhs is not acually optimised at all, and presumably it's quite small.
Nothing happens to it until it is inlined. So it's not as if two large
term are each undergoing extensive transformation.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4428#comment:16>
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