Re: [Haskell-cafe] existential types and cast

2012-07-04 Thread Paolino
Hi
How many handlers for each type of event in the list of handlers ?
If you have only one handler for each type , it should go in the typeclass,
and you don't need typeable.
If you have more than one maybe you can avoid using type indexing at all,
because it doesn't resolve the handler selection issue.
By the way , it's not clear to me why you don't have a simple Event
datatype describing all the possible events in advance.

Regards

paolino

2012/7/3 Corentin Dupont corentin.dup...@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@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


[Haskell-cafe] Inferring Safety

2012-07-04 Thread Ivan Lazar Miljenovic
When it says up the top of Haddock docs that a module is
Safe-Infered (which should probably Safe-Infer*r*ed), what does that
actually mean?

My understanding of Safe Haskell is that there's no unsafe* functions,
etc. being used unless the module author swears (by using -XSafe) that
the module is indeed safe...

Yet as I pointed out on Google+ [1], the Data.GraphViz [2] module of
my graphviz package is labelled as being safe-infered, despite having
this function in there:

dotizeGraph   :: (Ord cl, Graph gr) = GraphvizParams Node nl el cl l
 - gr nl el - gr (AttributeNode nl) (AttributeEdge el)
dotizeGraph params gr = unsafePerformIO
$ graphToGraph params' gr
  where
params' = params { fmtCluster = const []
 , fmtNode= const []
 , fmtEdge= const []
 }

This function uses `dot -Tcanon` to add in positional (as well as
possibly other) information to FGL graphs.  Now, as far as I know this
function _is_ safe (assuming that you have Graphviz installed), but I
certainly haven't proven it enough that for every possible input graph
the same positional attributes will be attached back (i.e. that the
graph will always be laid out the same), and thus I haven't used
-XSafe.

So what's going on here?

[1]: https://plus.google.com/101302416956767249890/posts/3NUWxd9P6xV
[2]: 
http://hackage.haskell.org/packages/archive/graphviz/2999.13.0.3/doc/html/Data-GraphViz.html

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
http://IvanMiljenovic.wordpress.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe