Hello,
We can’t permit overlap for type families because it is unsound to do so (ie you can break “well typed programs don’t go wrong”). But if it’s unsound for type families, it would not be surprising if it was unsound for fundeps too. (I don’t think anyone has done a soundness proof for fundeps + local constraints + overlapping instances, have they?) And indeed I think it is.
Imagine a system “FDL” that has functional dependencies and local type constraints. The big deal about this is that you get to exploit type equalities in *given* constraints. Consider Oleg’s example, cut down a bit:
class C a b | a -> b
instance C Int Bool
newtype N2 a = N2 (forall b. C a b => b)
t2 :: N2 Int
t2 = N2 True
We end up type-checking (True :: forall b. C Int b => b). From the functional dependency we know that (b~Bool), so the function should typecheck. GHC rejects this program; FDL would not.
But making use of these extra equalities in “given” constraints is quite tricky. To see why look first at Example 1:
module X where
class C a b | a -> b
data T a where
MkT :: C a b => b -> T a
module M1 where
import X
instance C Int Char where ...
f :: Char -> T Int
f c = MkT c
module M2 where
import X
instance C Int Bool
g :: T Int -> Bool
g (MkT x) = x
module Bad where
import M1
import M2
bad :: Char -> Bool
bad = g . f
This program is unsound: it lets you cast an Int to a Bool; result is a seg-fault.
You may say that the problem is the inconsistent functional dependencies in M1 and M2. But GHC won’t spot that. For type families, to avoid this we “eagerly” check for conflicts in type-family instances. In this case the conflict would be reported when compiling module Bad, because that is the first time when both instances are visible together.
So any FDL system should also make this eager check for conflicts.
What about overlap? Here’s Example 2:
{-# LANGUAGE IncoherentInstances #-}
module Bad where
import X
-- Overlapping instances
instance C Int Bool -- Instance 1
instance C a [a] -- Instance 2
f :: Char -> T Int
f c = MkT c -- Uses Instance 1
g :: T a -> a
g (MkT x) = x -- Uses Instance 2
bad :: Char -> Int
bad = g . f
But at the moment GHC makes an exception for *existentials*. Consider Example 3:
class C a b | a -> b
-- Overlapping instances
instance C Int Bool -- Instance 1
instance C a [a] -- Instance 2
data T where
MkT :: C a b => a -> b -> T
f :: Bool -> T
f x = MkT (3::Int) x -- Uses Instance 1
g :: T -> T
g (MkT n x) = MkT n (reverse x) -- Uses Instance 2
bad :: Bool -> T
bad = g . f
But even nuking IncoherentInstances altogether is not enough. Consider this variant of Example 3, call it Example 4:
module M where
class C a b | a -> b
instance C a [a] -- Instance 2
data T where
MkT :: C a b => a -> b -> T
g :: T -> T
g (MkT n x) = MkT n (reverse x) -- Uses Instance 2
module Bad where
import M
instance C Int Bool -- Instance 1
f :: Bool -> T
f x = MkT (3::Int) x -- Uses Instance 1
bad :: Bool -> T
bad = g . f