HaXml-1.25.6: 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 #

lookupST :: String -> SymTab a -> Maybe 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

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

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

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

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

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 #

Constructors

AttValue [Either String Reference] 

Instances

Instances details
Eq AttValue Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: AttValue -> AttValue -> Bool

(/=) :: AttValue -> AttValue -> Bool

Show AttValue Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> AttValue -> ShowS

show :: AttValue -> String

showList :: [AttValue] -> ShowS

Verbatim AttValue Source # 
Instance details

Defined in Text.XML.HaXml.Verbatim

Methods

verbatim :: AttValue -> String Source #

info :: Content t -> t Source #

Administrative parts of the document

data Prolog Source #

Constructors

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

Instances

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

Methods

showsPrec :: Int -> Prolog -> ShowS

show :: Prolog -> String

showList :: [Prolog] -> ShowS

data XMLDecl Source #

Constructors

XMLDecl VersionInfo (Maybe EncodingDecl) (Maybe SDDecl) 

Instances

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

Methods

showsPrec :: Int -> XMLDecl -> ShowS

show :: XMLDecl -> String

showList :: [XMLDecl] -> ShowS

data Misc Source #

Instances

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

type SDDecl = Bool Source #

type VersionInfo = String Source #

type Comment = String Source #

type PITarget = String Source #

The DTD

content model

data DocTypeDecl Source #

Constructors

DTD QName (Maybe ExternalID) [MarkupDecl] 

Instances

Instances details
Eq DocTypeDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: DocTypeDecl -> DocTypeDecl -> Bool

(/=) :: DocTypeDecl -> DocTypeDecl -> Bool

Show DocTypeDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> DocTypeDecl -> ShowS

show :: DocTypeDecl -> String

showList :: [DocTypeDecl] -> ShowS

data MarkupDecl Source #

Instances

Instances details
Eq MarkupDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: MarkupDecl -> MarkupDecl -> Bool

(/=) :: MarkupDecl -> MarkupDecl -> Bool

Show MarkupDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> MarkupDecl -> ShowS

show :: MarkupDecl -> String

showList :: [MarkupDecl] -> ShowS

data ExtSubset Source #

Constructors

ExtSubset (Maybe TextDecl) [ExtSubsetDecl] 

Instances

Instances details
Eq ExtSubset Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: ExtSubset -> ExtSubset -> Bool

(/=) :: ExtSubset -> ExtSubset -> Bool

Show ExtSubset Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> ExtSubset -> ShowS

show :: ExtSubset -> String

showList :: [ExtSubset] -> ShowS

data ExtSubsetDecl Source #

Instances

Instances details
Eq ExtSubsetDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show ExtSubsetDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> ExtSubsetDecl -> ShowS

show :: ExtSubsetDecl -> String

showList :: [ExtSubsetDecl] -> ShowS

data ElementDecl Source #

Instances

Instances details
Eq ElementDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: ElementDecl -> ElementDecl -> Bool

(/=) :: ElementDecl -> ElementDecl -> Bool

Show ElementDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> ElementDecl -> ShowS

show :: ElementDecl -> String

showList :: [ElementDecl] -> ShowS

data ContentSpec Source #

Constructors

EMPTY 
ANY 
Mixed Mixed 
ContentSpec CP 

Instances

Instances details
Eq ContentSpec Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: ContentSpec -> ContentSpec -> Bool

(/=) :: ContentSpec -> ContentSpec -> Bool

Show ContentSpec Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> ContentSpec -> ShowS

show :: ContentSpec -> String

showList :: [ContentSpec] -> ShowS

data CP Source #

Instances

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

Instances details
Eq Modifier Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: Modifier -> Modifier -> Bool

(/=) :: Modifier -> Modifier -> Bool

Show Modifier Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> Modifier -> ShowS

show :: Modifier -> String

showList :: [Modifier] -> ShowS

data Mixed Source #

Constructors

PCDATA 
PCDATAplus [QName] 

Instances

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

Instances details
Eq AttListDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: AttListDecl -> AttListDecl -> Bool

(/=) :: AttListDecl -> AttListDecl -> Bool

