Re: GADTs and functional dependencies

Am Dienstag, 23. September 2008 19:07 schrieben Sie:
{-# LANGUAGE GADTs, MultiParamTypeClasses, FunctionalDependencies #-}
data GADT a where
GADT :: GADT ()
class Class a b | a -> b
instance Class () ()
fun :: (Class a b) => GADT a -> b fun GADT = ()
I’d expect this to work but unfortunately, using GHC 6.8.2, it fails with the
following message:
FDGADT.hs:12:11: Couldn't match expected type `b' against inferred type `()' `b' is a rigid type variable bound by the type signature for `fun' at FDGADT.hs:11:16 In the expression: () In the definition of `fun': fun GADT = ()
What’s the reason for this? Is there a workaround? Does this work in 6.8.3 or 6.10.1?
This similar code using type families compiles in 6.8.3 and 6.9:
data GADT a where GADT :: GADT ()
type family F a type instance F () = ()
fun :: GADT a -> F a fun GADT = ()
Exactly. But this makes my code incompatible with GHC 6.6. :-( I thought, someone said that with the new typing machinery in GHC 6.10, more functional dependency programs are accepted because functional dependencies are handled similarly to type families (or something like that). Is this true? Since the type family version is okay, why shouldn’t the functional dependency version be okay? Best wishes, Wolfgang

On Wed, Sep 24, 2008 at 12:55:29PM +0200, Wolfgang Jeltsch wrote:
I thought, someone said that with the new typing machinery in GHC 6.10, more functional dependency programs are accepted because functional dependencies are handled similarly to type families (or something like that). Is this true? Since the type family version is okay, why shouldn’t the functional dependency version be okay?
In http://hackage.haskell.org/trac/ghc/ticket/345 Simon says: Ultimately, I think we can implement fundeps using type families, and then the fundep version will work too. Until then, it'll only work in type-family form. Thanks Ian

Am Mittwoch, 24. September 2008 15:11 schrieb Ian Lynagh:
On Wed, Sep 24, 2008 at 12:55:29PM +0200, Wolfgang Jeltsch wrote:
I thought, someone said that with the new typing machinery in GHC 6.10, more functional dependency programs are accepted because functional dependencies are handled similarly to type families (or something like that). Is this true? Since the type family version is okay, why shouldn’t the functional dependency version be okay?
In http://hackage.haskell.org/trac/ghc/ticket/345 Simon says: Ultimately, I think we can implement fundeps using type families, and then the fundep version will work too. Until then, it'll only work in type-family form.
Thanks Ian
And further:
So, since we now have a good workaround (well, actually, a better way to write the program rather than a workaround), I'll leave it open, but at low priority and with milestone bottom.
So for now the answer is: Use type families and thereby drop 6.6 compatibility? Best wishes, Wolfgang
participants (2)
-
Ian Lynagh
-
Wolfgang Jeltsch