
#12781: Significantly higher allocation with INLINE vs NOINLINE -------------------------------------+------------------------------------- Reporter: | Owner: MikolajKonarski | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: -------------------------------------+------------------------------------- The following program allocates much more memory ("bytes allocated in the heap") in its current form than with INLINE replaced by NOINLINE, as in the comment. That may be normal, but virtually every feature of this example is needed to trigger the behaviour and so I have no clear idea which language feature is responsible and should be avoided and, consequently, how to optimize my much more complex codebase (in which INLINES of once used functions tend to help and sometimes significantly so). As a comment to this ticket I will post another example, where the difference in allocation is pumped to a factor of 2000, as a proof that the issue is serious. {{{ {-# 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/12781 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler