On 11-09-12 08:53, o...@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 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

Reply via email to