[Haskell-cafe] existential types and cast

MigMit miguelimo38 at yandex.ru
Tue Jul 3 21:32:57 CEST 2012


Actually, using cast seems to be a perfect solution here. I can't see anything wrong with it.

Отправлено с iPad

03.07.2012, в 20:33, Corentin Dupont <corentin.dupont at gmail.com> написал(а):

> Hi all,
> I read somewhere (here: http://stackoverflow.com/questions/2300275/how-to-unpack-a-haskell-existential-type) that it's bad to try to unbox an existential type using a cast. OK, but without I really can't figure out how to do what I want:
> 
> data NewPlayer = NewPlayer deriving (Typeable, Eq)
> data NewRule = NewRule deriving (Typeable, Eq)
> 
> class (Eq e, Typeable e) => Event e where
>     data EventData e
> 
> instance Event NewPlayer where
>     data EventData NewPlayer = P Int
> 
> instance Event NewRule where
>     data EventData NewRule = R Int
> 
> instance Typeable1 EventData where 
>     typeOf1 _ = mkTyConApp (mkTyCon "EventData") []
> 
> data EventHandler = forall e . (Event e) => EH e (EventData e -> IO ())
> 
> addEvent :: (Event e) => e -> (EventData e -> IO ()) -> [EventHandler] -> [EventHandler] 
> addEvent e h ehs = (EH e h):ehs
> 
> triggerEvent :: (Event e) => e -> (EventData e) -> [EventHandler] -> IO ()
> triggerEvent e d ehs = do
>     let r = find (\(EH myEvent _) -> cast e == Just myEvent) ehs
>     case r of
>        Nothing -> return ()
>        Just (EH _ h) -> case cast h of
>         Just castedH -> castedH d
>         Nothing -> return ()
> 
> How to remove the casts from triggerEvent? All that I want is to apply the handler found on the data passed in parameter.
> I tried to add a function apply in the class, without success:
> apply :: (EventData e -> IO ()) -> (EventData e) -> IO ()
> apply = ($)
> 
> 
> Thanks!
> Corentin
> _______________________________________________
> 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/20120703/eda1f18f/attachment.htm>


More information about the Haskell-Cafe mailing list