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

CopyrightCopyright (C) 2008-2010 Uwe Schmidt
LicenseMIT
MaintainerUwe Schmidt (uwe@fh-wedel.de)
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Text.XML.HXT.DOM.TypeDefs

Description

The core data types of the HXT DOM.

Synopsis

Documentation

type XmlTree = NTree XNode Source #

Rose tree with XML nodes (XNode)

type XmlTrees = NTrees XNode Source #

List of rose trees with XML nodes

type XmlNavTree = NTZipper XNode Source #

Navigatable rose tree with XML nodes

type XmlNavTrees = [NTZipper XNode] Source #

List of navigatable rose trees with XML nodes

data XNode Source #

Represents elements

Constructors

XText String

ordinary text (leaf)

XBlob Blob

text represented more space efficient as bytestring (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, attributes 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

Instances

Eq XNode Source # 

Methods

(==) :: XNode -> XNode -> Bool #

(/=) :: XNode -> XNode -> Bool #

Show XNode Source # 

Methods

showsPrec :: Int -> XNode -> ShowS #

show :: XNode -> String #

showList :: [XNode] -> ShowS #

Binary XNode Source # 

Methods

put :: XNode -> Put #

get :: Get XNode #

putList :: [XNode] -> Put #

NFData XNode Source # 

Methods

rnf :: XNode -> () #

WNFData XNode Source # 

Methods

rwnf :: XNode -> () Source #

rwnf2 :: XNode -> () Source #

XmlNode XNode Source # 

Methods

isText :: XNode -> Bool Source #

isBlob :: XNode -> Bool Source #

isCharRef :: XNode -> Bool Source #

isEntityRef :: XNode -> Bool Source #

isCmt :: XNode -> Bool Source #

isCdata :: XNode -> Bool Source #

isPi :: XNode -> Bool Source #

isElem :: XNode -> Bool Source #

isRoot :: XNode -> Bool Source #

isDTD :: XNode -> Bool Source #

isAttr :: XNode -> Bool Source #

isError :: XNode -> Bool Source #

mkText :: String -> XNode Source #

mkBlob :: Blob -> XNode Source #

mkCharRef :: Int -> XNode Source #

mkEntityRef :: String -> XNode Source #

mkCmt :: String -> XNode Source #

mkCdata :: String -> XNode Source #

mkPi :: QName -> XmlTrees -> XNode Source #

mkError :: Int -> String -> XNode Source #

getText :: XNode -> Maybe String Source #

getBlob :: XNode -> Maybe Blob Source #

getCharRef :: XNode -> Maybe Int Source #

getEntityRef :: XNode -> Maybe String Source #

getCmt :: XNode -> Maybe String Source #

getCdata :: XNode -> Maybe String Source #

getPiName :: XNode -> Maybe QName Source #

getPiContent :: XNode -> Maybe XmlTrees Source #

getElemName :: XNode -> Maybe QName Source #

getAttrl :: XNode -> Maybe XmlTrees Source #

getDTDPart :: XNode -> Maybe DTDElem Source #

getDTDAttrl :: XNode -> Maybe Attributes Source #

getAttrName :: XNode -> Maybe QName Source #

getErrorLevel :: XNode -> Maybe Int Source #

getErrorMsg :: XNode -> Maybe String Source #

getName :: XNode -> Maybe QName Source #

getQualifiedName :: XNode -> Maybe String Source #

getUniversalName :: XNode -> Maybe String Source #

getUniversalUri :: XNode -> Maybe String Source #

getLocalPart :: XNode -> Maybe String Source #

getNamePrefix :: XNode -> Maybe String Source #

getNamespaceUri :: XNode -> Maybe String Source #

changeText :: (String -> String) -> XNode -> XNode Source #

changeBlob :: (Blob -> Blob) -> XNode -> XNode Source #

changeCmt :: (String -> String) -> XNode -> XNode Source #

changeName :: (QName -> QName) -> XNode -> XNode Source #

changeElemName :: (QName -> QName) -> XNode -> XNode Source #

changeAttrl :: (XmlTrees -> XmlTrees) -> XNode -> XNode Source #

changeAttrName :: (QName -> QName) -> XNode -> XNode Source #

changePiName :: (QName -> QName) -> XNode -> XNode Source #

changeDTDAttrl :: (Attributes -> Attributes) -> XNode -> XNode Source #

setText :: String -> XNode -> XNode Source #

setBlob :: Blob -> XNode -> XNode Source #

setCmt :: String -> XNode -> XNode Source #

setName :: QName -> XNode -> XNode Source #

setElemName :: QName -> XNode -> XNode Source #

setElemAttrl :: XmlTrees -> XNode -> XNode Source #

setAttrName :: QName -> XNode -> XNode Source #

setPiName :: QName -> XNode -> XNode Source #

setDTDAttrl :: Attributes -> XNode -> XNode Source #

rwnfAttributes :: Attributes -> () Source #

Evaluate an assoc list of strings

data DTDElem Source #

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"

kind: "IMPLIED" | "DEFAULT"

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 Blob = ByteString Source #

Binary large object implemented as a lazy bytestring

type Attributes = AssocList String String Source #

Attribute list

used for storing option lists and features of DTD parts

c_ok :: Int Source #

no error, everything is ok

c_warn :: Int Source #

Error level for XError, type warning

c_err :: Int Source #

Error level for XError, type error

c_fatal :: Int Source #

Error level for XError, type fatal error

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