HaXPath-0.3.0.1: An XPath-generating embedded domain specific language.
Safe HaskellSafe-Inferred
LanguageHaskell2010

HaXPath

Description

The core module of the XPath-generating DSL. This module should be used as a qualified import.

Synopsis

Basic data types

class IsExpression a Source #

Class of types which can be used to form a valid XPath expression. Library users should not create instances of this class.

Minimal complete definition

toExpression

Instances

Instances details
IsExpression (Bool' s) Source # 
Instance details

Defined in HaXPath

Methods

toExpression :: Bool' s -> Expression (Showed (Bool' s))

IsExpression (Node' s) Source # 
Instance details

Defined in HaXPath

Methods

toExpression :: Node' s -> Expression (Showed (Node' s))

IsExpression (Number' s) Source # 
Instance details

Defined in HaXPath

Methods

toExpression :: Number' s -> Expression (Showed (Number' s))

IsExpression (Text' s) Source # 
Instance details

Defined in HaXPath

Methods

toExpression :: Text' s -> Expression (Showed (Text' s))

IsContext c => IsExpression (Path' c s) Source # 
Instance details

Defined in HaXPath

Methods

toExpression :: Path' c s -> Expression (Showed (Path' c s))

type family Showed p where ... Source #

Type family which associates an expression type with the type that will be returned by show' when it is dislayed in XPath syntax. This allows flexiblity to use different string-like types, such as String, Text, ByteString or even builders for these types.

Equations

