Consider the following code, which typechecks:
module Scratch where
import GHC.Exts
ensure :: forall c x. c => x -> x
ensure = id
type Eq2 t = (forall x y. (Eq x, Eq y) => Eq (t x y) :: Constraint)
foo :: forall t a.
( Eq2 t
, Eq a
) => ()
foo = ensure @(Eq (a `t` a)) ()
foo
isn't doing anything useful here, but let's imagine it's doing some important business that requires an Eq (t a a)
instance. The compiler is able to take the (Eq2 t, Eq a)
constraints and elaborate an Eq (t a a)
dictionary, so the constraint is discharged and everything works.
Now suppose we want foo
to do some additional work that depends on an instance of the following rather convoluted class:
-- some class
class (forall ob x y. (SomeConstraint t ~ ob, ob x, ob y) => ob (t x y)) =>
SomeClass t
where
type SomeConstraint t :: * -> Constraint
foo' :: forall t a.
( Eq2 t
, Eq a
, SomeClass t -- <- the extra constraint
) => ()
foo' = ensure @(Eq (a `t` a)) ()
Note that in the body of foo'
we're still demanding only what we did in foo
: an Eq (t a a)
constraint. Moreover we haven't removed or modified the constraints the compiler used to elaborate an instance of Eq (t a a)
in foo
; we still demand (Eq2 t, Eq a)
in addition to the new constraint. So I would expect foo'
to typecheck as well.
Unfortunately, it looks like what actually happens is that the compiler forgets how to elaborate Eq (t a a)
. Here is the error we get in the body of foo'
:
• Could not deduce (Eq (t a a)) arising from a use of ‘ensure’
from the context: (Eq2 t, Eq a, SomeClass t)
bound by the type signature for:
foo' :: forall (t :: * -> * -> *) a.
(Eq2 t, Eq a, SomeClass t) =>
()
Given that the compiler can "deduce Eq (t a a)
" just fine "from the context (Eq2 t, Eq a)
", I don't understand why the richer context (Eq2 t, Eq a, SomeClass t)
causes Eq (t a a)
to become unavailable.
Is this a bug, or am I just doing something wrong? In either case, is there some workaround for this?