
Thomas Hartman wrote:
I don't think this will work.
From
http://www.haskell.org/ghc/docs/latest/html/libraries/fgl/src/Data-Graph-Ind...
the minimal implementatin for Graph is
-- | Minimum implementation: 'empty', 'isEmpty', 'match', 'mkGraph', 'labNodes' .... -- | Decompose a 'Graph' into the 'MContext' found for the given node and the -- remaining 'Graph'. match :: Node -> gr a b -> Decomp gr a b
Basically, match given a node returns the graph minus the node, and a "context for the node which has ingoing edges/labels, outgoing edges/labels, the node itself and the node label. With the & operator you can compose these two things and get back your original graph.
With the implementation you have described I can't see any way to implement this match function, unless per my above comment you're doing something weird like having no graph edges, or all possible graph edges. And then why use a graph?
It's a _complete_ graph, i.e. there is an edge between every two nodes. I want to compute the minimum spanning tree using http://www.haskell.org/ghc/docs/latest/html/libraries/fgl/Data-Graph-Inducti... without rewriting the FGL code and without generating the many edges explicitly. Eventually I want to have a "proper" tree (Data.Tree.Tree) for pre-order traversal. Preorder traversal of a MST gives a sub-optimal solution (not worse than twice as long as the optimum) for the travelling salesman problem (TSP). I may be on the wrong track, though. Thanks Christian
Unless I'm missing something...
Thomas.
2008/1/18, Christian Maeder
: 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

Hello,
It's a _complete_ graph, i.e. there is an edge between every two nodes.
I want to compute the minimum spanning tree. Eventually I want to have a sub-optimal solution for the travelling salesman problem (TSP).
A direct solution for this problem would be: -- | place a f-minimal element to the left, remember the minimal value min_left :: Ord b => (a -> b) -> [a] -> ([a],b) min_left _ [] = error "min_left: empty list" min_left f (x:xs) = ms (x,f x) [] xs $ map f xs where ms (y,v) nonmin (z:zs) (w:ws) | w < v = ms (z,w) (y:nonmin) zs ws | otherwise = ms (y,v) (z:nonmin) zs ws ms (y,v) nonmin _ _ = (y:nonmin,v) -- | the same for cross xs ys and a f with arity two mins :: Ord c => (a -> b -> c) -> [a] -> [b] -> [(a, ([b],c))] mins f xs ys = fst $ min_left (snd . snd) [(x,min_left (f x) ys) | x <- xs] -- | *complete* graph data CGraph a b = CGraph [a] (a -> a -> b) -- | give a list of edges with weight that form a minimal spanning tree prim :: Ord b => CGraph a b -> [(a,a,b)] prim (CGraph [] _) = [] prim (CGraph (x:xs) w) = build [x] xs where build _ [] = [] build seen open = let (f,(t:rest,v)):_ = mins w seen open in (f,t,v) : build (t:seen) rest -- | calculate the complete round trip and its (accumulated) weight round_trip :: (Eq a, Ord b, Num b) => CGraph a b -> [(a,a,b,b)] round_trip = rt 0 [] . prim where rt _ [] [] = [] rt s ((c,r,v):bs) [] = (c,r,v,s+v) : rt (s+v) bs [] rt s [] ((r,c,v):ys) = (r,c,v,s+v) : rt (s+v) [(c,r,v)] ys rt s (b@(z,t,w):bs) ((r,c,v):ys) | r == z = (r,c,v,s+v) : rt (s+v) ((c,r,v):b:bs) ys | otherwise = (z,t,w,s+w) : rt (s+w) bs ((r,c,v):ys) {- *Main> round_trip $ CGraph [0..5] (\ x y -> mod (x+y) 4) [(0,4,0,0),(4,5,1,1),(5,3,0,1),(3,1,0,1),(1,3,0,1),(3,2,1,2),(2,3,1,3),(3,5,0,3),(5,4,1,4),(4,0,0,4)] -} Have fun! /BR, Mirko Rahn
participants (2)
-
Christian Maeder
-
Mirko Rahn