
Hi folks, I'm trying to make a simple event driven engine. It simply consists of two functions: - "addEvent", where you pass the event name with a callback, - "triggerEvent" where you pass the event name with the data. the data shall be passed to the callback of the corresponding event. I have trouble making it correctly typed. Here is my try: * type Player = Int --dummy types for the example type Rule = Int data EventEnum = NewPlayer | NewRule deriving Eq data Data = P Player | R Rule data Handler = H (Data -> IO ()) addEvent :: EventEnum -> Handler -> [(EventEnum, Handler)] -> [(EventEnum, Handler)] addEvent e h es = (e,h):es triggerEvent :: EventEnum -> Data -> [(EventEnum, Handler)] -> IO () triggerEvent e d es = do let r = lookup e es case r of Nothing -> return () Just (H h) -> h d* The trouble is that I want the user to be only able to add an event that is compatible with its handler: For example the event NewPlayer should have a handler of type Player -> IO (). The data passed when triggering this event should be only of type Player. How can I do that? It sound like dependant typing... Thanks! Corentin

On Thu, Jun 14, 2012 at 12:15 PM, Corentin Dupont wrote: Hi folks,
I'm trying to make a simple event driven engine. It simply consists of two
functions:
- "addEvent", where you pass the event name with a callback,
- "triggerEvent" where you pass the event name with the data.
the data shall be passed to the callback of the corresponding event. I have trouble making it correctly typed.
Here is my try:
*
type Player = Int --dummy types for the example
type Rule = Int
data EventEnum = NewPlayer | NewRule deriving Eq
data Data = P Player | R Rule
data Handler = H (Data -> IO ()) addEvent :: EventEnum -> Handler -> [(EventEnum, Handler)] -> [(EventEnum,
Handler)]
addEvent e h es = (e,h):es triggerEvent :: EventEnum -> Data -> [(EventEnum, Handler)] -> IO ()
triggerEvent e d es = do
let r = lookup e es
case r of
Nothing -> return ()
Just (H h) -> h d* The trouble is that I want the user to be only able to add an event that
is compatible with its handler:
For example the event NewPlayer should have a handler of type Player -> IO
(). The data passed when triggering this event should be only of type
Player.
How can I do that? It sound like dependant typing... Haven't tried it, and I don't know if it actually does what you want in the
big picture. But you can do "dynamic" dependent typing with dummy (free)
type variables.
*type Player = Int --dummy types for the example
type Rule = Int
data Event d = New deriving Eq -- not necessary for this example, but you
might want to enumerate other events.
*
*class Handled data where -- Corresponds to your "Data" type
*
*data Handler d = H (d -> IO ())*
*
*
*instance Handled Player*
*instance Handled Rule*
*
*
*addEvent :: (Handled d) => Event d -> Handler d -> [(Event d, Handler d)]
-> [(Event d, Handler)]*
*triggerEvent :: (Handled d) => Event d -> d -> [(Event d, Handler d)] ->
IO ()*
*
*
Basically, this means that Events are "keyed" into separate spaces by the
Handled types. (New :: Event Player) has a different type as (New :: Event
Rule).
You might want to look into ScopedTypeVariables.

That look really nice!
Unfortunately I need to have an heterogeneous list of all events with their
handlers.
With this test code it won't compile:
test1 = addEvent (New :: Event Player) (H (undefined::(Player -> IO ()))) []
test2 = addEvent (New :: Event Rule) (H (undefined::(Rule -> IO ()))) test1
On Thu, Jun 14, 2012 at 10:05 PM, Alexander Solla
On Thu, Jun 14, 2012 at 12:15 PM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
Hi folks, I'm trying to make a simple event driven engine. It simply consists of two functions: - "addEvent", where you pass the event name with a callback, - "triggerEvent" where you pass the event name with the data. the data shall be passed to the callback of the corresponding event.
I have trouble making it correctly typed. Here is my try: * type Player = Int --dummy types for the example type Rule = Int data EventEnum = NewPlayer | NewRule deriving Eq data Data = P Player | R Rule data Handler = H (Data -> IO ())
addEvent :: EventEnum -> Handler -> [(EventEnum, Handler)] -> [(EventEnum, Handler)] addEvent e h es = (e,h):es
triggerEvent :: EventEnum -> Data -> [(EventEnum, Handler)] -> IO () triggerEvent e d es = do let r = lookup e es case r of Nothing -> return () Just (H h) -> h d*
The trouble is that I want the user to be only able to add an event that is compatible with its handler: For example the event NewPlayer should have a handler of type Player -> IO (). The data passed when triggering this event should be only of type Player. How can I do that? It sound like dependant typing...
Haven't tried it, and I don't know if it actually does what you want in the big picture. But you can do "dynamic" dependent typing with dummy (free) type variables.
* type Player = Int --dummy types for the example type Rule = Int data Event d = New deriving Eq -- not necessary for this example, but you might want to enumerate other events.
* *class Handled data where -- Corresponds to your "Data" type
* *data Handler d = H (d -> IO ())* * * *instance Handled Player* *instance Handled Rule* * * *addEvent :: (Handled d) => Event d -> Handler d -> [(Event d, Handler d)] -> [(Event d, Handler)]* *triggerEvent :: (Handled d) => Event d -> d -> [(Event d, Handler d)] -> IO ()* * * Basically, this means that Events are "keyed" into separate spaces by the Handled types. (New :: Event Player) has a different type as (New :: Event Rule).
You might want to look into ScopedTypeVariables.

