我正在编写一个用于处理图形的库。 主要任务 - 解析xml-tree。 树看起来像
<graph nodes=4 arcs=5>
<node id=1 />
<node id=2 />
<node id=3 />
<node id=4 />
<arc from=1 to=2 />
<arc from=1 to=3 />
<arc from=1 to=4 />
<arc from=2 to=4 />
<arc from=3 to=4 />
</graph>
存储结构:
type Id = Int
data Node = Node Id deriving (Show)
data Arc = Arc Id Id deriving (Show)
data Graph = Graph { nodes :: [Node],
arcs :: [Arc]}
如何将xml文件中的数据写入此结构? 我不能为这种xml树编写解析器(HXT库)
答案 0 :(得分:2)
您需要使用XML库吗? 'tagsoup'库对于非真正的xml可能同样有效:
import Text.HTML.TagSoup
import Data.Maybe
main = do
s <- readFile "A.dat"
-- get a list of nodes and arcs
let g' = catMaybes
[ case n of
TagOpen "node" [(_,n)] -> Just (Left $ Node (read n))
TagOpen "arc" [(_,n), (_,m)] -> Just (Right $ Arc (read n) (read m))
_ -> Nothing
| n <- parseTags s ]
-- collapse them into a graph
let g = foldr (\n g -> case n of
Left n -> g { nodes = n : nodes g }
Right a -> g { arcs = a : arcs g }
) (Graph [] []) g'
print g
运行此:
> main
Graph {nodes = [Node 1,Node 2,Node 3,Node 4], arcs = [Arc 1 2,Arc 1 3,Arc 1 4,Arc 2 4,Arc 3 4]}
答案 1 :(得分:1)
假设您将其转换为正确的XML(用引号括住所有属性值),以下代码将起作用(使用xml-enumerator):
{-# LANGUAGE OverloadedStrings #-}
import Text.XML.Enumerator.Parse
import Control.Monad
import Data.Text (unpack)
import Control.Applicative
type Id = Int
data Node = Node Id deriving (Show)
data Arc = Arc Id Id deriving (Show)
data Graph = Graph { nodes :: [Node],
arcs :: [Arc]}
deriving Show
main = parseFile_ "graph.xml" decodeEntities $ force "graph required" parseGraph
parseGraph = tagName "graph" getCounts $ \(nodeCount, arcCount) -> do
nodes <- replicateM nodeCount parseNode
arcs <- replicateM arcCount parseArc
return $ Graph nodes arcs
where
requireNum name = do
x <- requireAttr name
case reads $ unpack x of
(i, _):_ -> return i
_ -> fail $ "Invalid integer: " ++ unpack x
getCounts = do
n <- requireNum "nodes"
a <- requireNum "arcs"
return (n, a)
parseNode = force "node required" $ tagName "node"
(Node <$> requireNum "id") return
parseArc = force "arc required" $ tagName "arc"
(Arc <$> requireNum "from" <*> requireNum "to") return
输出:
Graph {nodes = [Node 1,Node 2,Node 3,Node 4], arcs = [Arc 1 2,Arc 1 3,Arc 1 4,Arc 2 4,Arc 3 4]}