| Portability | portable | 
|---|---|
| Stability | stable | 
| Maintainer | Uwe Schmidt (uwe@fh-wedel.de) | 
Text.XML.HXT.DOM.TypeDefs
Description
The core data types of the HXT DOM.
- module Data.AssocList
 - type XmlTree = NTree XNode
 - type XmlTrees = NTrees XNode
 - data XNode
 - data DTDElem
 - type Attributes = 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)]
 - module Text.XML.HXT.DOM.QualifiedName
 
Documentation
module Data.AssocList
Represents elements
Constructors
| XText String | ordinary text (leaf)  | 
| XCharRef Int | character reference (leaf)  | 
| XEntityRef String | entity reference (leaf)  | 
| XCmt String | comment (leaf)  | 
| XCdata String | CDATA section (leaf)  | 
| XPi QName XmlTrees | Processing 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 XmlTrees | tag with qualified name and list of attributes (inner node or leaf)  | 
| XDTD DTDElem Attributes | DTD element with assoc list for dtd element features  | 
| XAttr QName | attribute with qualified name, the attribute value is stored in children  | 
| XError Int String | error message with level and text  | 
Represents a DTD element
Constructors
| DOCTYPE | attr: 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"  | 
| ENTITY | for entity declarations  | 
| PENTITY | for parameter entity declarations  | 
| NOTATION | for 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  | 
| PEREF | for Parameter Entity References in DTDs  | 
type Attributes = AssocList String StringSource
Attribute list
used for storing option lists and features of DTD parts
data XmlNodeSet Source
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 | |
Fields 
  | |
Instances
type ChildNodes = [(Int, XmlNodeSet)]Source