[Q] Inlining done: evtRead

Hi Simon, a simplifier question... Roughly a year ago I started learning about imported Ids, their unfoldings etc. I have very small example program that compiles on Linux. ```haskell import GHC.Event main = print evtRead ``` `evtRead` is a newtype-wrapped Int. When you compile above program with HEAD GHC without optimisation, you'll see that `evtRead` gets passed directly to `show`. But with -O1 it's unfolding will be inlined, floated to toplevel, and dumped as static global data into the using Main module. This was not the case in GHC 8.4. Not sure about 8.6 (will check). Anyway here is the inlining notice that the simplifier gave me (-ddump-inlinings -dverbose-core2core)
Inlining done: GHC.Event.Internal.evtRead Inlined fn: (GHC.Types.I# 1#) `cast` (Sym (GHC.Event.Internal.N:Event[0]) :: GHC.Types.Coercible GHC.Types.Int GHC.Event.Internal.Event) Cont: Stop[BoringCtxt] GHC.Event.Internal.Event
I believe this is a regression, as copies of global data can pop up in potentially many different modules. What do you think? Which change could have caused this? Cheers, Gabor

Are you sure? GHC.Event isn't used on Windows, so I did this:
=================
module Bar where
newtype Evt = Evt Int
evtRead :: Evt
evtRead = Evt 33
instance Show Evt where
show = showEvt
showEvt :: Evt -> String
{-# NOINLINE showEvt #-}
showEvt (Evt x) = show x
============
module Foo where
import Bar
main = print evtRead
===============
And indeed when I compile these with -O I get
Foo.main1
= showEvt (Bar.evtRead1 `cast` (Sym (Bar.N:Evt[0]) :: Int ~R# Evt))
where Bar.evtRead1 is the static (I# 33) box.
No duplication.
Can you give me a repro case that isn't OS-specific? (I suppose I can try on Linux tomorrow, but I'm sure that the OS is only accidentally involved here.)
Simon
| -----Original Message-----
| From: Gabor Greif

I think you have to follow this:
-- | Data is available to be read.
evtRead :: Event
evtRead = Event 1
{-# INLINE evtRead #-}
On 1/8/19, Simon Peyton Jones
Are you sure? GHC.Event isn't used on Windows, so I did this:
================= module Bar where
newtype Evt = Evt Int
evtRead :: Evt evtRead = Evt 33
instance Show Evt where show = showEvt
showEvt :: Evt -> String {-# NOINLINE showEvt #-} showEvt (Evt x) = show x ============
module Foo where
import Bar
main = print evtRead ===============
And indeed when I compile these with -O I get
Foo.main1 = showEvt (Bar.evtRead1 `cast` (Sym (Bar.N:Evt[0]) :: Int ~R# Evt))
where Bar.evtRead1 is the static (I# 33) box.
No duplication.
Can you give me a repro case that isn't OS-specific? (I suppose I can try on Linux tomorrow, but I'm sure that the OS is only accidentally involved here.)
Simon
| -----Original Message----- | From: Gabor Greif
| Sent: 07 January 2019 23:28 | To: Simon Peyton Jones | Cc: ghc-devs | Subject: [Q] Inlining done: evtRead | | Hi Simon, | | a simplifier question... | | Roughly a year ago I started learning about imported Ids, their unfoldings | etc. | | I have very small example program that compiles on Linux. | | ```haskell | import GHC.Event | | main = print evtRead | ``` | | `evtRead` is a newtype-wrapped Int. When you compile above program | with HEAD GHC without optimisation, you'll see that `evtRead` gets | passed directly to `show`. | | But with -O1 it's unfolding will be inlined, floated to toplevel, and | dumped as static global data into the using Main module. This was not | the case in GHC 8.4. Not sure about 8.6 (will check). Anyway here is | the inlining notice that the simplifier gave me (-ddump-inlinings | -dverbose-core2core) | | > Inlining done: GHC.Event.Internal.evtRead | > Inlined fn: (GHC.Types.I# 1#) | > `cast` (Sym (GHC.Event.Internal.N:Event[0]) | > :: GHC.Types.Coercible GHC.Types.Int | > GHC.Event.Internal.Event) | > Cont: Stop[BoringCtxt] GHC.Event.Internal.Event | > | | I believe this is a regression, as copies of global data can pop up in | potentially many different modules. | | What do you think? Which change could have caused this? | | Cheers, | | Gabor

Oh well, your INLINE pragma is saying "please inline evtRead at every call site". And so GHC does exactly that.
That seems like obeying the pragma doesn't it?
Simon
| -----Original Message-----
| From: Gabor Greif

Hmm, yes. So why wasn't GHC 8.4 doing this? Did some commit fix the
inliner to respect the pragma?
Thanks and cheers,
Gabor
On 1/8/19, Simon Peyton Jones
Oh well, your INLINE pragma is saying "please inline evtRead at every call site". And so GHC does exactly that.
That seems like obeying the pragma doesn't it?
Simon
| -----Original Message----- | From: Gabor Greif
| Sent: 08 January 2019 00:06 | To: Simon Peyton Jones | Cc: ghc-devs | Subject: Re: [Q] Inlining done: evtRead | | I think you have to follow this: | | -- | Data is available to be read. | evtRead :: Event | evtRead = Event 1 | {-# INLINE evtRead #-} | | | On 1/8/19, Simon Peyton Jones wrote: | > Are you sure? GHC.Event isn't used on Windows, so I did this: | > | > ================= | > module Bar where | > | > newtype Evt = Evt Int | > | > evtRead :: Evt | > evtRead = Evt 33 | > | > instance Show Evt where | > show = showEvt | > | > showEvt :: Evt -> String | > {-# NOINLINE showEvt #-} | > showEvt (Evt x) = show x | > ============ | > | > module Foo where | > | > import Bar | > | > main = print evtRead | > =============== | > | > And indeed when I compile these with -O I get | > | > Foo.main1 | > = showEvt (Bar.evtRead1 `cast` (Sym (Bar.N:Evt[0]) :: Int ~R# Evt)) | > | > where Bar.evtRead1 is the static (I# 33) box. | > | > No duplication. | > | > Can you give me a repro case that isn't OS-specific? (I suppose I can | try | > on Linux tomorrow, but I'm sure that the OS is only accidentally involved | > here.) | > | > Simon | > | > | -----Original Message----- | > | From: Gabor Greif | > | Sent: 07 January 2019 23:28 | > | To: Simon Peyton Jones | > | Cc: ghc-devs | > | Subject: [Q] Inlining done: evtRead | > | | > | Hi Simon, | > | | > | a simplifier question... | > | | > | Roughly a year ago I started learning about imported Ids, their | > unfoldings | > | etc. | > | | > | I have very small example program that compiles on Linux. | > | | > | ```haskell | > | import GHC.Event | > | | > | main = print evtRead | > | ``` | > | | > | `evtRead` is a newtype-wrapped Int. When you compile above program | > | with HEAD GHC without optimisation, you'll see that `evtRead` gets | > | passed directly to `show`. | > | | > | But with -O1 it's unfolding will be inlined, floated to toplevel, and | > | dumped as static global data into the using Main module. This was not | > | the case in GHC 8.4. Not sure about 8.6 (will check). Anyway here is | > | the inlining notice that the simplifier gave me (-ddump-inlinings | > | -dverbose-core2core) | > | | > | > Inlining done: GHC.Event.Internal.evtRead | > | > Inlined fn: (GHC.Types.I# 1#) | > | > `cast` (Sym (GHC.Event.Internal.N:Event[0]) | > | > :: GHC.Types.Coercible GHC.Types.Int | > | > GHC.Event.Internal.Event) | > | > Cont: Stop[BoringCtxt] GHC.Event.Internal.Event | > | > | > | | > | I believe this is a regression, as copies of global data can pop up in | > | potentially many different modules. | > | | > | What do you think? Which change could have caused this? | > | | > | Cheers, | > | | > | Gabor | >

On Tue, Jan 8, 2019 at 2:10 AM Gabor Greif
Hmm, yes. So why wasn't GHC 8.4 doing this? Did some commit fix the inliner to respect the pragma?
Yes: https://gitlab.haskell.org/ghc/ghc/commit/b9b1f99954e69f23e9647d00e048938d55... But it's not on 8.6 branch (yet?).

Thanks Mikolaj and Simon,
this explains it. I'll study the related ticket next. Still, the
floating-out related duplication aspect looks like a problem, or would
you disagree? I mean,
a) If the INLINE pragma is such a commandment, why don't we respect it with -O0?
b) Would it be sensible to only inline in scrutinee (`case <id> of
...`) context, to avoid duplication? After all it's the guts of the
value we are interested in, not the whole package.
c) Could a global CSE pass pick up the floated-out value and revert it
to the original imported identifier?
d) Or should be simply remove the INLINE pragmas from the library
(0-ary objects)? Possibly changing to INLINABLE?
Just thinking out loud, as this appears like a pessimisation to me.
Cheers,
Gabor
On 1/8/19, Mikolaj Konarski
On Tue, Jan 8, 2019 at 2:10 AM Gabor Greif
wrote: Hmm, yes. So why wasn't GHC 8.4 doing this? Did some commit fix the inliner to respect the pragma?
Yes: https://gitlab.haskell.org/ghc/ghc/commit/b9b1f99954e69f23e9647d00e048938d55...
But it's not on 8.6 branch (yet?).

| a) If the INLINE pragma is such a commandment, why don't we respect it with
| -O0?
We ignore pragmas with -O0.
| b) Would it be sensible to only inline in scrutinee (`case <id> of
| ...`) context, to avoid duplication? After all it's the guts of the value
| we are interested in, not the whole package.
That's what happened before but see Note [Honour INLINE on 0-ary bindings] in CoreUnfold and Trac #15578
| c) Could a global CSE pass pick up the floated-out value and revert it to
| the original imported identifier?
CSE does not currently do CSE with imported unfoldings. It would be possible, but perhaps expensive, to do so.
| d) Or should be simply remove the INLINE pragmas from the library (0-ary
| objects)? Possibly changing to INLINABLE?
I have absolutely no idea why it is there. I bet that removing it is the right thing to do.
S
| -----Original Message-----
| From: Gabor Greif
participants (3)
-
Gabor Greif
-
Mikolaj Konarski
-
Simon Peyton Jones