
On 12 December 2010 12:26, Stephen Tetley
type instance (DUnit a ~ DUnit b) => DUnit (a,b) = DUnit a
Requires UndecidableInstances but should work: """ {-# LANGUAGE TypeFamilies #-} type family DUnit a :: * data Point u = P2 u u type instance DUnit (Point u) = u type instance DUnit (a,b) = GuardEq (DUnit a) (DUnit b) type family GuardEq a b :: * type instance GuardEq a a = a """ More realistically, you will have to write functions that produce/consume DUnit using type classes so you can pattern match on the "a" of "DUnit a". You could just have all your instances for "DUnit (a, b)" require (DUnit a ~ DUnit b): """ class Consume a where consume :: DUnit a -> Foo instance (DUnit a ~ DUnit b) => Consume (a, b) where consume a = undefined """ Cheers, Max