
#7875: Unhelpful IncoherentInstances suggestion with FunctionalDependencies -----------------------------+---------------------------------------------- Reporter: dreixel | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.7 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: -----------------------------+---------------------------------------------- Consider the following program (simplified from http://hpaste.org/86928): {{{ {-# LANGUAGE FlexibleContexts , FlexibleInstances , FunctionalDependencies , MultiParamTypeClasses , KindSignatures , UndecidableInstances #-} class Het a b | a -> b where het :: m (f c) -> a -> m b class GHet (a :: * -> *) (b :: * -> *) | a -> b instance GHet (K a) (K [a]) instance Het a b => GHet (K a) (K b) data A a = A (A a) data K x a = K x instance Het (A a) (A [a]) where het = het1 het1 :: (GHet (K a) (K b)) => m (f c) -> a -> m b het1 = undefined }}} In HEAD, it gives rise to the following error: {{{ Overlapping instances for GHet (K (A a)) (K (A [a])) arising from a use of ‛het1’ Matching instances: instance Het a b => GHet (K a) (K b) -- Defined at Bug.hs:14:10 There exists a (perhaps superclass) match: (The choice depends on the instantiation of ‛a’ To pick the first instance above, use -XIncoherentInstances when compiling the other instance declarations) In the expression: het1 In an equation for ‛het’: het = het1 In the instance declaration for ‛Het (A a) (A [a])’ }}} It's already strange that it says multiple instances match, but it only lists one. Furthermore, enabling `-XIncoherentInstances`, as suggested, does not change the error message. #7150 and #7171 might be related. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7875 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler