xml-conduit-1.4.0: Pure-Haskell utilities for dealing with XML with the conduit package.

Safe HaskellNone
LanguageHaskell98

Text.XML

Contents

Description

DOM-based parsing and rendering.

This module requires that all entities be resolved at parsing. If you need to interact with unresolved entities, please use Text.XML.Unresolved. This is the recommended module for most uses cases.

While many of the datatypes in this module are simply re-exported from Data.XML.Types, Document, Node and Element are all redefined here to disallow the possibility of unresolved entities. Conversion functions are provided to switch between the two sets of datatypes.

For simpler, bidirectional traversal of the DOM tree, see the Text.XML.Cursor module.

Synopsis

Data types

data Document Source #

Instances

Eq Document Source # 
Data Document Source # 

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 #

Show Document Source # 
ToMarkup Document Source # 
NFData Document Source # 

Methods

rnf :: Document -> () #

data Prologue :: * #

Instances

Eq Prologue 
Data Prologue 

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 
Show Prologue 
Generic Prologue 

Associated Types

type Rep Prologue :: * -> * #

Methods

from :: Prologue -> Rep Prologue x #

to :: Rep Prologue x -> Prologue #

NFData Prologue 

Methods

rnf :: Prologue -> () #

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

data Instruction :: * #

Instances

Eq Instruction 
Data Instruction 

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 
Show Instruction 
Generic Instruction 

Associated Types

type Rep Instruction :: * -> * #

NFData Instruction 

Methods

rnf :: Instruction -> () #

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

data Miscellaneous :: * #

Instances

Eq Miscellaneous 
Data Miscellaneous 

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 
Show Miscellaneous 
Generic Miscellaneous 

Associated Types

type Rep Miscellaneous :: * -> * #

NFData Miscellaneous 

Methods

rnf :: Miscellaneous -> () #

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

data Node Source #

Instances

Eq Node Source # 

Methods

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

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

Data Node Source # 

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 # 

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 # 

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

ToMarkup Node Source # 
NFData Node Source # 

Methods

rnf :: Node -> () #

data Element Source #

Instances

Eq Element Source # 

Methods

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

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

Data Element Source # 

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 # 
Show Element Source # 
ToMarkup Element Source #

Note that the special element name {http:/www.snoyman.comxml2html}ie-cond with the single attribute cond is used to indicate an IE conditional comment.

NFData Element Source # 

Methods

rnf :: Element -> () #

data Name :: * #

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 

Methods

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

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

Data Name 

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 

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 

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

IsString Name 

Methods

fromString :: String -> Name #

Generic Name 

Associated Types

type Rep Name :: * -> * #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

NFData Name 

Methods

rnf :: Name -> () #

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

data Doctype :: * #

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 

Methods

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

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

Data Doctype 

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 
Show Doctype 
Generic Doctype 

Associated Types

type Rep Doctype :: * -> * #

Methods

from :: Doctype -> Rep Doctype x #

to :: Rep Doctype x -> Doctype #

NFData Doctype 

Methods

rnf :: Doctype -> () #

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

data ExternalID :: * #

Constructors

SystemID Text 
PublicID Text Text 

Instances

Eq ExternalID 
Data ExternalID 

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 
Show ExternalID 
Generic ExternalID 

Associated Types

type Rep ExternalID :: * -> * #

NFData ExternalID 

Methods

rnf :: ExternalID -> () #

type Rep ExternalID 

Parsing

Files

Bytes

Text

Other

Rendering

Settings

def :: Default a => a #

The default value for this type.

Parsing

psRetainNamespaces :: ParseSettings -> Bool Source #

Whether the original xmlns attributes should be retained in the parsed values. For more information on motivation, see:

https://github.com/snoyberg/xml/issues/38

Default: False

Since 1.2.1

Entity decoding

decodeXmlEntities :: DecodeEntities Source #

Default implementation of DecodeEntities: handles numeric entities and the five standard character entities (lt, gt, amp, quot, apos).

decodeHtmlEntities :: DecodeEntities Source #

HTML4-compliant entity decoder. Handles numerics, the five standard character entities, and the additional 248 entities defined by HTML 4 and XHTML 1.

Note that HTML 5 introduces a drastically larger number of entities, and this code does not recognize most of them.

Rendering

rsNamespaces :: RenderSettings -> [(Text, Text)] Source #

Defines some top level namespace definitions to be used, in the form of (prefix, namespace). This has absolutely no impact on the meaning of your documents, but can increase readability by moving commonly used namespace declarations to the top level.

rsAttrOrder :: RenderSettings -> Name -> Map Name Text -> [(Name, Text)] Source #

Specify how to turn the unordered attributes used by the Text.XML module into an ordered list.

rsUseCDATA :: RenderSettings -> Content -> Bool Source #

Determines if for a given text content the renderer should use a CDATA node.

Default: False

Since: 1.3.3

orderAttrs :: [(Name, [Name])] -> Name -> Map Name Text -> [(Name, Text)] Source #

Convenience function to create an ordering function suitable for use as the value of rsAttrOrder. The ordering function is created from an explicit ordering of the attributes, specified as a list of tuples, as follows: In each tuple, the first component is the Name of an element, and the second component is a list of attributes names. When the given element is rendered, the attributes listed, when present, appear first in the given order, followed by any other attributes in arbitrary order. If an element does not appear, all of its attributes are rendered in arbitrary order.

Conversion