[Q] Inlining done: evtRead
Simon Peyton Jones
simonpj at microsoft.com
Tue Jan 8 00:00:16 UTC 2019
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 <ggreif at gmail.com>
| Sent: 07 January 2019 23:28
| To: Simon Peyton Jones <simonpj at microsoft.com>
| Cc: ghc-devs <ghc-devs at haskell.org>
| 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
More information about the ghc-devs
mailing list