HaXml-1.20: Utilities for manipulating XML documentsSource codeContentsIndex
Text.XML.HaXml.Types
Contents
A simple symbol table mapping strings (references) to values.
Symbol table operations
XML Types
The top-level document container
The main document content
Administrative parts of the document
The DTD
content model
attribute model
conditional sections
References
Entities
Basic value 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
type SymTab a = [(String, a)]
emptyST :: SymTab a
addST :: String -> a -> SymTab a -> SymTab a
lookupST :: String -> SymTab a -> Maybe a
data Document i = Document Prolog (SymTab EntityDef) (Element i) [Misc]
data Element i = Elem Name [Attribute] [Content i]
data ElemTag = ElemTag Name [Attribute]
data Content i
= CElem (Element i) i
| CString Bool CharData i
| CRef Reference i
| CMisc Misc i
type Attribute = (Name, AttValue)
data AttValue = AttValue [Either String Reference]
info :: Content t -> t
data Prolog = Prolog (Maybe XMLDecl) [Misc] (Maybe DocTypeDecl) [Misc]
data XMLDecl = XMLDecl VersionInfo (Maybe EncodingDecl) (Maybe SDDecl)
data Misc
= Comment Comment
| PI ProcessingInstruction
type ProcessingInstruction = (PITarget, String)
type SDDecl = Bool
type VersionInfo = String
type Comment = String
type PITarget = String
data DocTypeDecl = DTD Name (Maybe ExternalID) [MarkupDecl]
data MarkupDecl
= Element ElementDecl
| AttList AttListDecl
| Entity EntityDecl
| Notation NotationDecl
| MarkupMisc Misc
data ExtSubset = ExtSubset (Maybe TextDecl) [ExtSubsetDecl]
data ExtSubsetDecl
= ExtMarkupDecl MarkupDecl
| ExtConditionalSect ConditionalSect
data ElementDecl = ElementDecl Name ContentSpec
data ContentSpec
= EMPTY
| ANY
| Mixed Mixed
| ContentSpec CP
data CP
= TagName Name Modifier
| Choice [CP] Modifier
| Seq [CP] Modifier
data Modifier
= None
| Query
| Star
| Plus
data Mixed
= PCDATA
| PCDATAplus [Name]
data AttListDecl = AttListDecl Name [AttDef]
data AttDef = AttDef Name AttType DefaultDecl
data AttType
= StringType
| TokenizedType TokenizedType
| EnumeratedType EnumeratedType
data TokenizedType
= ID
| IDREF
| IDREFS
| ENTITY
| ENTITIES
| NMTOKEN
| NMTOKENS
data EnumeratedType
= NotationType NotationType
| Enumeration Enumeration
type NotationType = [Name]
type Enumeration = [NmToken]
data DefaultDecl
= REQUIRED
| IMPLIED
| DefaultTo AttValue (Maybe FIXED)
data FIXED = FIXED
data ConditionalSect
= IncludeSect IncludeSect
| IgnoreSect IgnoreSect
type IncludeSect = [ExtSubsetDecl]
type IgnoreSect = [IgnoreSectContents]
data Ignore = Ignore
data IgnoreSectContents = IgnoreSectContents Ignore [(IgnoreSectContents, Ignore)]
data Reference
= RefEntity EntityRef
| RefChar CharRef
type EntityRef = Name
type CharRef = Int
type PEReference = Name
data EntityDecl
= EntityGEDecl GEDecl
| EntityPEDecl PEDecl
data GEDecl = GEDecl Name EntityDef
data PEDecl = PEDecl Name PEDef
data EntityDef
= DefEntityValue EntityValue
| DefExternalID ExternalID (Maybe NDataDecl)
data PEDef
= PEDefEntityValue EntityValue
| PEDefExternalID ExternalID
data ExternalID
= SYSTEM SystemLiteral
| PUBLIC PubidLiteral SystemLiteral
newtype NDataDecl = NDATA Name
data TextDecl = TextDecl (Maybe VersionInfo) EncodingDecl
data ExtParsedEnt i = ExtParsedEnt (Maybe TextDecl) (Content i)
data ExtPE = ExtPE (Maybe TextDecl) [ExtSubsetDecl]
data NotationDecl = NOTATION Name (Either ExternalID PublicID)
newtype PublicID = PUBLICID PubidLiteral
newtype EncodingDecl = EncodingDecl String
data EntityValue = EntityValue [EV]
data EV
= EVString String
| EVRef Reference
newtype PubidLiteral = PubidLiteral String
newtype SystemLiteral = SystemLiteral String
type Name = String
type Names = [Name]
type NmToken = String
type NmTokens = [NmToken]
type CharData = String
type CDSect = CharData
A simple symbol table mapping strings (references) to values.
type SymTab a = [(String, a)]Source
Symbol table operations
emptyST :: SymTab aSource
addST :: String -> a -> SymTab a -> SymTab aSource
lookupST :: String -> SymTab a -> Maybe aSource
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]
show/hide Instances
The main document content
data Element i Source
Constructors
Elem Name [Attribute] [Content i]
show/hide Instances
data ElemTag Source
Constructors
ElemTag Name [Attribute]
show/hide Instances
data Content i Source
Constructors
CElem (Element i) i
CString Bool CharData ibool is whether whitespace is significant
CRef Reference i
CMisc Misc i
show/hide Instances
type Attribute = (Name, AttValue)Source
data AttValue Source
Constructors
AttValue [Either String Reference]
show/hide Instances
info :: Content t -> tSource
Administrative parts of the document
data Prolog Source
Constructors
Prolog (Maybe XMLDecl) [Misc] (Maybe DocTypeDecl) [Misc]
show/hide Instances
data XMLDecl Source
Constructors
XMLDecl VersionInfo (Maybe EncodingDecl) (Maybe SDDecl)
show/hide Instances
data Misc Source
Constructors
Comment Comment
PI ProcessingInstruction
show/hide Instances
type ProcessingInstruction = (PITarget, String)Source
type SDDecl = BoolSource
type VersionInfo = StringSource
type Comment = StringSource
type PITarget = StringSource
The DTD
content model
data DocTypeDecl Source
Constructors
DTD Name (Maybe ExternalID) [MarkupDecl]
show/hide Instances
data MarkupDecl Source
Constructors
Element ElementDecl
AttList AttListDecl
Entity EntityDecl
Notation NotationDecl
MarkupMisc Misc
show/hide Instances
data ExtSubset Source
Constructors
ExtSubset (Maybe TextDecl) [ExtSubsetDecl]
show/hide Instances
data ExtSubsetDecl Source
Constructors
ExtMarkupDecl MarkupDecl
ExtConditionalSect ConditionalSect
show/hide Instances
data ElementDecl Source
Constructors
ElementDecl Name ContentSpec
show/hide Instances
data ContentSpec Source
Constructors
EMPTY
ANY
Mixed Mixed
ContentSpec CP
show/hide Instances
data CP Source
Constructors
TagName Name Modifier
Choice [CP] Modifier
Seq [CP] Modifier
show/hide Instances
data Modifier Source
Constructors
NoneJust One
QueryZero Or One
StarZero Or More
PlusOne Or More
show/hide Instances
data Mixed Source
Constructors
PCDATA
PCDATAplus [Name]
show/hide Instances
attribute model
data AttListDecl Source
Constructors
AttListDecl Name [AttDef]
show/hide Instances
data AttDef Source
Constructors
AttDef Name AttType DefaultDecl
show/hide Instances
data AttType Source
Constructors
StringType
TokenizedType TokenizedType
EnumeratedType EnumeratedType
show/hide Instances
data TokenizedType Source
Constructors
ID
IDREF
IDREFS
ENTITY
ENTITIES
NMTOKEN
NMTOKENS
show/hide Instances
data EnumeratedType Source
Constructors
NotationType NotationType
Enumeration Enumeration
show/hide Instances
type NotationType = [Name]Source
type Enumeration = [NmToken]Source
data DefaultDecl Source
Constructors
REQUIRED
IMPLIED
DefaultTo AttValue (Maybe FIXED)
show/hide Instances
data FIXED Source
Constructors
FIXED
show/hide Instances
conditional sections
data ConditionalSect Source
Constructors
IncludeSect IncludeSect
IgnoreSect IgnoreSect
show/hide Instances
type IncludeSect = [ExtSubsetDecl]Source
type IgnoreSect = [IgnoreSectContents]Source
data Ignore Source
Constructors
Ignore
show/hide Instances
data IgnoreSectContents Source
Constructors
IgnoreSectContents Ignore [(IgnoreSectContents, Ignore)]
show/hide Instances
References
data Reference Source
Constructors
RefEntity EntityRef
RefChar CharRef
show/hide Instances
type EntityRef = NameSource
type CharRef = IntSource
type PEReference = NameSource
Entities
data EntityDecl Source
Constructors
EntityGEDecl GEDecl
EntityPEDecl PEDecl
show/hide Instances
data GEDecl Source
Constructors
GEDecl Name EntityDef
show/hide Instances
data PEDecl Source
Constructors
PEDecl Name PEDef
show/hide Instances
data EntityDef Source
Constructors
DefEntityValue EntityValue
DefExternalID ExternalID (Maybe NDataDecl)
show/hide Instances
data PEDef Source
Constructors
PEDefEntityValue EntityValue
PEDefExternalID ExternalID
show/hide Instances
data ExternalID Source
Constructors
SYSTEM SystemLiteral
PUBLIC PubidLiteral SystemLiteral
show/hide Instances
newtype NDataDecl Source
Constructors
NDATA Name
show/hide Instances
data TextDecl Source
Constructors
TextDecl (Maybe VersionInfo) EncodingDecl
show/hide Instances
data ExtParsedEnt i Source
Constructors
ExtParsedEnt (Maybe TextDecl) (Content i)
show/hide Instances
Eq i => Eq (ExtParsedEnt i)
data ExtPE Source
Constructors
ExtPE (Maybe TextDecl) [ExtSubsetDecl]
show/hide Instances
data NotationDecl Source
Constructors
NOTATION Name (Either ExternalID PublicID)
show/hide Instances
newtype PublicID Source
Constructors
PUBLICID PubidLiteral
show/hide Instances
newtype EncodingDecl Source
Constructors
EncodingDecl String
show/hide Instances
data EntityValue Source
Constructors
EntityValue [EV]
show/hide Instances
data EV Source
Constructors
EVString String
EVRef Reference
show/hide Instances
newtype PubidLiteral Source
Constructors
PubidLiteral String
show/hide Instances
newtype SystemLiteral Source
Constructors
SystemLiteral String
show/hide Instances
Basic value types
type Name = StringSource
type Names = [Name]Source
type NmToken = StringSource
type NmTokens = [NmToken]Source
type CharData = StringSource
type CDSect = CharDataSource
Produced by Haddock version 2.6.0