
#7641: Incorrect reporting of overlapping instances -----------------------------+---------------------------------------------- Reporter: snoyberg | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.6.1 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- I've reproduced this issue on both 7.6.1 and 7.6.2. It does not exist on 7.4.2. Given the following code (simplified from an actual case in Yesod): {{{ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} data Foo b = Foo deriving Show class ToFoo a b where toFoo :: a -> Foo b instance ToFoo (c -> ()) b where toFoo _ = Foo bar :: Foo () bar = baz () where baz () = toFoo $ \_ -> () main :: IO () main = print bar }}} This compiles and runs correctly with 7.4.2, producing the output "Foo". However, with 7.6.1 and 7.6.2 I get the following error message (identical between the two versions): {{{ test.hs:16:5: Overlapping instances for ToFoo (t0 -> ()) b arising from the ambiguity check for `baz' Matching givens (or their superclasses): (ToFoo (t -> ()) b) bound by the inferred type for `baz': ToFoo (t -> ()) b => () -> Foo b at test.hs:16:5-29 Matching instances: instance ToFoo (c -> ()) b -- Defined at test.hs:9:10 (The choice depends on the instantiation of `b, t0') When checking that `baz' has the inferred type `forall b t. ToFoo (t -> ()) b => () -> Foo b' Probable cause: the inferred type is ambiguous In an equation for `bar': bar = baz () where baz () = toFoo $ \ _ -> () }}} -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7641 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler