hexpat-0.20.11: XML parser/formatter based on expat

Safe HaskellNone
LanguageHaskell98

Text.XML.Expat.Internal.DocumentClass

Description

Type classes to allow for XML handling functions to be generalized to work with different document types.

Synopsis

Documentation

data XMLDeclaration text Source #

XML declaration, consisting of version, encoding and standalone.

The formatting functions always outputs only UTF-8, regardless of what encoding is specified here. If you want to produce a document in a different encoding, then set the encoding here, format the document, and then convert the output text from UTF-8 to your desired encoding using some text conversion library.

Constructors

XMLDeclaration text (Maybe text) (Maybe Bool) 

Instances

Eq text => Eq (XMLDeclaration text) Source # 

Methods

(==) :: XMLDeclaration text -> XMLDeclaration text -> Bool #

(/=) :: XMLDeclaration text -> XMLDeclaration text -> Bool #

Show text => Show (XMLDeclaration text) Source # 

data DocumentTypeDeclaration c tag text Source #

Stub for future expansion.

Instances

data Misc text Source #

Constructors

Comment !text 
ProcessingInstruction !text !text 

Instances

Eq text => Eq (Misc text) Source # 

Methods

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

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

Show text => Show (Misc text) Source # 

Methods

showsPrec :: Int -> Misc text -> ShowS #

show :: Misc text -> String #

showList :: [Misc text] -> ShowS #

NFData text => NFData (Misc text) Source # 

Methods

rnf :: Misc text -> () #

type family NodeType (d :: (* -> *) -> * -> * -> *) :: (* -> *) -> * -> * -> * Source #

Instances

type NodeType (DocumentG ann) Source # 
type NodeType (DocumentG ann) = NodeG ann

class (Functor c, List c, NodeClass (NodeType d) c) => DocumentClass d c where Source #

Methods

getXMLDeclaration :: d c tag text -> Maybe (XMLDeclaration text) Source #

Get the XML declaration for this document.

getDocumentTypeDeclaration :: d c tag text -> Maybe (DocumentTypeDeclaration c tag text) Source #

Get the Document Type Declaration (DTD) for this document.

getTopLevelMiscs :: d c tag text -> c (Misc text) Source #

Get the top-level Misc nodes for this document.

getRoot :: d c tag text -> NodeType d c tag text Source #

Get the root element for this document.

mkDocument :: Maybe (XMLDeclaration text) -> Maybe (DocumentTypeDeclaration c tag text) -> c (Misc text) -> NodeType d c tag text -> d c tag text Source #

Make a document with the specified fields.

Instances

(Functor c, List c) => DocumentClass (DocumentG ann) c Source # 

Methods

getXMLDeclaration :: DocumentG ann c tag text -> Maybe (XMLDeclaration text) Source #

getDocumentTypeDeclaration :: DocumentG ann c tag text -> Maybe (DocumentTypeDeclaration c tag text) Source #

getTopLevelMiscs :: DocumentG ann c tag text -> c (Misc text) Source #

getRoot :: DocumentG ann c tag text -> NodeType (DocumentG ann) c tag text Source #

mkDocument :: Maybe (XMLDeclaration text) -> Maybe (DocumentTypeDeclaration c tag text) -> c (Misc text) -> NodeType (DocumentG ann) c tag text -> DocumentG ann c tag text Source #

mkPlainDocument :: DocumentClass d c => NodeType d c tag text -> d c tag text Source #

Make a document with the specified root node and all other information set to defaults.

modifyXMLDeclaration :: DocumentClass d c => (Maybe (XMLDeclaration text) -> Maybe (XMLDeclaration text)) -> d c tag text -> d c tag text Source #

modifyDocumentTypeDeclaration :: DocumentClass d c => (Maybe (DocumentTypeDeclaration c tag text) -> Maybe (DocumentTypeDeclaration c tag text)) -> d c tag text -> d c tag text Source #

modifyTopLevelMiscs :: DocumentClass d c => (c (Misc text) -> c (Misc text)) -> d c tag text -> d c tag text Source #

modifyRoot :: DocumentClass d c => (NodeType d c tag text -> NodeType d c tag text) -> d c tag text -> d c tag text Source #