Show AttListDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> AttListDecl -> ShowS

show :: AttListDecl -> String

showList :: [AttListDecl] -> ShowS

data AttDef Source #

Instances

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

Methods

showsPrec :: Int -> AttDef -> ShowS

show :: AttDef -> String

showList :: [AttDef] -> ShowS

data AttType Source #

Instances

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

Methods

showsPrec :: Int -> AttType -> ShowS

show :: AttType -> String

showList :: [AttType] -> ShowS

data TokenizedType Source #

Instances

Instances details
Eq TokenizedType Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show TokenizedType Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> TokenizedType -> ShowS

show :: TokenizedType -> String

showList :: [TokenizedType] -> ShowS

data EnumeratedType Source #

Instances

Instances details
Eq EnumeratedType Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show EnumeratedType Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> EnumeratedType -> ShowS

show :: EnumeratedType -> String

showList :: [EnumeratedType] -> ShowS

data DefaultDecl Source #

Constructors

REQUIRED 
IMPLIED 
DefaultTo AttValue (Maybe FIXED) 

Instances

Instances details
Eq DefaultDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: DefaultDecl -> DefaultDecl -> Bool

(/=) :: DefaultDecl -> DefaultDecl -> Bool

Show DefaultDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> DefaultDecl -> ShowS

show :: DefaultDecl -> String

showList :: [DefaultDecl] -> ShowS

data FIXED Source #

Constructors

FIXED 

Instances

Instances details
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 ConditionalSect Source #

Instances

Instances details
Eq ConditionalSect Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show ConditionalSect Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> ConditionalSect -> ShowS

show :: ConditionalSect -> String

showList :: [ConditionalSect] -> ShowS

data Ignore Source #

Constructors

Ignore 

Instances

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

Methods

showsPrec :: Int -> Ignore -> ShowS

show :: Ignore -> String

showList :: [Ignore] -> ShowS

data IgnoreSectContents Source #

Instances

Instances details
Eq IgnoreSectContents Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show IgnoreSectContents Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> IgnoreSectContents -> ShowS

show :: IgnoreSectContents -> String

showList :: [IgnoreSectContents] -> ShowS

References

data Reference Source #

Instances

Instances details
Eq Reference Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: Reference -> Reference -> Bool

(/=) :: Reference -> Reference -> Bool

Show Reference Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> Reference -> ShowS

show :: Reference -> String

showList :: [Reference] -> ShowS

Verbatim Reference Source # 
Instance details

Defined in Text.XML.HaXml.Verbatim

Methods

verbatim :: Reference -> String Source #

Entities

data EntityDecl Source #

Instances

Instances details
Eq EntityDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: EntityDecl -> EntityDecl -> Bool

(/=) :: EntityDecl -> EntityDecl -> Bool

Show EntityDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> EntityDecl -> ShowS

show :: EntityDecl -> String

showList :: [EntityDecl] -> ShowS

data GEDecl Source #

Constructors

GEDecl Name EntityDef 

Instances

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

Methods

showsPrec :: Int -> GEDecl -> ShowS

show :: GEDecl -> String

showList :: [GEDecl] -> ShowS

data PEDecl Source #

Constructors

PEDecl Name PEDef 

Instances

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

Methods

showsPrec :: Int -> PEDecl -> ShowS

show :: PEDecl -> String

showList :: [PEDecl] -> ShowS

data EntityDef Source #

Instances

Instances details
Eq EntityDef Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: EntityDef -> EntityDef -> Bool

(/=) :: EntityDef -> EntityDef -> Bool

Show EntityDef Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> EntityDef -> ShowS

show :: EntityDef -> String

showList :: [EntityDef] -> ShowS

data PEDef Source #

Instances

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

data ExternalID Source #

Instances

Instances details
Eq ExternalID Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: ExternalID -> ExternalID -> Bool

(/=) :: ExternalID -> ExternalID -> Bool

Show ExternalID Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> ExternalID -> ShowS

show :: ExternalID -> String

showList :: [ExternalID] -> ShowS

newtype NDataDecl Source #

Constructors

NDATA Name 

