xml-types-0.3.8: Basic types for representing XML

Copyright2010-2011 John Millikin
LicenseMIT
Safe HaskellSafe
LanguageHaskell2010

Data.XML.Types

Contents

Description

Basic types for representing XML.

The idea is to have a full set of appropriate types, which various XML libraries can share. Instead of having equivalent-but-incompatible types for every binding, parser, or client, they all share the same types can can thus interoperate easily.

This library contains complete types for most parts of an XML document, including the prologue, node tree, and doctype. Some basic combinators are included for common tasks, including traversing the node tree and filtering children.

Synopsis

Types

Document prologue

data Document Source #

Instances
Eq Document Source # 
Instance details

Defined in Data.XML.Types

Data Document Source # 
Instance details

Defined in Data.XML.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Document -> c Document #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Document #

toConstr :: Document -> Constr #

dataTypeOf :: Document -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Document) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Document) #

gmapT :: (forall b. Data b => b -> b) -> Document -> Document #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Document -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Document -> r #

gmapQ :: (forall d. Data d => d -> u) -> Document -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Document -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Document -> m Document #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Document -> m Document #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Document -> m Document #

Ord Document Source # 
Instance details

Defined in Data.XML.Types

Show Document Source # 
Instance details

Defined in Data.XML.Types

Generic Document Source # 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Document :: Type -> Type #

Methods

from :: Document -> Rep Document x #

to :: Rep Document x -> Document #

NFData Document Source # 
Instance details

Defined in Data.XML.Types

Methods

rnf :: Document -> () #

type Rep Document Source # 
Instance details

Defined in Data.XML.Types

