在Haskell中读取GraphML

时间:2014-01-10 02:19:04

标签: haskell graph graphml

我正在尝试将包含单个有向图的GraphML文件读入Haskell Data.Graph,以便使用Math.Combinatorics.Graph模块运行分析。

但是,我找不到任何允许我读取GraphML文件的模块,产生Data.Graph。我找到的一个相关模块是ForSyDe.Backend.GraphML。但是,这似乎是ForSyDe DSL特有的,我现在想不出用它来阅读普通Data.Graph的方法。

你能指点我一个允许我阅读GraphML的库,最好是一些关于如何使用它的示例代码吗?

1 个答案:

答案 0 :(得分:4)

经过一周多的搜索,我认为目前还没有GraphML解析器库。因此我编写了自己的最小解析器。

我们假设我们有这个GraphML:

<?xml version="1.0" encoding="UTF-8"?>
<graphml xmlns="http://graphml.graphdrawing.org/xmlns"  
    xmlns:xsi="http://www.w3.org/2001/XMLSchema-instance"
    xsi:schemaLocation="http://graphml.graphdrawing.org/xmlns
     http://graphml.graphdrawing.org/xmlns/1.0/graphml.xsd">
  <graph id="G" edgedefault="undirected">
    <node id="n0"/>
    <node id="n1"/>
    <node id="n2"/>
    <node id="n3"/>
    <edge id="e1" source="n0" target="n1"/>
    <edge id="e1" source="n1" target="n2"/>
    <edge id="e1" source="n1" target="n3"/>
    <edge id="e1" source="n3" target="n0"/>
  </graph>
</graphml>

我创建了这个基于HXT的解析器,它能够解析GraphML的最小子集(刚好足以创建上述GraphML的Data.Graph)。以下文件的main函数表示如何使用它的示例:它打印图表中的节点列表(另请参阅this related question)。

{-# LANGUAGE Arrows, NoMonomorphismRestriction #-}
import Text.XML.HXT.Core
import qualified Data.Graph as DataGraph

data Graph = Graph
  { graphId :: String,
    nodes :: [String],
    edges :: [(String, String)] -- (Source, target)
  }
  deriving (Show, Eq)

atTag tag = deep (isElem >>> hasName tag)

parseEdges = atTag "edge" >>>
  proc e -> do
      source <- getAttrValue "source" -< e
      target <- getAttrValue "target" -< e
      returnA -< (source, target)

parseNodes = atTag "node" >>>
  proc n -> do
      nodeId <- getAttrValue "id" -< n
      returnA -< nodeId

parseGraph = atTag "graph" >>>
  proc g -> do
      graphId <- getAttrValue "id" -< g
      nodes <- listA parseNodes -< g
      edges <- listA parseEdges -< g
      returnA -< Graph{graphId=graphId, nodes=nodes, edges=edges}

getEdges = atTag "edge" >>> getAttrValue "source"

-- Get targets for a single node in a Graph
getTargets :: String -> Graph -> [String]
getTargets source graph = map snd $ filter ((==source).fst) $ edges graph

-- Convert a graph node into a Data.Graph-usable
getDataGraphNode :: Graph -> String -> (String, String, [String])
getDataGraphNode graph node = (node, node, getTargets node graph)

-- Convert a Graph instance into a Data.Graph list of (node, nodeid, edge) tuples
getDataGraphNodeList :: Graph -> [(String, String, [String])]
getDataGraphNodeList graph = map (getDataGraphNode graph) (nodes graph)

main :: IO()
main = do
    graphs <- runX (readDocument [withValidate no] "foo.graphml" >>> parseGraph)
    --  Convert Graph structure to Data.Graph-importable tuple list
    let graphEdges = getDataGraphNodeList $ head graphs
    -- Convert to a Data.Graph
    let (graph, vertexMap) = DataGraph.graphFromEdges' graphEdges
    -- Example of what to do with the Graph: Print vertices
    print $ map ((\ (vid, _, _) -> vid) . vertexMap) (DataGraph.vertices graph)