polysoup-0.2.2: Online XML parsing with polyparse and tagsoup

Safe HaskellNone
LanguageHaskell2010

Text.XML.PolySoup

Contents

Synopsis

Types

type XmlParser s a = Parser (Tag s) a Source #

XML forest parser with result type a.

type TagParser s a = Parser (Tag s) a Source #

data TagPred s a Source #

A tag predicate checks if the tag (HTML element) satisfies some properties and extracts attribute values. You can compose tag predicates using Applicative and Alternative operators: *>, <*, <|> etc.

Instances
Functor (TagPred s) Source # 
Instance details

Defined in Text.XML.PolySoup

Methods

fmap :: (a -> b) -> TagPred s a -> TagPred s b #

(<$) :: a -> TagPred s b -> TagPred s a #

Applicative (TagPred s) Source # 
Instance details

Defined in Text.XML.PolySoup

Methods

pure :: a -> TagPred s a #

(<*>) :: TagPred s (a -> b) -> TagPred s a -> TagPred s b #

liftA2 :: (a -> b -> c) -> TagPred s a -> TagPred s b -> TagPred s c #

(*>) :: TagPred s a -> TagPred s b -> TagPred s b #

(<*) :: TagPred s a -> TagPred s b -> TagPred s a #

Alternative (TagPred s) Source # 
Instance details

Defined in Text.XML.PolySoup

Methods

empty :: TagPred s a #

(<|>) :: TagPred s a -> TagPred s a -> TagPred s a #

some :: TagPred s a -> TagPred s [a] #

many :: TagPred s a -> TagPred s [a] #

Tag predicates

satisfyPred :: TagPred s a -> TagParser s a Source #

Make a tag parser from the tag predicate.

true :: TagPred s () Source #

Predicate which is always satisfied.

getTag :: TagPred s (Tag s) Source #

True predicate which returns the tag itself.

isTagOpen :: TagPred s () Source #

Check if the HTML element is an open tag.

isTagOpenName :: Eq s => s -> TagPred s () Source #

Check if the tag is an open tag and matches the given name.

isTagClose :: TagPred s () Source #

Check if the HTML element is a closing tag.

isTagCloseName :: Eq s => s -> TagPred s () Source #

Check if the tag is a closing tag and matches the given name.

isTagText :: TagPred s () Source #

Test if the tag is a text node.

isTagComment :: TagPred s () Source #

Test if the tag is a text node.

tagOpenName :: TagPred s s Source #

Get name of the open tag.

tagText :: TagPred s s Source #

Get text content of the tag.

tag :: Eq s => s -> TagPred s () Source #

A shorthand for isTagOpenName.

hasAttr :: (Show s, Eq s, StringLike s) => s -> s -> TagPred s () Source #

Check if the tag has the given attribute with the given value.

getAttr :: (Show s, Eq s, StringLike s) => s -> TagPred s s Source #

Get attribute value from the open tag.

maybeAttr :: (Show s, Eq s, StringLike s) => s -> TagPred s (Maybe s) Source #

Get attribute value from the open tag or Nothing, if the attribute is not present.

XML parsing combinators

ignore :: Eq s => XmlParser s () Source #

Ignore any number of XML elements on the current level.

ignoreAny :: Eq s => XmlParser s () Source #

Ignore XML tree or text element.

ignoreText :: XmlParser s () Source #

Ignore text element.

ignoreTag :: Eq s => XmlParser s () Source #

Ignore XML tree.

ignoreAnyM :: (Eq s, Monoid m) => XmlParser s m Source #

Version of the ignoreAny function with a monoid result type.

cut :: Eq s => TagPred s a -> XmlParser s a Source #

Parse XML element using the given tag predicate and ignore contents of the element.

findAll :: Eq s => XmlParser s a -> XmlParser s [a] Source #

Parse a list of XML elements and collect all values retrieved with a given parser.

findIgnore :: Eq s => XmlParser s a -> XmlParser s (Maybe a) Source #

Find first XML element accepted be the given parser and ignore the rest of elements in the collection.

findFirst :: Eq s => XmlParser s a -> XmlParser s a Source #

Find fist XML element accepted by the given parser. TODO: Change type to XmlParser s (Maybe a)?

text :: Eq s => XmlParser s s Source #

Parse text element and retrieve its content.

join :: Eq s => TagPred s a -> (a -> XmlParser s b) -> XmlParser s b Source #

Combine the tag parser with the XML parser which will be used to parse contents of the tag element.

joinP :: Eq s => TagPred s a -> XmlParser s b -> XmlParser s (a, b) Source #

Combine the tag parser with the XML parser which will be used to parse contents of the tag element. Parsing results will be returned in a form of a pair.

joinR :: Eq s => TagPred s a -> XmlParser s b -> XmlParser s b Source #

Combine the tag parser with the XML parser which will be used to parse contents of the tag element. Only results of the XML parser will be returned.

joinL :: Eq s => TagPred s a -> XmlParser s b -> XmlParser s a Source #

Combine the tag parser with the XML parser which will be used to parse contents of the tag element. Only results of the tag parser will be returned.

(>^>) :: Eq s => TagPred s a -> (a -> XmlParser s b) -> XmlParser s b infixr 2 Source #

Infix version of the join combinators.

(<^>) :: Eq s => TagPred s a -> XmlParser s b -> XmlParser s (a, b) infixr 2 Source #

Infix version of the joinP combinators.

(^>) :: Eq s => TagPred s a -> XmlParser s b -> XmlParser s b infixr 2 Source #

Infix version of the joinR combinators.

(<^) :: Eq s => TagPred s a -> XmlParser s b -> XmlParser s a infixr 2 Source #

Infix version of the joinL combinators.

XPath-like combinators

(>/>) :: Eq s => TagPred s a -> (a -> XmlParser s b) -> XmlParser s [b] infixr 2 Source #

Combine the tag parser with the XML parser. The XML parser can depend on the value of tag parser and will be called multiple times for tag children elements.

(</>) :: Eq s => TagPred s a -> XmlParser s b -> XmlParser s (a, [b]) infixr 2 Source #

Combine the tag parser with the XML parser. The XML parser will be called multiple times for tag children elements.

(/>) :: Eq s => TagPred s a -> XmlParser s b -> XmlParser s [b] infixr 2 Source #

Combine the tag parser with the XML parser. The XML parser will be called multiple times for tag children elements. Only results of XML parsing will be returned.

(</) :: Eq s => TagPred s a -> XmlParser s b -> XmlParser s a infixr 2 Source #

Combine the tag parser with the XML parser. The XML parser will be called multiple times for tag children elements. Only results of the tag parser will be returned.

(//>) :: Eq s => TagPred s a -> TagParser s b -> TagParser s [b] infixr 2 Source #

Similar to /> combinator but runs the XML parser for all descendant XML elements, not only for its children.

(<#>) :: (Eq s, Monoid m) => TagPred s a -> XmlParser s m -> XmlParser s (a, m) infixr 2 Source #

Combinators with results concatenation.

Similar to </> combinator but additionaly concatenates XML parser results.

(#>) :: (Eq s, Monoid m) => TagPred s a -> XmlParser s m -> XmlParser s m infixr 2 Source #

Similar to /> combinator but additionaly concatenates XML parser results.

(##>) :: (Eq s, Monoid m) => TagPred s a -> TagParser s m -> TagParser s m infixr 2 Source #

Similar to //> combinator but additionaly concatenates XML parser results.

Parsing

parseTags :: StringLike s => s -> [Tag s] Source #

Parser the given string to the list of tags.

tagsParseXml :: StringLike s => XmlParser s b -> [Tag s] -> b Source #

Parser the given tag list with the given XML parser.

parseXml :: StringLike s => XmlParser s b -> s -> b Source #

Parser the given string with the given XML parser.

elemTags :: Eq s => XmlParser s [Tag s] Source #

Collect all tags of the parsed XML element.

collTags :: Eq s => XmlParser s [Tag s] Source #

Retrieve tags related to a collection of XML elements.

Utilities

many_ :: Alternative f => f a -> f () Source #

Many combinator which ignores parsing results.

escapeXml :: StringLike str => str -> str Source #

Escape XML string.