
Hello,
Hello all,
Given an HList (http://homepages.cwi.nl/~ralf/HList/) would it be possible to do the following:
Create a class/function/magicks that would essentially do what hOccursMany does, except it would not return a list of elements, but a new HList. For example, would this allow us to be able to write more lax typing constraints and say extract only things that are in lists.
ie) HCons "hi" (HCons [2.2,3.3] (HCons 'a' hNil)) -> HCons "hi" (HCons [2.2,3.3] hNil)
(removing the Char element).
I tried to write something like this but I did not get very far, is it even possible? I'm new to this type-level programming :)
One approach is to write a HList filter function. You need to use type-level bools, type-level apply, and break up the filter function into two parts; you need a second typeclass to discriminate on the HBool which results from applying your predicate to each element of the HList. Below is some code that works for me. -Jeff --------------------------------------------------------- {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances -fallow-overlapping-instances #-} module MyHList where 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 data HNil = HNil deriving (Show, Read, Eq) data HCons e l = HCons e l deriving (Show, Read, Eq) data HTrue = HTrue deriving (Eq, Show) data HFalse = HFalse deriving (Eq, Show) class HApply f e v | f e -> v where hApply :: f -> e -> v -- This HFilter uses an accumulator to avoid using typecast. -- class HFilter acc p l l' | acc p l -> l' where hFilter :: acc -> p -> l -> l' instance HFilter acc p HNil acc where hFilter acc _ _ = acc instance (HApply p x b, HFilter1 b x acc p xs xs') => HFilter acc p (HCons x xs) xs' where hFilter acc p (HCons x xs) = hFilter1 (hApply p x) x acc p xs class HFilter1 b x acc p xs xs' | b x acc p xs -> xs' where hFilter1 :: b -> x -> acc -> p -> xs -> xs' instance HFilter acc p xs xs' => HFilter1 HFalse x acc p xs xs' where hFilter1 _ _ acc p xs = hFilter acc p xs instance HFilter (HCons x acc) p xs xs' => HFilter1 HTrue x acc p xs xs' where hFilter1 _ x acc p xs = hFilter (HCons x acc) p xs -- Here is a specific type-level function to check if something is a list. -- Can't avoid the typeCast here because of functional dependencies on HApply -- data IsList = IsList instance HApply IsList [a] HTrue where hApply _ _ = undefined instance TypeCast HFalse b => HApply (IsList) a b where hApply _ _ = undefined test = hFilter HNil IsList $ HCons "hi" (HCons [2.2,3.3] (HCons 'a' HNil)) --- This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden.