#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 simonpj):
Replying to [comment:8 rl]:
> 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"?
No. We specifically did not want that, because it's so unclear what it
means to say "the RHS it would have right before phase 0". The idea with
INLINE is that you ''know'' exactly what will get inlined, namely the
source code of the definition. That was the big change with the new
INLINE story.
> I was under the impression that GHC would inline into unfoldings as long
as it didn't affect phasing. Has that changed?
Only invisibly. If you write `INLINE[1]`, then it's OK for GHC to
optimise the rhs-to-be-inlined with phase=1 (only). Not phase=2, nor
phase=0, because both would change the above semantics of INLINE. But
while its OK to optimise the rhs-to-be-inlined with phase=1, it's not
necessary, and it complicated things, so I took it out again.
> 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.
That seems to be an inherent problem with keeping a template to inline
separate from the main body of the function.
Let's review what you are trying to acheive. In your example, the key
point is that in compositions of `map` all the `step` functions get fused
together.
{{{
mapM f (mapM g (Stream step1 s1 n1)
= mapM f (Stream step2 s n)
where
step2 s = ...step1...g...
= Stream step3 s n
where
step2 s = ...step1...g...
step3 s = ...step2...g...
}}}
Now you want `step2` to inline into `step3` so that they can fuse, and so
that f and g meet up and can fuse. (However you don't want `step3` to
inline into `(Stream step3 s n)` because `Stream` is a data constructor.)
Are you saying that you don't want this fusion of the `step` functions to
take place until phase 0? If so, a NOINLINE pragma would do. You don't
need to say INLINE, because there's only one occurrence of each `step`
function anyway.
Let's suppose there were multiple occurrences of `step`. You probably
don't mean "optimise as if there was no pragma, and then inline whatever
you have in phase 0". Reason: suppose f or g are gigantic. Then the
`step` functions would be gigantic, so duplicating them willy-nilly would
make gigantic code.
But you don't want to inhibit the inlining of f,g into the step functions,
because that's how f and g fuse together.
What goes wrong if you just don't put a pragma on `step`?
Simon
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4428#comment:9>
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