
If you want to get rid of the overlap in your type families, you have
to add an extra argument indicating if the two types are equal. For
this, you need a type family to indicate equality of types. Sadly, the
naive implementation (TEQ x x = True, TEQ x y = False) overlaps and
isn't allowed. I'm not sure how to work around this, I guess you do
need FunDeps, and then you are pulled into HList land. See also my
attempt at extensible records [1].
Regards,
Erik
[1] https://gist.github.com/2492939
On Thu, Jun 7, 2012 at 9:52 PM, Yves Parès
The doc page http://www.haskell.org/ghc/docs/7.4.1/html/users_guide/kind-polymorphism-and... show that lists are now usable as types.
So I'm trying to make a type level function to test if a type list contains a type. Unless I'm wrong, that calls to the use of a type family.
{-# LANGUAGE DataKinds, TypeOperators, KindSignatures, TypeFamilies #-}
data HBool = HTrue | HFalse -- Mandatory as Bool type is not currently promoted to a kind
type family Member x (l :: [*]) :: HBool
type instance Member x (x ': xs) = HTrue type instance Member x (y ': xs) = Member x xs type instance Member x (y ': '[]) = HFalse
But the compiler complains about my instance conflicting. Is what I'm trying to do feasible?
Second question: how can type level tuples (also mentioned in the doc page) be exploited? Aren't they redundant with type-level lists?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe