[Haskell-cafe] Undecidable instances with functional dependencies

Miguel Mitrofanov miguelimo38 at yandex.ru
Thu Feb 11 16:48:28 EST 2010


-- {-# LANGUAGE FunctionalDependencies#-}
-- {-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
module Register where
-- class Register a r | a -> r
class Register a where
     type R a
-- instance Register Int Int
instance Register Int where
     type R Int = Int
-- instance Register Float Float
instance Register Float where
     type R Float = Float
-- instance (Register a1 r1, Register a2 r2) => Register (a1, a2) (r1,  
r2)
instance (Register a, Register b) => Register (a, b) where
     type R (a, b) = (R a, R b)

On 12 Feb 2010, at 00:32, Henning Thielemann wrote:

>
> I have the following class and instance
>
>  class Register a r | a -> r where
>
>  instance (Register a ra, Register b rb) =>
>     Register (a,b) (ra,rb) where
>
> and GHC refuses the instance because of violated Coverage Condition.
> I have more instances like
>
>  instance Register Int8  (Reg Int8)  where
>  instance Register Word8 (Reg Word8) where
>
> and for the set of instances I plan, the instance resolution will  
> always terminate. I remember that the term 'undecidable instance' is  
> not fixed and may be relaxed if a more liberal condition can be  
> found. Is there a place, say a Wiki page, where we can collect  
> examples where we think that the current check of GHC is too  
> restrictive?
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list