Showed (Number' s) = s 
Showed (Text' s) = s 
Showed (Bool' s) = s 
Showed (Path' c s) = s 
Showed (Node' s) = s 
Showed (DocumentRoot' s) = s 

data Bool' s Source #

XPath boolean data type, which can be showed as the string type s.

Instances

Instances details
Eq (Bool' s) Source # 
Instance details

Defined in HaXPath

IsExpression (Bool' s) Source # 
Instance details

Defined in HaXPath

Methods

toExpression :: Bool' s -> Expression (Showed (Bool' s))

Ord (Bool' s) Source # 
Instance details

Defined in HaXPath

type Bool = Bool' String Source #

Bool' specialised so it can be shown as String.

false :: IsString s => Bool' s Source #

XPath false() value.

true :: IsString s => Bool' s Source #

XPath true() value.

data Number' s Source #

XPath numeric data type, which can be showed as the string type s.

Instances

Instances details
Eq (Number' s) Source # 
Instance details

Defined in HaXPath

IsExpression (Number' s) Source # 
Instance details

Defined in HaXPath

Methods

toExpression :: Number' s -> Expression (Showed (Number' s))

Ord (Number' s) Source # 
Instance details

Defined in HaXPath

IsString s => Num (Number' s) Source # 
Instance details

Defined in HaXPath

Methods

(+) :: Number' s -> Number' s -> Number' s #

(-) :: Number' s -> Number' s -> Number' s #

(*) :: Number' s -> Number' s -> Number' s #

negate :: Number' s -> Number' s #

abs :: Number' s -> Number' s #

signum :: Number' s -> Number' s #

fromInteger :: Integer -> Number' s #

type Number = Number' String Source #

Number' specialised so it can be shown as String.

data Text' s Source #

XPath textual (string) data type, which can be showed as the string type s.

Instances

Instances details
Eq (Text' s) Source # 
Instance details

Defined in HaXPath

IsExpression (Text' s) Source # 
Instance details

Defined in HaXPath

Methods

toExpression :: Text' s -> Expression (Showed (Text' s))

Ord (Text' s) Source # 
Instance details

Defined in HaXPath

IsString s => IsString (Text' s) Source # 
Instance details

Defined in HaXPath

Methods

fromString :: String -> Text' s #

type Text = Text' String Source #

Text' specialised so it can be shown as String.

text :: IsString s => Text' s Source #

The XPath text() function.

Nodes

data Node' s Source #

An XPath node which can be showed as the string type s.

Instances

Instances details
Filterable (Node' s) Source # 
Instance details

Defined in HaXPath

Methods

(#) :: Showed (Node' s) ~ s0 => Node' s -> [Bool' s0] -> Node' s Source #

IsExpression (Node' s) Source # 
Instance details

Defined in HaXPath

Methods

toExpression :: Node' s -> Expression (Showed (Node' s))

IsString s => DoubleSlashOperator (DocumentRoot' s) (Node' s) Source # 
Instance details

Defined in HaXPath

IsString s => DoubleSlashOperator (Node' s) (Node' s) Source # 
Instance details

Defined in HaXPath

Methods

(//.) :: Node' s -> Node' s -> Path' (Context (Node' s)) (Showed (Node' s)) Source #

SlashOperator (DocumentRoot' s) (Node' s) Source # 
Instance details

Defined in HaXPath

SlashOperator (Node' s) (Node' s) Source # 
Instance details

Defined in HaXPath

Methods

(/.) :: Node' s -> Node' s -> Path' (Context (Node' s)) (Showed (Node' s)) Source #

IsString s => DoubleSlashOperator (Node' s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

SlashOperator (Node' s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

(IsContext c, IsString s) => DoubleSlashOperator (Path' c s) (Node' s) Source # 
Instance details

Defined in HaXPath

Methods

(//.) :: Path' c s -> Node' s -> Path' (Context (Path' c s)) (Showed (Node' s)) Source #

IsContext c => SlashOperator (Path' c s) (Node' s) Source # 
Instance details

Defined in HaXPath

Methods

(/.) :: Path' c s -> Node' s -> Path' (Context (Path' c s)) (Showed (Node' s)) Source #

type Node = Node' String Source #

Node' specialised so it can be shown as String.

node :: IsString s => Node' s Source #

The XPath node() function.

namedNode :: IsString s => s -> Node' s Source #

Create a node with the given name.

data DocumentRoot' s Source #

Type to represent the root of the document. Useful in forming an XPaths which must begin from the root.

Instances

Instances details
IsString s => DoubleSlashOperator (DocumentRoot' s) (Node' s) Source # 
Instance details

Defined in HaXPath

SlashOperator (DocumentRoot' s) (Node' s) Source # 
Instance details

Defined in HaXPath

IsString s => DoubleSlashOperator (DocumentRoot' s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

SlashOperator (DocumentRoot' s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

root' :: DocumentRoot' s Source #

The root of the document. There is no corresponding XPath expression for root but it can be used to indicate that an XPath must be begin from the root by using this as the first step in the path.

type DocumentRoot = DocumentRoot' String Source #

DocumentRoot' specialised so it can be used in paths to be shown as String.

root :: DocumentRoot Source #

Specialisation of root' so it can be used in paths to be shown as String.

at :: s -> Text' s Source #

Access the value of a node's attribute in text form (equivalent to XPath's @).

Basic combinators

not :: IsString s => Bool' s -> Bool' s Source #

The XPath not(.) function.

(&&.) :: IsString s => Bool' s -> Bool' s -> Bool' s infixr 3 Source #

The XPath and operator.

(||.) :: IsString s => Bool' s -> Bool' s -> Bool' s infixr 2 Source #

The XPath or operator.

contains :: IsString s => Text' s -> Text' s -> Bool' s Source #

The XPath contains() function.

doesNotContain :: IsString s => Text' s -> Text' s -> Bool' s Source #

The opposite of contains.

class IsExpression t => Eq t Source #

Type class of XPath types that can be compared for equality. Library users should not create instances of this class.

Instances

Instances details
Eq (Bool' s) Source # 
Instance details

Defined in HaXPath

Eq (Number' s) Source # 
Instance details

Defined in HaXPath

Eq (Text' s) Source # 
Instance details

Defined in HaXPath

(=.) :: (Eq a, IsString (Showed a)) => a -> a -> Bool' (Showed a) infix 4 Source #

The XPath = operator.

(/=.) :: (Eq a, IsString (Showed a)) => a -> a -> Bool' (Showed a) infix 4 Source #

The XPath != operator.

class Eq t => Ord t Source #

Type class of XPath types that can be ordered. Library users should not create instances of this class.

Instances

Instances details
Ord (Bool' s) Source # 
Instance details

Defined in HaXPath

Ord (Number' s) Source # 
Instance details

Defined in HaXPath

Ord (Text' s) Source # 
Instance details

Defined in HaXPath

(<.) :: (Ord a, IsString (Showed a)) => a -> a -> Bool' (Showed a) infix 4 Source #

The XPath < operator.

(<=.) :: (Ord a, IsString (Showed a)) => a -> a -> Bool' (Showed a) infix 4 Source #

The XPath <= operator.

(>.) :: (Ord a, IsString (Showed a)) => a -> a -> Bool' (Showed a) infix 4 Source #

The XPath > operator.

(>=.) :: (Ord a, IsString (Showed a)) => a -> a -> Bool' (Showed a) infix 4 Source #

The XPath >= operator.

position :: IsString s => Number' s Source #

The XPath position() function.

Paths

data CurrentContext Source #

Type to indicate the XPath begins from the current context.

Instances

Instances details
IsContext CurrentContext Source # 
Instance details

Defined in HaXPath

Methods

toPathBegin :: proxy CurrentContext -> PathBegin

IsString s => DoubleSlashOperator (DocumentRoot' s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

IsString s => DoubleSlashOperator (Node' s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

SlashOperator (DocumentRoot' s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

SlashOperator (Node' s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

(IsContext c, IsString s) => DoubleSlashOperator (Path' c s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

IsContext c => SlashOperator (Path' c s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

data RootContext Source #

Type to indicate the XPath begins from the document root.

Instances

Instances details
IsContext RootContext Source # 
Instance details

Defined in HaXPath

Methods

toPathBegin :: proxy RootContext -> PathBegin

class IsContext c Source #

Class of valid types for the type parameter c in Path'. Library users should not create instances of this class.

Minimal complete definition

toPathBegin

Instances

Instances details
IsContext CurrentContext Source # 
Instance details

Defined in HaXPath

Methods

toPathBegin :: proxy CurrentContext -> PathBegin

IsContext RootContext Source # 
Instance details

Defined in HaXPath

Methods

toPathBegin :: proxy RootContext -> PathBegin

type family Context p where ... Source #

Type family which allows a context to be inferred. This allows for support of abbreviated syntax.

data Path' c s Source #

An XPath beginning from some context c (either the root context or the current context).

Instances

Instances details
IsString s => DoubleSlashOperator (DocumentRoot' s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

IsString s => DoubleSlashOperator (Node' s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

SlashOperator (DocumentRoot' s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

SlashOperator (Node' s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

IsContext c => Filterable (Path' c s) Source # 
Instance details

Defined in HaXPath

Methods

(#) :: Showed (Path' c s) ~ s0 => Path' c s -> [Bool' s0] -> Path' c s Source #

IsContext c => IsExpression (Path' c s) Source # 
Instance details

Defined in HaXPath

Methods

toExpression :: Path' c s -> Expression (Showed (Path' c s))

(IsContext c, IsString s) => DoubleSlashOperator (Path' c s) (Node' s) Source # 
Instance details

Defined in HaXPath

Methods

(//.) :: Path' c s -> Node' s -> Path' (Context (Path' c s)) (Showed (Node' s)) Source #

IsContext c => SlashOperator (Path' c s) (Node' s) Source # 
Instance details

Defined in HaXPath

Methods

(/.) :: Path' c s -> Node' s -> Path' (Context (Path' c s)) (Showed (Node' s)) Source #

(IsContext c, IsString s) => DoubleSlashOperator (Path' c s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

IsContext c => SlashOperator (Path' c s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

type Path c = Path' c String Source #

Path' specialised so it can be shown as String.

type AbsolutePath' = Path' RootContext Source #

An XPath beginning from the document root.

type AbsolutePath = AbsolutePath' String Source #

AbsolutePath' specialised so it can be shown as String.

type RelativePath' = Path' CurrentContext Source #

An XPath relative to the current context.

type RelativePath = RelativePath' String Source #

RelativePath' specialised so it can be shown as String.

type PathLike p = IsContext (Context p) Source #

Constraint for path-like types - i.e. either a Path' or otherwise a type that can be converted to one using abbreviated syntax rules.

show' :: (PathLike p, IsExpression p, Monoid (Showed p), IsString (Showed p), Show (Showed p)) => p -> Showed p Source #

Display an XPath expression. This is useful to sending the XPath expression to a separate XPath evaluator e.g. a web browser.

show :: (PathLike p, IsExpression p, Showed p ~ String) => p -> String Source #

Specialisation of show' to only generate Strings.

Axes

ancestor :: Node' s -> Path' CurrentContext s Source #

The XPath ancestor:: axis.

child :: Node' s -> Path' CurrentContext s Source #

The XPath child:: axis.

descendant :: Node' s -> Path' CurrentContext s Source #

The XPath descendant:: axis.

descendantOrSelf :: Node' s -> Path' CurrentContext s Source #

The XPath descendant-or-self:: axis.

following :: Node' s -> Path' CurrentContext s Source #

The XPath following:: axis.

followingSibling :: Node' s -> Path' CurrentContext s Source #

The XPath following-sibling:: axis.

parent :: Node' s -> Path' CurrentContext s Source #

The XPath parent:: axis.

self :: Node' s -> Path' CurrentContext s Source #

The XPath self:: axis.

Path combinators

class (PathLike p, PathLike q, Showed p ~ Showed q) => SlashOperator p q where Source #

Type class for the XPath / operator. It can operate on multiple types as the axes can be inferred based on XPath's abbreviated syntax. Library users should not create instances of this class.

Methods

(/.) :: p -> q -> Path' (Context p) (Showed q) infixl 8 Source #

The XPath / operator.

Instances

Instances details
SlashOperator (DocumentRoot' s) (Node' s) Source # 
Instance details

Defined in HaXPath

SlashOperator (Node' s) (Node' s) Source # 
Instance details

Defined in HaXPath

Methods

(/.) :: Node' s -> Node' s -> Path' (Context (Node' s)) (Showed (Node' s)) Source #

SlashOperator (DocumentRoot' s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

SlashOperator (Node' s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

IsContext c => SlashOperator (Path' c s) (Node' s) Source # 
Instance details

Defined in HaXPath

Methods

(/.) :: Path' c s -> Node' s -> Path' (Context (Path' c s)) (Showed (Node' s)) Source #

IsContext c => SlashOperator (Path' c s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

class (PathLike p, PathLike q, Showed p ~ Showed q) => DoubleSlashOperator p q where Source #

Type class for the XPath // operator. It can operate on multiple types as the axes can be inferred based on XPath's abbreviated syntax. Library users should not create instances of this class.

Methods

(//.) :: p -> q -> Path' (Context p) (Showed q) infixl 8 Source #

The XPath // operator.

Instances

Instances details
IsString s => DoubleSlashOperator (DocumentRoot' s) (Node' s) Source # 
Instance details

Defined in HaXPath

IsString s => DoubleSlashOperator (Node' s) (Node' s) Source # 
Instance details

Defined in HaXPath

Methods

(//.) :: Node' s -> Node' s -> Path' (Context (Node' s)) (Showed (Node' s)) Source #

IsString s => DoubleSlashOperator (DocumentRoot' s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

IsString s => DoubleSlashOperator (Node' s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

(IsContext c, IsString s) => DoubleSlashOperator (Path' c s) (Node' s) Source # 
Instance details

Defined in HaXPath

Methods

(//.) :: Path' c s -> Node' s -> Path' (Context (Path' c s)) (Showed (Node' s)) Source #

(IsContext c, IsString s) => DoubleSlashOperator (Path' c s) (Path' CurrentContext s) Source # 
Instance details

Defined in HaXPath

class (IsExpression p, PathLike p) => Filterable p where Source #

Type class to allow filtering of node sets. Library users should not create instances of this class.

Methods

(#) :: Showed p ~ s => p -> [Bool' s] -> p infixl 9 Source #

Filter the nodes returned by p such that they match the list of predicates.

Instances

Instances details
Filterable (Node' s) Source # 
Instance details

Defined in HaXPath

Methods

(#) :: Showed (Node' s) ~ s0 => Node' s -> [Bool' s0] -> Node' s Source #

IsContext c => Filterable (Path' c s) Source # 
Instance details

Defined in HaXPath

Methods

(#) :: Showed (Path' c s) ~ s0 => Path' c s -> [Bool' s0] -> Path' c s Source #

count :: (IsContext c, IsString s) => Path' c s -> Number' s Source #

The XPath count() function.

(|.) :: (PathLike p, PathLike q, IsExpression p, IsExpression q, Context p ~ Context q, Showed p ~ Showed q, IsString (Showed q)) => p -> q -> Path' (Context p) (Showed q) infix 7 Source #

The union of two node-sets.