[GHC] #9210: "overlapping instances" through FunctionalDependencies
GHC
ghc-devs at haskell.org
Mon Jun 16 12:52:56 UTC 2014
#9210: "overlapping instances" through FunctionalDependencies
-------------------------------------------+-------------------------------
Reporter: rwbarton | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type checker) | Version: 7.8.1
Keywords: | Operating System:
Architecture: Unknown/Multiple | Unknown/Multiple
Difficulty: Unknown | Type of failure:
Blocked By: | None/Unknown
Related Tickets: | Test Case:
| Blocking:
-------------------------------------------+-------------------------------
This program prints `("1",2)`, but if you reverse the order of the two
instances, it prints `(1,"2")`.
{{{
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
-- extracted from http://lpaste.net/105656
import Control.Applicative
import Data.Functor.Identity
modify :: ((a -> Identity b) -> s -> Identity t) -> (a -> b) -> (s -> t)
modify l f s = runIdentity (l (Identity . f) s)
class Foo s t a b | a b s -> t where
foo :: Applicative f => (a -> f b) -> s -> f t
instance Foo (x, a) (y, a) x y where
foo f (a,b) = (\fa -> (fa,b)) <$> f a
instance Foo (a, x) (a, y) x y where
foo f (a,b) = (\fb -> (a,fb)) <$> f b
main = print $ modify foo (show :: Int -> String) (1 :: Int, 2 :: Int)
}}}
Note that the two instances involved `Foo (Int, Int) (String, Int) Int
String` and `Foo (Int, Int) (Int, String) Int String` are not actually
overlapping. But, they have the same `a`, `b`, and `s` fields and it seems
that this makes GHC think that either one is equally valid, thanks to the
fundep.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9210>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list