#3526: Inliner behaviour with instances is confusing
-----------------------------+----------------------------------------------
Reporter: bos | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 6.10.4 | Severity: normal
Keywords: | Testcase:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
-----------------------------+----------------------------------------------
I have a fairly simple typeclass:
{{{
class Variate a where
uniform :: Gen s -> ST s a
}}}
With instances like this:
{{{
instance Variate Int8 where
uniform = f where f = uniform1 fromIntegral
{-# INLINE f #-}
uniform1 :: (Word32 -> a) -> Gen s -> ST s a
uniform1 f gen = do
i <- uniformWord32 gen
return $! f i
{-# INLINE uniform1 #-}
}}}
Notice the peculiar form of the instance definition. I had to write the
above instead of the more intuitive form:
{{{
instance Variate Int8 where
uniform = uniform1 fromIntegral
{-# INLINE uniform #-}
}}}
With the more obvious form, GHC's inliner didn't fire at all for this, and
I was unable to tell why. It was Duncan who suggested the more convoluted
instance above. The result is about a 3x performance difference
sometimes, so this has a noticeable effect.
I'm not completely sure that this is a bug, but I don't know how to
describe why one form works and the other doesn't, so the compiler's
behaviour is surprising to me.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3526>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs