Portability | portable |
---|---|
Stability | experimental |
Maintainer | Uwe Schmidt (uwe@fh-wedel.de) |
Safe Haskell | None |
Basic arrows for processing XML documents
All arrows use IO and a global state for options, errorhandling, ...
- class (Arrow a, ArrowList a, ArrowTree a) => ArrowXml a where
- isText :: a XmlTree XmlTree
- isBlob :: a XmlTree XmlTree
- isCharRef :: a XmlTree XmlTree
- isEntityRef :: a XmlTree XmlTree
- isCmt :: a XmlTree XmlTree
- isCdata :: a XmlTree XmlTree
- isPi :: a XmlTree XmlTree
- isXmlPi :: a XmlTree XmlTree
- isElem :: a XmlTree XmlTree
- isDTD :: a XmlTree XmlTree
- isAttr :: a XmlTree XmlTree
- isError :: a XmlTree XmlTree
- isRoot :: a XmlTree XmlTree
- hasText :: (String -> Bool) -> a XmlTree XmlTree
- isWhiteSpace :: a XmlTree XmlTree
- hasNameWith :: (QName -> Bool) -> a XmlTree XmlTree
- hasQName :: QName -> a XmlTree XmlTree
- hasName :: String -> a XmlTree XmlTree
- hasLocalPart :: String -> a XmlTree XmlTree
- hasNamePrefix :: String -> a XmlTree XmlTree
- hasNamespaceUri :: String -> a XmlTree XmlTree
- hasAttr :: String -> a XmlTree XmlTree
- hasQAttr :: QName -> a XmlTree XmlTree
- hasAttrValue :: String -> (String -> Bool) -> a XmlTree XmlTree
- hasQAttrValue :: QName -> (String -> Bool) -> a XmlTree XmlTree
- mkText :: a String XmlTree
- mkBlob :: a Blob XmlTree
- mkCharRef :: a Int XmlTree
- mkEntityRef :: a String XmlTree
- mkCmt :: a String XmlTree
- mkCdata :: a String XmlTree
- mkError :: Int -> a String XmlTree
- mkElement :: QName -> a n XmlTree -> a n XmlTree -> a n XmlTree
- mkAttr :: QName -> a n XmlTree -> a n XmlTree
- mkPi :: QName -> a n XmlTree -> a n XmlTree
- mkqelem :: QName -> [a n XmlTree] -> [a n XmlTree] -> a n XmlTree
- mkelem :: String -> [a n XmlTree] -> [a n XmlTree] -> a n XmlTree
- aelem :: String -> [a n XmlTree] -> a n XmlTree
- selem :: String -> [a n XmlTree] -> a n XmlTree
- eelem :: String -> a n XmlTree
- root :: [a n XmlTree] -> [a n XmlTree] -> a n XmlTree
- qattr :: QName -> a n XmlTree -> a n XmlTree
- attr :: String -> a n XmlTree -> a n XmlTree
- txt :: String -> a n XmlTree
- blb :: Blob -> a n XmlTree
- charRef :: Int -> a n XmlTree
- entityRef :: String -> a n XmlTree
- cmt :: String -> a n XmlTree
- warn :: String -> a n XmlTree
- err :: String -> a n XmlTree
- fatal :: String -> a n XmlTree
- spi :: String -> String -> a n XmlTree
- sqattr :: QName -> String -> a n XmlTree
- sattr :: String -> String -> a n XmlTree
- getText :: a XmlTree String
- getCharRef :: a XmlTree Int
- getEntityRef :: a XmlTree String
- getCmt :: a XmlTree String
- getCdata :: a XmlTree String
- getPiName :: a XmlTree QName
- getPiContent :: a XmlTree XmlTree
- getElemName :: a XmlTree QName
- getAttrl :: a XmlTree XmlTree
- getDTDPart :: a XmlTree DTDElem
- getDTDAttrl :: a XmlTree Attributes
- getAttrName :: a XmlTree QName
- getErrorLevel :: a XmlTree Int
- getErrorMsg :: a XmlTree String
- getQName :: a XmlTree QName
- getName :: a XmlTree String
- getUniversalName :: a XmlTree String
- getUniversalUri :: a XmlTree String
- getLocalPart :: a XmlTree String
- getNamePrefix :: a XmlTree String
- getNamespaceUri :: a XmlTree String
- getAttrValue :: String -> a XmlTree String
- getAttrValue0 :: String -> a XmlTree String
- getQAttrValue :: QName -> a XmlTree String
- getQAttrValue0 :: QName -> a XmlTree String
- changeText :: (String -> String) -> a XmlTree XmlTree
- changeBlob :: (Blob -> Blob) -> a XmlTree XmlTree
- changeCmt :: (String -> String) -> a XmlTree XmlTree
- changeQName :: (QName -> QName) -> a XmlTree XmlTree
- changeElemName :: (QName -> QName) -> a XmlTree XmlTree
- changeAttrName :: (QName -> QName) -> a XmlTree XmlTree
- changePiName :: (QName -> QName) -> a XmlTree XmlTree
- changeAttrValue :: (String -> String) -> a XmlTree XmlTree
- changeAttrl :: (XmlTrees -> XmlTrees -> XmlTrees) -> a XmlTree XmlTree -> a XmlTree XmlTree
- setQName :: QName -> a XmlTree XmlTree
- setElemName :: QName -> a XmlTree XmlTree
- setAttrName :: QName -> a XmlTree XmlTree
- setPiName :: QName -> a XmlTree XmlTree
- setAttrl :: a XmlTree XmlTree -> a XmlTree XmlTree
- addAttrl :: a XmlTree XmlTree -> a XmlTree XmlTree
- addAttr :: String -> String -> a XmlTree XmlTree
- removeAttr :: String -> a XmlTree XmlTree
- removeQAttr :: QName -> a XmlTree XmlTree
- processAttrl :: a XmlTree XmlTree -> a XmlTree XmlTree
- processTopDownWithAttrl :: a XmlTree XmlTree -> a XmlTree XmlTree
- (+=) :: a b XmlTree -> a b XmlTree -> a b XmlTree
- xshow :: a n XmlTree -> a n String
- xshowBlob :: a n XmlTree -> a n Blob
- class ArrowXml a => ArrowDTD a where
- isDTDDoctype :: a XmlTree XmlTree
- isDTDElement :: a XmlTree XmlTree
- isDTDContent :: a XmlTree XmlTree
- isDTDAttlist :: a XmlTree XmlTree
- isDTDEntity :: a XmlTree XmlTree
- isDTDPEntity :: a XmlTree XmlTree
- isDTDNotation :: a XmlTree XmlTree
- isDTDCondSect :: a XmlTree XmlTree
- isDTDName :: a XmlTree XmlTree
- isDTDPERef :: a XmlTree XmlTree
- hasDTDAttr :: String -> a XmlTree XmlTree
- getDTDAttrValue :: String -> a XmlTree String
- setDTDAttrValue :: String -> String -> a XmlTree XmlTree
- mkDTDElem :: DTDElem -> Attributes -> a n XmlTree -> a n XmlTree
- mkDTDDoctype :: Attributes -> a n XmlTree -> a n XmlTree
- mkDTDElement :: Attributes -> a n XmlTree
- mkDTDEntity :: Attributes -> a n XmlTree
- mkDTDPEntity :: Attributes -> a n XmlTree
Documentation
class (Arrow a, ArrowList a, ArrowTree a) => ArrowXml a whereSource
Arrows for processing XmlTree
s
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.
isText :: a XmlTree XmlTreeSource
test for text nodes
isBlob :: a XmlTree XmlTreeSource
isCharRef :: a XmlTree XmlTreeSource
test for char reference, used during parsing
isEntityRef :: a XmlTree XmlTreeSource
test for entity reference, used during parsing
isCmt :: a XmlTree XmlTreeSource
test for comment
isCdata :: a XmlTree XmlTreeSource
test for CDATA section, used during parsing
isPi :: a XmlTree XmlTreeSource
test for processing instruction
isXmlPi :: a XmlTree XmlTreeSource
test for processing instruction <?xml ...>
isElem :: a XmlTree XmlTreeSource
test for element
isDTD :: a XmlTree XmlTreeSource
test for DTD part, used during parsing
isAttr :: a XmlTree XmlTreeSource
test for attribute tree
isError :: a XmlTree XmlTreeSource
test for error message
isRoot :: a XmlTree XmlTreeSource
test for root node (element with name "/")
hasText :: (String -> Bool) -> a XmlTree XmlTreeSource
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 XmlTreeSource
test for text nodes with only white space
implemented with hasTest
hasNameWith :: (QName -> Bool) -> a XmlTree XmlTreeSource
test whether a node (element, attribute, pi) has a name with a special property
hasQName :: QName -> a XmlTree XmlTreeSource
test whether a node (element, attribute, pi) has a specific qualified name useful only after namespace propagation
hasName :: String -> a XmlTree XmlTreeSource
test whether a node has a specific name (prefix:localPart ore localPart), generally useful, even without namespace handling
hasLocalPart :: String -> a XmlTree XmlTreeSource
test whether a node has a specific name as local part, useful only after namespace propagation
hasNamePrefix :: String -> a XmlTree XmlTreeSource
test whether a node has a specific name prefix, useful only after namespace propagation
hasNamespaceUri :: String -> a XmlTree XmlTreeSource
test whether a node has a specific namespace URI useful only after namespace propagation
hasAttr :: String -> a XmlTree XmlTreeSource
test whether an element node has an attribute node with a specific name
hasQAttr :: QName -> a XmlTree XmlTreeSource
test whether an element node has an attribute node with a specific qualified name
hasAttrValue :: String -> (String -> Bool) -> a XmlTree XmlTreeSource
test whether an element node has an attribute with a specific value
hasQAttrValue :: QName -> (String -> Bool) -> a XmlTree XmlTreeSource
test whether an element node has an attribute with a qualified name and a specific value
mkText :: a String XmlTreeSource
text node construction arrow
mkBlob :: a Blob XmlTreeSource
blob node construction arrow
mkCharRef :: a Int XmlTreeSource
char reference construction arrow, useful for document output
mkEntityRef :: a String XmlTreeSource
entity reference construction arrow, useful for document output
mkCmt :: a String XmlTreeSource
comment node construction, useful for document output
mkCdata :: a String XmlTreeSource
CDATA construction, useful for document output
mkError :: Int -> a String XmlTreeSource
error node construction, useful only internally
mkElement :: QName -> a n XmlTree -> a n XmlTree -> a n XmlTreeSource
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 XmlTreeSource
attribute node construction: | the attribute value is computed by applying an arrow to the input
mkPi :: QName -> a n XmlTree -> a n XmlTreeSource
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 XmlTreeSource
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 XmlTreeSource
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 XmlTreeSource
convenient arrow for element constrution with attributes but without content, simple variant of mkelem
and mkElement
selem :: String -> [a n XmlTree] -> a n XmlTreeSource
convenient arrow for simple element constrution without attributes, simple variant of mkelem
and mkElement
eelem :: String -> a n XmlTreeSource
convenient arrow for constrution of empty elements without attributes, simple variant of mkelem
and mkElement
root :: [a n XmlTree] -> [a n XmlTree] -> a n XmlTreeSource
construction of an element node with name "/" for document roots
qattr :: QName -> a n XmlTree -> a n XmlTreeSource
alias for mkAttr
attr :: String -> a n XmlTree -> a n XmlTreeSource
convenient arrow for attribute constrution, simple variant of mkAttr
txt :: String -> a n XmlTreeSource
constant arrow for text nodes
blb :: Blob -> a n XmlTreeSource
constant arrow for blob nodes
charRef :: Int -> a n XmlTreeSource
constant arrow for char reference nodes
entityRef :: String -> a n XmlTreeSource
constant arrow for entity reference nodes
cmt :: String -> a n XmlTreeSource
constant arrow for comment
warn :: String -> a n XmlTreeSource
constant arrow for warning
err :: String -> a n XmlTreeSource
constant arrow for errors
fatal :: String -> a n XmlTreeSource
constant arrow for fatal errors
spi :: String -> String -> a n XmlTreeSource
constant arrow for simple processing instructions, see mkPi
sqattr :: QName -> String -> a n XmlTreeSource
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 XmlTreeSource
constant arrow for attribute nodes, attribute name and value are
| given by parameters, see mkAttr
getText :: a XmlTree StringSource
select the text of a text node
getCharRef :: a XmlTree IntSource
select the value of a char reference
getEntityRef :: a XmlTree StringSource
select the name of a entity reference node
getCmt :: a XmlTree StringSource
select the comment of a comment node
getCdata :: a XmlTree StringSource
select the content of a CDATA node
getPiName :: a XmlTree QNameSource
select the name of a processing instruction
getPiContent :: a XmlTree XmlTreeSource
select the content of a processing instruction
getElemName :: a XmlTree QNameSource
select the name of an element node
getAttrl :: a XmlTree XmlTreeSource
select the attribute list of an element node
getDTDPart :: a XmlTree DTDElemSource
select the DTD type of a DTD node
getDTDAttrl :: a XmlTree AttributesSource
select the DTD attributes of a DTD node
getAttrName :: a XmlTree QNameSource
select the name of an attribute
getErrorLevel :: a XmlTree IntSource
select the error level (c_warn, c_err, c_fatal) from an error node
getErrorMsg :: a XmlTree StringSource
select the error message from an error node
getQName :: a XmlTree QNameSource
select the qualified name from an element, attribute or pi
getName :: a XmlTree StringSource
select the prefix:localPart or localPart from an element, attribute or pi
getUniversalName :: a XmlTree StringSource
select the univeral name ({namespace URI} ++ localPart)
getUniversalUri :: a XmlTree StringSource
select the univeral name (namespace URI ++ localPart)
getLocalPart :: a XmlTree StringSource
select the local part
getNamePrefix :: a XmlTree StringSource
select the name prefix
getNamespaceUri :: a XmlTree StringSource
select the namespace URI
getAttrValue :: String -> a XmlTree StringSource
select the value of an attribute of an element node, always succeeds with empty string as default value ""
getAttrValue0 :: String -> a XmlTree StringSource
like getAttrValue
, but fails if the attribute does not exist
getQAttrValue :: QName -> a XmlTree StringSource
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 StringSource
like getQAttrValue
, but fails if attribute does not exist
changeText :: (String -> String) -> a XmlTree XmlTreeSource
edit the string of a text node
changeBlob :: (Blob -> Blob) -> a XmlTree XmlTreeSource
edit the blob of a blob node
changeCmt :: (String -> String) -> a XmlTree XmlTreeSource
edit the comment string of a comment node
changeQName :: (QName -> QName) -> a XmlTree XmlTreeSource
edit an element-, attribute- or pi- name
changeElemName :: (QName -> QName) -> a XmlTree XmlTreeSource
edit an element name
changeAttrName :: (QName -> QName) -> a XmlTree XmlTreeSource
edit an attribute name
changePiName :: (QName -> QName) -> a XmlTree XmlTreeSource
edit a pi name
changeAttrValue :: (String -> String) -> a XmlTree XmlTreeSource
edit an attribute value
changeAttrl :: (XmlTrees -> XmlTrees -> XmlTrees) -> a XmlTree XmlTree -> a XmlTree XmlTreeSource
edit an attribute list of an element node
setQName :: QName -> a XmlTree XmlTreeSource
replace an element, attribute or pi name
setElemName :: QName -> a XmlTree XmlTreeSource
replace an element name
setAttrName :: QName -> a XmlTree XmlTreeSource
replace an attribute name
setPiName :: QName -> a XmlTree XmlTreeSource
replace an element name
setAttrl :: a XmlTree XmlTree -> a XmlTree XmlTreeSource
replace an atribute list of an element node
addAttrl :: a XmlTree XmlTree -> a XmlTree XmlTreeSource
add a list of attributes to an element
addAttr :: String -> String -> a XmlTree XmlTreeSource
add (or replace) an attribute
removeAttr :: String -> a XmlTree XmlTreeSource
remove an attribute
removeQAttr :: QName -> a XmlTree XmlTreeSource
remove an attribute with a qualified name
processAttrl :: a XmlTree XmlTree -> a XmlTree XmlTreeSource
process the attributes of an element node with an arrow
processTopDownWithAttrl :: a XmlTree XmlTree -> a XmlTree XmlTreeSource
process a whole tree inclusive attribute list of element nodes
see also: processTopDown
(+=) :: a b XmlTree -> a b XmlTree -> a b XmlTreeSource
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 StringSource
apply an arrow to the input and convert the resulting XML trees into a string representation
xshowBlob :: a n XmlTree -> a n BlobSource
apply an arrow to the input and convert the resulting XML trees into a string representation
class ArrowXml a => ArrowDTD a whereSource
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)
isDTDDoctype :: a XmlTree XmlTreeSource
isDTDElement :: a XmlTree XmlTreeSource
isDTDContent :: a XmlTree XmlTreeSource
isDTDAttlist :: a XmlTree XmlTreeSource
isDTDEntity :: a XmlTree XmlTreeSource
isDTDPEntity :: a XmlTree XmlTreeSource
isDTDNotation :: a XmlTree XmlTreeSource
isDTDCondSect :: a XmlTree XmlTreeSource
isDTDName :: a XmlTree XmlTreeSource
isDTDPERef :: a XmlTree XmlTreeSource
hasDTDAttr :: String -> a XmlTree XmlTreeSource
getDTDAttrValue :: String -> a XmlTree StringSource
setDTDAttrValue :: String -> String -> a XmlTree XmlTreeSource
mkDTDElem :: DTDElem -> Attributes -> a n XmlTree -> a n XmlTreeSource
mkDTDDoctype :: Attributes -> a n XmlTree -> a n XmlTreeSource
mkDTDElement :: Attributes -> a n XmlTreeSource
mkDTDEntity :: Attributes -> a n XmlTreeSource
mkDTDPEntity :: Attributes -> a n XmlTreeSource