Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
The Selector Types
Node-level selectors and combinators
None | |
Any | * |
Append Selector Selector |
|
Elem Name | div |
Attrib AttribSelector | a[...] |
Descendant |
|
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
Show Selector Source # | |
Semigroup Selector Source # | The |
Monoid Selector Source # | The |
(<||>) :: 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
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] |
Instances
Eq AttribSelector Source # | |
Defined in Text.XML.Selectors.Types (==) :: AttribSelector -> AttribSelector -> Bool # (/=) :: AttribSelector -> AttribSelector -> Bool # | |
Show AttribSelector Source # | |
Defined in Text.XML.Selectors.Types showsPrec :: Int -> AttribSelector -> ShowS # show :: AttribSelector -> String # showList :: [AttribSelector] -> ShowS # |
Applying Selectors
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.