pugixml-0.2.0: pugixml binding.

Safe HaskellNone
LanguageHaskell2010

Text.XML.Pugi

Contents

Description

parse xml

> docA <- parse def "<a />"
> docA
Right Document <a />

> parseFile def "test.xml"
Document <test >

render xml

> Data.ByteString.Lazy.Char.putStrLn $ either undefined (pretty def) docA
<?xml version="1.0"?>
<a />

> prettyFile def docA

create xml

testHtml :: IO Document
testHtml = create $ doc -> do
    decl <- appendDeclaration "xml" doc
    appendAttrs [("version", "1.0"), ("lang", "ja")] decl

    appendDoctype "html" doc

    html <- appendElement "html" doc
    body <- appendElement "body" html
    div_ <- appendElement "div"  body
    a    <- appendElement "a"    div_
    appendAttr "href" "http://example.com" a
    txt  <- appendPCData "example.com" a
    return ()
-- testHtml for copy&paste to ghci.
> doc <- create $ \doc -> appendDeclaration "xml" doc >>= \decl -> appendAttrs [("version", "1.0"), ("lang", "ja")] decl >> appendDoctype "html" doc >> appendElement "html" doc >>= \html -> appendElement "body" html >>= \body -> appendElement "div"  body >>= \div_ -> appendElement "a"    div_ >>= \a -> appendAttr "href" "http://example.com" a >> appendPCData "example.com" a >> return ()

> doc
Document <?xml version="1.0" lang="ja"?><!DOCTYPE html><html><body><div><a href="http://example.com">example.com</a></div></body></html>

access xml tree

> let Just x = child "xml" doc
> x
Node <?xml version="1.0" lang="ja"?>

> nextSibling x
Just Node <!DOCTYPE html>

> Just html = nextSiblingByName "html" x

> html
Node <html><body><div><a href="http://example.com">example.com</a></div></body></html>

