[GHC] #12603: INLINE and manually inlining produce different code
GHC
ghc-devs at haskell.org
Sat Oct 29 16:27:45 UTC 2016
#12603: INLINE and manually inlining produce different code
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner: bgamari
Type: task | Status: new
Priority: high | Milestone: 8.2.1
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #12747 #12781 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by MikolajKonarski):
* priority: normal => high
@@ -10,1 +10,1 @@
- Edit: here is a minimal example:
+ Edit, by Mikolaj: here is a minimal example:
New description:
Mikolaj reported that he was seeing significantly different code generated
in the case of an `INLINE` pragma versus manually inlining. I haven't
looked into what the cause it and this isn't necessarily problematic; this
is just a reminder to look into what is happening.
See
https://github.com/LambdaHack/LambdaHack/blob/97724fe8c73e80b329ddf326a8eb001020870b2d/Game/LambdaHack/Common/Color.hs#L99.
Edit, by Mikolaj: here is a minimal example:
{{{
-- ghc --make Main.hs -O1; ./Main +RTS -s -RTS
seqFrame2 :: [Int] -> IO ()
{-# NOINLINE seqFrame2 #-}
seqFrame2 l = do
let crux = attrFromInt
-- Total time 2.052s ( 2.072s elapsed)
-- but the following version is many times slower:
-- let crux = attrFromIntINLINE
-- Total time 7.896s ( 7.929s elapsed)
mapM_ (\a -> crux a `seq` return ()) l
main :: IO ()
main = seqFrame2 $ replicate 100000000 0
data Attr = Attr !Int --- the bang is essential
attrFromInt :: Int -> Attr
{-# NOINLINE attrFromInt #-}
attrFromInt w = Attr (w + (2 ^ (8 :: Int)))
fgFromInt :: Int -> Int
{-# INLINE fgFromInt #-} -- removing this INLINE makes it many times
faster
-- just like the manually inlined version
-- and NOINLINE lands in between
fgFromInt w = w + (2 ^ (8 :: Int))
attrFromIntINLINE :: Int -> Attr
{-# NOINLINE attrFromIntINLINE #-}
attrFromIntINLINE w = Attr (fgFromInt w)
}}}
--
Comment:
IMHO, inlining forced with INLINE is just broken in GHC 8.0.1 --- it omits
some optimizations that ghc normally does when performing the inlining
without pragmas (may be related to the fact that .hi files function code
with INLINE is not optimized, as opposed INLINABLE or without pragmas). So
I'm bumping the priority.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12603#comment:21>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list