dom-parser-0.1.1: Simple monadic DOM parser

Safe HaskellNone
LanguageHaskell2010

Text.XML.DOM.Parser.Types

Contents

Synopsis

Parser internals

data ParserError Source #

DOM parser error description.

Constructors

PENotFound

Tag not found which should be.

Fields

PEWrongFormat

Tag contents has wrong format, (could not read text to value)

Fields

PEContentNotFound

Node should have text content, but it does not.

Fields

PEOther

Some other error

Fields

Instances

Eq ParserError Source # 
Ord ParserError Source # 
Show ParserError Source # 
Generic ParserError Source # 

Associated Types

type Rep ParserError :: * -> * #

Exception ParserError Source # 
type Rep ParserError Source # 

newtype ParserErrors Source #

Constructors

ParserErrors 

Instances

data ParserData f Source #

Parser scope parser runs in. Functor argument is usually Identity or [].

If functor is Identity then parser expects exactly ONE current element. This is common behavior for content parsers, or parsers expecting strict XML structure.

If functor is [] then parser expects arbitrary current elements count. This is the case when you use combinators divePath or diveElem (posible other variants of similar combinators). This kind of combinators performs search for elements somewhere in descendants and result have arbitrary length in common case.

Constructors

ParserData 

Fields

pdElements :: forall f f. Lens (ParserData f) (ParserData f) (f Element) (f Element) Source #

pdPath :: forall f. Lens' (ParserData f) [Text] Source #

Parser type

runDomParserT :: Monad m => Document -> DomParserT Identity m a -> m (Either ParserErrors a) Source #

Run parser on root element of Document.

Auxiliary

class Traversable f => DomTraversable f where Source #

Class of traversable functors which may be constructed from list. Or may not.

Minimal complete definition

buildDomTraversable

Methods

buildDomTraversable :: [a] -> Maybe (f a) Source #

If method return Nothing this means we can not build traversable from given list. In this case combinator should fail traversing.

throwWrongFormat :: (MonadError ParserErrors m, MonadReader (ParserData f) m) => Text -> m a Source #

Throw PEWrongFormat as very common case