[Haskell-cafe] TypeFamillies and UndecidableInstances - why?

Daniel Fischer daniel.is.fischer at web.de
Tue Jun 22 22:11:38 EDT 2010


On Wednesday 23 June 2010 03:41:47, 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)'
>
>
> What is undecidable? a is bound so TestMonad a should be bound so
> Functor (TestMonad a) should be valid.
>
> Is it a bug/missing feature in ghc or do I fail to see something?
>
> Regards

The constraint contains one type variable, as does the instance head, so 
the compiler can't be sure that type checking will terminate.
Here, UndeciableInstances means, "type checking will terminate, go ahead".


More information about the Haskell-Cafe mailing list