[GHC] #12603: INLINE and manually inlining produce different code
GHC
ghc-devs at haskell.org
Fri Oct 21 14:30:19 UTC 2016
#12603: INLINE and manually inlining produce different code
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner: bgamari
Type: task | Status: new
Priority: normal | 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: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by MikolajKonarski):
Phew, you goaded me into spending some extra time and using some extra
pragmas, I managed to concoct a tiny example that reproduces the original
problem (many times slower with INLINE vs manual inlining that exactly
mimics the supposed GHC behaviour; allocation the same). I haven't
checked, but most probably in the INLINE version, the constants are not
floated out, just as in the Core of the original problem show above.
{{{
import Data.Bits (unsafeShiftR, (.&.))
import Data.Word (Word32)
-- ghc --make Main.hs -O1; ./Main +RTS -s -RTS
seqFrame2 :: [AttrW32] -> IO ()
{-# NOINLINE seqFrame2 #-}
seqFrame2 l = do
let crux = attrCharFromW32
-- Total time 2.052s ( 2.072s elapsed)
-- let crux = attrCharFromW32'
-- Total time 7.896s ( 7.929s elapsed)
mapM_ (\a -> crux a `seq` return ()) l
main :: IO ()
main = seqFrame2 $ replicate 100000000 $ AttrW32 0
data Attr = Attr !Int !Int --- bangs here are essential
newtype AttrW32 = AttrW32 {attrW32 :: Word32}
attrCharFromW32 :: AttrW32 -> Attr
{-# NOINLINE attrCharFromW32 #-}
attrCharFromW32 w =
Attr (fromEnum $ unsafeShiftR (attrW32 w) 8 .&. (2 ^ (8 :: Int) -
1))
(fromEnum $ attrW32 w .&. (2 ^ (8 :: Int) - 1))
fgFromW32 :: AttrW32 -> Int
{-# INLINE fgFromW32 #-}
fgFromW32 w = fromEnum $ unsafeShiftR (attrW32 w) 8 .&. (2 ^ (8 :: Int) -
1)
bgFromW32 :: AttrW32 -> Int
{-# INLINE bgFromW32 #-}
bgFromW32 w = fromEnum $ attrW32 w .&. (2 ^ (8 :: Int) - 1)
attrCharFromW32' :: AttrW32 -> Attr
{-# NOINLINE attrCharFromW32' #-}
attrCharFromW32' w = Attr (fgFromW32 w) (bgFromW32 w)
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12603#comment:13>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list