[GHC] #14815: -XStrict prevents code inlining.
GHC
ghc-devs at haskell.org
Thu Mar 8 16:42:46 UTC 2018
#14815: -XStrict prevents code inlining.
-------------------------------------+-------------------------------------
Reporter: danilo2 | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone:
Component: Compiler | Version: 8.2.2
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: |
-------------------------------------+-------------------------------------
Old description:
> 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
New description:
Hi, let's consider the following code:
{{{#!hs
{-# 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
--
Comment (by bgamari):
Indeed it sounds like testing this would be fiddly at best.
That being said, it does seem quite unfortunate to simply close this. A
user enabled `-XStrict` thinking that it would improve program performance
and it got significantly worse, leaving the user with little recourse. I'm
not sure what we can do better here, but this doesn't seem like much of a
resolution.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14815#comment:7>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list