xml-conduit-selectors-0.2.0.2: jQuery-style CSS selectors for xml-conduit
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.XML.Selectors

Description

This module re-exports commonly used functionality from the Types and ToAxis modules. To parse jQuery selectors, you will also need to import JQ.

Basic usage example:

import Text.XML.Selectors
import Text.XML.Selectors.Parsers.JQ
import Text.XML as XML
import Text.XML.Cursor (Cursor, node, fromDocument)
import Data.Default
import Control.Monad (forM_)

main = do
  doc <- XML.readFile def "example.xml"
  selector <- jqString' "div.menu a[href!='#']"
  let cursors = match selector (fromDocument doc)
  forM_ cursors $ \cursor -> do
    let n = node cursor
    print n
Synopsis

The Selector Types

data Selector Source #

Node-level selectors and combinators

Constructors

None 
Any
*
Append Selector Selector

ab (both a and b must match)

Elem Name
div
Attrib AttribSelector
a[...]
Descendant

(whitespace)

Child
>
Sibling
~
NextSibling
+
FirstChild
:first-child
LastChild
:last-child
NthChild Int
:nth-child(n); :nth-last-child(-n)
Choice [Selector]
a,b,...
Having Selector
:has(b)
Not Selector
:not(b)

Instances

Instances details
Monoid Selector Source #

The Monoid instance, just like Semigroup, combines selectors with Append; the neutral value is, of course, Any.

Instance details

Defined in Text.XML.Selectors.Types

Semigroup Selector Source #

The Semigroup of selectors combines selectors with Append. a <> b selects all nodes that match a and also match b. Note however that the <> operator culls redundant combinations with the Any selector, e.g. Any <> Child <> Any is just Child, not Append Any (Append Child Any).

Instance details

Defined in Text.XML.Selectors.Types

Show Selector Source # 
Instance details

Defined in Text.XML.Selectors.Types

(<||>) :: Selector -> Selector -> Selector infixl 3 Source #

An alternative semigroup of selectors, representing choice. a <||> b selects all nodes that match a and also all nodes that match b. In other words: a <||> b == Choice a b. Note however that the <||> operator culls redundant applications of Choice, e.g., a <||> b <||> c becomes Choice [a, b, c] rather than Choice [a, Choice [b, c]]. This alternative semigroup could be extended into a monoid, with the empty choice (Choice []) as the neutral value, but we were far too lazy to add that.

data AttribSelector Source #

Attribute-level selectors

Constructors

AttribExists Name
[attr]
AttribIs Name Text
[attr=blah]
AttribIsNot Name Text
[attr!=blah]
AttribStartsWith Name Text
[attr^=blah]
AttribEndsWith Name Text
[attr$=blah]
AttribContains Name Text
[attr*=blah]
AttribContainsWord Name Text
[attr~=blah]
AttribContainsPrefix Name Text
[attr|=blah]

Applying Selectors

toAxis :: Selector -> Axis Source #

Turn a Selector into an Axis.

match :: Selector -> Cursor -> [Cursor] Source #

Directly apply a Selector to a Cursor, removing duplicates. Cursors are considered duplicate iff their focus node and ancestory are the same.

Due to the knot-tying of the Cursor type, this is not perfect: we are not considering the focus node's position within its parent, so any two nodes that are exactly identical themselves and share ancestory will be considered equal. E.g., in the following XML document:

<root>
  <parent>
     <child>Foo</child>
     <child>Foo</child>
  </parent>
</root>

...the two <child/> nodes will be considered equal, even though they are two distinct nodes in the DOM.

Unlike toAxis, the match function prepends an implicit self-or-descendant Axis to the selector in order to mimic the behavior of actual CSS selectors.