This is without class :-)<br><br>{-# LANGUAGE TypeFamilies, ExistentialQuantification, FlexibleContexts #-}<br>import Prelude hiding (lookup)<br>import Data.Typeable<br><br>type family Value a :: *<br>    <br>data Assoc = forall a . (Typeable (Value a), Typeable a) =&gt; Assoc a (Value a)<br>
<br>insert :: (Typeable (Value a), Typeable a) =&gt; a -&gt; Value a -&gt; [Assoc] -&gt; [Assoc]<br>insert k v = (Assoc k v :)<br><br>lookup :: (Typeable (Value a), Typeable a, Eq a) =&gt; a -&gt; [Assoc] -&gt; Value a<br>
lookup k [] = error &quot;noassoc&quot;<br>lookup k ((Assoc k&#39; v):xs) = case cast k&#39; of<br>        Nothing -&gt; lookup k xs<br>        Just k&#39;&#39; -&gt; if k&#39;&#39; == k then case cast v of<br>                Nothing -&gt; error &quot;nocast&quot;<br>
                Just v&#39; -&gt; v&#39;<br>            else lookup k xs<br><br>*Main&gt; type instance Value Integer  = Char<br>*Main&gt; type instance Value Int = String<br>*Main&gt; let u = insert (1::Integer) &#39;c&#39; $ insert (1::Int) &quot;ciao&quot; []<br>
*Main&gt; lookup (1 :: Integer)  u <br>&#39;c&#39;<br>*Main&gt; lookup (1 :: Int)  u <br>&quot;ciao&quot;<br>*Main&gt; <br><br>Regards<br>paolino<br><br><div class="gmail_quote">2012/8/1 Paolino <span dir="ltr">&lt;<a href="mailto:paolo.veronelli@gmail.com" target="_blank">paolo.veronelli@gmail.com</a>&gt;</span><br>
<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><br>Hello, I made some trial and error with ghci to make it happy. I&#39;m not really sure this has the type safety you asked.<br>
<br>{-# LANGUAGE TypeFamilies, ExistentialQuantification, FlexibleContexts #-}<br><br>import Prelude hiding (lookup)<br>
import Data.Typeable<br><br>class Typeable a =&gt; Key a where<br>    type Value a :: *<br>    <br>data Assoc = forall a . (Typeable (Value a),Key a) =&gt; Assoc a (Value a)<br><br>insert :: (Typeable (Value a), Key a) =&gt; a -&gt; Value a -&gt; [Assoc] -&gt; [Assoc]<br>

insert k v = (Assoc k v :)<br><br>lookup :: (Typeable (Value a), Eq a, Key a) =&gt; a -&gt; [Assoc] -&gt; Value a<br>lookup k [] = error &quot;noassoc&quot;<br>lookup k ((Assoc k&#39; v):xs) = case cast k&#39; of<br>        Nothing -&gt; lookup k xs<br>

        Just k&#39;&#39; -&gt; if k&#39;&#39; == k then case cast v of<br>                Nothing -&gt; error &quot;nocast&quot;<br>                Just v&#39; -&gt; v&#39;<br>            else lookup k xs<br><div class="gmail_quote">

<br>I&#39;ve tried without the typeclass with no luck.<br>For some reasons <br><br>type family Key a :: *<br>type family Value a :: *<br><br>and adding Typeable (Key a) to the contexts and Key &#39;a&#39; in place of &#39;a&#39; leads to a lot of type errors.<br>

Maybe it&#39;s possible with more help.<br><br>Hope I got it right.<br><br>Regards<span class="HOEnZb"><font color="#888888"><br>paolino</font></span><div><div class="h5"><br><br>2012/7/31 Alexander Foremny <span dir="ltr">&lt;<a href="mailto:alexanderforemny@gmail.com" target="_blank">alexanderforemny@gmail.com</a>&gt;</span><br>

<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Hello list,<br>
<br>
I am currently thinking that a problem of mine would best be solved if<br>
there was a Map-like data structure in which the value returned is<br>
parametrized over the lookup type.<br>
<br>
I wonder is this makes sense and if such a data structure exists or if<br>
it could be created while still being well typed. I essentially want<br>
to statically define a scope of Key values and dynamically define a<br>
list of keys.<br>
<br>
&gt; -- Scope of possible keys.<br>
&gt; type Label = String<br>
&gt; data Key a where<br>
&gt;     KeyStr :: Label -&gt; Key String<br>
&gt;     KeyInt :: Label -&gt; Key Int<br>
&gt;     KeyChoice :: Label -&gt; [a] -&gt; Key a<br>
<br>
&gt; -- Some key values, to be extended at runtime.<br>
&gt; strKey &quot;Some String&quot;<br>
&gt; strKey&#39; &quot;Another String&quot;<br>
&gt; intKey &quot;Some integer&quot;<br>
&gt; choiceKey &quot;Chose one&quot; [ &quot;a&quot;, &quot;b&quot;, &quot;c&quot; ] :: KeyChoice String<br>
<br>
Now I need a data structure to possibly associate a value to the key.<br>
<br>
&gt; data MapG = ...<br>
&gt; type Value a = a<br>
&gt; insert :: Key a -&gt; Value a -&gt; MapG Key Value -&gt; MapG Key Value<br>
&gt; lookup :: Key a -&gt; MapG Key Value -&gt; Maybe (Value a)<br>
<br>
I tried implementing this with multiple Map k a&#39;s. I tried adding a<br>
phantom type on some storage type of to implement KeyChoice as of type<br>
Key Int, but I ran into troubles with this approach. I wonder if<br>
Dynamic or Type Families could achieve this, but I am quite at a loss<br>
and would like to hear your opinion.<br>
<br>
I did try to search for this a bit, but I don&#39;t quite know how to<br>
phrase my problem. I&#39;d like to apologize in advance if this question<br>
has been asked already.<br>
<br>
Regards,<br>
Alexander Foremny<br>
<br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org" target="_blank">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
</blockquote></div></div></div><br>
</blockquote></div><br>