HaXml-1.25.5: Utilities for manipulating XML documents

Safe HaskellSafe
LanguageHaskell98

Text.XML.HaXml.Types

Contents

Description

This module defines an internal (generic) representation for XML documents including their DTDs.

History: The original module was derived by hand from the XML specification, following the grammar precisely. Then we simplified the types, removing layers of indirection and redundancy, and generally making things easier to work with. Then we allowed PEReferences to be ubiquitous, by removing them from the types and resolving all PE references at parse-time. Finally, we added a per-document symbol table for GEReferences, and a whitespace-significance flag for plaintext.

Synopsis

A simple symbol table mapping strings (references) to values.

type SymTab a = [(String, a)] Source #

Symbol table operations

addST :: String -> a -> SymTab a -> SymTab a Source #

XML Types

The top-level document container

data Document i Source #

The symbol table stored in a document holds all its general entity reference definitions.

Constructors

Document Prolog (SymTab EntityDef) (Element i) [Misc] 
Instances
Functor Document Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

fmap :: (a -> b) -> Document a -> Document b #

(<$) :: a -> Document b -> Document a #

Eq (Document i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: Document i -> Document i -> Bool #

(/=) :: Document i -> Document i -> Bool #

Show i => Show (Document i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> Document i -> ShowS #

show :: Document i -> String #

showList :: [Document i] -> ShowS #

The main document content

data Element i Source #

Constructors

Elem QName [Attribute] [Content i] 
Instances
Functor Element Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

fmap :: (a -> b) -> Element a -> Element b #

(<$) :: a -> Element b -> Element a #

Eq (Element i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: Element i -> Element i -> Bool #

(/=) :: Element i -> Element i -> Bool #

Show i => Show (Element i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> Element i -> ShowS #

show :: Element i -> String #

showList :: [Element i] -> ShowS #

Verbatim (Element i) Source # 
Instance details

Defined in Text.XML.HaXml.Verbatim

Methods

verbatim :: Element i -> String Source #

data ElemTag Source #

Constructors

ElemTag QName [Attribute] 
Instances
Eq ElemTag Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

data Content i Source #

Constructors

CElem (Element i) i 
CString Bool CharData i

bool is whether whitespace is significant

CRef Reference i 
CMisc Misc i 
Instances
Functor Content Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

fmap :: (a -> b) -> Content a -> Content b #

(<$) :: a -> Content b -> Content a #

Eq (Content i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: Content i -> Content i -> Bool #

(/=) :: Content i -> Content i -> Bool #

Show i => Show (Content i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> Content i -> ShowS #

show :: Content i -> String #

showList :: [Content i] -> ShowS #

Verbatim (Content i) Source # 
Instance details

Defined in Text.XML.HaXml.Verbatim

Methods

verbatim :: Content i -> String Source #

data AttValue Source #

Instances
Eq AttValue Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show AttValue Source # 
Instance details

Defined in Text.XML.HaXml.Types

Verbatim AttValue Source # 
Instance details

Defined in Text.XML.HaXml.Verbatim

info :: Content t -> t Source #

Administrative parts of the document

data Prolog Source #

Constructors

Prolog (Maybe XMLDecl) [Misc] (Maybe DocTypeDecl) [Misc] 
Instances
Eq Prolog Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Show Prolog Source # 
Instance details

Defined in Text.XML.HaXml.Types

data XMLDecl Source #

Instances
Eq XMLDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Show XMLDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

data Misc Source #

Instances
Eq Misc Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Show Misc Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> Misc -> ShowS #

show :: Misc -> String #

showList :: [Misc] -> ShowS #

The DTD

content model

data ExtSubset Source #

Instances
Eq ExtSubset Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show ExtSubset Source # 
Instance details

Defined in Text.XML.HaXml.Types

data CP Source #

Instances
Eq CP Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Show CP Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> CP -> ShowS #

show :: CP -> String #

showList :: [CP] -> ShowS #

data Modifier Source #

Constructors

None

Just One

Query

Zero Or One

Star

Zero Or More

Plus

One Or More

Instances
Eq Modifier Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show Modifier Source # 
Instance details

Defined in Text.XML.HaXml.Types

data Mixed Source #

Constructors

PCDATA 
PCDATAplus [QName] 
Instances
Eq Mixed Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Show Mixed Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> Mixed -> ShowS #

show :: Mixed -> String #

showList :: [Mixed] -> ShowS #

attribute model

data AttListDecl Source #

Constructors

AttListDecl QName [AttDef] 
Instances
Eq AttListDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show AttListDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

data AttDef Source #

Instances
Eq AttDef Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Show AttDef Source # 
Instance details

Defined in Text.XML.HaXml.Types

data AttType Source #

Instances
Eq AttType Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Show AttType Source # 
Instance details

Defined in Text.XML.HaXml.Types

data FIXED Source #

Constructors

FIXED 
Instances
Eq FIXED Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Show FIXED Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> FIXED -> ShowS #

show :: FIXED -> String #

showList :: [FIXED] -> ShowS #

conditional sections

data Ignore Source #

Constructors

Ignore 
Instances
Eq Ignore Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Show Ignore Source # 
Instance details

Defined in Text.XML.HaXml.Types

References

data Reference Source #

Instances
Eq Reference Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show Reference Source # 
Instance details

Defined in Text.XML.HaXml.Types

Verbatim Reference Source # 
Instance details

Defined in Text.XML.HaXml.Verbatim

Entities

data GEDecl Source #

Constructors

GEDecl Name EntityDef 
Instances
Eq GEDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Show GEDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

data PEDecl Source #

Constructors

PEDecl Name PEDef 
Instances
Eq PEDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Show PEDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

data PEDef Source #

Instances
Eq PEDef Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Show PEDef Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> PEDef -> ShowS #

show :: PEDef -> String #

showList :: [PEDef] -> ShowS #

newtype NDataDecl Source #

Constructors

NDATA Name 
Instances
Eq NDataDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show NDataDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

data TextDecl Source #

Instances
Eq TextDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show TextDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

data ExtParsedEnt i Source #

Constructors

ExtParsedEnt (Maybe TextDecl) (Content i) 
Instances
Eq (ExtParsedEnt i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show i => Show (ExtParsedEnt i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

data ExtPE Source #

Constructors

ExtPE (Maybe TextDecl) [ExtSubsetDecl] 
Instances
Eq ExtPE Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Show ExtPE Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> ExtPE -> ShowS #

show :: ExtPE -> String #

showList :: [ExtPE] -> ShowS #

newtype PublicID Source #

Constructors

PUBLICID PubidLiteral 
Instances
Eq PublicID Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show PublicID Source # 
Instance details

Defined in Text.XML.HaXml.Types

data EntityValue Source #

Constructors

EntityValue [EV] 
Instances
Eq EntityValue Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show EntityValue Source # 
Instance details

Defined in Text.XML.HaXml.Types

data EV Source #

Instances
Eq EV Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Show EV Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> EV -> ShowS #

show :: EV -> String #

showList :: [EV] -> ShowS #

Namespaces

data QName Source #

A QName is a (possibly) qualified name, in the sense of XML namespaces.

Constructors

N Name 
QN Namespace Name 
Instances
Eq QName Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Ord QName Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

compare :: QName -> QName -> Ordering #

(<) :: QName -> QName -> Bool #

(<=) :: QName -> QName -> Bool #

(>) :: QName -> QName -> Bool #

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

max :: QName -> QName -> QName #

min :: QName -> QName -> QName #

Show QName Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> QName -> ShowS #

show :: QName -> String #

showList :: [QName] -> ShowS #

data Namespace Source #

Namespaces are not defined in the XML spec itself, but at http://www.w3.org/TR/xml-names

Constructors

Namespace 

Fields

Instances
Eq Namespace Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show Namespace Source # 
Instance details

Defined in Text.XML.HaXml.Types

Basic value types

type Names = [Name] Source #