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