hxt-filter-8.4.2: A collection of tools for processing XML with Haskell (Filter variant).

Text.XML.HXT.DOM.XmlTreeFilter

Description

basic XmlTree filter

Synopsis

Documentation

isRoot :: XmlFilterSource

test whether the root of a tree contains a document root node.

isTag :: String -> XmlFilterSource

test whether the root of a tree contains a tag node.

see also: isNsTag

isNsTag :: String -> String -> XmlFilterSource

namespace aware test whether the root of a tree contains a tag node. Parameters are the local part and namespace. Only usable after namespace propagation.

see also: isTag

hasLocalPart :: String -> XmlFilterSource

test whether the root of a tree has a given local name see also : hasNamespace, hasPrefix, isTag, isAttr

hasPrefix :: String -> XmlFilterSource

test whether the root of a tree has a given prefix name see also : hasNamespace, hasLocalPart, isTag, isAttr

hasNamespace :: String -> XmlFilterSource

test whether the root of a tree belongs to a given namespace see also : isTag, isAttr, hasLocalPart, hasPrefix

isOfTag :: (TagName -> Bool) -> XmlFilterSource

test whether the root of a tree contains a tag node with a special name.

hasAttr :: String -> XmlFilterSource

test whether the node of a tree is a XTag node or a XPi node with an attibute of a specific name

see also: isAttr, hasNsAttr

hasNsAttr :: String -> String -> XmlFilterSource

test whether the tree is a XTag node with an attibute of a specific local name and namespace uri

see also: hasAttr, isNsAttr

hasValue :: String -> (String -> Bool) -> XmlFilterSource

test whether the given node is a XTag node or a XPI node with an attribute with a value with a specific property. In case of a match, the attribute value represented by a text node is returned as single element list, else the empty list is the result.

see also : getValue

isPi :: String -> XmlFilterSource

test whether the tree is a processing instruction with a given name.

isXmlPi :: XmlFilterSource

test whether the tree is a <?xml ... ?> declaration

isOfPi :: (TagName -> Bool) -> XmlFilterSource

test whether the root of a tree contains a processing instruction of a special name.

isXCdata :: XmlFilterSource

test whether the root of a tree contains a CDATA node.

isXCharRef :: XmlFilterSource

test whether the root of a tree contains a character reference node.

isXCmt :: XmlFilterSource

test whether the root of a tree contains a comment node.

isXDTD :: XmlFilterSource

test whether the root of a tree contains a DTD part.

isXEntityRef :: XmlFilterSource

test whether the root of a tree contains an entity reference node.

isXError :: XmlFilterSource

test whether the root of a tree contains an error node.

isXPi :: XmlFilterSource

test whether the root of a tree contains a processing instruction node.

isXTag :: XmlFilterSource

test whether the root of a tree contains a tag node.

isXAttr :: XmlFilterSource

test whether the root of a tree contains an attribute node.

isAttr :: String -> XmlFilterSource

test whether the root of a tree is an attribute node for a given attribute name

isNsAttr :: String -> String -> XmlFilterSource

namespace aware test whether the tree contains an attribute node. Parameters are the local part of the atribute name and the namespace. Only usable after namespace propagation.

see also: isNsTag, isAttr, hasNsAttr

isOfAttr :: (AttrName -> Bool) -> XmlFilterSource

general test for an attribute name

isXText :: XmlFilterSource

test whether the root of a tree contains a text node.

isText :: String -> XmlFilterSource

test whether the root of a tree contains a special text.

isOfText :: (String -> Bool) -> XmlFilterSource

test whether the root of a tree contains a text node with a special property

isWhiteSpace :: XmlFilterSource

test whether the root of a tree contains a text node only with whitespace.

isDoctype :: XmlFilterSource

test whether the root of a tree contains a DOCTYPE DTD part.

isAttlist :: XmlFilterSource

test whether the root of a tree contains an ATTLIST DTD part.

isElement :: XmlFilterSource

test whether the root of a tree contains an ELEMENT DTD part.

isEntity :: XmlFilterSource

test whether the root of a tree contains an ENTITY DTD part.

isPeRef :: XmlFilterSource

test whether the root of a tree contains a parameter ENTITY reference.

isDTDName :: XmlFilterSource

test whether the root of a tree contains a DTD name part.

isCondSect :: XmlFilterSource

test whether the root of a tree contains a conditional section DTD part.

isParameterEntity :: XmlFilterSource

test whether the root of a tree contains a parameter entity declaration.

isNotation :: XmlFilterSource

test whether the root of a tree contains a NOTATION DTD part.

isWarning :: XmlFilterSource

test whether the root of a tree contains an error node for a warning.

isError :: XmlFilterSource

