
This seems like an appropriate place to use type families.
{-# LANGUAGE TypeFamilies, GADTs #-}
module DeriveType where
type family DeriveType a
data A = A
data B = B
type instance DeriveType A = B
data ComplexType a where
SomeConstructor :: a -> DeriveType a -> ComplexType a
specialCaseFunc :: ComplexType A -> B
specialCaseFunc (SomeConstructor _ b) = b
On Mon, Jul 28, 2008 at 6:32 PM, Bryan Donlan
Hi,
Is there any theoretical reason that functional dependencies can't be used to resolve a polymorphic type to a concrete type? For example:
-- compile with -fglasgow-exts
class DeriveType a b | a -> b
data A = A data B = B
instance DeriveType A B
simpleNarrow :: DeriveType A b => b -> B simpleNarrow = id
Since 'b' is uniquely determined by the fundep in DeriveType, it seems that this ought to work; ie, since the only type equation satisfying DeriveType A b is B -> B, it should reduce to that before trying to fit its type against its body.
The motivation is this case:
data ComplexType a where SomeConstructor :: DeriveType a b => a -> b -> ComplexType a
specialCaseFunc :: ComplexType A -> B specialCaseFunc (SomeConstructor _ b) = b
Essentially, if I have a data structure with two types used as fields, and one uniquely determines the other, I'd like to use these instances to avoid re-stating the implied one in the type equations, if possible.
Is there some theoretical reason for this not to work, or is it just a limitation of GHC's current implementation? (Note, I'm testing with GHC 6.8.2, so it's possible this might be fixed in trunk already...)
Thanks,
Bryan Donlan _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe