hxt-7.1: A collection of tools for processing XML with Haskell.ContentsIndex
Text.XML.HXT.DOM.TypeDefs
Description

The core data types of HDOM.

Version : $Id: TypeDefs.hs,v 1.13 20061109 20:27:42 hxml Exp $

Synopsis
module Data.AssocList
type XmlTree = NTree XNode
type XmlTrees = NTrees XNode
data XNode
= XText String
| XCharRef Int
| XEntityRef String
| XCmt String
| XCdata String
| XPi QName XmlTrees
| XTag QName XmlTrees
| XDTD DTDElem Attributes
| XAttr QName
| XError Int String
data DTDElem
= DOCTYPE
| ELEMENT
| CONTENT
| ATTLIST
| ENTITY
| PENTITY
| NOTATION
| CONDSECT
| NAME
| PEREF
type Attributes = AssocList String String
data QName = QN {
namePrefix :: String
localPart :: String
namespaceUri :: String
}
qualifiedName :: QName -> String
universalName :: QName -> String
universalUri :: QName -> String
buildUniversalName :: (String -> String -> String) -> QName -> String
mkName :: String -> QName
mkPrefixLocalPart :: String -> String -> QName
mkNsName :: String -> String -> QName
mkSNsName :: String -> QName
nullQName :: QName
equalQName :: QName -> QName -> Bool
equivQName :: QName -> QName -> Bool
equivUri :: String -> String -> Bool
equalQNameBy :: (String -> String -> Bool) -> QName -> QName -> Bool
normalizeNsUri :: String -> String
type NsEnv = AssocList String String
c_ok :: Int
c_warn :: Int
c_err :: Int
c_fatal :: Int
data XmlNodeSet = XNS {
thisNode :: Bool
attrNodes :: [QName]
childNodes :: ChildNodes
}
type ChildNodes = [(Int, XmlNodeSet)]
Documentation
module Data.AssocList
type XmlTree = NTree XNode
Node of xml tree representation
type XmlTrees = NTrees XNode
List of nodes of xml tree representation
data XNode
Represents elements
Constructors
XText Stringordinary text (leaf)
XCharRef Intcharacter reference (leaf)
XEntityRef Stringentity reference (leaf)
XCmt Stringcomment (leaf)
XCdata StringCDATA section (leaf)
XPi QName XmlTreesProcessing Instr with qualified name (leaf) with list of attributes. If tag name is xml, attributs are "version", "encoding", "standalone", else attribute list is empty, content is a text child node
XTag QName XmlTreestag with qualified name and list of attributes (inner node or leaf)
XDTD DTDElem AttributesDTD element with assoc list for dtd element features
XAttr QNameattribute with qualified name, the attribute value is stored in children
XError Int Stringerror message with level and text
show/hide Instances
data DTDElem
Represents a DTD element
Constructors
DOCTYPEattr: name, system, public, XDTD elems as children
ELEMENT

attr: name, kind

name: element name

kind: "EMPTY" | "ANY" | "#PCDATA" | children | mixed

CONTENT

element content

attr: kind, modifier

modifier: "" | "?" | "*" | "+"

kind: seq | choice

ATTLIST

attributes: name - name of element

value - name of attribute

type: "CDATA" | "ID" | "IDREF" | "IDREFS" | "ENTITY" | "ENTITIES" |

"NMTOKEN" | "NMTOKENS" |"NOTATION" | "ENUMTYPE"

kind: "IMPLIED" | "DEFAULT"

ENTITYfor entity declarations
PENTITYfor parameter entity declarations
NOTATIONfor notations
CONDSECT

for INCLUDEs, IGNOREs and peRefs: attr: type

type = INCLUDE, IGNORE or %...;

NAME

attr: name

for lists of names in notation types or nmtokens in enumeration types

PEREFfor Parameter Entity References in DTDs
show/hide Instances
type Attributes = AssocList String String

Attribute list

used for storing option lists and features of DTD parts

data QName

Namespace support for element and attribute names.

A qualified name consists of a name prefix, a local name and a namespace uri. All modules, which are not namespace aware, use only the localPart component. When dealing with namespaces, the document tree must be processed by propagateNamespaces to split names of structure "prefix:localPart" and label the name with the apropriate namespace uri

Constructors
QN
namePrefix :: Stringthe name prefix part of a qualified name "namePrefix:localPart"
localPart :: Stringthe local part of a qualified name "namePrefix:localPart"
namespaceUri :: Stringthe associated namespace uri
show/hide Instances
qualifiedName :: QName -> String
builds the full name "prefix:localPart", if prefix is not null, else the local part is the result
universalName :: QName -> String
builds the "universal" name, that is the namespace uri surrounded with "{" and "}" followed by the local part (specialisation of buildUniversalName)
universalUri :: QName -> String
builds an "universal" uri, that is the namespace uri followed by the local part. This is usefull for RDF applications, where the subject, predicate and object often are concatenated from namespace uri and local part (specialisation of buildUniversalName)
buildUniversalName :: (String -> String -> String) -> QName -> String
builds a string from the namespace uri and the local part. If the namespace uri is empty, the local part is returned, else namespace uri and local part are combined with the combining function given by the first parameter
mkName :: String -> QName
constructs a simple, namespace unaware name, namePrefix and namespaceUri are set to the empty string.
mkPrefixLocalPart :: String -> String -> QName

constructs a simple name, with prefix and localPart but without a namespace uri.

see also mkName, mkNsName, mkSNsName

mkNsName :: String -> String -> QName

constructs a simple, namespace aware name, with prefix:localPart as first parameter, namspace uri as second.

see also mkName, mkPrefixLocalPart

mkSNsName :: String -> QName

constructs a simple name, with prefix:localPart as 1 parameter, with empty namspace uri, same as 'mkPrefixLocalPart, but with a single parameter

see also mkNsName, mkPrefixLocalPart

nullQName :: QName
Empty QName
equalQName :: QName -> QName -> Bool
Equality of QNames: Two QNames are equal, if the local parts are equal and the namespace URIs are equal. The comparison works with and without namespace propagation. If namespaces have been propagated, the name is split into prefix and local part and the namespace uri is set. In this case the prefix is not significant for equality test. If namespaces have not been propagated, the local part contains the full name, prefix and namespace URI are empty. The full name (prefix and local part) is used for comparison.
equivQName :: QName -> QName -> Bool
Equivalent QNames are defined as follows: The URIs are normalized before comparison. Comparison is done with equalQNameBy and equivUri
equivUri :: String -> String -> Bool
Comparison of normalized namespace URIs using normalizeNsUri
equalQNameBy :: (String -> String -> Bool) -> QName -> QName -> Bool
Sometimes a weaker equality relation than equalQName is appropriate, e.g no case significance in names, ... a name normalization function can be applied to the strings before comparing. Called by equalQName and equivQName
normalizeNsUri :: String -> String
Normalization of URIs: Normalization is done by conversion into lowercase letters. A trailing "/" is ignored
type NsEnv = AssocList String String
Type for the namespace association list, used when propagating namespaces by modifying the QName values in a tree
c_ok :: Int
no error, everything is ok
c_warn :: Int
Error level for XError, type warning
c_err :: Int
Error level for XError, type error
c_fatal :: Int
Error level for XError, type fatal error
data XmlNodeSet

data type for representing a set of nodes as a tree structure

this structure is e.g. used to repesent the result of an XPath query such that the selected nodes can be processed or selected later in processing a document tree

Constructors
XNS
thisNode :: Boolis this node part of the set ?
attrNodes :: [QName]the set of attribute nodes
childNodes :: ChildNodesthe set of child nodes, a list of pairs of index and node set
show/hide Instances
type ChildNodes = [(Int, XmlNodeSet)]
Produced by Haddock version 0.8