
Hi, Given a complete graph as a list of nodes whose edge labels are given by a function over two nodes: data CGraph a b = CGraph [a] (a -> a -> b) Can I define an instance for the fgl Graph class? import Data.Graph.Inductive.Graph instance Graph CGraph where empty = CGraph [] -- and now? I had no idea how to define empty (except using undefined). I thought of requiring a context for the node labels of type a, but this type is not mentioned in the class header. So it looked to me like the impossibility to define sets (requiring an Ord) as monads. (i.e. instance Monad Data.Set.Set) Any working proposals for my graph problem? Cheers Christian

Hi Christian,
On Jan 18, 2008 1:55 PM, Christian Maeder
data CGraph a b = CGraph [a] (a -> a -> b)
Can I define an instance for the fgl Graph class?
I had no idea how to define empty (except using undefined).
Well, presumably the function does not need to be defined on values not in the list, so returning an error is fair enough-- empty = CGraph [] (const $ error "Node not in graph") I suppose you want to use the index in the list as the Node (= Int), which should be fine, but you'll run into problems with mkGraph, because you don't have an Eq constraint on a, so you can't implement the function to pass to CGraph. Since mkGraph is required to have the type mkGraph :: [LNode a] -> [LEdge b] -> CGraph a b for *all* a and b, you don't have a way to add an Eq constraint anywhere, either. So, no dice... However, if you'd be able to live with data CGraph a b = CGraph [LNode a] (Node -> Node -> b) then you should be able to write the instance like this-- instance Graph CGraph where empty = CGraph [] (const $ error "Node not in graph") isEmpty (CGraph xs _) = null xs labNodes (CGraph xs _) = xs mkGraph nodes edges = CGraph nodes f where f x y = fromMaybe (error "Edge not found") (lookup (x,y) edges') edges' = map (\(x,y,l) -> ((x,y),l)) edges match x (CGraph nodes f) = case lookup x nodes of Nothing -> (Nothing, CGraph nodes f) Just l -> let nodes' = filter ((/= x) . fst) nodes left = map (\(y,_) -> (f y x, y)) nodes' right = map (\(y,_) -> (f x y, y)) nodes' in (Just (left, x, l, right), CGraph nodes' f) - Benja

Benja Fallenstein wrote:
However, if you'd be able to live with
data CGraph a b = CGraph [LNode a] (Node -> Node -> b)
then you should be able to write the instance like this--
instance Graph CGraph where empty = CGraph [] (const $ error "Node not in graph") isEmpty (CGraph xs _) = null xs labNodes (CGraph xs _) = xs mkGraph nodes edges = CGraph nodes f where f x y = fromMaybe (error "Edge not found") (lookup (x,y) edges') edges' = map (\(x,y,l) -> ((x,y),l)) edges match x (CGraph nodes f) = case lookup x nodes of Nothing -> (Nothing, CGraph nodes f) Just l -> let nodes' = filter ((/= x) . fst) nodes left = map (\(y,_) -> (f y x, y)) nodes' right = map (\(y,_) -> (f x y, y)) nodes' in (Just (left, x, l, right), CGraph nodes' f)
Thanks for pointing out this proposal. The actual problem is mkGraph that needs all the many edges created beforehand (that's what I wanted to avoid). Cheers Christian

Hi Christian,
On Jan 21, 2008 10:57 AM, Christian Maeder
Thanks for pointing out this proposal. The actual problem is mkGraph that needs all the many edges created beforehand (that's what I wanted to avoid).
Well, uh, at the risk of being obvious, if you can avoid using fgl functions that call mkGraph, then there is nothing to say that mkGraph has ever to be called, and conversely, if you must use fgl functions that call mkGraph, then there is no way to avoid the fact that it gets the edge labels in a list... :-) A quick grep of the library shows that use of mkGraph is very rare. I haven't chased down the uses of functions that call mkGraph, though, so I don't really know whether many or few functions use mkGraph internally. Of course, you can use (mkGraph = error "mkGraph") and see whether you trip over it at all. Best, - Benja
participants (2)
-
Benja Fallenstein
-
Christian Maeder