
Thanks Martijn, Oleg and Ryan for your kind replies!
@Ryan and Martijn: I considered putting the viewEvent in the typeclass, but
I figured out that would break the separation of concerns. Indeed this
typeclass "Event" belongs to the inner engine, while the display is done in
another component (not even the same library) using a specific technology
(for instance HTML).
So it doesn't feel right to mix the logic of the event engine with the
display...
@Oleg: Yes the set of events is closed and I would be much happier with a
GADT! But no matter how hard I tried I couldn't manage.
Here is the full problem:
*{-# LANGUAGE ExistentialQuantification, TypeFamilies, DeriveDataTypeable
#-}
import Data.Typeable
-- | Define the events and their related data
class (Eq e, Typeable e, Show e) => Event e where
data EventData e
-- | Groups of events
data PlayerEvent = Arrive | Leave deriving (Typeable, Show, Eq)
-- | events types
data Player = Player PlayerEvent deriving (Typeable, Show, Eq)
data Message m = Message String deriving (Typeable, Show, Eq)
-- | event instances
instance Event Player where data
EventData Player = PlayerData {playerData :: Int}
instance (Typeable m) => Event (Message m) where data EventData (Message
m) = MessageData {messageData :: m}
-- | structure to store an event
data EventHandler = forall e . (Event e) =>
EH {eventNumber :: Int,
event :: e,
handler :: (EventData e) -> IO ()} deriving Typeable
-- store a new event with its handler in the list
addEvent :: (Event e) => e -> (EventData e -> IO ()) -> [EventHandler] ->
[EventHandler]
addEvent event handler ehs = undefined
-- trigger all the corresponding events in the list, passing the **data to
the handlers
triggerEvent :: (Event e) => e -> (EventData e) -> [EventHandler] -> IO ()
triggerEvent event edata ehs = undefined
--Examples:
msg :: Message Int
msg = Message "give me a number"
myList = addEvent msg (\(MessageData n) -> putStrLn $ "Your number is: " ++
show n) []
trigger = triggerEvent msg (MessageData 1) **myList --Yelds "Your number
is: 1"*
Has you can see this allows me to associate an arbitrary data type to each
event with the type family "EventData". Furthermore some events like
"Message" let the user choose the data type using the type parameter. This
way I have nice signatures for the functions "addEvent" and "triggerEvent".
The right types for the handlers and the data passed is enforced at
compilation time.
But I couldn't find any way to convert this into a GATD and get rid of the
"Event" class......
Thanks,
Corentin
On Tue, Sep 11, 2012 at 1:51 PM, Martijn Schrage
On 11-09-12 08:53, oleg@okmij.org wrote:
Corentin Dupon wrote about essentially the read-show problem:
class (Typeable e) => Event e
data Player = Player Int deriving (Typeable) data Message m = Message String deriving (Typeable)
instance Event Player
instance (Typeable m) => Event (Message m)
viewEvent :: (Event e) => e -> IO () viewEvent event = do case cast event of Just (Player a) -> putStrLn $ show a Nothing -> return () case cast event of Just (Message s) -> putStrLn $ show s Nothing -> return ()
Indeed the overloaded function cast needs to know the target type -- the type to cast to. In case of Player, the pattern (Player a) uniquely determines the type of the desired value: Player. This is not so for Message: the pattern (Message s) may correspond to the type Message (), Message Int, etc.
To avoid the problem, just specify the desired type explicitly
I had the same idea, but it doesn't work. Fixing m to () causes the cast to fail for any other type, so viewEvent (Message "yes" :: Message ())will work, but viewEvent (Message "no" :: Message Char) won't.
Putting viewEvent in the Event class though, like Ryan suggested, seems to be an elegant solution that stays close to the original source.
Cheers, Martijn
case cast event of Just (Message s::Message ()) -> putStrLn $ show s Nothing -> return ()
(ScopedTypeVariables extension is needed). The exact type of the message doesn't matter, so I chose Message ().
BTW, if the set of events is closed, GADTs seem a better fit
data Player data Message s
data Event e where Player :: Int -> Event Player Message :: String -> Event (Message s)
viewEvent :: Event e -> IO () viewEvent (Player a) = putStrLn $ show a viewEvent (Message s) = putStrLn $ show s
_______________________________________________ Haskell-Cafe mailing listHaskell-Cafe@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe