[GHC] #12603: INLINE and manually inlining produce different code
GHC
ghc-devs at haskell.org
Mon Oct 24 08:45:41 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):
I have an example that may or may not capture the original case 2
(allocation bloat due to INLINE, here by a factor of 2000). Perhaps it's
just INLINE pushing the subexpression `mapVT n` over the threshold where
some kind of simplification and/or floating out is not done any more. If
it's interesting, please let me know and I will file a new bug report.
{{{
{-# LANGUAGE BangPatterns, RankNTypes #-}
import Control.Monad.ST.Strict
import qualified Data.IntMap.Strict as IM
import Data.List
import Data.Maybe
-- ghc --make -O1 InlineBloat.hs; ./InlineBloat +RTS -s
data P = P !Int
instance Enum P where
fromEnum (P x) = x
toEnum n = undefined
main = do
let {-# NOINLINE z #-}
z = 44
dis :: Int -> ()
{-# INLINE dis #-} -- change here to NOINLINE
--
-- with INLINE:
-- 384,409,080 bytes allocated in the heap
-- with NOINLINE:
-- 169,080 bytes allocated in the heap
dis pI =
let p0 = let (_, x) = pI `quotRem` z in P x
p1 = let (y, _) = pI `quotRem` z in P y
!_ = isJust $ IM.lookup (fromEnum p0) IM.empty
!_ = isJust $ IM.lookup (fromEnum p1) IM.empty
in ()
mapVT :: forall s. Int -> ST s ()
{-# NOINLINE l #-}
l = [0..1600]
{-# INLINE mapVT #-}
mapVT _ = mapM_ (\x -> return $! dis x) l
!runRes = foldl' (\() n -> runST (mapVT n)) () [1..10000]
return ()
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12603#comment:17>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list