HaXml-1.25.11: Utilities for manipulating XML documents
Safe HaskellSafe-Inferred
LanguageHaskell98

Text.XML.HaXml.Types

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

Instances details
Functor Document Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

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 #

Eq (Document i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

The main document content

data Element i Source #

Constructors

Elem QName [Attribute] [Content i] 

Instances

Instances details
Functor Element Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Verbatim (Element i) Source # 
Instance details

Defined in Text.XML.HaXml.Verbatim

Methods

verbatim :: Element i -> String Source #

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 #

Eq (Element i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

data ElemTag Source #

Constructors

ElemTag QName [Attribute] 

Instances

Instances details
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

Instances details
Functor Content Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

Verbatim (Content i) Source # 
Instance details

Defined in Text.XML.HaXml.Verbatim

Methods

verbatim :: Content i -> String Source #

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 #

Eq (Content i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

data AttValue Source #

Instances

Instances details
Verbatim AttValue Source # 
Instance details

Defined in Text.XML.HaXml.Verbatim

Show AttValue Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq AttValue Source # 
Instance details

Defined in Text.XML.HaXml.Types

info :: Content t -> t Source #

Administrative parts of the document

data Prolog Source #

Constructors

Prolog (Maybe XMLDecl) [Misc] (Maybe DocTypeDecl) [Misc] 

Instances

Instances details
Show Prolog Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq Prolog Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

data XMLDecl Source #

Instances

Instances details
Show XMLDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq XMLDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

data Misc Source #

Instances

Instances details
Show Misc Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> Misc -> ShowS #

show :: Misc -> String #

showList :: [Misc] -> ShowS #

Eq Misc Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

The DTD

content model

data DocTypeDecl Source #

Constructors

DTD QName (Maybe ExternalID) [MarkupDecl] 

Instances

Instances details
Show DocTypeDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq DocTypeDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

data ExtSubset Source #

Instances

Instances details
Show ExtSubset Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq ExtSubset Source # 
Instance details

Defined in Text.XML.HaXml.Types

data ElementDecl Source #

Instances

Instances details
Show ElementDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq ElementDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

data ContentSpec Source #

Constructors

EMPTY 
ANY 
Mixed Mixed 
ContentSpec CP 

Instances

Instances details
Show ContentSpec Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq ContentSpec Source # 
Instance details

Defined in Text.XML.HaXml.Types

data CP Source #

Instances

Instances details
Show CP Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> CP -> ShowS #

show :: CP -> String #

showList :: [CP] -> ShowS #

Eq CP Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

data Modifier Source #

Constructors

None

Just One

Query

Zero Or One

Star

Zero Or More

Plus

One Or More

Instances

Instances details
Show Modifier Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq Modifier Source # 
Instance details

Defined in Text.XML.HaXml.Types

data Mixed Source #

Constructors

PCDATA 
PCDATAplus [QName] 

Instances

Instances details
Show Mixed Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> Mixed -> ShowS #

show :: Mixed -> String #

showList :: [Mixed] -> ShowS #

Eq Mixed Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

attribute model

data AttListDecl Source #

Constructors

AttListDecl QName [AttDef] 

Instances

Instances details
Show AttListDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq AttListDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

data AttDef Source #

Instances

Instances details
Show AttDef Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq AttDef Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

data AttType Source #

Instances

Instances details
Show AttType Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq AttType Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

data TokenizedType Source #

Instances

Instances details
Show TokenizedType Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq TokenizedType Source # 
Instance details

Defined in Text.XML.HaXml.Types

data DefaultDecl Source #

Instances

Instances details
Show DefaultDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq DefaultDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

data FIXED Source #

Constructors

FIXED 

Instances

Instances details
Show FIXED Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> FIXED -> ShowS #

show :: FIXED -> String #

showList :: [FIXED] -> ShowS #

Eq FIXED Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

conditional sections

data Ignore Source #

Constructors

Ignore 

Instances

Instances details
Show Ignore Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq Ignore Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

References

data Reference Source #

Instances

Instances details
Verbatim Reference Source # 
Instance details

Defined in Text.XML.HaXml.Verbatim

Show Reference Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq Reference Source # 
Instance details

Defined in Text.XML.HaXml.Types

Entities

data EntityDecl Source #

Instances

Instances details
Show EntityDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq EntityDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

data GEDecl Source #

Constructors

GEDecl Name EntityDef 

Instances

Instances details
Show GEDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq GEDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

data PEDecl Source #

Constructors

PEDecl Name PEDef 

Instances

Instances details
Show PEDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq PEDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

data EntityDef Source #

Instances

Instances details
Show EntityDef Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq EntityDef Source # 
Instance details

Defined in Text.XML.HaXml.Types

data PEDef Source #

Instances

Instances details
Show PEDef Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> PEDef -> ShowS #

show :: PEDef -> String #

showList :: [PEDef] -> ShowS #

Eq PEDef Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

data ExternalID Source #

Instances

Instances details
Show ExternalID Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq ExternalID Source # 
Instance details

Defined in Text.XML.HaXml.Types

newtype NDataDecl Source #

Constructors

NDATA Name 

Instances

Instances details
Show NDataDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq NDataDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

data TextDecl Source #

Instances

Instances details
Show TextDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq TextDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

data ExtParsedEnt i Source #

Constructors

ExtParsedEnt (Maybe TextDecl) (Content i) 

Instances

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

Defined in Text.XML.HaXml.Types

Eq (ExtParsedEnt i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

data ExtPE Source #

Constructors

ExtPE (Maybe TextDecl) [ExtSubsetDecl] 

Instances

Instances details
Show ExtPE Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> ExtPE -> ShowS #

show :: ExtPE -> String #

showList :: [ExtPE] -> ShowS #

Eq ExtPE Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

data NotationDecl Source #

Instances

Instances details
Show NotationDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq NotationDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

newtype PublicID Source #

Constructors

PUBLICID PubidLiteral 

Instances

Instances details
Show PublicID Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq PublicID Source # 
Instance details

Defined in Text.XML.HaXml.Types

newtype EncodingDecl Source #

Constructors

EncodingDecl String 

Instances

Instances details
Show EncodingDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq EncodingDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

data EntityValue Source #

Constructors

EntityValue [EV] 

Instances

Instances details
Show EntityValue Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq EntityValue Source # 
Instance details

Defined in Text.XML.HaXml.Types

data EV Source #

Instances

Instances details
Show EV Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> EV -> ShowS #

show :: EV -> String #

showList :: [EV] -> ShowS #

Eq EV Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

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

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

newtype PubidLiteral Source #

Constructors

PubidLiteral String 

Instances

Instances details
Show PubidLiteral Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq PubidLiteral Source # 
Instance details

Defined in Text.XML.HaXml.Types

newtype SystemLiteral Source #

Constructors

SystemLiteral String 

Instances

Instances details
Show SystemLiteral Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq SystemLiteral Source # 
Instance details

Defined in Text.XML.HaXml.Types

Namespaces

data QName Source #

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

Constructors

N Name 
QN Namespace Name 

Instances

Instances details
Show QName Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> QName -> ShowS #

show :: QName -> String #

showList :: [QName] -> ShowS #

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 #

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

Instances details
Show Namespace Source # 
Instance details

Defined in Text.XML.HaXml.Types

Eq Namespace Source # 
Instance details

Defined in Text.XML.HaXml.Types

Basic value types

type Names = [Name] Source #