module Pangraph.Internal.HexmlExtra where
import Data.List (concatMap)
import Data.ByteString (ByteString)
import Text.XML.Hexml
import Pangraph
followChildren :: Node -> [ByteString] -> [Node]
followChildren h [] = [h]
followChildren h bs = (concatMap recurse . childrenBy h) (head bs)
where
recurse :: Node -> [Node]
recurse n = followChildren n (tail bs)
hexmlParse :: ByteString -> Node
hexmlParse file = case parse file of
Right t -> t
Left l -> error $ "HexML parser failed:\n" ++ show l
convertAtt :: Text.XML.Hexml.Attribute -> Pangraph.Attribute
convertAtt a = (attributeName a, attributeValue a)