test whether the root of a tree contains an error node for an error.

isFatalError :: XmlFilterSource

test whether the root of a tree contains an error node for a fatal error.

mkXTag :: String -> XmlFilter -> XmlFilter -> XmlFilterSource

constructor filter for a tag node. a new tree is constructed. the attributes and the children are computed by applying the aproprate filter to the input tree

  • 1.parameter n : the tag name
  • 2.parameter af : the filter for the attribute list
  • 3.parameter cf : the filter for the children
  • returns : the constructor filter

mkQTag :: QName -> XmlFilter -> XmlFilter -> XmlFilterSource

Version with qualified names of mkXTag

mkXNsTag :: String -> String -> XmlFilter -> XmlFilter -> XmlFilterSource

constructor filter for a tag node. a new tree is constructed. the attributes and the children are computed by applying the aproprate filter to the input tree

  • 1.parameter n : the tag name in form of prefix:localpart
  • 2.parameter ns: the namespace uri
  • 3.parameter af : the filter for the attribute list
  • 4.parameter cf : the filter for the children
  • returns : the constructor filter

mkXAttr :: String -> XmlFilter -> XmlFilterSource

filter for attribute construction. a new tree with attribute name and a value computed by a filter is build.

mkQAttr :: QName -> XmlFilter -> XmlFilterSource

Qualified version mkXAttr

mkXNsAttr :: String -> String -> XmlFilter -> XmlFilterSource

filter for attribute construction. a new tree with attribute name and namespace and a value computed by a filter is build.

mkXText :: String -> XmlFilterSource

constructor filter for a text node. a new tree is constructed. the input tree is ignored.

mkXCharRef :: Int -> XmlFilterSource

constructor filter for a character reference node. a new tree is constructed. the input tree is ignored.

mkXEntityRef :: String -> XmlFilterSource

constructor filter for an entity reference node. a new tree is constructed. the input tree is ignored.

mkXCmt :: XmlFilter -> XmlFilterSource

constructor filter for a comment node. a new tree is constructed. the xml string representation of the filter result forms the comment

mkXDTD :: DTDElem -> Attributes -> XmlTrees -> XmlFilterSource

constructor filter for a DTD part. a new tree is constructed. the input tree is ignored.

mkXCdata :: XmlFilter -> XmlFilterSource

constructor filter for a CDATA section node. a new tree is constructed. the input tree is ignored.

mkXPi :: String -> XmlFilter -> XmlFilterSource

constructor filter for a processing instruction a new tree is constructed from the text representation of the input tree

mkXError :: Int -> String -> XmlFilterSource

constructor filter for an error message node. a new tree is constructed. the input tree is ignored.

getName :: XmlFilterSource

filter for selecting the name of a tag node, an attribute node or a pi node. Result of the filter is a single element list with a text node or the empty list

getAttrl :: XmlFilterSource

filter for selecting the attibute list

getValue :: String -> XmlFilterSource

filter for selecting the value of an attribute in a tag node. Result of the filter is a single element list with a text node or the empty list

see also : hasValue, getNsValue

getNsValue :: String -> String -> XmlFilterSource

filter for selecting the value of an attribute with namespace in a tag node. Result of the filter is a single element list with a text node or the empty list

see also : getValue, isNsAttr

getDTDValue :: String -> XmlFilterSource

filter for selecting an attribute of a DTD node. Result of the filter is a single element list with a text node or the empty list

getXCmt :: XmlFilterSource

filter for selecting content of a comment. Result of the filter is a single element list with a text node or the empty list

getXCdata :: XmlFilterSource

filter for selecting the CDATA content. Result of the filter is a single element list with a text node or the empty list

replaceQName :: String -> XmlFilterSource

edit filter for changing the name of a tag node, an attribute or a pi. result of the filter is a single element list with a tag node or the empty list

modifyText :: (String -> String) -> XmlFilterSource

edit filter for changing the text of a text node. result of the filter is a single element list with a text node or the empty list

example for editing all text nodes of a tree with an edit function f:

processBottomUp (modifyText f `when` isXText)

modifyQName :: (TagName -> TagName) -> XmlFilterSource

edit filter for changing the name of a tag node. result of the filter is a single element list with a text node or the empty list

processAttrl :: XmlSFilter -> XmlFilterSource

process the attribute list of a tag node with a tree list filter. for other trees this filter acts like none

processAttr :: XmlFilter -> XmlFilterSource

elementwise processing of the attributes of a tag. for other trees this filter acts like none

see also : processAttrl

replaceAttrl :: XmlTrees -> XmlFilterSource

replace an attribute list to be renamed when replaceAttrl is eliminated

del1Attr :: String -> XmlFilterSource

