0
votes
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
module OverlappingSpecificsError where

class EqM a b where
    (===) :: a -> b -> Bool

instance {-# OVERLAPPABLE #-} Eq a => EqM a a where
    a === b = a == b

instance {-# OVERLAPPABLE #-} EqM a b where
    a === b = False

aretheyreallyeq :: (Eq a, Eq b) => Either a b -> Either a b -> Bool
aretheyreallyeq (Left a1) (Right b2) = a1 == b2

aretheyeq :: (Eq a, Eq b) => Either a b -> Either a b -> Bool
aretheyeq (Left a1) (Right b2) = a1 === b2

Neither aretheyreallyeq or aretheyeq compile, but the error for aretheyreallyeq makes sense to me, and also tells me that aretheyeq should not give an error: One of the instances that GHCi suggests are possible for EqM in aretheyeq should be impossible due to the same error on aretheyreallyeq. What's going on?

The point is, GHCi insists that both of the instances of EqM are applicable in aretheyeq. But a1 is of type a and b2 is of type b, so in order for the first instance to be applicable, it would have to have the types a and b unify.

But this should not be possible, since they are declared as type variables at the function signature (that is, using the first EqM instance would give rise to the function being of type Either a a -> Either a a -> Bool, and the error in aretheyreallyeq tells me that GHCi will not allow that (which is what I expected anyway).

Am I missing something, or is this a bug in how overlapping instances with multi-parameter type classes are checked?

I am thinking maybe it has to do with the fact that a and b could be further instantiated later on to the point where they are equal, outside aretheyeq, and then the first instance would be valid? But the same is true for aretheyreallyeq. The only difference is that if they do not ever unify we have an option for aretheyeq, but we do not for aretheyreallyeq. In any case, Haskell does not have dynamic dispatch for plenty of good and obvious reasons, so what is the fear in committing to the instance that will always work regardless of whether later on a and b are unifiable? Maybe there is some way to present this that would make choosing the instance when calling the function possible in some way?

It is worth noting that if I remove the second instance, then the function obviously still does not compile, stating that no instance EqM a b can be found. So if I do not have that instance, then none works, but when that one works, suddenly the other does too and I have an overlap? Smells like bug to me miles away.

4
You might want to compare types a and b for equality at runtime instead of compile time. If so, you could use Typeable a, Typeable b as an additional constraint. Note that, if you do, you will have to satisfy the constraints at each call.chi

4 Answers

2
votes

It isn't a bug in sense of working exactly as documented. Starting with

Now suppose that, in some client module, we are searching for an instance of the target constraint (C ty1 .. tyn). The search works like this:

The first stage of finding candidate instances works as you expect; EqM a b is the only candidate and so the prime candidate. But the last step is

Now find all instances, or in-scope given constraints, that unify with the target constraint, but do not match it. Such non-candidate instances might match when the target constraint is further instantiated. If all of them are incoherent top-level instances, the search succeeds, returning the prime candidate. Otherwise the search fails.

The EqM a a instance falls into this category, and isn't incoherent, so the search fails. And you can achieve the behavior you want by marking it as {-# INCOHERENT #-} instead of overlappable.

3
votes

Instance matching on generic variables works this way in order to prevent some potentially confusing (and dangerous) scenarios.

If the compiler gave in to your intuition and chose the EqM a b instance when compiling aretheyeq (because a and b do not necessarily unify, as you're saying), then the following call:

x = aretheyeq (Left 'z') (Right 'z')

would return False, contrary to intuition.

Q: wait a second! But in this case, a ~ Char and b ~ Char, and we also have Eq a and Eq b, which means Eq Char, which should make it possible to choose the EqM a a instance, shouldn't it?

Well, yes, I suppose this could be happening in theory, but Haskell just doesn't work this way. Class instances are merely extra parameters passed to functions (as method dictionaries), so in order for there to be an instance, it must either be unambiguously choosable within the function itself, or it must be passed in from the consumer.

The former (unambiguously choosable instance) necessarily requires that there is just one instance. And indeed, if you remove the EqM a a instance, your function compiles and always returns False.

The latter (passing an instance from the consumer) means a constraint on the function, like this:

aretheyeq :: EqM a b => Either a b -> Either a b -> Bool

What you are asking is that Haskell essentially has two different versions of this function: one requiring that a ~ b and picking the EqM a a instance, and the other not requiring that, and picking the EqM a b instance.

And then the compiler would cleverly pick the "right" version. So that if I call aretheyeq (Left 'z') (Right 'z'), the first version gets called, but if I call aretheyeq (Left 'z') (Right 42) - the second.

But now think further: if there are two versions of aretheyeq, and which one to pick depends on whether the types are equal, then consider this:

dummy :: a -> b -> Bool
dummy a b = aretheyeq (Left a) (Right b)

How does dummy know which version of aretheyeq to pick? So now there has to be two versions of dummy as well: one for when a ~ b and another for other cases.

And so on. The ripple effect continues until there are concrete types.

Q: wait a second! Why two versions? Can't there be just one version, which then decides what to do based on what arguments are passed in?

Ah, but it can't! This is because types are erased at compile time. By the time the function starts to run, it's already compiled, and there is no more type information. So everything has to be decided at compile time: which instance to pick, and the ripple effect from it.

0
votes

To further complete Alexey's answer, which really gave me the hint at what I should do to achieve the behaviour I wanted, I compiled the following minimum working example of a slightly different situation more alike my real use case (which has to do with ExistentialQuantification):

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ExistentialQuantification #-}
module ExistentialTest where

class Class1 a b where
    foo :: a -> b

instance {-# INCOHERENT #-} Monoid a => Class1 a (Either b a) where
    foo x = Right (x <> x)

instance {-# INCOHERENT #-} Monoid a => Class1 a (Either a b) where
    foo x = Left x

data Bar a = Dir a | forall b. Class1 b a => FromB b

getA :: Bar a -> a
getA (Dir a) = a
getA (FromB b) = foo b

createBar :: Bar (Either String t)
createBar = FromB "abc"

createBar2 :: Bar (Either t String)
createBar2 = FromB "def"

If you remove the {-# INCOHERENT #-} annotations, you get exactly the same compile errors as in my original example on both createBar and createBar2, and the point is the same: in createBar it is clear that the only suitable instance is the second one, whereas in createBar2 the only suitable one is the first one, but Haskell refuses to compile because of this apparent confusion it might create when using it, until you annotate them with INCOHERENT.

And then, the code works exactly as you'd expect it to: getA createBar returns Left "abc" whereas getA createBar2 returns Right "defdef", which is exactly the only thing that could happen in a sensible type system.

So, my conclusion is: the INCOHERENT annotation is precisely to allow what I wanted to do since the beginning without Haskell complaining about potentially confusing instances and indeed taking the only one that makes sense. A doubt remains as to whether INCOHERENT may make it so that instances that indeed remain overlapping even after taking into account everything compile, using an arbitrary one (which is obviously bad and dangerous). So, a corollary to my conclusion is: only use INCOHERENT when you absolutely need to and are absolutely convinced that there is indeed only one valid instance.

I still think it is a bit absurd that Haskell has no more natural and safe way to tell the compiler to stop worrying about me being potentially being confused and doing what is obviously the only type checking answer to the problem...

-1
votes

aretheyreallyeq fails because there are two different type variables in scope. In

aretheyreallyeq :: (Eq a, Eq b) => Either a b -> Either a b -> Bool
aretheyreallyeq (Left a1) (Right b2) = a1 == b2

a1 :: a, and b2 :: b, there's no method for comparing values of potentially different types (as this is how they're declared), so this fails. This has nothing to do with any of the enabled extensions or pragmas of course.

aretheyeq fails because there are two instances that could match, not that they definitely do. I'm not sure what version of GHC you're using but here's the exception message I see and it seems to be fairly clear to me:

    • Overlapping instances for EqM a b arising from a use of ‘===’
      Matching instances:
        instance [overlappable] EqM a b -- Defined at /home/tmp.hs:12:31
        instance [overlappable] Eq a => EqM a a
          -- Defined at /home/tmp.hs:9:31
      (The choice depends on the instantiation of ‘a, b’
       To pick the first instance above, use IncoherentInstances
       when compiling the other instance declarations)
    • In the expression: a1 === b2
      In an equation for ‘aretheyeq’:
          aretheyeq (Left a1) (Right b2) = a1 === b2

In this case, my interpretation is that it's saying that given certain choices for a and b, there are potentially multiple different matching instances.