Thanks Paolino, I will try to see how I can use your implementation!<br>Corentin<br><br><div class="gmail_quote">On Wed, Jul 4, 2012 at 9:24 PM, Paolino <span dir="ltr">&lt;<a href="mailto:paolo.veronelli@gmail.com" target="_blank">paowolo.veronelli@gmail.com</a>&gt;</span> wrote:<br>
<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Hi Corentin,<br>This is how I would model your request (without concrete constructors for Player and Rule)<br>I&#39;m sure there are better descriptions also  as I&#39;m not an expert.<br>
<br>paolino<br><br>{-# LANGUAGE DataKinds, GADTs, KindSignatures #-}<br>
<br>data Player<br>data Rule <br><br>data Data = Player | Rule<br>data EventKind  = Action | Reaction <br><br>data Event :: EventKind -&gt; * where<br>  NewPlayer  :: Player -&gt; Event Action<br>  NewRule    :: Rule -&gt; Event Action<br>

  NewHandler :: (Event Action -&gt; IO ()) -&gt; Event Reaction<br><br>handle ::  Event Action -&gt; Event Reaction -&gt; IO ()<br>handle x (NewHandler f) = f x<br><br>reaction :: Event a -&gt; [Event Reaction] -&gt; IO [Event Reaction]<br>

<br>reaction f@(NewHandler _) es = return $ f:es<br>reaction p@(NewPlayer _) es = mapM_ (handle p) es &gt;&gt; return es<br>reaction r@(NewRule _) es = mapM_ (handle r) es &gt;&gt; return es<div class="HOEnZb"><div class="h5">
<br><br><div class="gmail_quote">
2012/7/4 Corentin Dupont <span dir="ltr">&lt;<a href="mailto:corentin.dupont@gmail.com" target="_blank">corentin.dupont@gmail.com</a>&gt;</span><br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">

Hi,<br>for example, in my game (Nomic) if a new player arrives, I trigger a &quot;NewPlayer&quot; event. All handlers registered for that event should be triggered, and passed a structure &quot;Player&quot; containing all the infos of the incoming player.<br>


If there is a new rule submitted, that the same: the event &quot;NewRule&quot; is triggered and the handlers are passed a structure &quot;Rule&quot;. Thus I want the handlers registered on NewPlayer to have the type Player -&gt; xxx, and on NewRule to have the type Rule -&gt; xxx. I want to be able to associate an arbitrary data type (here Player and Rule) to an event.<br>


The handlers are inherently of different types, but I want to store them in a unique list hence the existential...<div><div><br><br><div class="gmail_quote">On Wed, Jul 4, 2012 at 4:33 PM, Paolino <span dir="ltr">&lt;<a href="mailto:paolo.veronelli@gmail.com" target="_blank">paolo.veronelli@gmail.com</a>&gt;</span> wrote:<br>


<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Hi Corentin, <br>If you could explain *why* there should be a type associated to each event value, it would help, maybe.<br>


If it&#39;s a design choice , maybe it&#39;s wrong design. One reason to use dynamic typing would be to plug  in new type of events. But if you already have the events semantics , this is not useful.<br>
If the language of events is complex , possibly recursive, you can use GADTs to enforce their validity by construction and you don&#39;t need to typefy the event values, but some of their characteristics.<br>Remember type machinery is good to give correctness at the compilation time which Typeable defeats moving checks at runtime. So lifting values to types and eliminating this information with existentials and casting seems wrong.<br>



<br>paolino<br><br><div class="gmail_quote">2012/7/4 Corentin Dupont <span dir="ltr">&lt;<a href="mailto:corentin.dupont@gmail.com" target="_blank">corentin.dupont@gmail.com</a>&gt;</span><br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">


<div>
Hi Paolino,<br>the user can add as many handlers he wants for each event.<br>When a event is triggered along with a data, all handlers associated to that event should be triggered and passed the data.<br>The trick is, there is one type of data associated with each event. That&#39;s why I cannot use a Event datatype: how to associate a data type to each event value? This would be some sort of dependant typing if I&#39;m not mistaken.<br>




That&#39;s why my events exists both on type level and value level:<br><i>data NewPlayer = NewPlayer <br></i></div>wich allows me to associate it a typf data with type indexing.<i>..<br></i><div><div><br>Regards<span><font color="#888888"><br>



Corentin</font></span><div><div><br><br><div class="gmail_quote">
On Wed, Jul 4, 2012 at 12:58 PM, Paolino <span dir="ltr">&lt;<a href="mailto:paolo.veronelli@gmail.com" target="_blank">paolo.veronelli@gmail.com</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">




Hi<br>How many handlers for each type of event in the list of handlers ?<br>If you have only one handler for each type , it should go in the typeclass, and you don&#39;t need typeable.<br>If you have more than one maybe you can avoid using type indexing at all, because it doesn&#39;t resolve the handler selection issue.<br>





By the way , it&#39;s not clear to me why you don&#39;t have a simple Event datatype describing all the possible events in advance. <br><br>Regards <br><br>paolino<br><br><div class="gmail_quote">2012/7/3 Corentin Dupont <span dir="ltr">&lt;<a href="mailto:corentin.dupont@gmail.com" target="_blank">corentin.dupont@gmail.com</a>&gt;</span><br>





<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div><div>Hi all,<br>I read somewhere (here: <a href="http://stackoverflow.com/questions/2300275/how-to-unpack-a-haskell-existential-type" target="_blank">http://stackoverflow.com/questions/2300275/how-to-unpack-a-haskell-existential-type</a>) that it&#39;s bad to try to unbox an existential type using a cast. OK, but without I really can&#39;t figure out how to do what I want:<br>






<br><i>data NewPlayer = NewPlayer deriving (Typeable, Eq)<br>data NewRule = NewRule deriving (Typeable, Eq)<br><br>class (Eq e, Typeable e) =&gt; Event e where<br>    data EventData e<br><br>instance Event NewPlayer where<br>






    data EventData NewPlayer = P Int<br><br>instance Event NewRule where<br>    data EventData NewRule = R Int<br><br>instance Typeable1 EventData where <br>    typeOf1 _ = mkTyConApp (mkTyCon &quot;EventData&quot;) []<br>






<br>data EventHandler = forall e . (Event e) =&gt; EH e (EventData e -&gt; IO ())<br><br>addEvent :: (Event e) =&gt; e -&gt; (EventData e -&gt; IO ()) -&gt; [EventHandler] -&gt; [EventHandler] <br>addEvent e h ehs = (EH e h):ehs<br>






<br>triggerEvent :: (Event e) =&gt; e -&gt; (EventData e) -&gt; [EventHandler] -&gt; IO ()<br>triggerEvent e d ehs = do<br>    let r = find (\(EH myEvent _) -&gt; cast e == Just myEvent) ehs<br>    case r of<br>       Nothing -&gt; return ()<br>






       Just (EH _ h) -&gt; case cast h of<br>        Just castedH -&gt; castedH d<br>        Nothing -&gt; return ()</i><br><br>How to remove the casts from triggerEvent? All that I want is to apply the handler found on the data passed in parameter.<br>






I tried to add a function apply in the class, without success:<br><i>apply :: (EventData e -&gt; IO ()) -&gt; (EventData e) -&gt; IO ()<br>apply = ($)</i><br><br><br>Thanks!<span><font color="#888888"><br>
Corentin<br>
</font></span><br></div></div><div>_______________________________________________<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>
<br></div></blockquote></div><br>
</blockquote></div><br>
</div></div></div></div></blockquote></div><br>
</blockquote></div><br>
</div></div></blockquote></div><br>
</div></div></blockquote></div><br>