delete an attribute from the attribute list of a tag tree

add1Attr :: XmlTree -> XmlFilterSource

add an attribute to the attribute list of a tag. If the attribute already exists, it's substituted,

see also: sattr, +=

addAttrl :: XmlFilter -> XmlFilterSource

adds an attribute list computed by a filter, uses add1Attr.

see also: +=

addAttr :: String -> String -> XmlFilterSource

add or change an attribute with a given string as value for a XTag or XPi tree, uses add1Attr.

addAttrInt :: String -> Int -> XmlFilterSource

add or change an attribute with an Int value. uses addAttr.

modifyAttr :: String -> (String -> String) -> XmlFilterSource

edit filter for changing the value of an attribute in a tag node. result of the filter is a single element list with the tag node or the empty list.

  • 1.parameter n : the name of the attribute
  • 2.parameter f : the edit function for the attribute value
  • returns : the edit filter

addDTDAttr :: String -> String -> XmlFilterSource

add or change an attribute of a DTD tree

(+=) :: XmlFilter -> XmlFilter -> XmlFilterSource

convenient function for tag node tree construction

infixl 7

filter combinator for tag tree constrcution take a 1. filter for computing a tag node tree (or a whole list of tag node trees) then add all trees computed by the 2. filter to the attribute list when they represent attributes else append them to the list of children.

if the 1. filter computes a list of tag nodes, the results of the 2. filter are added to all trees

example: etag "a" += sattr "href" "#42" += txt "the answer" gives the tree <a href="#42">the answer</a>

example: ( etag "a" +++ etag "b" ) += sattr "x" "42" gives the tree <a x="42"/><b x="42"/>

see also : etag, tag, add1Attr, modifyChildren, ++=

(++=) :: XmlFilter -> [XmlFilter] -> XmlFilterSource

convenient filter function adding a whole list of trees, just for not writing to many ( ... ).

infixl 7

 f ++= gl  == f += cat gl

see also : +=

valueOf :: String -> XmlTree -> StringSource

combination of getValue and conversion into a String

intValueOf :: String -> XmlTree -> IntSource

combination of getValue and conversion to a Int

tag :: String -> [XmlFilter] -> [XmlFilter] -> XmlFilterSource

variant of mkXTag with a list of filters for the attributes and a list of filters for the children. this variant leads to a more readable source for a complicated construction filter than the simple solution with a combination of mkXTag and cat.

see also : mkXTag, stag, etag, cat, +=

stag :: String -> [XmlFilter] -> XmlFilterSource

variant of tag, useful for tags without attributes and with a list of filters for constructing the children

see also : mkXTag, tag, etag, cat, +=

atag :: String -> [XmlFilter] -> XmlFilterSource

variant of tag, useful for tags with attributes but without children

see also : mkXTag, tag, stag, etag, cat

etag :: String -> XmlFilterSource

Short cut for empty tags without attributes

see also : tag, atag, stag, mkXTag and +=

qetag :: QName -> XmlFilterSource

Qualified version of etag

qtag :: QName -> XmlFilter -> XmlFilter -> XmlFilterSource

Alias for mkQTag

rootTag :: [XmlFilter] -> [XmlFilter] -> XmlFilterSource

filter for creating a document root node with a list of filters for the attributes and a list of filters for the document.

see also : tag

qattr :: QName -> XmlFilter -> XmlFilterSource

Alias for mkQAttr

sattr :: String -> String -> XmlFilterSource

short cut for attribute construction with string constants

set also : attr, mkXAttr and mkXText

txt :: String -> XmlFilterSource

short cut for mkXText

cmt :: String -> XmlFilterSource

short cut for simple comment the input tree is ignored

see also : mkXCmt

spi :: String -> String -> XmlFilterSource

short cut for generating simple processing instructions (spi) the input tree is ignored

spi "xyz" "abc" is equal to mkXPi "xyz" (txt "abc") (the name pi is already used in prelude)

cdata :: String -> XmlFilterSource

short cut for generating simple cdata sections, the input tree is ignored

dtd :: DTDElem -> [XmlFilter] -> [XmlFilter] -> XmlFilterSource

DTD part generation with filter for attributes and children see also: mkXDTDTree

warn :: String -> XmlFilterSource

short cut for mkXError c_warn.

see also : mkXError

err :: String -> XmlFilterSource

short cut for mkXError c_fatal.

see also : mkXError

fatal :: String -> XmlFilterSource

short cut for mkXError c_fatal.

see also : mkXError

hasOption :: String -> XmlFilterSource

check whether an option is set

reads the value of an attribute, usually applied to a document root node, and checks if the value represents True. The following strings are interpreted as true: "1", "True", "true", "yes", "Yes".