
Robert Dockins wrote: ] In the second instance, what you really want to say is "instance c [a] ] c, only where c is not an application of (->)". As I recall, there is ] a way to express such type equality/unequality using typeclasses, but ] I don't remember how to do it offhand. For those playing along at home, here's the less general version which uses Oleg Kiselyov's "IsFunction" relation and associated TypeCast machinery from the HList paper...
{-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -fallow-undecidable-instances #-}
data HTrue data HFalse
class IsFunction a b | a -> b instance TypeCast f HTrue => IsFunction (x->y) f instance TypeCast f HFalse => IsFunction a f
class TypeCast a b | a -> b, b->a where typeCast :: a -> b class TypeCast' t a b | t a -> b, t b -> a where typeCast' :: t->a->b class TypeCast'' t a b | t a -> b, t b -> a where typeCast'' :: t->a->b instance TypeCast' () a b => TypeCast a b where typeCast x = typeCast' () x instance TypeCast'' t a b => TypeCast' t a b where typeCast' = typeCast'' instance TypeCast'' () a a where typeCast'' _ x = x
class Apply a b c where -- | a b -> c where apply :: a -> b -> c
instance Apply b [a] c => Apply (a->b) [a] c where apply f [] = error "Not enough arguments" apply f (x:xs) = apply (f x) xs
instance IsFunction c HFalse => Apply c [a] c where apply f _ = f
main = do print (apply g [(1::Int)..] ::String)
g :: Int -> Int -> Int -> Int -> String g w x y z = show $ w*x + y*z