On Thu, Jun 14, 2012 at 2:04 PM, Corentin Dupont
That look really nice! Unfortunately I need to have an heterogeneous list of all events with their handlers. With this test code it won't compile:
test1 = addEvent (New :: Event Player) (H (undefined::(Player -> IO ()))) [] test2 = addEvent (New :: Event Rule) (H (undefined::(Rule -> IO ()))) test1
Right, okay. Heterogenous lists are tricky, but I think we can get away with using ExistentialQuantification, since you seem to only want to dispatch over the heterogenous types. The assumption I made is a big deal! It means you can't extract the d value. You can only apply properly typed functions (your handlers) on it. * {-# LANGUAGE ExistentialQuantification #-} * * type Player = Int * * type Rule = Int * * data Event d = New d * * * *class Handled data where -- Together with EventHandler, corresponds to your "Data" type* * * *data EventHandler = forall d . (Handled d) => EH (Event d) (d -> IO ()) -- EventHandler takes the place of your (Event d, Handler d) pairs without referring to d.* * * *instance Handled Player* *instance Handled Rule* *addEvent :: (Handled d) => Event d -> Handler d -> [EventHandler] -> [EventHandler] -- Every [EventHandler] made using addEvent will be of "correct" types (i.e., preserve the typing invariants you want), but YOU must ensure that only [EventHandler]s made in this way are used. This can be done statically with another type and an explicit export list. We can talk about that later, if this works in principle.* *triggerEvent :: (Handled d) => Event d -> d -> [EventHandler] -> IO ()*

