
#14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Hi, let's consider the following code: {{{ {-# LANGUAGE Strict #-} -- Comment/uncommenting this {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} module K where import Control.Monad.Trans import qualified Control.Monad.State.Strict as S import Control.Monad.Primitive newtype StateT s m a = StateT (S.StateT s m a) -- S is Control.Monad.State.Strict deriving (Functor, Applicative, Monad, MonadTrans) instance PrimMonad m => PrimMonad (StateT s m) where type PrimState (StateT s m) = PrimState m primitive ~a = lift (primitive a) ; {-# INLINE primitive #-} }}} If compiled with `-XStrict` this code is not inlined properly and it badly affects the performance. While discussing it on Haskell IRC `lyxia` helped very much with discovering the CORE differences. The lazy version has couple of things which the strict version is missing in form of `[InlPrag=INLINE (sat-args=0)]` on toplevel identifiers. Core: https://gist.github.com/Lysxia/34684c9ca9fe4772ea38a5065414f542 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14815 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler