What does `~` (tilde) mean in an instance context, and why is it necessary to resolve overlap in some cases? - haskell

A complication.
Consider the following snippet:
class D u a where printD :: u -> a -> String
instance D a a where printD _ _ = "Same type instance."
instance {-# overlapping #-} D u (f x) where printD _ _ = "Instance with a type constructor."
And this is how it works:
λ printD 1 'a'
...
...No instance for (D Integer Char)...
...
λ printD 1 1
"Same type instance."
λ printD [1] [1]
...
...Overlapping instances for D [Integer] [Integer]
...
λ printD [1] ['a']
"Instance with a type constructor."
Note that the overlapping instances are not resolved, despite the pragma being supplied to this
end.
A solution.
It took some guesswork to arrive at the following adjusted definition:
class D' u a where printD' :: u -> a -> String
instance (u ~ a) => D' u a where printD' _ _ = "Same type instance."
instance {-# overlapping #-} D' u (f x) where printD' _ _ = "Instance with a type constructor."
It works as I expected the previous to:
λ printD' 1 'a'
...
...No instance for (Num Char)...
...
λ printD' 1 1
"Same type instance."
λ printD' [1] [1]
"Instance with a type constructor."
λ printD' [1] ['a']
"Instance with a type constructor."
My questions.
I am having a hard time understanding what is happening here. Is there an explanation?
Particularly, I can put forward two separate questions:
Why is the overlap not resolved in the first snippet?
Why is the overlap resolved in the second snippet?
But, if the issues are connected, perhaps a single, unified theory would serve explaining this case better.
P.S. concerning a close / duplicate vote I am aware that ~ signifies type equality, and I am consciously using it to obtain the behaviour I need (particularly, printD' 1 'a' not matching). It hardly explains anything concerning specifically the case I presented, where the two ways of stating type equality (the ~ and the instance D a a) lead to two subtly distinct behaviours.
note I tested the snippets above with ghc 8.4.3 and 8.6.0.20180810

First: only instance head matters during instance selection: what's on the left of => does not matter. So, instance D a a prevents selection unless they are equal; instance ... => D u a can always be selected.
Now, the overlap pragmas only come into play if one instance is already more "specific" than the other. "Specific", in this case, means "if there exists a substitution of type variables that can instantiate an instance head A to instance head B, then B is more specific than A". In
instance D a a
instance {-# OVERLAPPING #-} D u (f x)
neither is more specific than the other, as there is no substitution a := ? that makes D a a into D u (f x), nor is there any substitution u := ?; f := ?; x := x that makes D u (f x) into D a a. The {-# OVERLAPPING #-} pragma does nothing (at least, pertaining to the problem). So, when resolving the constraint D [Integer] [Integer], the compiler finds both instances to be candidates, neither more specific than the other, and gives an error.
In
instance (u ~ a) => D u a
instance {-# OVERLAPPING #-} D u (f x)
the second instance is more specific than the first one, because the first one can be instantiated with u := u; a := f x to get to the second one. The pragma now pulls its weight. When resolving D [Integer] [Integer], both instances match, the first one with u := [Integer]; a := [Integer], and the second with u := [Integer]; f := []; x := Integer. However, the second is both more specific and OVERLAPPING, so the first one is discarded as a candidate and the second instance is used. (Side note: I think the first instance should be OVERLAPPABLE, and the second instance should have no pragma. This way, all future instances implicitly overlap the catch-all instance, instead of having to annotate each one.)
With that trick, selection is done with the right priority, and then equality between the two arguments is forced anyway. This combination achieves what you want, apparently.
One way to visualize what is happening is a Venn diagram. From the first attempt, instance D a a and instance D u (f x) form two sets, the sets of the pairs of types that each one can match. These sets do overlap, but there are many pairs of types only D a a matches, and many pairs only D u (f x) matches. Neither can be said to be more specific, so the OVERLAPPING pragma fails. In the second attempt, D u a actually covers the entire universe of pairs of types, and D u (f x) is a subset (read: inside) of it. Now, the OVERLAPPING pragma works. Thinking in this way also shows us another way to make this work, by creating a new set that covers exactly the intersection of the first try.
instance D a a
instance D u (f x)
instance {-# OVERLAPPING #-} (f x) (f x)
But I'd go with the one with two instances unless you really need to use this one for some reason.
Note, however, that overlapping instances are considered a bit fragile. As you noticed, it is often tricky to understand which instance is picked and why. One needs to consider all the instances in scope, their priorities, and essentially run a nontrivial selection algorithm in one's mind to understand what's going on. When the instances are defined across multiple modules (including orphans) things become even more complex, because selection rules might differ according to the local imports. This can even lead to incoherence. It is best to avoid them when possible.
See also the GHC manual.

Related

Overlapping instances and ORing constraints

I want to have a class which represents a property P x and I have an implication of the form A x \or B x => P x.
I have tried to implement this as follows:
class P x
instance A x => P x
instance B x => P x
However this fails with overlapping instances if both A x and B x hold.
(I encountered this when dealing with natural numbers, Max and Min functions)
What is the correct way of expressing this constraint?
#Li-yaoXia is correct to say you can't do this. #Chi's explanation isn't what's going on. The => in an instance decl is not implication (at least not in the Prolog sense).
instance A x => P x
Means x is an instance of class P. Typically the x will be a concrete type like Int, or at least a type constructor with argument variables like Maybe a. The => then says: for type x an instance of P, require A x. That is, the implication goes the opposite way to how it looks.
It's a (common) newbie mistake to think it means 'first check all constraints hold then check if the instance head holds.'
Then also having
instance B x => P x
means x is an instance of P; also require B x. So if your two instances were to compile, you'd be requiring (P x) IMPLIES ((A x) AND (B x)). That is, the same as
instance (A x, B x) => P x
But your instances don't compile. Because their two heads are identical P x; that's a repeat. (I expect not an overlapping instances error, but a repeated instance error.)
Overlapping instances are nothing to do with what's going on here. (But #Chi is wrong to suggest they require any sort of indeterminism: if you try to write indeterministic overlapping instances, usually the program gets rejected. Unless you switch on all sorts of dangerous extensions.)

Overlapping instances - how to circumvent them

I am a beginner at Haskell, so please be indulgent. For reasons that are not important here, I am trying to define a operator <^> that takes a function and an argument and returns the value of the function by the argument, irrespective of which of the function and the argument came first. In short, I would like to be able to write the following:
foo :: Int -> Int
foo x = x * x
arg :: Int
arg = 2
foo <^> arg -- valid, returns 4
arg <^> foo -- valid, returns 4
I have tried to accomplish that through type families, as follows:
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeFamilies, TypeOperators #-}
class Combine t1 t2 where
type Output t1 t2 :: *
(<^>) :: t1 -> t2 -> Output t1 t2
instance Combine (a->b) a where
type Output (a->b) a = b
f <^> x = f x
instance Combine a (a->b) where
type Output a a->b = b
x <^> f = f x
On this code, GHC throws a Conflicting family instance declarations. My guess is that the overlap GHC complains about occurs when type a->b and type a are the same. I don't know Haskell well enough, but I suspect that with recursive type definitions, one may be able to construct such a situation. I have a couple of questions:
Since this is a rather remote scenario that will never occur in my application (in particular not with foo and arg above), I was wondering if there was a way of specifying a dummy default instance to use in case of overlap? I have tried the different OVERLAPS and OVERLAPPING flags, but they didn't have any effect.
If not, is there a better way of achieving what I want?
Thanks!
This is a bad idea, in my view, but I'll play along.
A possible solution is to switch to functional dependencies. Usually I tend to avoid fundeps in favor of type families, but here they make the instances compile in a simple way.
class Combine t1 t2 r | t1 t2 -> r where
(<^>) :: t1 -> t2 -> r
instance Combine (a->b) a b where
f <^> x = f x
instance Combine a (a->b) b where
x <^> f = f x
Note that this class will likely cause problems during type inference if we use polymorphic functions. This is because, with polymorphic functions, the code can easily become ambiguous.
For instance id <^> id could pick any of the two instances. Above, melpomene already reported const <^> id being ambiguous as well.
The following is weakly related, but I want to share it anyway:
What about type families instead? I tried to experiment a bit, and I just discovered a limitation which I did not know. Consider the closed type family
type family Output a b where
Output (a->b) a = b
Output a (a->b) = b
The code above compiles, but then the type Output a (a->b) is stuck. The second equation does not get applied, as if the first one could potentially match.
Usually, I can understand this in some other scenarios, but here unifying
Output (a' -> b') b' ~ Output a (a -> b)
seems to fail since we would need a ~ (a' -> b') ~ (a' -> a -> b) which is impossible, with finite types. For some reason, GHC does not use this argument (does it pretend infinite types exist in this check? why?)
Anyway, this makes replacing fundeps with type families harder than it could be, it seems. I have no idea about why GHC accepts the fundeps code I posted, yet refuses the OP's code which is essentially the same thing, except using type families.
#chi is close; an approach using either FunDeps or Closed Type Families is possible. But the Combine instances are potentially ambiguous/unifiable just as much as the CTF Output equations.
When chi says the FunDep code is accepted, that's only half-true: GHC plain leads you down the garden path. It will accept the instances but then you find you can't use them/you get weird error messages. See the Users Guide at "potential for overlap".
If you're looking to resolve a potentially ambiguous Combine constraint, you might get an error suggesting you try IncoherentInstances (or INCOHERENT pragma). Don't do that. You have a genuinely incoherent problem; all that will do is defer the problem to somewhere else. It's always possible to avoid Incoherent -- providing you can rejig your instances (as follows) and they're not locked away in libraries.
Notice that because of the potential ambiguity, another Haskell compiler (Hugs) doesn't let you write Combine like that. It has a more correct implementation of Haskell's (not-well-stated) rules.
The answer is to use a sort of overlap where one instance is strictly more specific. You must first decide which you way you want to prefer in case of ambiguity. I'll choose function prefixed to argument:
{-# LANGUAGE UndecidableInstances, TypeFamilies #-}
instance {-# OVERLAPPING #-} (r ~ b)
=> Combine (a->b) a r where ...
instance {-# OVERLAPPABLE #-} (Combine2 t1 t2 r)
=> Combine t1 t2 r where
(<^>) = revApp
class Combine2 t1 t2 r | t1 t2 -> r where
revApp :: t1 -> t2 -> r
instance (b ~ r) => Combine2 a (a->b) r where
revApp x f = f x
Notice that the OVERLAPPABLE instance for Combine has bare tyvars, it's a catch-all so it's always matchable. All the compiler has to do is decide whether some wanted constraint is of the form of the OVERLAPPING instance.
The Combine2 constraint on the OVERLAPPABLE instance is no smaller than the head, so you need UndecidableInstances. Also beware that deferring to Combine2 will mean that if the compiler still can't resolve, you're likely to get puzzling error messages.
Talking of bare tyvars/"always matchable", I've used an additional trick to make the compiler work really hard to improve the types: There's bare r in the head of the instance, with an Equality type improvement constraint (b ~ r) =>. To use the ~, you need to switch on TypeFamilies even though you're not writing any type families.
A CTF approach would be similar. You need a catch-all equation on Output that calls an auxiliary type function. Again you need UndecidableInstances.

Strange program that requires incoherent instances yet always seems to pick the "right" one?

Consider the following program, which only compiles with incoherent instances enabled:
{-# LANGUAGE TypeFamilies, MultiParamTypeClasses, FlexibleInstances #-}
{-# LANGUAGE IncoherentInstances #-}
main = do
print (g (undefined :: Int))
print (g (undefined :: Bool))
print (g (undefined :: Char))
data True
class CA t where
type A t; type A t = True
fa :: t -> String
instance CA Int where
fa _ = "Int"
class CB t where
type B t; type B t = True
fb :: t -> String
instance CB Bool where
fb _ = "Bool"
class CC t where
type C t; type C t = True
fc :: t -> String
instance CC Char where
fc _ = "Char"
class CAll t t1 t2 t3 where
g :: (t1 ~ A t, t2 ~ B t, t3 ~ C t) => t -> String
instance (CA t) => CAll t True t2 t3 where g = fa
instance (CB t) => CAll t t1 True t3 where g = fb
instance (CC t) => CAll t t1 t2 True where g = fc
When compiling without incoherent instances it claims multiple instances match. This would seem to imply that when incoherent instances are allowed, the instances would be chosen arbitrarily.
Unless I'm exceedingly lucky, this would result in compile errors as the instance constraints in most cases would not be satisfied.
But with incoherent instances I get no compile errors, and indeed get the following output with the "correct" instances chosen:
"Int"
"Bool"
"Char"
So I can only conclude either one of a few things here:
GHC is backtracking on instance context failures (something it says it doesn't do in it's own documentation)
GHC actually knows there's only one instance that matches, but isn't brave enough to use it unless one turns on incoherent instances
I've just got exceedingly lucky (1 in 33 = 27 chance)
Something else is happening.
I suspect the answer is 4 (maybe combined with 2). I'd like any answer to explain what's going on here, and how much I can rely on this behavior with incoherent instances? If it's reliable it seems I could use this behaviour to make quite complex class hierarchies, that actually behave somewhat like subtyping, e.g. I could say all types of class A and class B are in class C, and an instance writer could make an instance for A without having to explicitly make an instance for C.
Edit:
I suspect the answer has something to do with this in the GHC docs:
Find all instances I that match the target constraint; that is, the target constraint is a substitution instance of I. These instance declarations are the candidates.
Eliminate any candidate IX for which both of the following hold:
There is another candidate IY that is strictly more specific; that is, IY is a substitution instance of IX but not vice versa.
Either IX is overlappable, or IY is overlapping. (This "either/or" design, rather than a "both/and" design, allow a client to deliberately override an instance from a library, without requiring a change to the library.)
If exactly one non-incoherent candidate remains, select it. If all remaining candidates are incoherent, select an arbitary one. Otherwise the search fails (i.e. when more than one surviving candidate is not incoherent).
If the selected candidate (from the previous step) is incoherent, the search succeeds, returning that candidate.
If not, find all instances 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, the search succeeds, returning the selected candidate; if not, the search fails.
Correct me if I'm wrong, but whether incoherent instances is selected or not, in the first step, there's only one instance that "matches". In the incoherent case, we fall out with that "matched" case at step 4. But in the non-incoherent case, we then go to step 4, and even though only one instance "matches", we find other instances "unify". So we must reject.
Is this understanding correct?
And if so, could someone explain exactly what "match" and "unify" mean, and the difference between them?

How to apply wildcard in constraint in Haskell?

It sounds trivial but I can't find out what I'm supposed to do.
The following is my type definition:
data CDeq q a = Shallow (q a)
| Deep{ hq ⦂ q a
, susp ⦂ CDeq q (q a)
, tq ⦂ q a }
and I want it to have an instance of Show.
Since GHC doesn't allow deriving here, I just tried to write one myself:
instance (Show a, Show ????) => Show (CDeq q a) where
....
but I got stuck.
I don't know how to represent that for all type v, (q v) can be shown in Haskell.
I can't simply do the following:
instance (Show a, Show (q a)) => Show (CDeq q a) where
....
since to show CDeq q (q a), Show (q (q a)) is required, then Show (q (q (q a))) is required, then on and on.
So I am wondering is there a syntax such that I can express the meaning I stated up there?
I once thought forall could be the solution to this, but it doesn't work:
instance (Show a, forall v. Show (q v)) => Show (CDeq q a)
There's a class Show1 in Prelude.Extras to represent "for all type v, (q v) can be shown".
class Show1 f where
showsPrec1 :: Show a => Int -> f a -> ShowS
default showsPrec1 :: (Show (f a), Show a) => Int -> f a -> ShowS
showsPrec1 = showsPrec
...
You can use this to write a show instance for CDeq q a.
instance (Show a, Show1 q) => Show (CDeq q a) where
....
Where you would use show or showsPrec on a q x you'll instead use show1 or showsPrec1.
If you use these, you should also provide instances for CDeq q.
instance (Show1 q) => Show1 (CDeq q) where
showsPrec1 = showsPrec
#Cirdec's already accepted answer is a great pragmatic answer for this use case. I wanted to write a bit about more general techniques (especially the Data.Constraint.Forall mentioned in a comment, since that almost works for this use case but doesn't quite, and there's another thing from constraints that does work), but I wanted to also try to explain a bit about why this isn't directly possible first and what Show1, Forall, and Lifting do to work around that (they're each different trade offs). So it got a little long, apologies.
By standard Haskell mechanisms you can't have such a "wildcard" constraint. The reason is that Show makes a constraint from a type, with potentially a different instance (with different method definitions) for each type you could apply it to.
When your code requires a Show (CDeq q a) instance and finds instance (Show a, Show ????) => Show (CDeq q a), that means it now also needs to find an instance for Show a and Show ????.
Show a is easy; either a has already been chosen as some concrete type like Int, and it can use the Show instance for that type (or error if there isn't one in scope). Or your code was in a function that was polymorphic in a; in that case there must have been a Show a constraint on the function you wrote, so the compiler will just rely on the caller having chosen some particular a and passed in the Show a instance definition.
But the wildcard constraint Show ???? is different. We're not talking about a concrete type here, so that path to resolution isn't going to work. And we're not even talking about a polymorphic constraint in the sense that there's a type variable the caller would choose (in that case we could punt the problem of choosing a single instance dictionary to the caller).
What you need is to be able to show q a, and q (q a), and q (q (q a), etc. But each of those could have its own instance! The types are gone at runtime, so the compiler can't even attempt to round up all of those instances (or require the caller to pass in an unbounded number of instances) and emit code that switches between which show it calls. It needs to emit code that only calls one version of show; either a specific one from a specific instance it's been able to choose, or one that is passed in by the caller to the function.
One way to workaround this is with an alternative type class like Show1. Here the "unit of overloading" is on the * -> * type constructor. It's impossible to make a Show1 instance for types like Int (they're not the right shape), but a single Show1 q instance is applicable to all types of the form q a, so you don't need an unbounded number of instances to support q a, q (q a), q (q (q a)), etc anymore.
But there also are Show instances that are polymorphic in some type variables. For example the list instance is Show a => Show [a]; knowing that this instance exists (and there aren't any overlapping instances), we know we'll be using the same instance for [a], [[a]], [[[a]]], etc. If we could somehow write a constraint that required a polymorphic instance like that.
There's no direct way to say we want a polymorphic instance - the constraint language only allows us to ask for instances for particular types, or particular types that the caller chooses. But the Data.Forall module in the constraints package (https://hackage.haskell.org/package/constraints), which #Cirdec suggested in a comment, uses clever tricks internally to provide a few ways of doing this.1 Here's an example of how that would look:
{-# LANGUAGE FlexibleContexts
, ScopedTypeVariables
, TypeApplications
, TypeOperators
#-}
module Foo where
import Data.Constraint ( (:-), (\\) )
import Data.Constraint.Forall (ForallF, instF)
data Nested q a = Stop | Deeper a (Nested q (q a))
data None a = None
instance Show (None a)
where show None = "None"
instance (Show a, ForallF Show q) => Show (Nested q a)
where show Stop = "Stop"
show (Deeper a r) = show a ++ " " ++ show r
\\ (instF #Show #q #a)
The constraint ForallF Show q represents forall a. Show (q a).2 But it's not that constraint directly, so we can't just derive Show using this; we need to write an instance manually so we can do some massaging.
A ForallF constraint gives us access to instF which is of type forall p f a. ForallF p f :- p (f a). The :- is a type of the constraints package; values of type c :- d represent a proof that when the constraint c holds the constraint d also holds (or in terms of instance dictionaries: it contains a dictionary for d that's parameterised on a dictionary for c). So ForallF p f :- p (f a) is a proof that when we have ForallF p f we can get p (f a). Type application syntax is a less verbose way of pinning down the types at which we're using instF, we want the left side of :- to tie back to the ForallF Show q that we know we have from the instance constraint. That means the right hand side will give us a Show (q a), as we needed! The \\ operator just takes an expression on the left and an c :- d on the right, and basically connects c and d instances for us; the expression will be evaluated with access to a dictionary for d, but the overall expression only needs c.
Here's an example of use:
λ Deeper 'a' (Deeper None (Deeper None Stop))
'a' None None Stop
it :: Nested None Char
Hurrah! But why did I use None? What happens when we try it with nested lists?
λ :t Deeper [] (Deeper [] Stop)
Deeper [] (Deeper [] Stop) :: Nested [] [t]
λ Deeper [] (Deeper [] Stop)
<interactive>:65:1: error:
• No instance for (Show
(Data.Constraint.Forall.Skolem
(Data.Constraint.Forall.ComposeC Show [])))
arising from a use of ‘print’
• In a stmt of an interactive GHCi command: print it
Drat. What went wrong? Well, our polymorphic Show instance for lists is actually Show a => Show [a]. The instance head is polymorphic, so it applies to all types of forms [a]. But it also needs the extra constraint that Show a holds, so it's not truly polymorphic. Basically what happens is the internal unexported thing in Data.Constraint doesn't have an instance for Show (it can't have any instances for the technique to work), so we get the error above. And that's actually a good thing; dictionaries for [a] contain a nested dictionary for a, so the trick of getting an instance we know is polymorphic and then unsafeCoercing it to the right type wouldn't be applicable here. ForallF only works to find instances that are completely polymorphic, with no restrictions at all.
But there is one more thing the constraints package has to offer here! Data.Constraint.Lifting gives us a class Lifting p f, that represents the idea "p (f a) holds whenever p a holds". The idea that the constraint p "lifts through" the type constructor f. This is actually exactly the notion you needed, since you can just apply it recursively to nest arbitrarily many depths of q.
{-# LANGUAGE FlexibleContexts
, ScopedTypeVariables
, TypeApplications
, TypeOperators
#-}
module Foo where
import Data.Constraint ( (:-), (\\) )
import Data.Constraint.Lifting ( Lifting (lifting) )
data Nested q a = Stop | Deeper a (Nested q (q a))
instance (Show a, Lifting Show q) => Show (Nested q a)
where show Stop = "Stop"
show (Deeper a r) = show a ++ " " ++ show r
\\ (lifting #Show #q #a)
Here the lifting method of the class Lifting is doing basically what instF was doing before. lifting :: Lifting p f => p a :- p (f a), so when we have Lifting Show q and we have Show a, then we can use \\ and lifting (used at the right type) to get the Show (q a) dictionary we need to recursively invoke show.
Now we can show Nested applied to list types:
λ Deeper [] (Deeper [[True]] Stop)
[] [[True]] Stop
it :: Nested [] [Bool]
Data.Constraint.Lifting does have a lot of predefined instances for things in the prelude, but you'll likely to have to write your own instances. Fortunately this pretty much is generally a matter of writing:
instance Lifting SomeClass MyType
where lifting = Sub Dict
The instance resolver does all the actual work for you, provided your type really does allow that class to be "lifted through" it.
1 My understanding of the code in that module is not 100% complete (and the full details are a bit involved to make it as safe as possible), but basically the technique is to apply a class to a hidden unexported thing and capture the dictionary. Since no third-party instance could have actually referenced our unexported thing, the only way an instance could be resolved is if it was actually polymorphic and would work for anything. So then the captured dictionary can just be unsafeCoerced to apply to any type you like.
2 There are a few other variants of Forall* for representing different "shapes" of polymorphism in the constraint. I believe you can't make a one-size-fits-all version because you have to not mention the variable you're being polymorphic over, which means you can't actually use the constraint applied, you have to have something that takes the class as a parameter as well as all of the non-polymorphic parameters and applies them together in a particular fashion.

Why context is not considered when selecting typeclass instance in Haskell?

I understand that when having
instance (Foo a) => Bar a
instance (Xyy a) => Bar a
GHC doesn't consider the contexts, and the instances are reported as duplicate.
What is counterintuitive, that (I guess) after selecting an instance, it still needs to check if the context matches, and if not, discard the instance. So why not reverse the order, and discard instances with non-matching contexts, and proceed with the remaining set.
Would this be intractable in some way? I see how it could cause more constraint resolution work upfront, but just as there is UndecidableInstances / IncoherentInstances, couldn't there be a ConsiderInstanceContexts when "I know what I am doing"?
This breaks the open-world assumption. Assume:
class B1 a
class B2 a
class T a
If we allow constraints to disambiguate instances, we may write
instance B1 a => T a
instance B2 a => T a
And may write
instance B1 Int
Now, if I have
f :: T a => a
Then f :: Int works. But, the open world assumption says that, once something works, adding more instances cannot break it. Our new system doesn't obey:
instance B2 Int
will make f :: Int ambiguous. Which implementation of T should be used?
Another way to state this is that you've broken coherence. For typeclasses to be coherent means that there is only one way to satisfy a given constraint. In normal Haskell, a constraint c has only one implementation. Even with overlapping instances, coherence generally holds true. The idea is that instance T a and instance {-# OVERLAPPING #-} T Int do not break coherence, because GHC can't be tricked into using the former instance in a place where the latter would do. (You can trick it with orphans, but you shouldn't.) Coherence, at least to me, seems somewhat desirable. Typeclass usage is "hidden", in some sense, and it makes sense to enforce that it be unambiguous. You can also break coherence with IncoherentInstances and/or unsafeCoerce, but, y'know.
In a category theoretic way, the category Constraint is thin: there is at most one instance/arrow from one Constraint to another. We first construct two arrows a : () => B1 Int and b : () => B2 Int, and then we break thinness by adding new arrows x_Int : B1 Int => T Int, y_Int : B2 Int => T Int such that x_Int . a and y_Int . b are both arrows () => T Int that are not identical. Diamond problem, anyone?
This does not answer you question as to why this is the case. Note, however, that you can always define a newtype wrapper to disambiguate between the two instances:
newtype FooWrapper a = FooWrapper a
newtype XyyWrapper a = XyyWrapper a
instance (Foo a) => Bar (FooWrapper a)
instance (Xyy a) => Bar (XyyWrapper a)
This has the added advantage that by passing around either a FooWrapper or a XyyWrapper you explicitly control which of the two instances you'd like to use if your a happens to satisfy both.
Classes are a bit weird. The original idea (which still pretty much works) is a sort of syntactic sugar around what would otherwise be data statements. For example you can imagine:
data Num a = Num {plus :: a -> a -> a, ... , fromInt :: Integer -> a}
numInteger :: Num Integer
numInteger = Num (+) ... id
then you can write functions which have e.g. type:
test :: Num x -> x -> x -> x -> x
test lib a b c = a + b * (abs (c + b))
where (+) = plus lib
(*) = times lib
abs = absoluteValue lib
So the idea is "we're going to automatically derive all of this library code." The question is, how do we find the library that we want? It's easy if we have a library of type Num Int, but how do we extend it to "constrained instances" based on functions of type:
fooLib :: Foo x -> Bar x
xyyLib :: Xyy x -> Bar x
The present solution in Haskell is to do a type-pattern-match on the output-types of those functions and propagate the inputs to the resulting declaration. But when there's two outputs of the same type, we would need a combinator which merges these into:
eitherLib :: Either (Foo x) (Xyy x) -> Bar x
and basically the problem is that there is no good constraint-combinator of this kind right now. That's your objection.
Well, that's true, but there are ways to achieve something morally similar in practice. Suppose we define some functions with types:
data F
data X
foobar'lib :: Foo x -> Bar' x F
xyybar'lib :: Xyy x -> Bar' x X
bar'barlib :: Bar' x y -> Bar x
Clearly the y is a sort of "phantom type" threaded through all of this, but it remains powerful because given that we want a Bar x we will propagate the need for a Bar' x y and given the need for the Bar' x y we will generate either a Bar' x X or a Bar' x y. So with phantom types and multi-parameter type classes, we get the result we want.
More info: https://www.haskell.org/haskellwiki/GHC/AdvancedOverlap
Adding backtracking would make instance resolution require exponential time, in the worst case.
Essentially, instances become logical statements of the form
P(x) => R(f(x)) /\ Q(x) => R(f(x))
which is equivalent to
(P(x) \/ Q(x)) => R(f(x))
Computationally, the cost of this check is (in the worst case)
c_R(n) = c_P(n-1) + c_Q(n-1)
assuming P and Q have similar costs
c_R(n) = 2 * c_PQ(n-1)
which leads to exponential growth.
To avoid this issue, it is important to have fast ways to choose a branch, i.e. to have clauses of the form
((fastP(x) /\ P(x)) \/ (fastQ(x) /\ Q(x))) => R(f(x))
where fastP and fastQ are computable in constant time, and are incompatible so that at most one branch needs to be visited.
Haskell decided that this "fast check" is head compatibility (hence disregarding contexts). It could use other fast checks, of course -- it's a design decision.

Resources