Instances

Instances details
Eq NDataDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: NDataDecl -> NDataDecl -> Bool

(/=) :: NDataDecl -> NDataDecl -> Bool

Show NDataDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> NDataDecl -> ShowS

show :: NDataDecl -> String

showList :: [NDataDecl] -> ShowS

data TextDecl Source #

Constructors

TextDecl (Maybe VersionInfo) EncodingDecl 

Instances

Instances details
Eq TextDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: TextDecl -> TextDecl -> Bool

(/=) :: TextDecl -> TextDecl -> Bool

Show TextDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> TextDecl -> ShowS

show :: TextDecl -> String

showList :: [TextDecl] -> ShowS

data ExtParsedEnt i Source #

Constructors

ExtParsedEnt (Maybe TextDecl) (Content i) 

Instances

Instances details
Eq (ExtParsedEnt i) Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: ExtParsedEnt i -> ExtParsedEnt i -> Bool

(/=) :: ExtParsedEnt i -> ExtParsedEnt i -> Bool

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

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> ExtParsedEnt i -> ShowS

show :: ExtParsedEnt i -> String

showList :: [ExtParsedEnt i] -> ShowS

data ExtPE Source #

Constructors

ExtPE (Maybe TextDecl) [ExtSubsetDecl] 

Instances

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

data NotationDecl Source #

Constructors

NOTATION Name (Either ExternalID PublicID) 

Instances

Instances details
Eq NotationDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: NotationDecl -> NotationDecl -> Bool

(/=) :: NotationDecl -> NotationDecl -> Bool

Show NotationDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> NotationDecl -> ShowS

show :: NotationDecl -> String

showList :: [NotationDecl] -> ShowS

newtype PublicID Source #

Constructors

PUBLICID PubidLiteral 

Instances

Instances details
Eq PublicID Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: PublicID -> PublicID -> Bool

(/=) :: PublicID -> PublicID -> Bool

Show PublicID Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> PublicID -> ShowS

show :: PublicID -> String

showList :: [PublicID] -> ShowS

newtype EncodingDecl Source #

Constructors

EncodingDecl String 

Instances

Instances details
Eq EncodingDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: EncodingDecl -> EncodingDecl -> Bool

(/=) :: EncodingDecl -> EncodingDecl -> Bool

Show EncodingDecl Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> EncodingDecl -> ShowS

show :: EncodingDecl -> String

showList :: [EncodingDecl] -> ShowS

data EntityValue Source #

Constructors

EntityValue [EV] 

Instances

Instances details
Eq EntityValue Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: EntityValue -> EntityValue -> Bool

(/=) :: EntityValue -> EntityValue -> Bool

Show EntityValue Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> EntityValue -> ShowS

show :: EntityValue -> String

showList :: [EntityValue] -> ShowS

data EV Source #

Constructors

EVString String 
EVRef Reference 

Instances

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

newtype PubidLiteral Source #

Constructors

PubidLiteral String 

Instances

Instances details
Eq PubidLiteral Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: PubidLiteral -> PubidLiteral -> Bool

(/=) :: PubidLiteral -> PubidLiteral -> Bool

Show PubidLiteral Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> PubidLiteral -> ShowS

show :: PubidLiteral -> String

showList :: [PubidLiteral] -> ShowS

newtype SystemLiteral Source #

Constructors

SystemLiteral String 

Instances

Instances details
Eq SystemLiteral Source # 
Instance details

Defined in Text.XML.HaXml.Types

Show SystemLiteral Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> SystemLiteral -> ShowS

show :: SystemLiteral -> String

showList :: [SystemLiteral] -> 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

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

Instances details
Eq Namespace Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

(==) :: Namespace -> Namespace -> Bool

(/=) :: Namespace -> Namespace -> Bool

Show Namespace Source # 
Instance details

Defined in Text.XML.HaXml.Types

Methods

showsPrec :: Int -> Namespace -> ShowS

show :: Namespace -> String

showList :: [Namespace] -> ShowS

Basic value types

type Name = String Source #

type Names = [Name] Source #

type NmToken = String Source #

type CharData = String Source #