
#12781: Significantly higher allocation with INLINE vs NOINLINE -------------------------------------+------------------------------------- Reporter: MikolajKonarski | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by MikolajKonarski): Here is the example where the code with INLINE allocates 2000 times more heap memory that with NOINLINE: {{{ {-# 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 () {-# NOINLINE l #-} l = [0..1600] mapVT :: forall s. Int -> ST s () {-# 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/12781#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler