Re: [Haskell-cafe] serialize an unknown type

I'm trying to get around my problem (still stuck...).
I have really to call a function like this:
triggerEvent :: (Typeable e, Show e, Eq e) => Event e -> EventData e ->
State Game ()
This function simply execute an event given the corresponding data and
change the state of the game.
Now as explained my web framework won't accept random types (like "e") to
be passed around.
So I said to myself "OK, so let's store the events in a list and ask the
gui to just give me the number of the event".
So I have an heterogeneous list of events [EventWrap]:
data EventWrap where
EW :: (Typeable e, Show e, Eq e) => {eventNumber :: Int, event :: Event
e} -> EventWrap
Do you think this solution can lead me somewhere?? I have actually doubts I
can find back my "Event e" from the list because of the implicit forall in
the GADT.....
Thanks,
Corentin
On Wed, Oct 24, 2012 at 3:37 PM, Chris Smith
"Corentin Dupont"
wrote: I could ask my user to make his new type an instance of a class as suggested by Alberto...
If you are working with unknown types, then your options are: (a) constrain to some type class, or (b) have your clients pass in functions to operate on the type alongside the values. Actually the first is just a special case of the second with syntactic sugar...

Hi Corentin It looks like you are writing the event handler on the server side. If so, the range of events you can handle is fixed to just those you implement handlers for - having an openly extensible event type is useless if this is the case. Ignoring client/server for a moment, a function (State -> State) would be the most "extensible" API you could allow for clients. You don't need to worry about an open set of Event types, a client knows the state exactly and doesn't need extensibility. Client/Server operation won't allow a state transformer API as Haskell can't readily serialize functions. But you can implement a "command language" enumerating state changing operations. The second Quickcheck paper gives a very good example of how to implement such a command language. Testing Monadic Code with QuickCheck (2002) Koen Claessen , John Hughes www.cse.chalmers.se/~rjmh/Papers/QuickCheckST.ps Or Citeseer if you need a PDF: http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.19.9275

Hi,
I designed my event engine like this:
-- | events types
data Player = Arrive | Leave deriving (Typeable, Show, Eq)
data RuleEvent = Proposed | Activated | Rejected | Added | Modified |
Deleted deriving (Typeable, Show, Eq)
data Time deriving Typeable
data InputChoice c deriving Typeable
(...)
-- | events names
data Event a where
Player :: Player -> Event Player
RuleEv :: RuleEvent -> Event RuleEvent
Time :: UTCTime -> Event Time
InputChoice :: (Eq c, Show c) => PlayerNumber -> String -> [c] -> c ->
Event (InputChoice c)
(...)
-- | data associated with each events
data EventData a where
PlayerData :: {playerData :: PlayerInfo} -> EventData Player
RuleData :: {ruleData :: Rule} -> EventData RuleEvent
TimeData :: {timeData :: UTCTime} -> EventData Time
InputChoiceData :: (Show c, Read c, Typeable c) => {inputChoiceData ::
c} -> EventData (InputChoice c)
(...)
-- associate an event with an handler
data EventHandler where
EH :: (Typeable e, Show e, Eq e) =>
{eventNumber :: EventNumber,
event :: Event e,
handler :: (EventNumber, EventData e) -> Exp ()} ->
EventHandler
--execute all the handlers of the specified event with the given data
triggerEvent :: (Typeable a, Show a, Eq a) => Event a -> EventData a ->
[EventHandler] -> State Game ()
I use a type parameter "e" on Event and EventData to be sure that the right
data is shuffled to the right event handler.
It worked well until now. But now I'm hitting a wall with the GUI, because
the data sent back for InputChoice can only be a String.
So, I need to call triggerEvent with: Event(InputChoice String) and EventData
(InputChoice String)...
Which doesn't work obviously because the types are not the same than
initially (for example, the event was built with Event(InputChoice Bool)).
Cheers,
C
On Wed, Oct 24, 2012 at 7:25 PM, Stephen Tetley
Hi Corentin
It looks like you are writing the event handler on the server side. If so, the range of events you can handle is fixed to just those you implement handlers for - having an openly extensible event type is useless if this is the case.
Ignoring client/server for a moment, a function (State -> State) would be the most "extensible" API you could allow for clients. You don't need to worry about an open set of Event types, a client knows the state exactly and doesn't need extensibility.
Client/Server operation won't allow a state transformer API as Haskell can't readily serialize functions. But you can implement a "command language" enumerating state changing operations. The second Quickcheck paper gives a very good example of how to implement such a command language.
Testing Monadic Code with QuickCheck (2002) Koen Claessen , John Hughes www.cse.chalmers.se/~rjmh/Papers/QuickCheckST.ps
Or Citeseer if you need a PDF: http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.19.9275
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
-
Corentin Dupont
-
Stephen Tetley