Contexts for type family instances

Hello all I've a type family DUnit that I use to allow the unit type, usually a Double, of geometric things (points, vectors...) to be parametric:
type family DUnit a :: *
E.g for Points
data Point u = P2 u u
type instance (Point u) = u
I can make an type instance for Maybe like this, using DUnit on the right hand side:
type instance DUnit (Maybe a) = DUnit a
But pair is a problem. Is there a way to assert both parts of a pair should have the same DUnit? The code below won't compile but it should illustrate what I'm trying to do.
type instance (DUnit a ~ DUnit b) => DUnit (a,b) = DUnit a
I don't want to pick an arbitrary side, e.g:
type instance DUnit (a,b) = DUnit a
or
type instance DUnit (a,b) = DUnit b
Thanks Best wishes Stephen

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
participants (2)
-
Max Bolingbroke
-
Stephen Tetley