[Haskell-cafe] existential types and cast

Corentin Dupont corentin.dupont at gmail.com
Wed Jul 4 15:43:41 CEST 2012


Hi Paolino,
the user can add as many handlers he wants for each event.
When a event is triggered along with a data, all handlers associated to
that event should be triggered and passed the data.
The trick is, there is one type of data associated with each event. That'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'm not
mistaken.
That's why my events exists both on type level and value level:
*data NewPlayer = NewPlayer
*wich allows me to associate it a type of data with type indexing.*..
*
Regards
Corentin

On Wed, Jul 4, 2012 at 12:58 PM, Paolino <paolo.veronelli at gmail.com> wrote:

> Hi
> How many handlers for each type of event in the list of handlers ?
> If you have only one handler for each type , it should go in the
> typeclass, and you don't need typeable.
> If you have more than one maybe you can avoid using type indexing at all,
> because it doesn't resolve the handler selection issue.
> By the way , it's not clear to me why you don't have a simple Event
> datatype describing all the possible events in advance.
>
> Regards
>
> paolino
>
> 2012/7/3 Corentin Dupont <corentin.dupont at gmail.com>
>
>> Hi all,
>> I read somewhere (here:
>> http://stackoverflow.com/questions/2300275/how-to-unpack-a-haskell-existential-type)
>> that it's bad to try to unbox an existential type using a cast. OK, but
>> without I really can't figure out how to do what I want:
>>
>> *data NewPlayer = NewPlayer deriving (Typeable, Eq)
>> data NewRule = NewRule deriving (Typeable, Eq)
>>
>> class (Eq e, Typeable e) => Event e where
>>     data EventData e
>>
>> instance Event NewPlayer where
>>     data EventData NewPlayer = P Int
>>
>> instance Event NewRule where
>>     data EventData NewRule = R Int
>>
>> instance Typeable1 EventData where
>>     typeOf1 _ = mkTyConApp (mkTyCon "EventData") []
>>
>> data EventHandler = forall e . (Event e) => EH e (EventData e -> IO ())
>>
>> addEvent :: (Event e) => e -> (EventData e -> IO ()) -> [EventHandler] ->
>> [EventHandler]
>> addEvent e h ehs = (EH e h):ehs
>>
>> triggerEvent :: (Event e) => e -> (EventData e) -> [EventHandler] -> IO ()
>> triggerEvent e d ehs = do
>>     let r = find (\(EH myEvent _) -> cast e == Just myEvent) ehs
>>     case r of
>>        Nothing -> return ()
>>        Just (EH _ h) -> case cast h of
>>         Just castedH -> castedH d
>>         Nothing -> return ()*
>>
>> How to remove the casts from triggerEvent? All that I want is to apply
>> the handler found on the data passed in parameter.
>> I tried to add a function apply in the class, without success:
>> *apply :: (EventData e -> IO ()) -> (EventData e) -> IO ()
>> apply = ($)*
>>
>>
>> Thanks!
>> Corentin
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120704/2609e98c/attachment.htm>


More information about the Haskell-Cafe mailing list