I have a GADT that captures some equality info and a GetFoo
class that produces a Foo a b
:
data Foo :: Type -> Type -> Type where
FooNotEq :: Foo a b
FooEq :: Foo a a
FooPairEq :: Foo (a, a) (a, a)
type GetFoo :: Type -> Type -> Constraint
class GetFoo a b where
getFoo :: Foo a b
When writing instances for GetFoo
, I can write them in different ways in regards to OVERLAPPABLE
/OVERLAPPING
pragmas:
instance {-# OVERLAPPABLE #-} GetFoo a b where
getFoo = FooNotEq
instance {-# OVERLAPPABLE #-} GetFoo a a where
getFoo = FooEq
instance GetFoo (a, a) (a, a) where
getFoo = FooPairEq
or
instance GetFoo a b where
getFoo = FooNotEq
instance {-# OVERLAPPING #-} GetFoo a a where
getFoo = FooEq
instance {-# OVERLAPPING #-} GetFoo (a, a) (a, a) where
getFoo = FooPairEq
or even
instance {-# OVERLAPPABLE #-} GetFoo a b where -- OVERLAPPING here is also fine
getFoo = FooNotEq
instance {-# OVERLAPPING #-} GetFoo a a where
getFoo = FooEq
instance {-# OVERLAPPING #-} GetFoo (a, a) (a, a) where
getFoo = FooPairEq
This last chunk of instances confuses me though, according to the verbiage in instance overlap section of the user guide. With getFoo @Int @Int
for example, I would expect that the GetFoo a b
and GetFoo a a
instances would be the “candidates”. The candidate elimination logic is described as follows:
- Eliminate any candidate 𝐼𝑋 for which there is another candidate 𝐼𝑌 such that both of the following hold:
- 𝐼𝑌 is strictly more specific than 𝐼𝑋. That is, 𝐼𝑌 is a substitution instance of 𝐼𝑋 but not vice versa.
- Either 𝐼𝑋 is overlappable, or 𝐼𝑌 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.)
So for condition 1, I would expect GetFoo a a
to be more specific than GetFoo a b
, so that one holds. For condition 2 though, it would seem that the “either/or” bit isn’t enforced. Assuming IY is GetFoo a a
and IX is GetFoo a b
, IY is overlapping and IX is overlappable (not either/or) in the above example. I would expect condition 2 to not hold, but from a simple test, GHC is happy (and correctly picks GetFoo a a
):
spec :: Spec
spec = do
describe "getFoo" do
it "FooEq" do
getFoo @Int @Int `shouldBe` FooEq
Is there something I’m missing in the overlap docs describing why GHC is happy in this case?