[Haskell-cafe] functional graphs

Christian Maeder Christian.Maeder at dfki.de
Mon Jan 21 04:49:14 EST 2008


Thomas Hartman wrote:
> I don't think this will work.
> 
> From
> 
> http://www.haskell.org/ghc/docs/latest/html/libraries/fgl/src/Data-Graph-Inductive-Graph.html
> 
> 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-Inductive-Query-MST.html
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 <Christian.Maeder at dfki.de>:
>> 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


More information about the Haskell-Cafe mailing list