
Dear Haskellers, I have a question regarding the correspondence between functional dependencies and associated types.
{-# LANGUAGE TypeFamilies, FlexibleInstances, MultiParamTypeClasses, FunctionalDependencies #-}
With associated types, we can define a (useless[^1]) type class
class Useless a where type T a useless :: a -> T a
and instances
instance Useless () where type T () = () useless = id
instance Useless a => Useless (() -> a) where type T (() -> a) = T a useless f = useless (f ())
Now we can compute `()` in many different ways: useless () useless (\()->()) ... I thought I could express the same with a multi-parameter type class and a functional dependency:
class UselessFD a b | a -> b where uselessFD :: a -> b
But the corresponding instances
instance UselessFD () () where uselessFD = id
instance UselessFD a b => UselessFD (() -> a) b where uselessFD f = uselessFD (f ())
are not accepted (at least by ghc-6.10.1) without allowing undecidable instances: useless.lhs:50:2: Illegal instance declaration for `UselessFD (() -> a) b' (the Coverage Condition fails for one of the functional dependencies; Use -XUndecidableInstances to permit this) In the instance declaration for `UselessFD (() -> a) b' Is there a simple explanation for this? Cheers, Sebastian [^1]: Originally, I was implementing hidden generation of unique identifiers. So instead of `useless :: (() -> () -> ... -> ()) -> ()` I got something like `withUnique :: (ID -> ... -> ID -> a) -> a`.

On Fri, 5 Dec 2008, Sebastian Fischer wrote:
Dear Haskellers,
I have a question regarding the correspondence between functional dependencies and associated types.
{-# LANGUAGE TypeFamilies, FlexibleInstances, MultiParamTypeClasses, FunctionalDependencies #-}
With associated types, we can define a (useless[^1]) type class
class Useless a where type T a useless :: a -> T a
and instances
instance Useless () where type T () = () useless = id
instance Useless a => Useless (() -> a) where type T (() -> a) = T a useless f = useless (f ())
Now we can compute `()` in many different ways:
useless () useless (\()->()) ...
I thought I could express the same with a multi-parameter type class and a functional dependency:
class UselessFD a b | a -> b where uselessFD :: a -> b
But the corresponding instances
instance UselessFD () () where uselessFD = id
instance UselessFD a b => UselessFD (() -> a) b where uselessFD f = uselessFD (f ())
are not accepted (at least by ghc-6.10.1) without allowing undecidable instances:
useless.lhs:50:2: Illegal instance declaration for `UselessFD (() -> a) b' (the Coverage Condition fails for one of the functional dependencies; Use -XUndecidableInstances to permit this) In the instance declaration for `UselessFD (() -> a) b'
Is there a simple explanation for this?
GHC does not implement the same conditions for type families and functional dependencies. Theoretically the same conditions may be used for both. The Coverage Condition is unnecessarily restrictive. A more relaxed condition has been proposed in the literature (JFP paper on using CHRs for FDs; our ICFP'08 paper), which GHC implements for type families but not functional dependencies. -- Tom Schrijvers Department of Computer Science K.U. Leuven Celestijnenlaan 200A B-3001 Heverlee Belgium tel: +32 16 327544 e-mail: tom.schrijvers@cs.kuleuven.be url: http://www.cs.kuleuven.be/~toms/
participants (2)
-
Sebastian Fischer
-
Tom Schrijvers