X-0.3.1.0: A light-weight XML library

Copyright(c) Galois Inc. 2007
(c) Herbert Valerio Riedel 2019
LicenseBSD-3-Clause AND GPL-3.0-or-later
Safe HaskellSafe
LanguageHaskell2010

Text.XML.Input

Contents

Description

Lightweight XML parsing

Synopsis

High-level DOM Parser

parseXML :: XmlSource s => s -> Either (Pos, String) [Content] Source #

parseXML to a list of Content chunks

NOTE: As opposed to parseXMLDoc, this function will not discard any BOM characters.

parseXMLDoc :: XmlSource s => s -> Either (Pos, String) Element Source #

Parse a XML document to an Element

If you need access to the prolog and epilog use parseXMLRoot

An optional (single) leading BOM (U+FEFF) character will be discard (and not counted in the source positions).

parseXMLRoot :: XmlSource s => s -> Either (Pos, String) Root Source #

Parse a XML document

An optional (single) leading BOM (U+FEFF) character will be discard (and not counted in the source positions).

Token Scanner

class XmlSource s where Source #

Methods

uncons :: s -> Maybe (Char, s) Source #

Instances
XmlSource String Source # 
Instance details

Defined in Text.XML.Lexer

XmlSource Text Source # 
Instance details

Defined in Text.XML.Lexer

Methods

uncons :: Text -> Maybe (Char, Text) Source #

XmlSource Text Source # 
Instance details

Defined in Text.XML.Lexer

Methods

uncons :: Text -> Maybe (Char, Text) Source #

XmlSource (Scanner s) Source # 
Instance details

Defined in Text.XML.Lexer

Methods

uncons :: Scanner s -> Maybe (Char, Scanner s) Source #

data Scanner s Source #

This type may be used to provide a custom scanning function for extracting characters.

Instances
XmlSource (Scanner s) Source # 
Instance details

Defined in Text.XML.Lexer

Methods

uncons :: Scanner s -> Maybe (Char, Scanner s) Source #

customScanner :: (s -> Maybe (Char, s)) -> s -> Scanner s Source #

This type may be used to provide a custom scanning function for extracting characters.

data Token Source #

XML Lexer token.

Constructors

TokStart !Pos QName [Attr] Bool

opening start-tag (the Bool field denotes whether this is an empty tag)

TokEnd !Pos QName

closing end-tag

TokCRef ShortText

character entity reference

TokText CData

character data

TokError !Pos String

Lexer error

TokXmlDecl XmlDeclaration 
TokComment Comment 
TokPI !Pos PI 
TokDTD Text 
Instances
Data Token Source # 
Instance details

Defined in Text.XML.Lexer

Methods

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

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

toConstr :: Token -> Constr #

dataTypeOf :: Token -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Token Source # 
Instance details

Defined in Text.XML.Lexer

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Generic Token Source # 
Instance details

Defined in Text.XML.Lexer

Associated Types

type Rep Token :: Type -> Type #

Methods

from :: Token -> Rep Token x #

to :: Rep Token x -> Token #

NFData Token Source # 
Instance details

Defined in Text.XML.Lexer

Methods

rnf :: Token -> () #

type Rep Token Source # 
Instance details

Defined in Text.XML.Lexer

type Rep Token = D1 (MetaData "Token" "Text.XML.Lexer" "X-0.3.1.0-FtMev6r53LM7jz5ldGnRwK" False) (((C1 (MetaCons "TokStart" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Pos) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QName)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Attr]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) :+: C1 (MetaCons "TokEnd" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Pos) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QName))) :+: (C1 (MetaCons "TokCRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ShortText)) :+: C1 (MetaCons "TokText" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CData)))) :+: ((C1 (MetaCons "TokError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Pos) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "TokXmlDecl" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 XmlDeclaration))) :+: (C1 (MetaCons "TokComment" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Comment)) :+: (C1 (MetaCons "TokPI" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Pos) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PI)) :+: C1 (MetaCons "TokDTD" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))))

scanXML :: XmlSource source => source -> [Token] Source #

Run XML lexer over XmlSource