
I suppose having a good description of what I'd like to do might help: I'd like to be able to make an N-Tuple an instance of a type class.
class Foo a where instance Foo (,) where instance Foo (,,) where .... The different kindedness of (,) and (,,) prevent this from working.
Not that this is going to help you much, but perhaps you might want to refine the problem specification:-) Claus {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE EmptyDataDecls #-} import Data.Char data Ap0 (f :: *) data Ap1 (f :: * -> *) data Ap2 (f :: * -> * -> *) data Ap3 (f :: * -> * -> * -> *) type family F a b type instance F (Ap0 b) b = b type instance F (Ap1 f) b = f b type instance F (Ap2 f) b = f b b type instance F (Ap3 f) b = f b b b class Foo a b where foo :: a -> b -> F a b unfoo :: a -> F a b -> b instance Foo (Ap0 Bool) Bool where foo _ b = b unfoo _ b = b instance Foo (Ap2 (,)) Bool where foo _ b = (b,not b) unfoo _ (a,b) = a&&b instance Foo (Ap2 (,)) Char where foo _ c = (chr (ord c+1), chr (ord c+2)) unfoo _ (a,b) = maximum [a,b] instance Foo (Ap3 (,,)) Char where foo _ c = (c, chr (ord c+1), chr (ord c+2)) unfoo _ (a,b,c) = maximum [a,b,c] f bs | unfoo (undefined::Ap2 (,)) bs = foo (undefined::Ap3 (,,)) 'a' | otherwise = foo (undefined::Ap3 (,,)) 'b' g what1 what2 bs | unfoo what1 bs = foo what2 'a' | otherwise = foo what2 '0' main = do print (f (True,False)::(Char,Char,Char)) print (g (undefined::Ap0 Bool) (undefined::Ap3 (,,)) False ::(Char,Char,Char)) print (g (undefined::Ap2 (,)) (undefined::Ap2 (,)) (True,False)::(Char,Char))