[Haskell-cafe] Undecidable instances with functional dependencies

Henning Thielemann schlepptop at henning-thielemann.de
Mon Feb 15 19:35:04 EST 2010


Miguel Mitrofanov schrieb:
> -- {-# 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)
>
So type functions are undecidable by default?



More information about the Haskell-Cafe mailing list