
On Tue, Sep 13, 2011 at 4:58 PM, Grigory Sarnitskiy
Is there a way to make the following code working?
{-# LANGUAGE TypeFamilies #-}
data family Foo a
data instance (Num a) => Foo a = A a deriving Show
data instance (Fractional a) => Foo a = B a deriving Show
I want to have different constructors for 'Foo a' depending on a class of 'a'. Note also, that in the example above I also meant constructor A to be available for (Fractional a) => Foo, since in that case 'a' has Num too. How can I achieve it, maybe not with TypeFamilies? Current error is
Conflicting family instance declarations: data instance Foo a -- Defined at 1.hs:7:33-35 data instance Foo a -- Defined at 1.hs:5:33-35
Directly, with current GHC? Doubly, maybe triply impossible. Type and data families aren't allowed to overlap, and there's no way to dispatch over whether a type is or is not a member of a class. (You can require that it be a member, but you can't say "if not, do this other thing"). Also, you can't give type and data families superclass contexts the way you can classes. I haven't actually encountered this before, but I think that what you've written here is datatype contexts for the various instances of the data family, which means you can only construct a 'Foo a' if the 'a' is a member of the class - but it in no way affects which instance is chosen. Datatype contexts are considered a misfeature, besides.[1] Anyway. What's your wider goal? [1] http://hackage.haskell.org/trac/haskell-prime/wiki/NoDatatypeContexts
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Work is punishment for failing to procrastinate effectively.