
#9210: "overlapping instances" through FunctionalDependencies -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.2 checker) | Resolution: | Keywords: FunDeps Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by AntC): Replying to [comment:7 diatchki]:
Here is a simplified version of the example in the ticket:
Thanks Iavor, are you sure this is the ticket you meant? This one is about the order of declaration of instances affecting type inference, and the problem seems to have cleared up, according to comment:5.
{{{ class Foo a b c | a b -> c
instance Foo (x, a) x ((), a) instance Foo (x, a) a (x, ()) }}}
These two instances are accepted by GHC 8.0.1, ...
You mean the instance decls compile? They partially overlap, so GHC will delay any error reporting until a use site.
... but should be rejected as they violate the FD on the class.
They're inconsistent only for the cases of overlap per your counter- example below, not in general. That is, not when `x` is different to `a`.
Here is the counter example: {{{ Foo (Int,Int) Int ((), Int) Foo (Int,Int) Int (Int, ()) }}}
I get attempts at those usages roundly rejected by GHC. (It suggested I `AllowAmbiguousTypes`, but that didn't help. I also switched on `UndecidableInstances` to give it maximum help.) {{{ {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, FlexibleContexts, AllowAmbiguousTypes, UndecidableInstances #-} class Foo a b c | a b -> c where { foo :: a -> b -> c } instance Foo (x, a) x ((), a) where foo (x, a) x2 = ((), a) instance Foo (x, a) a (x, ()) where foo (x, a) a2 = (x, ()) f1 = foo (True, 'c') False f2 = foo (True, 'd') 'e' f3 = foo (5 :: Int, 7 :: Int) (9 :: Int) main = print $ "results" ++ show f1 ++ show f2 ++ show f3 prog.hs:12:6: error: • Couldn't match type ‘Int’ with ‘()’ arising from a functional dependency between: constraint ‘Foo (Int, Int) Int (Int, ())’ arising from a use of ‘foo’ instance ‘Foo (x, a) x ((), a)’ at prog.hs:7:10-29 • In the expression: foo (5 :: Int, 7 :: Int) (9 :: Int) In an equation for ‘f3’: f3 = foo (5 :: Int, 7 :: Int) (9 :: Int) }}} (Per the O.P., if I switch round the order of those instance declarations, I do get a different error message, essentially just a mirror image.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9210#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler