dom-parser-0.0.1: Simple monad for parsing DOM

Safe HaskellNone
LanguageHaskell2010

Text.XML.DOM.Parser

Contents

Synopsis

Parser internals

data ParserData Source

Constructors

ParserData 

Fields

_pdCursor :: !Cursor

Cursor to current parser's environment

_pdAxis :: !Axis

Context axis to follow deeper

_pdPath :: ![Text]

Path for errors

data ParserError Source

DOM parser error description.

Constructors

PENotFound

Tag not found which should be.

Fields

_pePath :: ![Text]

path of element

PEWrongFormat

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

Fields

_pePath :: ![Text]

path of element

_peDetails :: Text
 
PEWrongTagName

Such tag name is not expected in this place

Fields

_pePath :: ![Text]

path of element

_peDetails :: !Text
 
PENotElement

Node is not an element but should be

Fields

_pePath :: ![Text]

path of element

PEContentNotFound

Node should have text content, but it does not.

Fields

_pePath :: ![Text]

path of element

PEOther

Any other error

Fields

_pePath :: ![Text]

path of element

_peDetails :: !Text
 

renderPath :: [Text] -> String Source

Render path for showing error

Parser itself

type DomParser = ExceptT [ParserError] (Reader ParserData) Source

Parser monad where all parsing actions live

runDomParser :: Document -> DomParser a -> Either [ParserError] a Source

Run parser on root element of Document.

type ContentParser a = Text -> Either Text a Source

Content parser type. Parser is just a function taking Text and returning either error description or successfully parsed value.

Common parsers

unitFromDom :: DomParser () Source

Always successfully parses any DOM to ()

voidFromDom :: DomParser Void Source

Never parses successfully. It is just mzero

textFromContent :: ContentParser Text Source

Does not strip content. Returns content unmodified.

stringFromContent :: ContentParser String Source

Does not strip content. Returns content unmodified.

charFromContent :: ContentParser Char Source

Expects content to be a singe non-blank character. Blank characters are stripped to parse pretty-printed XML files.

boolFromContent :: ContentParser Bool Source

Expects content to be y, yes, t, true or 1 for True value. n, no, f, false or 0 for False value. Case is not significant, blank characters are striped.

Parser classes

class FromDom a where Source

Typeclass for structures which may be parsed from XML DOM. Usually you should pass parsing function explicitly to combinators like inElem, maybeInElem or inTags , but sometimes you need term search. Especially when you try to parse polymorphic types. Or you maybe generate parser with TH for your types, so typeclass would be convenient also.

class FromContent a where Source

Usually you should pass ContentParser to combinators like elemContent or maybeElemContent explicitly. But sometimes you need term search. Especially for code generated with TH.

Methods

fromContent :: ContentParser a Source

Should return either error message (what was wrong) or parsed value

Combinators

inElem :: Text -> DomParser a -> DomParser a Source

Find first element with given name in current element and run parser inside of found element. Throws PENotFound error if element not found.

inElems :: Text -> DomParser a -> DomParser [a] Source

Find all elements with gievn name in current element and run parser inside of this elements.

maybeInElem :: Text -> DomParser a -> DomParser (Maybe a) Source

Try to find element with given name and run parser inside of it. If not found return Nothing

inElemsPred Source

Arguments

:: Traversable f 
=> ([Cursor] -> f Cursor)

Some predicate like listToMaybe

-> Text

Name of tags to find in current tag

-> DomParser a

Parser to run inside found cursors

-> DomParser (f a) 

Generic elements combinator. Takes predicate filtering/converting list of cursors to some traversable (with posible filtering and/or reordering)

inAxis Source

Arguments

:: [Text]

Path suffix to append to path before run parser

-> Axis

Axis to append to context

-> DomParser a

Parser to run

-> DomParser a 

Run parser within axis context. Expected to not use directly.

inDescendants :: DomParser a -> DomParser a Source

Given parser will match tag in arbitrary deepness

inTags Source

Arguments

:: [Text]

Sequence of tag names parser must match inside

-> DomParser a

Parser to run

-> DomParser a 

Given parser will match inside specific

Content getters

tryCurrentContentText :: DomParser (Maybe Text) Source

Get concatenated text from current parser's node(s). If current context have no Content nodes then return Nothing.

tryCurrentName :: DomParser (Maybe Name) Source

Return the name of current cursor we staying in. Return Nothing if we are not staying on element node

currentName :: DomParser Name Source

Return name of current element the parser in.

currentAttr :: Text -> DomParser Text Source

Take attribute from current node (if it is an element). Throws PENotFound or PENotElement

Helpers

fromContentR :: forall a. (Read a, Typeable a) => Text -> Either Text a Source

newtype CurrentContent a Source

Helper newtype returning currentContent for any type with instance FromContent

Constructors

CurrentContent 

Fields

unCurrentContent :: a
 

Raw node getters

currentNodes :: DomParser [Node] Source

Get children nodes from current parser's node.

Checkers

checkCurrentLaxName :: Text -> DomParser () Source

Throw PEWrongTagName if name of current element does not match with given.

checkCurrentName Source

Arguments

:: (Name -> Maybe Text)

name checking predicate

-> DomParser () 

Run predicate with current tag name. Parser fails if predicate returned (Just msg) or node is not an element.