
On Wed, 23 Jun 2010, Maciej Piechotka wrote:
When I tried to do something like:
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeFamilies #-}
class Test a where type TestMonad a :: * -> * from :: a b -> TestMonad a b to :: TestMonad a b -> a b
data Testable a b = Testable (a b)
instance (Test a, Functor (TestMonad a)) => Functor (Testable a) where f `fmap` Testable v = Testable $! (to . fmap f . from) v
It asks for adding UndecidableInstances as:
test.hs:11:0: Constraint is no smaller than the instance head in the constraint: Functor (TestMonad a) (Use -XUndecidableInstances to permit this) In the instance declaration for `Functor (Testable a)'
Basically, the compiler starts with "Is `Testable a` a Functor?" and ends with "Is `a` a Test and (figure out what `TestMonad a`) a Functor?" The second question is more work to do than it started with. The `Test a` constraint is fine, because you're at least narrowing down the type in question. But `TestMonad a` is a type function that could be literally anything, including `Testable a` itself, which would leave us at: instance (Functor (Testable a)) => Functor (Testable a) Which is obviously problematic. Friendly, --Christopher Lane Hinson