
#12600: Overloaded method causes insufficient specialization -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: -------------------------------------+------------------------------------- The `foo` function in the following code does not get specialized completely by `ghc -O2`, even though all the overloaded functions in the module are marked `INLINE`. Specifically, it gets compiled into a call to a function with an `Eq Int` dictionary passed at runtime. {{{#!hs module Foo where class Eq1 f where eq1 :: (Eq a) => f a -> f a -> Bool data F a = F !a !a data G f a = G !(f a) !(f a) instance Eq1 F where eq1 = \(F a b) (F c d) -> -- In order to reproduce the problem, the body of this function needs to be -- large enough to prevent GHC from voluntarily inlining it. larger $ larger $ larger $ larger $ larger $ larger $ a == c && b == d {-# INLINE eq1 #-} larger :: a -> a larger = id {-# NOINLINE larger #-} instance (Eq1 f) => Eq1 (G f) where eq1 = \(G a b) (G c d) -> eq1 a c && eq1 b d {-# INLINE eq1 #-} foo :: G F Int -> G F Int -> Bool foo a b = eq1 a b }}} Looking at the dumps, it looks like there may be a problem is the specializer. It creates a specialization of `eq1` with the type `(Eq a) => G F a -> G F a -> Bool` rather than the fully-specialized type: `G F Int -> G F Int -> Bool` -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12600 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler