hxt-9.3.1.10: A collection of tools for processing XML with Haskell.

CopyrightCopyright (C) 2011 Uwe Schmidt
LicenseMIT
MaintainerUwe Schmidt (uwe@fh-wedel.de)
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Text.XML.HXT.Arrow.XmlArrow

Description

Basic arrows for processing XML documents

All arrows use IO and a global state for options, errorhandling, ...

Synopsis

Documentation

class (Arrow a, ArrowList a, ArrowTree a) => ArrowXml a where Source

Arrows for processing XmlTrees

These arrows can be grouped into predicates, selectors, constructors, and transformers.

All predicates (tests) act like none for failure and this for success. A logical and can be formed by a1 >>> a2 , a locical or by a1 <+> a2 .

Selector arrows will fail, when applied to wrong input, e.g. selecting the text of a node with getText will fail when applied to a none text node.

Edit arrows will remain the input unchanged, when applied to wrong argument, e.g. editing the content of a text node with changeText applied to an element node will return the unchanged element node.

Minimal complete definition

Nothing

Methods

isText :: a XmlTree XmlTree Source

test for text nodes

isBlob :: a XmlTree XmlTree Source

isCharRef :: a XmlTree XmlTree Source

test for char reference, used during parsing

isEntityRef :: a XmlTree XmlTree Source

test for entity reference, used during parsing

isCmt :: a XmlTree XmlTree Source

test for comment

isCdata :: a XmlTree XmlTree Source

test for CDATA section, used during parsing

isPi :: a XmlTree XmlTree Source

test for processing instruction

isXmlPi :: a XmlTree XmlTree Source

test for processing instruction <?xml ...>

isElem :: a XmlTree XmlTree Source

test for element

isDTD :: a XmlTree XmlTree Source

test for DTD part, used during parsing

isAttr :: a XmlTree XmlTree Source

test for attribute tree

isError :: a XmlTree XmlTree Source

test for error message

isRoot :: a XmlTree XmlTree Source

test for root node (element with name "/")

hasText :: (String -> Bool) -> a XmlTree XmlTree Source

test for text nodes with text, for which a predicate holds

example: hasText (all (`elem` " \t\n")) check for text nodes with only whitespace content

isWhiteSpace :: a XmlTree XmlTree Source

test for text nodes with only white space

implemented with hasTest

hasNameWith :: (QName -> Bool) -> a XmlTree XmlTree Source

test whether a node (element, attribute, pi) has a name with a special property

hasQName :: QName -> a XmlTree XmlTree Source

test whether a node (element, attribute, pi) has a specific qualified name useful only after namespace propagation

hasName :: String -> a XmlTree XmlTree Source

test whether a node has a specific name (prefix:localPart ore localPart), generally useful, even without namespace handling

hasLocalPart :: String -> a XmlTree XmlTree Source

test whether a node has a specific name as local part, useful only after namespace propagation

hasNamePrefix :: String -> a XmlTree XmlTree Source

test whether a node has a specific name prefix, useful only after namespace propagation

hasNamespaceUri :: String -> a XmlTree XmlTree Source

test whether a node has a specific namespace URI useful only after namespace propagation

hasAttr :: String -> a XmlTree XmlTree Source

test whether an element node has an attribute node with a specific name

hasQAttr :: QName -> a XmlTree XmlTree Source

test whether an element node has an attribute node with a specific qualified name

hasAttrValue :: String -> (String -> Bool) -> a XmlTree XmlTree Source

test whether an element node has an attribute with a specific value

hasQAttrValue :: QName -> (String -> Bool) -> a XmlTree XmlTree Source

test whether an element node has an attribute with a qualified name and a specific value

mkText :: a String XmlTree Source

text node construction arrow

mkBlob :: a Blob XmlTree Source

blob node construction arrow

mkCharRef :: a Int XmlTree Source

char reference construction arrow, useful for document output

mkEntityRef :: a String XmlTree Source

entity reference construction arrow, useful for document output

mkCmt :: a String XmlTree Source

comment node construction, useful for document output

mkCdata :: a String XmlTree Source

CDATA construction, useful for document output

mkError :: Int -> a String XmlTree Source

error node construction, useful only internally

mkElement :: QName -> a n XmlTree -> a n XmlTree -> a n XmlTree Source

element construction: | the attributes and the content of the element are computed by applying arrows to the input

mkAttr :: QName -> a n XmlTree -> a n XmlTree Source

attribute node construction: | the attribute value is computed by applying an arrow to the input

mkPi :: QName -> a n XmlTree -> a n XmlTree Source

processing instruction construction: | the content of the processing instruction is computed by applying an arrow to the input

mkqelem :: QName -> [a n XmlTree] -> [a n XmlTree] -> a n XmlTree Source

convenient arrow for element construction, more comfortable variant of mkElement

example for simplifying mkElement :

mkElement qn (a1 <+> ... <+> ai) (c1 <+> ... <+> cj)

equals

mkqelem qn [a1,...,ai] [c1,...,cj]

mkelem :: String -> [a n XmlTree] -> [a n XmlTree] -> a n XmlTree Source

convenient arrow for element construction with strings instead of qualified names as element names, see also mkElement and mkelem

aelem :: String -> [a n XmlTree] -> a n XmlTree Source

convenient arrow for element constrution with attributes but without content, simple variant of mkelem and mkElement

selem :: String -> [a n XmlTree] -> a n XmlTree Source

convenient arrow for simple element constrution without attributes, simple variant of mkelem and mkElement

eelem :: String -> a n XmlTree Source

convenient arrow for constrution of empty elements without attributes, simple variant of mkelem and mkElement

root :: [a n XmlTree] -> [a n XmlTree] -> a n XmlTree Source

construction of an element node with name "/" for document roots

qattr :: QName -> a n XmlTree -> a n XmlTree Source

alias for mkAttr

attr :: String -> a n XmlTree -> a n XmlTree Source

convenient arrow for attribute constrution, simple variant of mkAttr

txt :: String -> a n XmlTree Source

constant arrow for text nodes

blb :: Blob -> a n XmlTree Source

constant arrow for blob nodes

charRef :: Int -> a n XmlTree Source

constant arrow for char reference nodes

entityRef :: String -> a n XmlTree Source

constant arrow for entity reference nodes

cmt :: String -> a n XmlTree Source

constant arrow for comment

warn :: String -> a n XmlTree Source

constant arrow for warning

err :: String -> a n XmlTree Source

constant arrow for errors

fatal :: String -> a n XmlTree Source

constant arrow for fatal errors

spi :: String -> String -> a n XmlTree Source

constant arrow for simple processing instructions, see mkPi

sqattr :: QName -> String -> a n XmlTree Source

constant arrow for attribute nodes, attribute name is a qualified name and value is a text, | see also mkAttr, qattr, attr

sattr :: String -> String -> a n XmlTree Source

constant arrow for attribute nodes, attribute name and value are | given by parameters, see mkAttr

getText :: a XmlTree String Source

select the text of a text node

getCharRef :: a XmlTree Int Source

select the value of a char reference

getEntityRef :: a XmlTree String Source

select the name of a entity reference node

getCmt :: a XmlTree String Source

select the comment of a comment node

getCdata :: a XmlTree String Source

select the content of a CDATA node

getPiName :: a XmlTree QName Source

select the name of a processing instruction

getPiContent :: a XmlTree XmlTree Source

select the content of a processing instruction

getElemName :: a XmlTree QName Source

select the name of an element node

getAttrl :: a XmlTree XmlTree Source

select the attribute list of an element node

getDTDPart :: a XmlTree DTDElem Source

select the DTD type of a DTD node

getDTDAttrl :: a XmlTree Attributes Source

select the DTD attributes of a DTD node

getAttrName :: a XmlTree QName Source

select the name of an attribute

getErrorLevel :: a XmlTree Int Source

select the error level (c_warn, c_err, c_fatal) from an error node

getErrorMsg :: a XmlTree String Source

select the error message from an error node

getQName :: a XmlTree QName Source

select the qualified name from an element, attribute or pi

getName :: a XmlTree String Source

select the prefix:localPart or localPart from an element, attribute or pi

getUniversalName :: a XmlTree String Source

select the univeral name ({namespace URI} ++ localPart)

getUniversalUri :: a XmlTree String Source

select the univeral name (namespace URI ++ localPart)

