X-0.3.1.0: A light-weight XML library

Copyright(c) Herbert Valerio Riedel 2019
LicenseGPL-3.0-or-later
Safe HaskellSafe
LanguageHaskell2010

Text.XML.Types

Contents

Description

Basic XML types.

Synopsis

Root node representation

data Root' cnode Source #

Represents the implicit root node of an XML document

Since: 0.2.0

Constructors

Root 

Fields

Instances
Functor Root' Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

fmap :: (a -> b) -> Root' a -> Root' b #

(<$) :: a -> Root' b -> Root' a #

Foldable Root' Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

fold :: Monoid m => Root' m -> m #

foldMap :: Monoid m => (a -> m) -> Root' a -> m #

foldr :: (a -> b -> b) -> b -> Root' a -> b #

foldr' :: (a -> b -> b) -> b -> Root' a -> b #

foldl :: (b -> a -> b) -> b -> Root' a -> b #

foldl' :: (b -> a -> b) -> b -> Root' a -> b #

foldr1 :: (a -> a -> a) -> Root' a -> a #

foldl1 :: (a -> a -> a) -> Root' a -> a #

toList :: Root' a -> [a] #

null :: Root' a -> Bool #

length :: Root' a -> Int #

elem :: Eq a => a -> Root' a -> Bool #

maximum :: Ord a => Root' a -> a #

minimum :: Ord a => Root' a -> a #

sum :: Num a => Root' a -> a #

product :: Num a => Root' a -> a #

Traversable Root' Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

traverse :: Applicative f => (a -> f b) -> Root' a -> f (Root' b) #

sequenceA :: Applicative f => Root' (f a) -> f (Root' a) #

mapM :: Monad m => (a -> m b) -> Root' a -> m (Root' b) #

sequence :: Monad m => Root' (m a) -> m (Root' a) #

Data cnode => Data (Root' cnode) Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Root' cnode -> c (Root' cnode) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Root' cnode) #

toConstr :: Root' cnode -> Constr #

dataTypeOf :: Root' cnode -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Root' cnode -> Root' cnode #

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

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

gmapQ :: (forall d. Data d => d -> u) -> Root' cnode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Root' cnode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Root' cnode -> m (Root' cnode) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Root' cnode -> m (Root' cnode) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Root' cnode -> m (Root' cnode) #

