[Haskell-cafe] event handler

Corentin Dupont corentin.dupont at gmail.com
Sun Jun 17 00:31:49 CEST 2012


Hi Alexander,
sorry my initial example was maybe misleading. What I really what to do is
to associate each event with an arbitrary data type. For example, consider
the following events:
NewPlayer
NewRule
Message
User

I want to associate the following data types with each, to pass to there
respective handlers:
NewPlayer ---> Player
NewRule ---> Rule
Message ---> String
User ---> String

Message and User have the same data type associated, that's why we can't
use this type as a key to index the event...


On Sun, Jun 17, 2012 at 12:04 AM, Alexander Solla <alex.solla at gmail.com>wrote:

>
>
> On Fri, Jun 15, 2012 at 1:59 PM, Corentin Dupont <
> corentin.dupont at gmail.com> wrote:
>
>> I made some modifications based on your suggestions (see below).
>> I made a two parameters class:
>> *class (Typeable e, Typeable d) => Handled e d *
>> Because after all what I want is to associate an event with its type
>> parameters.
>>
>
> I think our approaches are diverging.  In particular, I don't think you
> want to use both
>
> newPlayer :: Event Player
> newRule    :: Event Rule
>
> and also
>
> data NewPlayer
> data NewRule
>
> without a very good reason.  These are representations of the same
> relationship (the attachment/joining of "New" Event semantics to a Player
> or Rule) at different levels in the abstraction hierarchy.  All Handled e d
> type class is doing is attempting to (1) constrain some types, (2)
> "equate"/join NewPlayer and newPlayer (as far as I can see), which would be
> unnecessary without either NewPlayer or newPlayer.  That said, you can
> definitely have a good reason I'm not aware of.
>
> So what is your use case for NewPlayer, for example?
>
>
>> I don't know why I cannot implement you suggestion to restrict the
>> instances of Event:
>> *data **(Handled e d) => **Event e = Event deriving (Typeable, Eq)
>> *gives me a
>> *Not in scope: type variable `d'*
>
>
> Yeah, that's undecidable.  What would happen if you had
>
> instance Handled New    Player
> instance Handled New    Rule
>
> and you tried to make an (Event Player)?  The compiler couldn't decide
> between the instances.  In principle, functional dependencies (or type
> families, as you mentioned) would make d depend on e uniquely, but I don't
> think the data declaration is smart enough to figure it out, since it
> appears to be using scoping rules to deal with the possibility of
> undecidability.  If you want to try, the syntax would be:
>
> {-# LANGUAGE FunctionalDependencies #-}
> class Handled e d | e -> d where -- ...
>
> Of course, apparently the situation with multiple conflicting instances
> "should" never happen if you use NewPlayer and NewRule and so on.  But that
> compiler can't know it unless you tell it somehow.
>
>
>> But apart from that it works very well! It's quite a nice interface!
>> Also just to know, is there a way of getting ride of all these "Typeable"?
>>
>
> Yes, but you would just be re-inventing the wheel.
>
> I pretty much constantly keep "deriving (Data, Eq, Ord, Show, Typeable)"
> in my clipboard.  I don't use Typeable (or Data), but useful libraries do.
>  For example, SafeCopy.
>
> I mean that I have events like:
>> Message String
>> UserEvent String
>> That have a "data" of the same type, but they are not related.
>>
>
> Using my old version of the code for reference, nothing is stopping you
> from doing:
>
> data Event e = New | Message String | User String
>
>
>
>>
>> {-# LANGUAGE ExistentialQuantification, DeriveDataTypeable,
>> MultiParamTypeClasses #-}
>>
>> *module Events (addEvent, newPlayer, newRule) where
>>
>> import Control.Monad
>> import Data.List
>> import Data.Typeable
>>
>>
>> newtype Player = P Int deriving Typeable
>> newtype Rule = R Int deriving Typeable
>> data Event e = Event deriving (Typeable, Eq)
>>
>> data NewPlayer deriving Typeable
>> data NewRule deriving Typeable
>>
>> newPlayer :: Event NewPlayer
>> newPlayer = Event
>> newRule :: Event NewRule
>> newRule = Event
>>
>> class (Typeable e, Typeable d) => Handled e d
>> instance Handled NewPlayer Player
>> instance Handled NewRule Rule
>>
>> data EventHandler = forall e d . (Handled e d) => EH (Event e) (d -> IO
>> ())
>>
>> addEvent :: (Handled e d) => Event e -> (d -> IO ()) -> [EventHandler] ->
>> [EventHandler]
>>  addEvent e h ehs = (EH e h):ehs
>>
>> triggerEvent :: (Handled e d) => Event e -> d -> [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 ()
>>
>> -- TESTS
>>
>> h1 :: Player -> IO ()
>> h1 (P a) = putStrLn $ "Welcome Player " ++ (show a) ++ "!"
>> h2 :: Rule -> IO ()
>> h2 (R a) = putStrLn $ "New Rule " ++ (show a)
>> eventList1 = addEvent newPlayer h1 []
>> eventList2 = addEvent newRule h2 eventList1
>>
>> trigger1 = triggerEvent newPlayer (P 1) eventList2 --Yelds "Welcome
>> Player 1!"
>> trigger2 = triggerEvent newRule (R 2) eventList2 --Yelds "New Rule 2" *
>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120617/07bb51c0/attachment.htm>


More information about the Haskell-Cafe mailing list