Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
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
- 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 QName [Attribute] [Content i]
- data ElemTag = ElemTag QName [Attribute]
- data Content i
- type Attribute = (QName, 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
- type ProcessingInstruction = (PITarget, String)
- type SDDecl = Bool
- type VersionInfo = String
- type Comment = String
- type PITarget = String
- data DocTypeDecl = DTD QName (Maybe ExternalID) [MarkupDecl]
- data MarkupDecl
- data ExtSubset = ExtSubset (Maybe TextDecl) [ExtSubsetDecl]
- data ExtSubsetDecl
- data ElementDecl = ElementDecl QName ContentSpec
- data ContentSpec
- data CP
- data Modifier
- data Mixed
- = PCDATA
- | PCDATAplus [QName]
- data AttListDecl = AttListDecl QName [AttDef]
- data AttDef = AttDef QName AttType DefaultDecl
- data AttType
- data TokenizedType
- data EnumeratedType
- type NotationType = [Name]
- type Enumeration = [NmToken]
- data DefaultDecl
- data FIXED = FIXED
- data ConditionalSect
- type IncludeSect = [ExtSubsetDecl]
- type IgnoreSect = [IgnoreSectContents]
- data Ignore = Ignore
- data IgnoreSectContents = IgnoreSectContents Ignore [(IgnoreSectContents, Ignore)]
- data Reference
- type EntityRef = Name
- type CharRef = Int
- type PEReference = Name
- data EntityDecl
- data GEDecl = GEDecl Name EntityDef
- data PEDecl = PEDecl Name PEDef
- data EntityDef
- data PEDef
- data ExternalID
- 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
- newtype PubidLiteral = PubidLiteral String
- newtype SystemLiteral = SystemLiteral String
- data QName
- data Namespace = Namespace {}
- 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.
Symbol table operations
XML Types
The top-level document container
The symbol table stored in a document holds all its general entity reference definitions.
The main document content
Constructors
CElem (Element i) i | |
CString Bool CharData i | bool is whether whitespace is significant |
CRef Reference i | |
CMisc Misc i |
Administrative parts of the document
Constructors
XMLDecl VersionInfo (Maybe EncodingDecl) (Maybe SDDecl) |
Instances
Constructors
Comment Comment | |
PI ProcessingInstruction |
type ProcessingInstruction = (PITarget, String) Source #
type VersionInfo = String Source #
The DTD
content model
data DocTypeDecl Source #
Constructors
DTD QName (Maybe ExternalID) [MarkupDecl] |
Instances
Show DocTypeDecl Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> DocTypeDecl -> ShowS # show :: DocTypeDecl -> String # showList :: [DocTypeDecl] -> ShowS # | |
Eq DocTypeDecl Source # | |
Defined in Text.XML.HaXml.Types |
data MarkupDecl Source #
Constructors
Element ElementDecl | |
AttList AttListDecl | |
Entity EntityDecl | |
Notation NotationDecl | |
MarkupMisc Misc |
Instances
Show MarkupDecl Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> MarkupDecl -> ShowS # show :: MarkupDecl -> String # showList :: [MarkupDecl] -> ShowS # | |
Eq MarkupDecl Source # | |
Defined in Text.XML.HaXml.Types |
Constructors
ExtSubset (Maybe TextDecl) [ExtSubsetDecl] |
data ExtSubsetDecl Source #
Constructors
ExtMarkupDecl MarkupDecl | |
ExtConditionalSect ConditionalSect |
Instances
Show ExtSubsetDecl Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> ExtSubsetDecl -> ShowS # show :: ExtSubsetDecl -> String # showList :: [ExtSubsetDecl] -> ShowS # | |
Eq ExtSubsetDecl Source # | |
Defined in Text.XML.HaXml.Types Methods (==) :: ExtSubsetDecl -> ExtSubsetDecl -> Bool # (/=) :: ExtSubsetDecl -> ExtSubsetDecl -> Bool # |
data ElementDecl Source #
Constructors
ElementDecl QName ContentSpec |
Instances
Show ElementDecl Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> ElementDecl -> ShowS # show :: ElementDecl -> String # showList :: [ElementDecl] -> ShowS # | |
Eq ElementDecl Source # | |
Defined in Text.XML.HaXml.Types |
data ContentSpec Source #
Instances
Show ContentSpec Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> ContentSpec -> ShowS # show :: ContentSpec -> String # showList :: [ContentSpec] -> ShowS # | |
Eq ContentSpec Source # | |
Defined in Text.XML.HaXml.Types |
Instances
Constructors
PCDATA | |
PCDATAplus [QName] |
attribute model
data AttListDecl Source #
Constructors
AttListDecl QName [AttDef] |
Instances
Show AttListDecl Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> AttListDecl -> ShowS # show :: AttListDecl -> String # showList :: [AttListDecl] -> ShowS # | |
Eq AttListDecl Source # | |
Defined in Text.XML.HaXml.Types |
Constructors
AttDef QName AttType DefaultDecl |
Constructors
StringType | |
TokenizedType TokenizedType | |
EnumeratedType EnumeratedType |
Instances
data TokenizedType Source #
Instances
Show TokenizedType Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> TokenizedType -> ShowS # show :: TokenizedType -> String # showList :: [TokenizedType] -> ShowS # | |
Eq TokenizedType Source # | |
Defined in Text.XML.HaXml.Types Methods (==) :: TokenizedType -> TokenizedType -> Bool # (/=) :: TokenizedType -> TokenizedType -> Bool # |
data EnumeratedType Source #
Constructors
NotationType NotationType | |
Enumeration Enumeration |
Instances
Show EnumeratedType Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> EnumeratedType -> ShowS # show :: EnumeratedType -> String # showList :: [EnumeratedType] -> ShowS # | |
Eq EnumeratedType Source # | |
Defined in Text.XML.HaXml.Types Methods (==) :: EnumeratedType -> EnumeratedType -> Bool # (/=) :: EnumeratedType -> EnumeratedType -> Bool # |
type NotationType = [Name] Source #
type Enumeration = [NmToken] Source #
data DefaultDecl Source #
Instances
Show DefaultDecl Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> DefaultDecl -> ShowS # show :: DefaultDecl -> String # showList :: [DefaultDecl] -> ShowS # | |
Eq DefaultDecl Source # | |
Defined in Text.XML.HaXml.Types |
Constructors
FIXED |
conditional sections
data ConditionalSect Source #
Constructors
IncludeSect IncludeSect | |
IgnoreSect IgnoreSect |
Instances
Show ConditionalSect Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> ConditionalSect -> ShowS # show :: ConditionalSect -> String # showList :: [ConditionalSect] -> ShowS # | |
Eq ConditionalSect Source # | |
Defined in Text.XML.HaXml.Types Methods (==) :: ConditionalSect -> ConditionalSect -> Bool # (/=) :: ConditionalSect -> ConditionalSect -> Bool # |
type IncludeSect = [ExtSubsetDecl] Source #
type IgnoreSect = [IgnoreSectContents] Source #
Constructors
Ignore |
data IgnoreSectContents Source #
Constructors
IgnoreSectContents Ignore [(IgnoreSectContents, Ignore)] |
Instances
Show IgnoreSectContents Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> IgnoreSectContents -> ShowS # show :: IgnoreSectContents -> String # showList :: [IgnoreSectContents] -> ShowS # | |
Eq IgnoreSectContents Source # | |
Defined in Text.XML.HaXml.Types Methods (==) :: IgnoreSectContents -> IgnoreSectContents -> Bool # (/=) :: IgnoreSectContents -> IgnoreSectContents -> Bool # |
References
type PEReference = Name Source #
Entities
data EntityDecl Source #
Constructors
EntityGEDecl GEDecl | |
EntityPEDecl PEDecl |
Instances
Show EntityDecl Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> EntityDecl -> ShowS # show :: EntityDecl -> String # showList :: [EntityDecl] -> ShowS # | |
Eq EntityDecl Source # | |
Defined in Text.XML.HaXml.Types |
Constructors
DefEntityValue EntityValue | |
DefExternalID ExternalID (Maybe NDataDecl) |
Constructors
PEDefEntityValue EntityValue | |
PEDefExternalID ExternalID |
data ExternalID Source #
Constructors
SYSTEM SystemLiteral | |
PUBLIC PubidLiteral SystemLiteral |
Instances
Show ExternalID Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> ExternalID -> ShowS # show :: ExternalID -> String # showList :: [ExternalID] -> ShowS # | |
Eq ExternalID Source # | |
Defined in Text.XML.HaXml.Types |
Constructors
TextDecl (Maybe VersionInfo) EncodingDecl |
Instances
data ExtParsedEnt i Source #
Constructors
ExtParsedEnt (Maybe TextDecl) (Content i) |
Instances
Show i => Show (ExtParsedEnt i) Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> ExtParsedEnt i -> ShowS # show :: ExtParsedEnt i -> String # showList :: [ExtParsedEnt i] -> ShowS # | |
Eq (ExtParsedEnt i) Source # | |
Defined in Text.XML.HaXml.Types Methods (==) :: ExtParsedEnt i -> ExtParsedEnt i -> Bool # (/=) :: ExtParsedEnt i -> ExtParsedEnt i -> Bool # |
Constructors
ExtPE (Maybe TextDecl) [ExtSubsetDecl] |
data NotationDecl Source #
Constructors
NOTATION Name (Either ExternalID PublicID) |
Instances
Show NotationDecl Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> NotationDecl -> ShowS # show :: NotationDecl -> String # showList :: [NotationDecl] -> ShowS # | |
Eq NotationDecl Source # | |
Defined in Text.XML.HaXml.Types |
Constructors
PUBLICID PubidLiteral |
Instances
newtype EncodingDecl Source #
Constructors
EncodingDecl String |
Instances
Show EncodingDecl Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> EncodingDecl -> ShowS # show :: EncodingDecl -> String # showList :: [EncodingDecl] -> ShowS # | |
Eq EncodingDecl Source # | |
Defined in Text.XML.HaXml.Types |
data EntityValue Source #
Constructors
EntityValue [EV] |
Instances
Show EntityValue Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> EntityValue -> ShowS # show :: EntityValue -> String # showList :: [EntityValue] -> ShowS # | |
Eq EntityValue Source # | |
Defined in Text.XML.HaXml.Types |
newtype PubidLiteral Source #
Constructors
PubidLiteral String |
Instances
Show PubidLiteral Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> PubidLiteral -> ShowS # show :: PubidLiteral -> String # showList :: [PubidLiteral] -> ShowS # | |
Eq PubidLiteral Source # | |
Defined in Text.XML.HaXml.Types |
newtype SystemLiteral Source #
Constructors
SystemLiteral String |
Instances
Show SystemLiteral Source # | |
Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> SystemLiteral -> ShowS # show :: SystemLiteral -> String # showList :: [SystemLiteral] -> ShowS # | |
Eq SystemLiteral Source # | |
Defined in Text.XML.HaXml.Types Methods (==) :: SystemLiteral -> SystemLiteral -> Bool # (/=) :: SystemLiteral -> SystemLiteral -> Bool # |
Namespaces
A QName is a (possibly) qualified name, in the sense of XML namespaces.
Namespaces are not defined in the XML spec itself, but at http://www.w3.org/TR/xml-names