Hello everybody!
I'm soliciting once again your help!
It's been several days I'm blocked by this problem:
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Typeable
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 ()
gives me a:
Ambiguous type variable `t0' in the constraint:
(Typeable t0) arising from a use of `cast'
Probable fix: add a type signature that fixes these type variable(s)
In the expression: cast event
In the expression:
case cast event of {
Just (Message s) -> putStrLn $ show s
Nothing -> return () }
This is because Message has a type variable, while Player has not...
How to get this to work? I tried everything, existential types, scoped type variables etc. without success...
Thanks!!
Corentin