[Haskell-cafe] TypeFamillies and UndecidableInstances - why?

Maciej Piechotka uzytkownik2 at gmail.com
Tue Jun 22 21:41:47 EDT 2010


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
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 836 bytes
Desc: This is a digitally signed message part
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20100622/16268cf9/attachment.bin


More information about the Haskell-Cafe mailing list