[GHC] #13228: Surprising inlining failure
GHC
ghc-devs at haskell.org
Fri Feb 3 03:01:25 UTC 2017
#13228: Surprising inlining failure
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 8.2.1
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Runtime
Unknown/Multiple | performance bug
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
When I fail to mark something seemingly unrelated `INLINE`, something else
doesn't inline. In the below (cut down dramatically from my recent lazy ST
work), if I don't mark `>>` inline in the `Monad` instance, then `*>`
never inlines, and none of the rules fire when compiling `foom` and
`basic`. If `>>` is marked inline, then everything works as expected.
{{{#!hs
module RulesLazy (ST, strictToLazyST, lazyToStrictST) where
import qualified Control.Monad.ST as ST
-- No, this is not really lazy ST
newtype ST s a = ST (s -> (a, s))
instance Functor (ST s) where
fmap _ _ = undefined
instance Applicative (ST s) where
pure _ = undefined
_ <*> _ = undefined
m *> n = m `thenST` n
{-# NOINLINE [1] thenST #-}
thenST :: ST s a -> ST s b -> ST s b
_ `thenST` _ = ST $ \_ -> undefined
instance Monad (ST s) where
{-# INLINE (>>) #-} -- CRITICAL LINE
m >> n = m `thenST` n
_ >>= _ = undefined
{-# NOINLINE [1] strictToLazyST #-}
strictToLazyST :: ST.ST s a -> ST s a
strictToLazyST _ = ST $ \_ -> undefined
{-# NOINLINE [1] lazyToStrictST #-}
lazyToStrictST :: ST s a -> ST.ST s a
lazyToStrictST _ = undefined
{-# RULES
"then/S2L" forall m n . m `thenST` strictToLazyST n =
strictToLazyST (lazyToStrictST m *> n)
"L2S/S2L" forall m . lazyToStrictST (strictToLazyST m) = m
#-}
module RulesBurn where
import RulesLazy
import qualified Control.Monad.ST as SST
{-# NOINLINE foom #-}
foom :: SST.ST s a -> SST.ST s b -> SST.ST s c -> ST s c
foom m n o = (strictToLazyST m *> strictToLazyST n) *> strictToLazyST o
{-# NOINLINE basic #-}
basic :: ST s a -> SST.ST s b -> ST s b
basic m n = m *> strictToLazyST n
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13228>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list