Hi,
it works very well!
I tried to implement it. Here is my test code. Apparently I need some casts
to search the list.
The syntax looks good. Only addEvent will be on the interface, so that
should be fine. If I understand well, that's this function that enforces
the right types to be used. The events are referenced via the type of data
they use.
It just bothers me a little that I'm not able to enumerate the events, and
also that the user is able to create events with wrong types (like New ::
Event String), even if they won't be able to register them.
I also have several unrelated events that use the same type of data, so
this would be a problem. Adding more events like
*data Event d = NewPlayer | NewRule deriving (Typeable, Eq)*
is not correct because I can add wrong events like:
addEvent (NewPlayer :: Event Rule) (H(undefined::(Rule -> IO()))) []
**
Also one question: I don't understand the "where" clause in your class. If
I remove it, it works the same...
Here is my code:
*newtype Player = P Int deriving Typeable
newtype Rule = R Int deriving Typeable
data Event d = New deriving (Typeable, Eq)
class (Typeable d) => Handled d where
data Handler d = H (d -> IO ())
data EventHandler = forall d . (Handled d) => EH (Event d) (Handler d)
instance Handled Player
instance Handled Rule
addEvent :: (Handled d) => Event d -> Handler d -> [EventHandler] ->
[EventHandler]
addEvent e h ehs = (EH e h):ehs
triggerEvent :: (Handled d) => Event d -> 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 h)) -> case cast h of
Just castedH -> castedH d
Nothing -> return ()
h1 :: Player -> IO ()
h1 (P a) = putStrLn $ "Welcome Player " ++ (show a) ++ "!"
h2 :: Rule -> IO ()
h2 (R a) = putStrLn $ "New Rule " ++ (show a)
eventList1 = addEvent (New :: Event Player) (H h1) []
eventList2 = addEvent (New :: Event Rule) (H h2) eventList1
trigger1 = triggerEvent (New :: Event Player) (P 1) eventList2 -- yelds
"Welcome Player 1!"
trigger2 = triggerEvent (New :: Event Rule) (R 2) eventList2 --yelds "New
Rule* 2"
Best,
Corentin
On Fri, Jun 15, 2012 at 12:40 AM, Alexander Solla
On Thu, Jun 14, 2012 at 2:04 PM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
That look really nice! Unfortunately I need to have an heterogeneous list of all events with their handlers. With this test code it won't compile:
test1 = addEvent (New :: Event Player) (H (undefined::(Player -> IO ()))) [] test2 = addEvent (New :: Event Rule) (H (undefined::(Rule -> IO ()))) test1
Right, okay. Heterogenous lists are tricky, but I think we can get away with using ExistentialQuantification, since you seem to only want to dispatch over the heterogenous types. The assumption I made is a big deal! It means you can't extract the d value. You can only apply properly typed functions (your handlers) on it.
* {-# LANGUAGE ExistentialQuantification #-} *
* type Player = Int *
* type Rule = Int *
* data Event d = New d * * *
*class Handled data where -- Together with EventHandler, corresponds to your "Data" type* * *
*data EventHandler = forall d . (Handled d) => EH (Event d) (d -> IO ()) -- EventHandler takes the place of your (Event d, Handler d) pairs without referring to d.*
* *
*instance Handled Player*
*instance Handled Rule*
*addEvent :: (Handled d) => Event d -> Handler d -> [EventHandler] -> [EventHandler] -- Every [EventHandler] made using addEvent will be of "correct" types (i.e., preserve the typing invariants you want), but YOU must ensure that only [EventHandler]s made in this way are used. This can be done statically with another type and an explicit export list. We can talk about that later, if this works in principle.*
*triggerEvent :: (Handled d) => Event d -> d -> [EventHandler] -> IO ()*

On Fri, Jun 15, 2012 at 6:38 AM, Corentin Dupont
It just bothers me a little that I'm not able to enumerate the events, and also that the user is able to create events with wrong types (like New :: Event String), even if they won't be able to register them.
This can be solved with an explicit export list/smart constructors. newPlayer :: Event Player newRule :: Event Rule (hide the New constructor) In any case, my thinking was that your original data Event = *NewPlayer | NewRule* * * was basically trying to "join" the semantics of "new things" with Player and Rule. But the original approach ran into the problem you mention below -- it is difficult to maintain invariants, since the types want to "multiply". So formally, I factored: data Event = NewPlayer | NewRule ==> data Event = New (Player | Rule) ==> data Event d = New -- (since the original event didn't want a Player or Rule value. It witnessed the type relation) On the other hand, if you want to make sure that a type must be "Handled" before you can issue an Event, you can do: data (Handled d) => Evend d = New I'm pretty sure the compiler will complain if you try to make a (New :: Event String). I like this idea better than smart constructors for events, if only because you get to use ScopedTypeVariables.
I also have several unrelated events that use the same type of data, so this would be a problem.
Can you clarify?
Adding more events like *data Event d = NewPlayer | NewRule deriving (Typeable, Eq)* is not correct because I can add wrong events like: addEvent (NewPlayer :: Event Rule) (H(undefined::(Rule -> IO()))) [] ** Also one question: I don't understand the "where" clause in your class. If I remove it, it works the same...
Yes, unnecessary where clauses are optional. Here is my code:
*newtype Player = P Int deriving Typeable newtype Rule = R Int deriving Typeable data Event d = New deriving (Typeable, Eq)
class (Typeable d) => Handled d where data Handler d = H (d -> IO ())
data EventHandler = forall d . (Handled d) => EH (Event d) (Handler d)
instance Handled Player instance Handled Rule
addEvent :: (Handled d) => Event d -> Handler d -> [EventHandler] -> [EventHandler] addEvent e h ehs = (EH e h):ehs
triggerEvent :: (Handled d) => Event d -> 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 h)) -> case cast h of Just castedH -> castedH d Nothing -> return ()
h1 :: Player -> IO () h1 (P a) = putStrLn $ "Welcome Player " ++ (show a) ++ "!" h2 :: Rule -> IO () h2 (R a) = putStrLn $ "New Rule " ++ (show a) eventList1 = addEvent (New :: Event Player) (H h1) [] eventList2 = addEvent (New :: Event Rule) (H h2) eventList1
trigger1 = triggerEvent (New :: Event Player) (P 1) eventList2 -- yelds "Welcome Player 1!" trigger2 = triggerEvent (New :: Event Rule) (R 2) eventList2 --yelds "New Rule* 2"
Best, Corentin
On Fri, Jun 15, 2012 at 12:40 AM, Alexander Solla
wrote: On Thu, Jun 14, 2012 at 2:04 PM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
That look really nice! Unfortunately I need to have an heterogeneous list of all events with their handlers. With this test code it won't compile:
test1 = addEvent (New :: Event Player) (H (undefined::(Player -> IO ()))) [] test2 = addEvent (New :: Event Rule) (H (undefined::(Rule -> IO ()))) test1
Right, okay. Heterogenous lists are tricky, but I think we can get away with using ExistentialQuantification, since you seem to only want to dispatch over the heterogenous types. The assumption I made is a big deal! It means you can't extract the d value. You can only apply properly typed functions (your handlers) on it.
* {-# LANGUAGE ExistentialQuantification #-} *
* type Player = Int *
* type Rule = Int *
* data Event d = New d * * *
*class Handled data where -- Together with EventHandler, corresponds to your "Data" type* * *
*data EventHandler = forall d . (Handled d) => EH (Event d) (d -> IO ()) -- EventHandler takes the place of your (Event d, Handler d) pairs without referring to d.*
* *
*instance Handled Player*
*instance Handled Rule*
*addEvent :: (Handled d) => Event d -> Handler d -> [EventHandler] -> [EventHandler] -- Every [EventHandler] made using addEvent will be of "correct" types (i.e., preserve the typing invariants you want), but YOU must ensure that only [EventHandler]s made in this way are used. This can be done statically with another type and an explicit export list. We can talk about that later, if this works in principle.*
*triggerEvent :: (Handled d) => Event d -> d -> [EventHandler] -> IO ()*

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 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'*
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"?
{-# 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" *
On Fri, Jun 15, 2012 at 4:53 PM, Alexander Solla
On Fri, Jun 15, 2012 at 6:38 AM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
It just bothers me a little that I'm not able to enumerate the events, and also that the user is able to create events with wrong types (like New :: Event String), even if they won't be able to register them.
This can be solved with an explicit export list/smart constructors.
newPlayer :: Event Player newRule :: Event Rule (hide the New constructor)
In any case, my thinking was that your original
data Event = *NewPlayer | NewRule* * * was basically trying to "join" the semantics of "new things" with Player and Rule. But the original approach ran into the problem you mention below -- it is difficult to maintain invariants, since the types want to "multiply". So formally, I factored:
data Event = NewPlayer | NewRule ==> data Event = New (Player | Rule) ==> data Event d = New -- (since the original event didn't want a Player or Rule value. It witnessed the type relation)
On the other hand, if you want to make sure that a type must be "Handled" before you can issue an Event, you can do:
data (Handled d) => Evend d = New
I'm pretty sure the compiler will complain if you try to make a (New :: Event String). I like this idea better than smart constructors for events, if only because you get to use ScopedTypeVariables.
I also have several unrelated events that use the same type of data, so this would be a problem.
Can you clarify?
I mean that I have events like: Message String UserEvent String That have a "data" of the same type, but they are not related.
Adding more events like *data Event d = NewPlayer | NewRule deriving (Typeable, Eq)* is not correct because I can add wrong events like: addEvent (NewPlayer :: Event Rule) (H(undefined::(Rule -> IO()))) [] ** Also one question: I don't understand the "where" clause in your class. If I remove it, it works the same...
Yes, unnecessary where clauses are optional.
Here is my code:
*newtype Player = P Int deriving Typeable newtype Rule = R Int deriving Typeable data Event d = New deriving (Typeable, Eq)
class (Typeable d) => Handled d where data Handler d = H (d -> IO ())
data EventHandler = forall d . (Handled d) => EH (Event d) (Handler d)
instance Handled Player instance Handled Rule
addEvent :: (Handled d) => Event d -> Handler d -> [EventHandler] -> [EventHandler] addEvent e h ehs = (EH e h):ehs
triggerEvent :: (Handled d) => Event d -> 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 h)) -> case cast h of Just castedH -> castedH d Nothing -> return ()
h1 :: Player -> IO () h1 (P a) = putStrLn $ "Welcome Player " ++ (show a) ++ "!" h2 :: Rule -> IO () h2 (R a) = putStrLn $ "New Rule " ++ (show a) eventList1 = addEvent (New :: Event Player) (H h1) [] eventList2 = addEvent (New :: Event Rule) (H h2) eventList1
trigger1 = triggerEvent (New :: Event Player) (P 1) eventList2 -- yelds "Welcome Player 1!" trigger2 = triggerEvent (New :: Event Rule) (R 2) eventList2 --yelds "New Rule* 2"
Best, Corentin
On Fri, Jun 15, 2012 at 12:40 AM, Alexander Solla
wrote: On Thu, Jun 14, 2012 at 2:04 PM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
That look really nice! Unfortunately I need to have an heterogeneous list of all events with their handlers. With this test code it won't compile:
test1 = addEvent (New :: Event Player) (H (undefined::(Player -> IO ()))) [] test2 = addEvent (New :: Event Rule) (H (undefined::(Rule -> IO ()))) test1
Right, okay. Heterogenous lists are tricky, but I think we can get away with using ExistentialQuantification, since you seem to only want to dispatch over the heterogenous types. The assumption I made is a big deal! It means you can't extract the d value. You can only apply properly typed functions (your handlers) on it.
* {-# LANGUAGE ExistentialQuantification #-} *
* type Player = Int *
* type Rule = Int *
* data Event d = New d * * *
*class Handled data where -- Together with EventHandler, corresponds to your "Data" type* * *
*data EventHandler = forall d . (Handled d) => EH (Event d) (d -> IO ()) -- EventHandler takes the place of your (Event d, Handler d) pairs without referring to d.*
* *
*instance Handled Player*
*instance Handled Rule*
*addEvent :: (Handled d) => Event d -> Handler d -> [EventHandler] -> [EventHandler] -- Every [EventHandler] made using addEvent will be of "correct" types (i.e., preserve the typing invariants you want), but YOU must ensure that only [EventHandler]s made in this way are used. This can be done statically with another type and an explicit export list. We can talk about that later, if this works in principle.*
*triggerEvent :: (Handled d) => Event d -> d -> [EventHandler] -> IO ()*

Just wondering, could type families be of any help here?
I don't know type families, but can it be a mean to regroup together the
event types, that are now completely separated :
*data NewPlayer deriving Typeable
data NewRule deriving Typeable*
On Fri, Jun 15, 2012 at 10:59 PM, Corentin Dupont 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 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'* 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"? {-# 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" * On Fri, Jun 15, 2012 at 4:53 PM, Alexander Solla On Fri, Jun 15, 2012 at 6:38 AM, Corentin Dupont <
corentin.dupont@gmail.com> wrote: It just bothers me a little that I'm not able to enumerate the events,
and also that the user is able to create events with wrong types (like New
:: Event String), even if they won't be able to register them. This can be solved with an explicit export list/smart constructors. newPlayer :: Event Player
newRule :: Event Rule
(hide the New constructor) In any case, my thinking was that your original data Event = *NewPlayer | NewRule*
*
*
was basically trying to "join" the semantics of "new things" with Player
and Rule. But the original approach ran into the problem you mention below
-- it is difficult to maintain invariants, since the types want to
"multiply". So formally, I factored: data Event = NewPlayer | NewRule ==>
data Event = New (Player | Rule) ==>
data Event d = New -- (since the original event didn't want a Player or
Rule value. It witnessed the type relation) On the other hand, if you want to make sure that a type must be "Handled"
before you can issue an Event, you can do: data (Handled d) => Evend d = New I'm pretty sure the compiler will complain if you try to make a (New ::
Event String). I like this idea better than smart constructors for events,
if only because you get to use ScopedTypeVariables. I also have several unrelated events that use the same type of data, so
this would be a problem. Can you clarify? I mean that I have events like:
Message String
UserEvent String
That have a "data" of the same type, but they are not related. Adding more events like
*data Event d = NewPlayer | NewRule deriving (Typeable, Eq)*
is not correct because I can add wrong events like:
addEvent (NewPlayer :: Event Rule) (H(undefined::(Rule -> IO()))) []
**
Also one question: I don't understand the "where" clause in your class.
If I remove it, it works the same... Yes, unnecessary where clauses are optional. Here is my code: *newtype Player = P Int deriving Typeable
newtype Rule = R Int deriving Typeable
data Event d = New deriving (Typeable, Eq) class (Typeable d) => Handled d where
data Handler d = H (d -> IO ()) data EventHandler = forall d . (Handled d) => EH (Event d) (Handler d) instance Handled Player
instance Handled Rule addEvent :: (Handled d) => Event d -> Handler d -> [EventHandler] ->
[EventHandler]
addEvent e h ehs = (EH e h):ehs triggerEvent :: (Handled d) => Event d -> 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 h)) -> case cast h of
Just castedH -> castedH d
Nothing -> return () h1 :: Player -> IO ()
h1 (P a) = putStrLn $ "Welcome Player " ++ (show a) ++ "!"
h2 :: Rule -> IO ()
h2 (R a) = putStrLn $ "New Rule " ++ (show a)
eventList1 = addEvent (New :: Event Player) (H h1) []
eventList2 = addEvent (New :: Event Rule) (H h2) eventList1 trigger1 = triggerEvent (New :: Event Player) (P 1) eventList2 -- yelds
"Welcome Player 1!"
trigger2 = triggerEvent (New :: Event Rule) (R 2) eventList2 --yelds
"New Rule* 2" Best,
Corentin On Fri, Jun 15, 2012 at 12:40 AM, Alexander Solla On Thu, Jun 14, 2012 at 2:04 PM, Corentin Dupont <
corentin.dupont@gmail.com> wrote: That look really nice!
Unfortunately I need to have an heterogeneous list of all events with
their handlers.
With this test code it won't compile: test1 = addEvent (New :: Event Player) (H (undefined::(Player -> IO
()))) []
test2 = addEvent (New :: Event Rule) (H (undefined::(Rule -> IO ())))
test1 Right, okay. Heterogenous lists are tricky, but I think we can get
away with using ExistentialQuantification, since you seem to only want to
dispatch over the heterogenous types. The assumption I made is a big deal!
It means you can't extract the d value. You can only apply properly typed
functions (your handlers) on it. *
{-# LANGUAGE ExistentialQuantification #-}
* *
type Player = Int
* *
type Rule = Int
* *
data Event d = New d
*
*
* *class Handled data where -- Together with EventHandler, corresponds
to your "Data" type*
*
* *data EventHandler = forall d . (Handled d) => EH (Event d) (d -> IO
()) -- EventHandler takes the place of your (Event d, Handler d) pairs
without referring to d.* *
* *instance Handled Player* *instance Handled Rule* *addEvent :: (Handled d) => Event d -> Handler d -> [EventHandler] ->
[EventHandler] -- Every [EventHandler] made using addEvent will be of
"correct" types (i.e., preserve the typing invariants you want), but YOU
must ensure that only [EventHandler]s made in this way are used. This can
be done statically with another type and an explicit export list. We can
talk about that later, if this works in principle.* *triggerEvent :: (Handled d) => Event d -> d -> [EventHandler] -> IO ()
*

On Fri, Jun 15, 2012 at 1:59 PM, Corentin Dupont
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" *

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
On Fri, Jun 15, 2012 at 1:59 PM, Corentin Dupont < corentin.dupont@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" *

On Sat, Jun 16, 2012 at 3:31 PM, Corentin Dupont
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...
In that case, you definitely want FunctionalDependencies or TypeFamilies, and will probably want to drop the constraint (Handler e d) on Event e (if it doesn't work), and maybe enforce it with explicit exports.

OK, so here's my last attempt. What do you think?
The Event class is optional (it works without because of EventData is
enforcing the use of the right types) however, I find it more clear because
it clearly specifies which types are events.
*
data NewPlayer = NewPlayer deriving (Typeable, Eq)
data NewRule = NewRule deriving (Typeable, Eq)
class (Eq e, Typeable e) => Event e
instance Event NewPlayer
instance Event NewRule
data family EventData e
data instance EventData NewPlayer = P Int
data instance 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 ()
-- TESTS
h1 :: EventData NewPlayer -> IO ()
h1 (P a) = putStrLn $ "Welcome Player " ++ (show a) ++ "!"
h2 :: EventData NewRule -> 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" *
Thanks again!!
Corentin
On Sun, Jun 17, 2012 at 12:46 AM, Alexander Solla
On Sat, Jun 16, 2012 at 3:31 PM, Corentin Dupont < corentin.dupont@gmail.com> wrote:
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...
In that case, you definitely want FunctionalDependencies or TypeFamilies, and will probably want to drop the constraint (Handler e d) on Event e (if it doesn't work), and maybe enforce it with explicit exports.
participants (2)
-
Alexander Solla
-
Corentin Dupont