| 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- = DefEntityValue EntityValue
- | DefExternalID ExternalID (Maybe NDataDecl)
 
- 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
| Prolog (Maybe XMLDecl) [Misc] (Maybe DocTypeDecl) [Misc] | 
Constructors
| XMLDecl VersionInfo (Maybe EncodingDecl) (Maybe SDDecl) | 
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
| Eq DocTypeDecl Source # | |
| Defined in Text.XML.HaXml.Types | |
| Show DocTypeDecl Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> DocTypeDecl -> ShowS show :: DocTypeDecl -> String showList :: [DocTypeDecl] -> ShowS | |
data MarkupDecl Source #
Constructors
| Element ElementDecl | |
| AttList AttListDecl | |
| Entity EntityDecl | |
| Notation NotationDecl | |
| MarkupMisc Misc | 
Instances
| Eq MarkupDecl Source # | |
| Defined in Text.XML.HaXml.Types | |
| Show MarkupDecl Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> MarkupDecl -> ShowS show :: MarkupDecl -> String showList :: [MarkupDecl] -> ShowS | |
Constructors
| ExtSubset (Maybe TextDecl) [ExtSubsetDecl] | 
Instances
data ExtSubsetDecl Source #
Constructors
| ExtMarkupDecl MarkupDecl | |
| ExtConditionalSect ConditionalSect | 
Instances
| Eq ExtSubsetDecl Source # | |
| Defined in Text.XML.HaXml.Types | |
| Show ExtSubsetDecl Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> ExtSubsetDecl -> ShowS show :: ExtSubsetDecl -> String showList :: [ExtSubsetDecl] -> ShowS | |
data ElementDecl Source #
Constructors
| ElementDecl QName ContentSpec | 
Instances
| Eq ElementDecl Source # | |
| Defined in Text.XML.HaXml.Types | |
| Show ElementDecl Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> ElementDecl -> ShowS show :: ElementDecl -> String showList :: [ElementDecl] -> ShowS | |
data ContentSpec Source #
Instances
| Eq ContentSpec Source # | |
| Defined in Text.XML.HaXml.Types | |
| Show ContentSpec Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> ContentSpec -> ShowS show :: ContentSpec -> String showList :: [ContentSpec] -> ShowS | |
Constructors
| PCDATA | |
| PCDATAplus [QName] | 
attribute model
data AttListDecl Source #
Constructors
| AttListDecl QName [AttDef] | 
Instances
| Eq AttListDecl Source # | |
| Defined in Text.XML.HaXml.Types | |
| Show AttListDecl Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> AttListDecl -> ShowS show :: AttListDecl -> String showList :: [AttListDecl] -> ShowS | |
Constructors
| AttDef QName AttType DefaultDecl | 
Constructors
| StringType | |
| TokenizedType TokenizedType | |
| EnumeratedType EnumeratedType | 
data TokenizedType Source #
Instances
| Eq TokenizedType Source # | |
| Defined in Text.XML.HaXml.Types | |
| Show TokenizedType Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> TokenizedType -> ShowS show :: TokenizedType -> String showList :: [TokenizedType] -> ShowS | |
data EnumeratedType Source #
Constructors
| NotationType NotationType | |
| Enumeration Enumeration | 
Instances
| Eq EnumeratedType Source # | |
| Defined in Text.XML.HaXml.Types Methods (==) :: EnumeratedType -> EnumeratedType -> Bool (/=) :: EnumeratedType -> EnumeratedType -> Bool | |
| Show EnumeratedType Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> EnumeratedType -> ShowS show :: EnumeratedType -> String showList :: [EnumeratedType] -> ShowS | |
type NotationType = [Name] Source #
type Enumeration = [NmToken] Source #
data DefaultDecl Source #
Instances
| Eq DefaultDecl Source # | |
| Defined in Text.XML.HaXml.Types | |
| Show DefaultDecl Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> DefaultDecl -> ShowS show :: DefaultDecl -> String showList :: [DefaultDecl] -> ShowS | |
Constructors
| FIXED | 
conditional sections
data ConditionalSect Source #
Constructors
| IncludeSect IncludeSect | |
| IgnoreSect IgnoreSect | 
Instances
| Eq ConditionalSect Source # | |
| Defined in Text.XML.HaXml.Types Methods (==) :: ConditionalSect -> ConditionalSect -> Bool (/=) :: ConditionalSect -> ConditionalSect -> Bool | |
| Show ConditionalSect Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> ConditionalSect -> ShowS show :: ConditionalSect -> String showList :: [ConditionalSect] -> ShowS | |
type IncludeSect = [ExtSubsetDecl] Source #
type IgnoreSect = [IgnoreSectContents] Source #
Constructors
| Ignore | 
data IgnoreSectContents Source #
Constructors
| IgnoreSectContents Ignore [(IgnoreSectContents, Ignore)] | 
Instances
| Eq IgnoreSectContents Source # | |
| Defined in Text.XML.HaXml.Types Methods (==) :: IgnoreSectContents -> IgnoreSectContents -> Bool (/=) :: IgnoreSectContents -> IgnoreSectContents -> Bool | |
| Show IgnoreSectContents Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> IgnoreSectContents -> ShowS show :: IgnoreSectContents -> String showList :: [IgnoreSectContents] -> ShowS | |
References
type PEReference = Name Source #
Entities
data EntityDecl Source #
Constructors
| EntityGEDecl GEDecl | |
| EntityPEDecl PEDecl | 
Instances
| Eq EntityDecl Source # | |
| Defined in Text.XML.HaXml.Types | |
| Show EntityDecl Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> EntityDecl -> ShowS show :: EntityDecl -> String showList :: [EntityDecl] -> ShowS | |
Constructors
| DefEntityValue EntityValue | |
| DefExternalID ExternalID (Maybe NDataDecl) | 
Instances
Constructors
| PEDefEntityValue EntityValue | |
| PEDefExternalID ExternalID | 
data ExternalID Source #
Constructors
| SYSTEM SystemLiteral | |
| PUBLIC PubidLiteral SystemLiteral | 
Instances
| Eq ExternalID Source # | |
| Defined in Text.XML.HaXml.Types | |
| Show ExternalID Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> ExternalID -> ShowS show :: ExternalID -> String showList :: [ExternalID] -> ShowS | |
Instances
Constructors
| TextDecl (Maybe VersionInfo) EncodingDecl | 
data ExtParsedEnt i Source #
Constructors
| ExtParsedEnt (Maybe TextDecl) (Content i) | 
Instances
| Eq (ExtParsedEnt i) Source # | |
| Defined in Text.XML.HaXml.Types Methods (==) :: ExtParsedEnt i -> ExtParsedEnt i -> Bool (/=) :: ExtParsedEnt i -> ExtParsedEnt i -> Bool | |
| 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 | |
Constructors
| ExtPE (Maybe TextDecl) [ExtSubsetDecl] | 
data NotationDecl Source #
Constructors
| NOTATION Name (Either ExternalID PublicID) | 
Instances
| Eq NotationDecl Source # | |
| Defined in Text.XML.HaXml.Types | |
| Show NotationDecl Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> NotationDecl -> ShowS show :: NotationDecl -> String showList :: [NotationDecl] -> ShowS | |
Constructors
| PUBLICID PubidLiteral | 
newtype EncodingDecl Source #
Constructors
| EncodingDecl String | 
Instances
| Eq EncodingDecl Source # | |
| Defined in Text.XML.HaXml.Types | |
| Show EncodingDecl Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> EncodingDecl -> ShowS show :: EncodingDecl -> String showList :: [EncodingDecl] -> ShowS | |
data EntityValue Source #
Constructors
| EntityValue [EV] | 
Instances
| Eq EntityValue Source # | |
| Defined in Text.XML.HaXml.Types | |
| Show EntityValue Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> EntityValue -> ShowS show :: EntityValue -> String showList :: [EntityValue] -> ShowS | |
newtype PubidLiteral Source #
Constructors
| PubidLiteral String | 
Instances
| Eq PubidLiteral Source # | |
| Defined in Text.XML.HaXml.Types | |
| Show PubidLiteral Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> PubidLiteral -> ShowS show :: PubidLiteral -> String showList :: [PubidLiteral] -> ShowS | |
newtype SystemLiteral Source #
Constructors
| SystemLiteral String | 
Instances
| Eq SystemLiteral Source # | |
| Defined in Text.XML.HaXml.Types | |
| Show SystemLiteral Source # | |
| Defined in Text.XML.HaXml.Types Methods showsPrec :: Int -> SystemLiteral -> ShowS show :: SystemLiteral -> String showList :: [SystemLiteral] -> ShowS | |
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