type Rep Document = D1 (MetaData "Document" "Data.XML.Types" "xml-types-0.3.8-Ild6ntrYnKf3VPv4eSNXKw" False) (C1 (MetaCons "Document" PrefixI True) (S1 (MetaSel (Just "documentPrologue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Prologue) :*: (S1 (MetaSel (Just "documentRoot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Element) :*: S1 (MetaSel (Just "documentEpilogue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Miscellaneous]))))

data Prologue Source #

Instances
Eq Prologue Source # 
Instance details

Defined in Data.XML.Types

Data Prologue Source # 
Instance details

Defined in Data.XML.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Prologue -> c Prologue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Prologue #

toConstr :: Prologue -> Constr #

dataTypeOf :: Prologue -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Prologue) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Prologue) #

gmapT :: (forall b. Data b => b -> b) -> Prologue -> Prologue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Prologue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Prologue -> r #

gmapQ :: (forall d. Data d => d -> u) -> Prologue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Prologue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Prologue -> m Prologue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Prologue -> m Prologue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Prologue -> m Prologue #

Ord Prologue Source # 
Instance details

Defined in Data.XML.Types

Show Prologue Source # 
Instance details

Defined in Data.XML.Types

Generic Prologue Source # 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Prologue :: Type -> Type #

Methods

from :: Prologue -> Rep Prologue x #

to :: Rep Prologue x -> Prologue #

NFData Prologue Source # 
Instance details

Defined in Data.XML.Types

Methods

rnf :: Prologue -> () #

type Rep Prologue Source # 
Instance details

Defined in Data.XML.Types

type Rep Prologue = D1 (MetaData "Prologue" "Data.XML.Types" "xml-types-0.3.8-Ild6ntrYnKf3VPv4eSNXKw" False) (C1 (MetaCons "Prologue" PrefixI True) (S1 (MetaSel (Just "prologueBefore") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Miscellaneous]) :*: (S1 (MetaSel (Just "prologueDoctype") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Doctype)) :*: S1 (MetaSel (Just "prologueAfter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Miscellaneous]))))

data Instruction Source #

Instances
Eq Instruction Source # 
Instance details

Defined in Data.XML.Types

Data Instruction Source # 
Instance details

Defined in Data.XML.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Instruction -> c Instruction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Instruction #

toConstr :: Instruction -> Constr #

dataTypeOf :: Instruction -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Instruction) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Instruction) #

gmapT :: (forall b. Data b => b -> b) -> Instruction -> Instruction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Instruction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Instruction -> r #

gmapQ :: (forall d. Data d => d -> u) -> Instruction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Instruction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Instruction -> m Instruction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Instruction -> m Instruction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Instruction -> m Instruction #

Ord Instruction Source # 
Instance details

Defined in Data.XML.Types

Show Instruction Source # 
Instance details

Defined in Data.XML.Types

Generic Instruction Source # 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Instruction :: Type -> Type #

NFData Instruction Source # 
Instance details

Defined in Data.XML.Types

Methods

rnf :: Instruction -> () #

type Rep Instruction Source # 
Instance details

Defined in Data.XML.Types

type Rep Instruction = D1 (MetaData "Instruction" "Data.XML.Types" "xml-types-0.3.8-Ild6ntrYnKf3VPv4eSNXKw" False) (C1 (MetaCons "Instruction" PrefixI True) (S1 (MetaSel (Just "instructionTarget") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "instructionData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Miscellaneous Source #

Instances
Eq Miscellaneous Source # 
Instance details

Defined in Data.XML.Types

Data Miscellaneous Source # 
Instance details

Defined in Data.XML.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Miscellaneous -> c Miscellaneous #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Miscellaneous #

toConstr :: Miscellaneous -> Constr #

dataTypeOf :: Miscellaneous -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Miscellaneous) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Miscellaneous) #

gmapT :: (forall b. Data b => b -> b) -> Miscellaneous -> Miscellaneous #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Miscellaneous -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Miscellaneous -> r #

gmapQ :: (forall d. Data d => d -> u) -> Miscellaneous -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Miscellaneous -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Miscellaneous -> m Miscellaneous #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Miscellaneous -> m Miscellaneous #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Miscellaneous -> m Miscellaneous #

Ord Miscellaneous Source # 
Instance details

Defined in Data.XML.Types

Show Miscellaneous Source # 
Instance details

Defined in Data.XML.Types

Generic Miscellaneous Source # 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Miscellaneous :: Type -> Type #

NFData Miscellaneous Source # 
Instance details

Defined in Data.XML.Types

Methods

rnf :: Miscellaneous -> () #

type Rep Miscellaneous Source # 
Instance details

Defined in Data.XML.Types

type Rep Miscellaneous = D1 (MetaData "Miscellaneous" "Data.XML.Types" "xml-types-0.3.8-Ild6ntrYnKf3VPv4eSNXKw" False) (C1 (MetaCons "MiscInstruction" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Instruction)) :+: C1 (MetaCons "MiscComment" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

Document body

data Node Source #

Instances
Eq Node Source # 
Instance details

Defined in Data.XML.Types

Methods

(==) :: Node -> Node -> Bool #

(/=) :: Node -> Node -> Bool #

Data Node Source # 
Instance details

Defined in Data.XML.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Node -> c Node #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Node #

toConstr :: Node -> Constr #

dataTypeOf :: Node -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Node) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Node) #

gmapT :: (forall b. Data b => b -> b) -> Node -> Node #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Node -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Node -> r #

gmapQ :: (forall d. Data d => d -> u) -> Node -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Node -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Node -> m Node #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Node -> m Node #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Node -> m Node #

Ord Node Source # 
Instance details

Defined in Data.XML.Types

Methods

compare :: Node -> Node -> Ordering #

(<) :: Node -> Node -> Bool #

(<=) :: Node -> Node -> Bool #

(>) :: Node -> Node -> Bool #

(>=) :: Node -> Node -> Bool #

max :: Node -> Node -> Node #

min :: Node -> Node -> Node #

Show Node Source # 
Instance details

Defined in Data.XML.Types

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

IsString Node Source # 
Instance details

Defined in Data.XML.Types

Methods

fromString :: String -> Node #

Generic Node Source # 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Node :: Type -> Type #

Methods

from :: Node -> Rep Node x #

to :: Rep Node x -> Node #

NFData Node Source # 
Instance details

Defined in Data.XML.Types

Methods

rnf :: Node -> () #

type Rep Node Source # 
Instance details

Defined in Data.XML.Types

data Element Source #

Constructors

Element 
Instances
Eq Element Source # 
Instance details

Defined in Data.XML.Types

Methods

(==) :: Element -> Element -> Bool #

(/=) :: Element -> Element -> Bool #

Data Element Source # 
Instance details

Defined in Data.XML.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Element -> c Element #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Element #

toConstr :: Element -> Constr #

dataTypeOf :: Element -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Element) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Element) #

gmapT :: (forall b. Data b => b -> b) -> Element -> Element #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Element -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Element -> r #

gmapQ :: (forall d. Data d => d -> u) -> Element -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Element -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Element -> m Element #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Element -> m Element #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Element -> m Element #

Ord Element Source # 
Instance details

Defined in Data.XML.Types

Show Element Source # 
Instance details

Defined in Data.XML.Types

Generic Element Source # 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Element :: Type -> Type #

Methods

from :: Element -> Rep Element x #

to :: Rep Element x -> Element #

NFData Element Source # 
Instance details

Defined in Data.XML.Types

Methods

rnf :: Element -> () #

type Rep Element Source # 
Instance details

Defined in Data.XML.Types

type Rep Element = D1 (MetaData "Element" "Data.XML.Types" "xml-types-0.3.8-Ild6ntrYnKf3VPv4eSNXKw" False) (C1 (MetaCons "Element" PrefixI True) (S1 (MetaSel (Just "elementName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name) :*: (S1 (MetaSel (Just "elementAttributes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Name, [Content])]) :*: S1 (MetaSel (Just "elementNodes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node]))))

data Content Source #

Constructors

ContentText Text 
ContentEntity Text

For pass-through parsing

Instances
Eq Content Source # 
Instance details

Defined in Data.XML.Types

Methods

(==) :: Content -> Content -> Bool #

(/=) :: Content -> Content -> Bool #

Data Content Source # 
Instance details

Defined in Data.XML.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Content -> c Content #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Content #

toConstr :: Content -> Constr #

dataTypeOf :: Content -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Content) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Content) #

gmapT :: (forall b. Data b => b -> b) -> Content -> Content #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Content -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Content -> r #

gmapQ :: (forall d. Data d => d -> u) -> Content -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Content -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Content -> m Content #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Content -> m Content #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Content -> m Content #

Ord Content Source # 
Instance details

Defined in Data.XML.Types

Show Content Source # 
Instance details

Defined in Data.XML.Types

IsString Content Source # 
Instance details

Defined in Data.XML.Types

Methods

fromString :: String -> Content #

Generic Content Source # 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Content :: Type -> Type #

Methods

from :: Content -> Rep Content x #

to :: Rep Content x -> Content #

NFData Content Source # 
Instance details

Defined in Data.XML.Types

Methods

rnf :: Content -> () #

type Rep Content Source # 
Instance details

Defined in Data.XML.Types

type Rep Content = D1 (MetaData "Content" "Data.XML.Types" "xml-types-0.3.8-Ild6ntrYnKf3VPv4eSNXKw" False) (C1 (MetaCons "ContentText" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "ContentEntity" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Name Source #

A fully qualified name.

Prefixes are not semantically important; they are included only to simplify pass-through parsing. When comparing names with Eq or Ord methods, prefixes are ignored.

The IsString instance supports Clark notation; see http://www.jclark.com/xml/xmlns.htm and http://infohost.nmt.edu/tcc/help/pubs/pylxml/etree-QName.html. Use the OverloadedStrings language extension for very simple Name construction:

myname :: Name
myname = "{http://example.com/ns/my-namespace}my-name"
Instances
Eq Name Source # 
Instance details

Defined in Data.XML.Types

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Data Name Source # 
Instance details

Defined in Data.XML.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name #

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) #

gmapT :: (forall b. Data b => b -> b) -> Name -> Name #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r #

gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name #

Ord Name Source # 
Instance details

Defined in Data.XML.Types

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 
Instance details

Defined in Data.XML.Types

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

IsString Name Source # 
Instance details

Defined in Data.XML.Types

Methods

fromString :: String -> Name #

Generic Name Source # 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

NFData Name Source # 
Instance details

Defined in Data.XML.Types

Methods

rnf :: Name -> () #

type Rep Name Source # 
Instance details

Defined in Data.XML.Types

type Rep Name = D1 (MetaData "Name" "Data.XML.Types" "xml-types-0.3.8-Ild6ntrYnKf3VPv4eSNXKw" False) (C1 (MetaCons "Name" PrefixI True) (S1 (MetaSel (Just "nameLocalName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Just "nameNamespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "namePrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))))

Doctypes

data Doctype Source #

Note: due to the incredible complexity of DTDs, this type only supports external subsets. I've tried adding internal subset types, but they quickly gain more code than the rest of this module put together.

It is possible that some future version of this library might support internal subsets, but I am no longer actively working on adding them.

Constructors

Doctype 
Instances
Eq Doctype Source # 
Instance details

Defined in Data.XML.Types

Methods

(==) :: Doctype -> Doctype -> Bool #

(/=) :: Doctype -> Doctype -> Bool #

Data Doctype Source # 
Instance details

Defined in Data.XML.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Doctype -> c Doctype #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Doctype #

toConstr :: Doctype -> Constr #

dataTypeOf :: Doctype -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Doctype) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doctype) #

gmapT :: (forall b. Data b => b -> b) -> Doctype -> Doctype #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Doctype -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Doctype -> r #

gmapQ :: (forall d. Data d => d -> u) -> Doctype -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Doctype -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Doctype -> m Doctype #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Doctype -> m Doctype #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Doctype -> m Doctype #

Ord Doctype Source # 
Instance details

Defined in Data.XML.Types

Show Doctype Source # 
Instance details

Defined in Data.XML.Types

Generic Doctype Source # 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Doctype :: Type -> Type #

Methods

from :: Doctype -> Rep Doctype x #

to :: Rep Doctype x -> Doctype #

NFData Doctype Source # 
Instance details

Defined in Data.XML.Types

Methods

rnf :: Doctype -> () #

type Rep Doctype Source # 
Instance details

Defined in Data.XML.Types

type Rep Doctype = D1 (MetaData "Doctype" "Data.XML.Types" "xml-types-0.3.8-Ild6ntrYnKf3VPv4eSNXKw" False) (C1 (MetaCons "Doctype" PrefixI True) (S1 (MetaSel (Just "doctypeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "doctypeID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ExternalID))))

data ExternalID Source #

Constructors

SystemID Text 
PublicID Text Text 
Instances
Eq ExternalID Source # 
Instance details

Defined in Data.XML.Types

Data ExternalID Source # 
Instance details

Defined in Data.XML.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExternalID -> c ExternalID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExternalID #

toConstr :: ExternalID -> Constr #

dataTypeOf :: ExternalID -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExternalID) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExternalID) #

gmapT :: (forall b. Data b => b -> b) -> ExternalID -> ExternalID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExternalID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExternalID -> r #

gmapQ :: (forall d. Data d => d -> u) -> ExternalID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExternalID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExternalID -> m ExternalID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExternalID -> m ExternalID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExternalID -> m ExternalID #

Ord ExternalID Source # 
Instance details

Defined in Data.XML.Types

Show ExternalID Source # 
Instance details

Defined in Data.XML.Types

Generic ExternalID Source # 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep ExternalID :: Type -> Type #

NFData ExternalID Source # 
Instance details

Defined in Data.XML.Types

Methods

rnf :: ExternalID -> () #

type Rep ExternalID Source # 
Instance details

Defined in Data.XML.Types

Incremental processing

data Event Source #

Some XML processing tools are incremental, and work in terms of events rather than node trees. The Event type allows a document to be fully specified as a sequence of events.

Event-based XML libraries include:

Instances
Eq Event Source # 
Instance details

Defined in Data.XML.Types

Methods

(==) :: Event -> Event -> Bool #

(/=) :: Event -> Event -> Bool #

Data Event Source # 
Instance details

Defined in Data.XML.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Event -> c Event #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Event #

toConstr :: Event -> Constr #

dataTypeOf :: Event -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Event) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Event) #

gmapT :: (forall b. Data b => b -> b) -> Event -> Event #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r #

gmapQ :: (forall d. Data d => d -> u) -> Event -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Event -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Event -> m Event #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Event -> m Event #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Event -> m Event #

Ord Event Source # 
Instance details

Defined in Data.XML.Types

Methods

compare :: Event -> Event -> Ordering #

(<) :: Event -> Event -> Bool #

(<=) :: Event -> Event -> Bool #

(>) :: Event -> Event -> Bool #

(>=) :: Event -> Event -> Bool #

max :: Event -> Event -> Event #

min :: Event -> Event -> Event #

Show Event Source # 
Instance details

Defined in Data.XML.Types

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 
Instance details

Defined in Data.XML.Types

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

NFData Event Source # 
Instance details

Defined in Data.XML.Types

Methods

rnf :: Event -> () #

type Rep Event Source # 
Instance details

Defined in Data.XML.Types

type Rep Event = D1 (MetaData "Event" "Data.XML.Types" "xml-types-0.3.8-Ild6ntrYnKf3VPv4eSNXKw" False) (((C1 (MetaCons "EventBeginDocument" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EventEndDocument" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "EventBeginDoctype" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe ExternalID))) :+: (C1 (MetaCons "EventEndDoctype" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EventInstruction" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Instruction))))) :+: ((C1 (MetaCons "EventBeginElement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Name, [Content])])) :+: C1 (MetaCons "EventEndElement" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name))) :+: (C1 (MetaCons "EventContent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Content)) :+: (C1 (MetaCons "EventComment" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "EventCDATA" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))))

Combinators

Filters

Element traversal

Node traversal

Attributes