getLocalPart :: a XmlTree String Source

select the local part

getNamePrefix :: a XmlTree String Source

select the name prefix

getNamespaceUri :: a XmlTree String Source

select the namespace URI

getAttrValue :: String -> a XmlTree String Source

select the value of an attribute of an element node, always succeeds with empty string as default value ""

getAttrValue0 :: String -> a XmlTree String Source

like getAttrValue, but fails if the attribute does not exist

getQAttrValue :: QName -> a XmlTree String Source

like getAttrValue, but select the value of an attribute given by a qualified name, always succeeds with empty string as default value ""

getQAttrValue0 :: QName -> a XmlTree String Source

like getQAttrValue, but fails if attribute does not exist

changeText :: (String -> String) -> a XmlTree XmlTree Source

edit the string of a text node

changeBlob :: (Blob -> Blob) -> a XmlTree XmlTree Source

edit the blob of a blob node

changeCmt :: (String -> String) -> a XmlTree XmlTree Source

edit the comment string of a comment node

changeQName :: (QName -> QName) -> a XmlTree XmlTree Source

edit an element-, attribute- or pi- name

changeElemName :: (QName -> QName) -> a XmlTree XmlTree Source

edit an element name

changeAttrName :: (QName -> QName) -> a XmlTree XmlTree Source

edit an attribute name

changePiName :: (QName -> QName) -> a XmlTree XmlTree Source

edit a pi name

changeAttrValue :: (String -> String) -> a XmlTree XmlTree Source

edit an attribute value

changeAttrl :: (XmlTrees -> XmlTrees -> XmlTrees) -> a XmlTree XmlTree -> a XmlTree XmlTree Source

edit an attribute list of an element node

setQName :: QName -> a XmlTree XmlTree Source

replace an element, attribute or pi name

setElemName :: QName -> a XmlTree XmlTree Source

replace an element name

setAttrName :: QName -> a XmlTree XmlTree Source

replace an attribute name

setPiName :: QName -> a XmlTree XmlTree Source

replace an element name

setAttrl :: a XmlTree XmlTree -> a XmlTree XmlTree Source

replace an atribute list of an element node

addAttrl :: a XmlTree XmlTree -> a XmlTree XmlTree Source

add a list of attributes to an element

addAttr :: String -> String -> a XmlTree XmlTree Source

add (or replace) an attribute

removeAttr :: String -> a XmlTree XmlTree Source

remove an attribute

removeQAttr :: QName -> a XmlTree XmlTree Source

remove an attribute with a qualified name

processAttrl :: a XmlTree XmlTree -> a XmlTree XmlTree Source

process the attributes of an element node with an arrow

processTopDownWithAttrl :: a XmlTree XmlTree -> a XmlTree XmlTree Source

process a whole tree inclusive attribute list of element nodes see also: processTopDown

(+=) :: a b XmlTree -> a b XmlTree -> a b XmlTree infixl 7 Source

convenient op for adding attributes or children to a node

usage: tf += cf

the tf arrow computes an element node, and all trees computed by cf are added to this node, if a tree is an attribute, it is inserted in the attribute list else it is appended to the content list.

attention: do not build long content list this way because += is implemented by ++

examples:

eelem "a"
  += sattr "href" "page.html"
  += sattr "name" "here"
  += txt "look here"

is the same as

mkelem [ sattr "href" "page.html"
       , sattr "name" "here"
       ]
       [ txt "look here" ]

and results in the XML fragment: <a href="page.html" name="here">look here</a>

advantage of the += operator is, that attributes and content can be added any time step by step. if tf computes a whole list of trees, e.g. a list of "td" or "tr" elements, the attributes or content is added to all trees. useful for adding "class" or "style" attributes to table elements.

xshow :: a n XmlTree -> a n String Source

apply an arrow to the input and convert the resulting XML trees into a string representation

xshowBlob :: a n XmlTree -> a n Blob Source

apply an arrow to the input and convert the resulting XML trees into a string representation

class ArrowXml a => ArrowDTD a where Source

Document Type Definition arrows

These are separated, because they are not needed for document processing, only when processing the DTD, e.g. for generating access funtions for the toolbox from a DTD (se example DTDtoHaskell in the examples directory)

Minimal complete definition

Nothing