
#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): Here is an even simpler version of INLINE allocation bloat, but with less difference vs NOINLINE. I guess virtually every feature of this example is needed to trigger the bloat. {{{ {-# LANGUAGE RankNTypes #-} import Control.Monad.ST.Strict import qualified Data.IntMap.Strict as IM -- 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 and observe lower alloc dis pI = let p0 = let (_, x) = pI `quotRem` z in P x p1 = let (_, x) = pI `quotRem` z in P x m = IM.lookup (fromEnum p0) IM.empty b = IM.member (fromEnum p1) IM.empty in m == Just 'c' `seq` b `seq` () {-# NOINLINE l #-} l = [0..10000000] mapVT :: forall s. () -> ST s () {-# INLINE mapVT #-} mapVT _ = mapM_ (\x -> return $! dis x) l return $! runST (mapVT ()) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12603#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler