Hi Corentin, This is how I would model your request (without concrete constructors for Player and Rule) I'm sure there are better descriptions also as I'm not an expert.
paolino {-# LANGUAGE DataKinds, GADTs, KindSignatures #-} data Player data Rule data Data = Player | Rule data EventKind = Action | Reaction data Event :: EventKind -> * where NewPlayer :: Player -> Event Action NewRule :: Rule -> Event Action NewHandler :: (Event Action -> IO ()) -> Event Reaction handle :: Event Action -> Event Reaction -> IO () handle x (NewHandler f) = f x reaction :: Event a -> [Event Reaction] -> IO [Event Reaction] reaction f@(NewHandler _) es = return $ f:es reaction p@(NewPlayer _) es = mapM_ (handle p) es >> return es reaction r@(NewRule _) es = mapM_ (handle r) es >> return es 2012/7/4 Corentin Dupont <corentin.dup...@gmail.com> > Hi, > for example, in my game (Nomic) if a new player arrives, I trigger a > "NewPlayer" event. All handlers registered for that event should be > triggered, and passed a structure "Player" containing all the infos of the > incoming player. > If there is a new rule submitted, that the same: the event "NewRule" is > triggered and the handlers are passed a structure "Rule". Thus I want the > handlers registered on NewPlayer to have the type Player -> xxx, and on > NewRule to have the type Rule -> xxx. I want to be able to associate an > arbitrary data type (here Player and Rule) to an event. > The handlers are inherently of different types, but I want to store them > in a unique list hence the existential... > > > On Wed, Jul 4, 2012 at 4:33 PM, Paolino <paolo.verone...@gmail.com> wrote: > >> Hi Corentin, >> If you could explain *why* there should be a type associated to each >> event value, it would help, maybe. >> If it's a design choice , maybe it'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. >> If the language of events is complex , possibly recursive, you can use >> GADTs to enforce their validity by construction and you don't need to >> typefy the event values, but some of their characteristics. >> 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. >> >> paolino >> >> 2012/7/4 Corentin Dupont <corentin.dup...@gmail.com> >> >>> 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 typf data with type indexing.*.. >>> * >>> >>> Regards >>> Corentin >>> >>> >>> On Wed, Jul 4, 2012 at 12:58 PM, Paolino <paolo.verone...@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.dup...@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@haskell.org >>>>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>>>> >>>>> >>>> >>> >> >
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe