[Haskell-cafe] type variable in class instance
Corentin Dupont
corentin.dupont at gmail.com
Wed Sep 12 12:55:20 CEST 2012
If I understand, the SomeEvent event acts as a proxy to hide the diversity
of the events? That's interesting.
This way I don't have to use an heterogeneous list and a lot of casting...
On Wed, Sep 12, 2012 at 7:44 AM, <oleg at okmij.org> wrote:
>
> Let me see if I understand. You have events of different sorts: events
> about players, events about timeouts, events about various
> messages. Associated with each sort of event is a (potentially open)
> set of data types: messages can carry payload of various types. A
> handler specifies behavior of a system upon the reception of an
> event. A game entity (player, monster, etc) is a collection of
> behaviors. The typing problem is building the heterogeneous collection
> of behaviors and routing an event to the appropriate handler. Is this
> right?
>
> There seem to be two main implementations, with explicit types and latent
> (dynamic) types. The explicit-type representation is essentially HList
> (a Type-indexed Record, TIR, to be precise). Let's start with the
> latent-type representation. Now I understand your problem better, I
> think your original approach was the right one. GADT was a
> distraction, sorry. Hopefully you find the code below better reflects
> your intentions.
>
> {-# LANGUAGE ExistentialQuantification, DeriveDataTypeable #-}
> {-# LANGUAGE StandaloneDeriving #-}
>
> import Data.Typeable
>
> -- Events sorts
>
> data Player = Player PlayerN PlayerStatus
> deriving (Eq, Show, Typeable)
>
> type PlayerN = Int
> data PlayerStatus = Enetering | Leaving
> deriving (Eq, Show)
>
> newtype Message m = Message m
> deriving (Eq, Show)
>
> deriving instance Typeable1 Message
>
> newtype Time = Time Int
> deriving (Eq, Show, Typeable)
>
> data SomeEvent = forall e. Typeable e => SomeEvent e
> deriving (Typeable)
>
> -- They are all events
>
> class Typeable e => Event e where -- the Event
> predicate
> what_event :: SomeEvent -> Maybe e
> what_event (SomeEvent e) = cast e
>
>
> instance Event Player
> instance Event Time
> instance Typeable m => Event (Message m)
>
> instance Event SomeEvent where
> what_event = Just
>
> -- A handler is a reaction on an event
> -- Given an event, a handler may decline to handle it
> type Handler e = e -> Maybe (IO ())
>
> inj_handler :: Event e => Handler e -> Handler SomeEvent
> inj_handler h se | Just e <- what_event se = h e
> inj_handler _ _ = Nothing
>
>
> type Handlers = [Handler SomeEvent]
>
> trigger :: Event e => e -> Handlers -> IO ()
> trigger e [] = fail "Not handled"
> trigger e (h:rest)
> | Just rh <- h (SomeEvent e) = rh
> | otherwise = trigger e rest
>
> -- Sample behaviors
>
> -- viewing behavior (although viewing is better with Show since all
> -- particular events implement it anyway)
>
> view_player :: Handler Player
> view_player (Player x s) = Just . putStrLn . unwords $
> ["Player", show x, show s]
>
> -- View a particular message
> view_msg_str :: Handler (Message String)
> view_msg_str (Message s) = Just . putStrLn . unwords $
> ["Message", s]
>
> -- View any message
> view_msg_any :: Handler SomeEvent
> view_msg_any (SomeEvent e)
> | (tc1,[tr]) <- splitTyConApp (typeOf e),
> (tc2,_) <- splitTyConApp (typeOf (undefined::Message ())),
> tc1 == tc2 =
> Just . putStrLn . unwords $ ["Some message of the type", show tr]
> view_msg_any _ = Nothing
>
> viewers = [inj_handler view_player, inj_handler view_msg_str, view_msg_any]
>
>
> test1 = trigger (Player 1 Leaving) viewers
> -- Player 1 Leaving
>
> test2 = trigger (Message "str1") viewers
> -- Message str1
>
> test3 = trigger (Message (2::Int)) viewers
> -- Some message of the type Int
>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20120912/eff9cb1d/attachment.htm>
More information about the Haskell-Cafe
mailing list