Show cnode => Show (Root' cnode) Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

showsPrec :: Int -> Root' cnode -> ShowS #

show :: Root' cnode -> String #

showList :: [Root' cnode] -> ShowS #

Generic (Root' cnode) Source # 
Instance details

Defined in Text.XML.Types.Core

Associated Types

type Rep (Root' cnode) :: Type -> Type #

Methods

from :: Root' cnode -> Rep (Root' cnode) x #

to :: Rep (Root' cnode) x -> Root' cnode #

NFData cnode => NFData (Root' cnode) Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

rnf :: Root' cnode -> () #

type Rep (Root' cnode) Source # 
Instance details

Defined in Text.XML.Types.Core

type MiscNodes = [Either Comment PI] Source #

Sequence of "miscellaneous" nodes

Since: 0.2.0

data XmlDeclaration Source #

Denotes the <?xml version="1.0" encoding="..." standalone="..." ?> declaration

Since: 0.2.0

Instances
Data XmlDeclaration Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

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

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

toConstr :: XmlDeclaration -> Constr #

dataTypeOf :: XmlDeclaration -> DataType #

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

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

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

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

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

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

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

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

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

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

Show XmlDeclaration Source # 
Instance details

Defined in Text.XML.Types.Core

Generic XmlDeclaration Source # 
Instance details

Defined in Text.XML.Types.Core

Associated Types

type Rep XmlDeclaration :: Type -> Type #

NFData XmlDeclaration Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

rnf :: XmlDeclaration -> () #

type Rep XmlDeclaration Source # 
Instance details

Defined in Text.XML.Types.Core

Element nodes

data Element' cnode Source #

XML elements

Constructors

Element 

Fields

Instances
Functor Element' Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

fmap :: (a -> b) -> Element' a -> Element' b #

(<$) :: a -> Element' b -> Element' a #

Foldable Element' Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

fold :: Monoid m => Element' m -> m #

foldMap :: Monoid m => (a -> m) -> Element' a -> m #

foldr :: (a -> b -> b) -> b -> Element' a -> b #

foldr' :: (a -> b -> b) -> b -> Element' a -> b #

foldl :: (b -> a -> b) -> b -> Element' a -> b #

foldl' :: (b -> a -> b) -> b -> Element' a -> b #

foldr1 :: (a -> a -> a) -> Element' a -> a #

foldl1 :: (a -> a -> a) -> Element' a -> a #

toList :: Element' a -> [a] #

null :: Element' a -> Bool #

length :: Element' a -> Int #

elem :: Eq a => a -> Element' a -> Bool #

maximum :: Ord a => Element' a -> a #

minimum :: Ord a => Element' a -> a #

sum :: Num a => Element' a -> a #

product :: Num a => Element' a -> a #

Traversable Element' Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

traverse :: Applicative f => (a -> f b) -> Element' a -> f (Element' b) #

sequenceA :: Applicative f => Element' (f a) -> f (Element' a) #

mapM :: Monad m => (a -> m b) -> Element' a -> m (Element' b) #

sequence :: Monad m => Element' (m a) -> m (Element' a) #

IsContent Element Source # 
Instance details

Defined in Text.XML.Types.Internal

Node Element Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> Element -> Element Source #

Data cnode => Data (Element' cnode) Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

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

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

toConstr :: Element' cnode -> Constr #

dataTypeOf :: Element' cnode -> DataType #

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

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

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

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

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

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

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

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

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

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

Show cnode => Show (Element' cnode) Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

showsPrec :: Int -> Element' cnode -> ShowS #

show :: Element' cnode -> String #

showList :: [Element' cnode] -> ShowS #

Generic (Element' cnode) Source # 
Instance details

Defined in Text.XML.Types.Core

Associated Types

type Rep (Element' cnode) :: Type -> Type #

Methods

from :: Element' cnode -> Rep (Element' cnode) x #

to :: Rep (Element' cnode) x -> Element' cnode #

NFData cnode => NFData (Element' cnode) Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

rnf :: Element' cnode -> () #

Node [Element] Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> [Element] -> Element Source #

Node ([Attr], [Element]) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> ([Attr], [Element]) -> Element Source #

Node ([Attr], Element) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> ([Attr], Element) -> Element Source #

Node (Attr, Element) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> (Attr, Element) -> Element Source #

type Rep (Element' cnode) Source # 
Instance details

Defined in Text.XML.Types.Core

type Rep (Element' cnode) = D1 (MetaData "Element'" "Text.XML.Types.Core" "X-0.3.1.0-FtMev6r53LM7jz5ldGnRwK" False) (C1 (MetaCons "Element" PrefixI True) (S1 (MetaSel (Just "elName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 QName) :*: (S1 (MetaSel (Just "elAttribs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Attr]) :*: S1 (MetaSel (Just "elContent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [cnode]))))

blank_element :: Element Source #

Blank elements

__NOTE: This value is not a propler Element.

xmlns_elem_wellformed :: [(ShortText, URI)] -> Element -> Bool Source #

Verify whether sub-tree is wellformed with respect to namespaces

The first argument denotes an optional parent context of xmlns-declarations that are in scope (where ShortText and URI have the same semantics as for the arguments of xmlns_attr). In case of duplicate prefixes, earlier entries shadow later entries.

NOTE: This function doesn't take into account the namespace prefixes of xs:QName-valued text-nodes or attributes; if you need to handle such cases, see the xmlns_elem_wellformed' function.

Since: 0.3.1

xmlns_elem_wellformed' :: (Either Attr [Content] -> [QName] -> [QName]) -> [(ShortText, URI)] -> Element -> Bool Source #

Variant of xmlns_elem_wellformed which supports introspecting xs:QName valued attributes and text-nodes.

The first argument is a function for extracting a (possibly empty) list of QNames from attribute values and text-nodes:

  • Its first Either Attr [Content] argument denotes either a (non-empty) attribute or an element's children which contain at least one non-empty text-node fragment.
  • The second argument of type [QName] denotes the path of element QNames in reverse order (i.e. the top-level element of the traversal is last item in this list) leading to the currently focused attribute or text-node.

This QName extracing function may return a list to accomodate for test fields which may contain multiple xs:QName such as e.g. for

<xs:list itemType="xs:QName" />

The qnameFromText function can be useful for decoding xs:QNames text values.

xmlns_elem_wellformed' (\_ _ -> []) topns el = xmlns_elem_wellformed topns el

Since: 0.3.1

Element attributes

data Attr Source #

XML attributes

Constructors

Attr 

Fields

Instances
Eq Attr Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

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

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

Data Attr Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

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

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

toConstr :: Attr -> Constr #

dataTypeOf :: Attr -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Attr Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

compare :: Attr -> Attr -> Ordering #

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

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

(>) :: Attr -> Attr -> Bool #

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

max :: Attr -> Attr -> Attr #

min :: Attr -> Attr -> Attr #

Show Attr Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

showsPrec :: Int -> Attr -> ShowS #

show :: Attr -> String #

showList :: [Attr] -> ShowS #

Generic Attr Source # 
Instance details

Defined in Text.XML.Types.Core

Associated Types

type Rep Attr :: Type -> Type #

Methods

from :: Attr -> Rep Attr x #

to :: Rep Attr x -> Attr #

NFData Attr Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

rnf :: Attr -> () #

Node Attr Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> Attr -> Element Source #

Node [Attr] Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> [Attr] -> Element Source #

Node ([Attr], [CData]) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> ([Attr], [CData]) -> Element Source #

Node ([Attr], [Element]) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> ([Attr], [Element]) -> Element Source #

Node ([Attr], [Content]) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> ([Attr], [Content]) -> Element Source #

Node ([Attr], Text) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> ([Attr], Text) -> Element Source #

Node ([Attr], ShortText) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> ([Attr], ShortText) -> Element Source #

Node ([Attr], CData) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> ([Attr], CData) -> Element Source #

Node ([Attr], Element) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> ([Attr], Element) -> Element Source #

Node ([Attr], Content) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> ([Attr], Content) -> Element Source #

Node (Attr, Text) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> (Attr, Text) -> Element Source #

Node (Attr, ShortText) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> (Attr, ShortText) -> Element Source #

Node (Attr, CData) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> (Attr, CData) -> Element Source #

Node (Attr, Element) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> (Attr, Element) -> Element Source #

Node (Attr, Content) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> (Attr, Content) -> Element Source #

type Rep Attr Source # 
Instance details

Defined in Text.XML.Types.Core

type Rep Attr = D1 (MetaData "Attr" "Text.XML.Types.Core" "X-0.3.1.0-FtMev6r53LM7jz5ldGnRwK" False) (C1 (MetaCons "Attr" PrefixI True) (S1 (MetaSel (Just "attrKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 QName) :*: S1 (MetaSel (Just "attrVal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

xmlns_attr Source #

Arguments

:: ShortText

namespace prefix (if empty, denotes the default namespace; see also xmlns_def_attr)

-> URI

Namespace URI

-> Attr 

Smart constructor for xmlns:<prefix> = <namespace-uri>

Invariant: <namespace-uri> MUST be non-empty for non-empty prefixes

Since: 0.3.0

xmlns_def_attr Source #

Arguments

:: URI

Default namespace URI (use empty URI to reset default namespace)

-> Attr 

Smart constructor for xmlns = [<namespace-uri>|""] (i.e. for declaring the default namespace)

xmlns_attr "" ns == xmlns_def_attr ns

Since: 0.3.0

xmlns_from_attr :: Attr -> Maybe (ShortText, URI) Source #

Convert xmlns Attr into a (prefix,namespace-uri) pair; returns Nothing if the argument isn't a xmlns attribute.

An empty prefix denotes the default-namespace

xmlns_from_attr (xmlns_attr pfx ns) == Just (pfx,ns)

Since: 0.3.0

Non-element content nodes

data Content Source #

XML content

Since: 0.2.0

Instances
Data Content Source # 
Instance details

Defined in Text.XML.Types.Core

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 #

Show Content Source # 
Instance details

Defined in Text.XML.Types.Core

Generic Content Source # 
Instance details

Defined in Text.XML.Types.Core

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 Text.XML.Types.Core

Methods

rnf :: Content -> () #

IsContent Element Source # 
Instance details

Defined in Text.XML.Types.Internal

IsContent Content Source # 
Instance details

Defined in Text.XML.Types.Internal

Node Element Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> Element -> Element Source #

Node Content Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> Content -> Element Source #

Node [Element] Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> [Element] -> Element Source #

Node [Content] Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> [Content] -> Element Source #

Node ([Attr], [Element]) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> ([Attr], [Element]) -> Element Source #

Node ([Attr], [Content]) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> ([Attr], [Content]) -> Element Source #

Node ([Attr], Element) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> ([Attr], Element) -> Element Source #

Node ([Attr], Content) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> ([Attr], Content) -> Element Source #

Node (Attr, Element) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> (Attr, Element) -> Element Source #

Node (Attr, Content) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> (Attr, Content) -> Element Source #

type Rep Content Source # 
Instance details

Defined in Text.XML.Types.Core

data PI Source #

Processing instruction

Since: 0.2.0

Constructors

PI 

Fields

Instances
Data PI Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

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

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

toConstr :: PI -> Constr #

dataTypeOf :: PI -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PI Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

showsPrec :: Int -> PI -> ShowS #

show :: PI -> String #

showList :: [PI] -> ShowS #

Generic PI Source # 
Instance details

Defined in Text.XML.Types.Core

Associated Types

type Rep PI :: Type -> Type #

Methods

from :: PI -> Rep PI x #

to :: Rep PI x -> PI #

NFData PI Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

rnf :: PI -> () #

IsContent PI Source # 
Instance details

Defined in Text.XML.Types.Internal

type Rep PI Source # 
Instance details

Defined in Text.XML.Types.Core

type Rep PI = D1 (MetaData "PI" "Text.XML.Types.Core" "X-0.3.1.0-FtMev6r53LM7jz5ldGnRwK" False) (C1 (MetaCons "PI" PrefixI True) (S1 (MetaSel (Just "piTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ShortText) :*: S1 (MetaSel (Just "piData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

data CData Source #

XML CData

Constructors

CData 

Fields

Instances
Data CData Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

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

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

toConstr :: CData -> Constr #

dataTypeOf :: CData -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CData Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

showsPrec :: Int -> CData -> ShowS #

show :: CData -> String #

showList :: [CData] -> ShowS #

Generic CData Source # 
Instance details

Defined in Text.XML.Types.Core

Associated Types

type Rep CData :: Type -> Type #

Methods

from :: CData -> Rep CData x #

to :: Rep CData x -> CData #

NFData CData Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

rnf :: CData -> () #

IsContent CData Source # 
Instance details

Defined in Text.XML.Types.Internal

Node CData Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> CData -> Element Source #

Node [CData] Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> [CData] -> Element Source #

Node ([Attr], [CData]) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> ([Attr], [CData]) -> Element Source #

Node ([Attr], CData) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> ([Attr], CData) -> Element Source #

Node (Attr, CData) Source # 
Instance details

Defined in Text.XML

Methods

node :: QName -> (Attr, CData) -> Element Source #

type Rep CData Source # 
Instance details

Defined in Text.XML.Types.Core

type Rep CData = D1 (MetaData "CData" "Text.XML.Types.Core" "X-0.3.1.0-FtMev6r53LM7jz5ldGnRwK" False) (C1 (MetaCons "CData" PrefixI True) (S1 (MetaSel (Just "cdVerbatim") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 CDataKind) :*: S1 (MetaSel (Just "cdData") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

data CDataKind Source #

Constructors

CDataText

Ordinary character data; pretty printer escapes &, < etc.

CDataVerbatim

Unescaped character data; pretty printer embeds it in <![CDATA[..

CDataRaw

As-is character data; pretty printer passes it along without any escaping or CDATA wrap-up.

Instances
Eq CDataKind Source # 
Instance details

Defined in Text.XML.Types.Core

Data CDataKind Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

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

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

toConstr :: CDataKind -> Constr #

dataTypeOf :: CDataKind -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CDataKind Source # 
Instance details

Defined in Text.XML.Types.Core

Generic CDataKind Source # 
Instance details

Defined in Text.XML.Types.Core

Associated Types

type Rep CDataKind :: Type -> Type #

NFData CDataKind Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

rnf :: CDataKind -> () #

type Rep CDataKind Source # 
Instance details

Defined in Text.XML.Types.Core

type Rep CDataKind = D1 (MetaData "CDataKind" "Text.XML.Types.Core" "X-0.3.1.0-FtMev6r53LM7jz5ldGnRwK" False) (C1 (MetaCons "CDataText" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CDataVerbatim" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CDataRaw" PrefixI False) (U1 :: Type -> Type)))

blank_cdata :: CData Source #

Empty text-node

newtype Comment Source #

Represents a XML comment

Invariant: SHOULD not contain -- (occurences of -- will be automatically substituted by -~ on serialization)

Since: 0.2.0

Constructors

Comment Text 
Instances
Data Comment Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

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

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

toConstr :: Comment -> Constr #

dataTypeOf :: Comment -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Comment Source # 
Instance details

Defined in Text.XML.Types.Core

Generic Comment Source # 
Instance details

Defined in Text.XML.Types.Core

Associated Types

type Rep Comment :: Type -> Type #

Methods

from :: Comment -> Rep Comment x #

to :: Rep Comment x -> Comment #

NFData Comment Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

rnf :: Comment -> () #

IsContent Comment Source # 
Instance details

Defined in Text.XML.Types.Internal

type Rep Comment Source # 
Instance details

Defined in Text.XML.Types.Core

type Rep Comment = D1 (MetaData "Comment" "Text.XML.Types.Core" "X-0.3.1.0-FtMev6r53LM7jz5ldGnRwK" True) (C1 (MetaCons "Comment" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

Namespace-qualified names

data QName Source #

XML (expanded) namespace-qualified names

Used by attrKey and elName.

Constructors

QName 

Fields

Instances
Eq QName Source #

Compares namespace URI and local name for equality (i.e. the namespace prefix is ignored)

Since: 0.3.0

Instance details

Defined in Text.XML.Types.Core

Methods

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

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

Data QName Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

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

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

toConstr :: QName -> Constr #

dataTypeOf :: QName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord QName Source #

Compares namespace URI and local name for equality (i.e. the namespace prefix is effectively ignored)

The http://www.w3.org/2000/xmlns/ namespace is considered less than any other namespace (including the null namespace)

Since: 0.3.0

Instance details

Defined in Text.XML.Types.Core

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.Types.Core

Methods

showsPrec :: Int -> QName -> ShowS #

show :: QName -> String #

showList :: [QName] -> ShowS #

Generic QName Source # 
Instance details

Defined in Text.XML.Types.Core

Associated Types

type Rep QName :: Type -> Type #

Methods

from :: QName -> Rep QName x #

to :: Rep QName x -> QName #

NFData QName Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

rnf :: QName -> () #

type Rep QName Source # 
Instance details

Defined in Text.XML.Types.Core

blank_name :: QName Source #

Blank names

NOTE: This value is not a proper QName.

qnameToText :: QName -> Text Source #

Convert a QName to its text-representation, i.e.

QName          ::= PrefixedName | UnprefixedName
PrefixedName   ::= Prefix ':' LocalPart
UnprefixedName ::= LocalPart
Prefix         ::= NCName
LocalPart      ::= NCName

See also NCName

>>> qnameToText (QName "foo" "urn:example.org:bar" (Just "doo"))
"doo:foo"
>>> qnameToText (QName "foo" "urn:example.org:bar" Nothing)
"foo"

See also qnameFromText

Since: 0.3.1

qnameFromText :: (ShortText -> URI) -> Text -> Maybe QName Source #

Decode a QName from its text-representation (see qnameToText)

This is the inverse to the qnameToText function. However, qnameToText is a lossy conversion, therefore this function needs to reconstruct the namespace (i.e. qURI) with the help of a lookup function provided in the first argument: The lookup functions takes a ShortText which can be either

  • the empty string (i.e. "") which denotes an unprefixed name, or
  • a non-empty NCName string which denotes a prefixed name.

The result of this function shall be the respective namespace URI to associate with this QName. An empty URI may be returned In case of unprefixed names to denote the name being in no namespace.

Finally, this function returns Nothing in case of syntax errors or when the prefix lookup function returns an empty URI (see isNullURI) for a prefixed name.

Since: 0.3.1

Components of QNames

type NCName = ShortText Source #

A NCName

NB: Among other properties this means that an NCName shall never be the empty string.

Since: 0.2.0

newtype LName Source #

XML local names

Invariant: MUST be a proper NCName

Constructors

LName 

Fields

Instances
Eq LName Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

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

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

Data LName Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

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

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

toConstr :: LName -> Constr #

dataTypeOf :: LName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LName Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

compare :: LName -> LName -> Ordering #

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

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

(>) :: LName -> LName -> Bool #

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

max :: LName -> LName -> LName #

min :: LName -> LName -> LName #

Show LName Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

showsPrec :: Int -> LName -> ShowS #

show :: LName -> String #

showList :: [LName] -> ShowS #

IsString LName Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

fromString :: String -> LName #

Generic LName Source # 
Instance details

Defined in Text.XML.Types.Core

Associated Types

type Rep LName :: Type -> Type #

Methods

from :: LName -> Rep LName x #

to :: Rep LName x -> LName #

NFData LName Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

rnf :: LName -> () #

type Rep LName Source # 
Instance details

Defined in Text.XML.Types.Core

type Rep LName = D1 (MetaData "LName" "Text.XML.Types.Core" "X-0.3.1.0-FtMev6r53LM7jz5ldGnRwK" True) (C1 (MetaCons "LName" PrefixI True) (S1 (MetaSel (Just "unLName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NCName)))

newtype URI Source #

URIs resembling anyURI

Invariant: MUST be a valid URI-reference as defined in RFC3986

NOTE: The special empty URI is valid for denoting QNames that aren't in any namespace.

Constructors

URI 

Fields

Instances
Eq URI Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

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

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

Data URI Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

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

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

toConstr :: URI -> Constr #

dataTypeOf :: URI -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord URI Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

compare :: URI -> URI -> Ordering #

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

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

(>) :: URI -> URI -> Bool #

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

max :: URI -> URI -> URI #

min :: URI -> URI -> URI #

Show URI Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

showsPrec :: Int -> URI -> ShowS #

show :: URI -> String #

showList :: [URI] -> ShowS #

IsString URI Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

fromString :: String -> URI #

Generic URI Source # 
Instance details

Defined in Text.XML.Types.Core

Associated Types

type Rep URI :: Type -> Type #

Methods

from :: URI -> Rep URI x #

to :: Rep URI x -> URI #

NFData URI Source # 
Instance details

Defined in Text.XML.Types.Core

Methods

rnf :: URI -> () #

type Rep URI Source # 
Instance details

Defined in Text.XML.Types.Core

type Rep URI = D1 (MetaData "URI" "Text.XML.Types.Core" "X-0.3.1.0-FtMev6r53LM7jz5ldGnRwK" True) (C1 (MetaCons "URI" PrefixI True) (S1 (MetaSel (Just "unURI") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ShortText)))

isNullURI :: URI -> Bool Source #

Test for empty URI

>>> isNullURI (URI mempty)
True
>>> isNullURI (URI "")
True
>>> isNullURI (URI " ")
False

Since: 0.3.0

Miscellaneous

type Pos = Int Source #

Position expressed in number of code-points

A negative value denotes EOF