[Haskell-cafe] Using promoted lists

Yves Parès yves.pares at gmail.com
Thu Jun 7 21:52:44 CEST 2012


The doc page
http://www.haskell.org/ghc/docs/7.4.1/html/users_guide/kind-polymorphism-and-promotion.html#promotionshow
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?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120607/c664e4c2/attachment.htm>


More information about the Haskell-Cafe mailing list