[Haskell-cafe] serialize an unknown type
Corentin Dupont
corentin.dupont at gmail.com
Thu Oct 25 12:18:12 CEST 2012
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 <stephen.tetley at gmail.com>wrote:
> 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 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/20121025/fe05b0ec/attachment.htm>
More information about the Haskell-Cafe
mailing list