> evaluate [xpath|string(//a/href)|] html
"http://example.com"

> let ns = evaluate [xpath|//a/href|] html

> nodeSetSize ns
1
> nodeSetIndex ns 0
Right ("href","http://example.com")

modify xml

modify doc $ \d -> selectSingleNode [xpath|//a|] d >>= \(Left a) -> setOrAppendAttr "href" "#" a
Document <?xml version="1.0" lang="ja"?><!DOCTYPE html><html><body><div><a href="#">example.com</a></div></body></html>

Synopsis

Document

type Document = Document_ Unknown Immutable Source

parse

render

Node

data Node_ k m Source

type Node = Node_ Unknown Immutable Source

type MutableNode k = Node_ k Mutable Source

data NodeKind Source

Constructors

Element

<name>children</name>

PCData

value

CData

<![CDATA[value]]>

Comment

<!--value-->

Pi

<?name value?>

Declaration

<?name?>

Doctype

<!DOCTYPE value>

Unknown 

getter

type family M m a Source

M Immutable a = a
M Mutable   a = Modify a

class NodeLike n m where Source

instance NodeLike Document_ Immutable
instance NodeLike Node_     Immutable
instance NodeLike Document_ Mutable
instance NodeLike Node_     Mutable

Methods

asNode :: n k m -> M m (Node_ k m) Source

nodeEqual :: n k m -> n l o -> M m Bool Source

forgetNodeKind :: n k m -> n Unknown m Source

prettyNode :: PrettyConfig -> Int -> n k m -> M m ByteString Source

hashValue :: n k m -> M m CSize Source

nodeType :: n k m -> M m NodeType Source

getName :: HasName k => n k m -> M m ByteString Source

getValue :: HasValue k => n k m -> M m ByteString Source

parent :: n k m -> M m (Maybe (Node_ Unknown m)) Source

firstChild :: HasChildren k => n k m -> M m (Maybe (Node_ Unknown m)) Source

lastChild :: HasChildren k => n k m -> M m (Maybe (Node_ Unknown m)) Source

nextSibling :: n k m -> M m (Maybe (Node_ Unknown m)) Source

prevSibling :: n k m -> M m (Maybe (Node_ Unknown m)) Source

child :: HasChildren k => ByteString -> n k m -> M m (Maybe (Node_ Unknown m)) Source

attribute :: HasAttribute k => ByteString -> n k m -> M m (Maybe ByteString) Source

nextSiblingByName :: ByteString -> n k m -> M m (Maybe (Node_ Unknown m)) Source

prevSiblingByName :: ByteString -> n k m -> M m (Maybe (Node_ Unknown m)) Source

findChildByNameAndAttr Source

Arguments

:: HasChildren k 
=> ByteString

node name

-> ByteString

attribute name

-> ByteString

attribute value

-> n k m 
-> M m (Maybe (Node_ Unknown m)) 

findChildByAttr Source

Arguments

:: HasChildren k 
=> ByteString

attribute name

-> ByteString

attribute value

-> n k m 
-> M m (Maybe (Node_ Unknown m)) 

childValue :: HasChildren k => n k m -> M m ByteString Source

childValueByName :: HasChildren k => ByteString -> n k m -> M m ByteString Source

text :: n k m -> M m ByteString Source

findAttribute :: (ByteString -> ByteString -> Bool) -> n k m -> M m (Maybe Attribute) Source

find attribute by predicate. since v0.2.0.

findChild :: (Node -> Bool) -> n k m -> M m (Maybe (Node_ Unknown m)) Source

find child by predicate. since v0.2.0.

findNode :: (Node -> Bool) -> n k m -> M m (Maybe (Node_ Unknown m)) Source

find node by predicate. since v0.2.0.

mapSibling :: (Node_ Unknown m -> a) -> n k m -> M m [a] Source

mapAttrs :: HasAttribute k => (ByteString -> ByteString -> a) -> n k m -> M m [a] Source

path :: Char -> n k m -> M m ByteString Source

firstElementByPath :: Char -> ByteString -> n k m -> M m (Maybe (Node_ Unknown m)) Source

root :: n k m -> M m (Maybe (Node_ Unknown m)) Source

evaluate :: EvalXPath r => XPath r -> n k m -> M m r Source

selectSingleNode :: XPath (NodeSet m) -> n k m -> M m (XPathNode m) Source

selectNodes :: XPath (NodeSet m) -> n k m -> M m (NodeSet m) Source

setter

create :: Monad m => (MutableDocument -> Modify ()) -> m Document Source

create document from scratch.

modify :: Monad m => Document -> (MutableDocument -> Modify ()) -> m Document Source

modify document.

class MutableNodeLike n where Source

Methods

setName :: HasName k => ByteString -> n k Mutable -> Modify () Source

setValue :: HasValue k => ByteString -> n k Mutable -> Modify () Source

appendAttr :: HasAttribute k => ByteString -> ByteString -> n k Mutable -> Modify () Source

prependAttr :: HasAttribute k => ByteString -> ByteString -> n k Mutable -> Modify () Source

setAttr :: HasAttribute k => ByteString -> ByteString -> n k Mutable -> Modify () Source

appendChild :: HasChildren k => NodeType -> n k Mutable -> Modify (MutableNode l) Source

generic appendChild method. Recommend to use appendElement etc...

prependChild :: HasChildren k => NodeType -> n k Mutable -> Modify (MutableNode l) Source

generic prependChild method. Recommend to use prependElement etc...

appendCopy :: HasChildren k => Node_ k a -> n l Mutable -> Modify (MutableNode k) Source

prependCopy :: HasChildren k => Node_ k a -> n l Mutable -> Modify (MutableNode k) Source

removeAttr :: HasAttribute k => ByteString -> n k Mutable -> Modify () Source

removeChild :: HasChildren k => Node_ k a -> n l Mutable -> Modify () Source

appendFlagment :: HasChildren k => ParseConfig -> ByteString -> n k Mutable -> Modify () Source

appendAttrs :: (MutableNodeLike n, HasAttribute k) => [Attribute] -> n k Mutable -> Modify () Source

specified append/prepend child

XPath

data XPath rt Source

class EvalXPath a Source

Minimal complete definition

evaluateXPath

xpath :: QuasiQuoter Source

generate xpath object.

[xpath|query|] == ((xpathObject) :: XPath (instance of EvalXPath))

NodeSet

data NodeSet m Source

Instances

nodeSetMapM :: (XPathNode m -> IO a) -> NodeSet m -> IO [a] Source

nodeSetMapM_ :: (XPathNode m -> IO ()) -> NodeSet m -> IO () Source

nodeSetMap :: (XPathNode m -> a) -> NodeSet m -> [a] Source

reexport

def :: Default a => a

The default value for this type.