hxt-css-0.1.0.1: CSS selectors for HXT

Stabilityprovisional
Safe HaskellNone
LanguageHaskell2010

Text.XML.HXT.CSS

Contents

Description

Turn a CSS selector into an HXT arrow.

Synopsis

Documentation

css :: (ArrowXml a, Css s) => s -> a XmlTree XmlTree Source

Select elements from an HTML document with a CSS selector.

cssShallow :: (ArrowXml a, Css s) => s -> a XmlTree XmlTree Source

Like css, except that the selector is anchored at the top. For example, cssShallow "div" will only select div elements that are in the input of the arrow, it will not recursively search for divs contained deeper in the document tree. The latter can be selected by cssShallow "* div" but is recommended to use css for that. In other words, cssShallow "div" corresponds to the "/div" XPath expression, whereas cssShallow "* div" corresponds to "//div".

cssNav :: (ArrowXml a, Css s) => s -> a XmlNavTree XmlNavTree Source

Like css, except that it operates on navigatable XML trees.

cssShallowNav :: (ArrowXml a, Css s) => s -> a XmlNavTree XmlNavTree Source

Like cssShallow, except that it operates on navigatable XML trees.

class Css s Source

Things that can be used as a CSS selector. The String instance uses safeParseCSS to parse the string.

Minimal complete definition

select

Supported selectors

  • Element selectors: *, E, .class, #id
  • Relationship selectors: E F, E > F, E + F, E ~ F
  • Attribute selectors: [attr], [attr="value"], [attr~="value"], [attr|="value"], [attr^="value"], [attr$="value"], [attr*="value"]
  • Pseudo-classes: :not(..), :empty, :root, :first-child, :last-child, :only-child, :nth-child(N), :nth-last-child(N), :first-of-type, :last-of-type, :only-of-type, :nth-of-type(N), :nth-last-of-type(N)

The argument to the :nth-child() family of pseudo-classes can take one of the following forms: 6, 2n, n+2, 3n-1, -n+6, odd, even.

Example

import Text.XML.HXT.Core
import Text.XML.HXT.CSS

test :: IO [XmlTree]
test = runX $ doc >>> css "div > span + p:not(:nth-of-type(3n-1))"
  where
    doc = readDocument [withParseHTML yes, withWarnings no] path
    path = "/path/to/document.html"