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

HaXPath.Schematic

Description

Wrapper over the HaXPath module which supports stronger type gurantuees such that XPaths must be valid with respect to the document schema. This module should be used as a qualified import.

Synopsis

Basic data types

class ToNonSchematic t where Source #

Type class for conversion from a schematic value to its underlying, non-schematic version.

Associated Types

type NonSchematic t Source #

Corresponding non-schematic type.

Methods

toNonSchematic :: t -> NonSchematic t Source #

Convert from the schematic to the non-schematic version.

Instances

Instances details
ToNonSchematic (Bool' as s) Source # 
Instance details

Defined in HaXPath.Schematic

Associated Types

type NonSchematic (Bool' as s) Source #

Methods

toNonSchematic :: Bool' as s -> NonSchematic (Bool' as s) Source #

ToNonSchematic (DocumentRoot' sc s) Source # 
Instance details

Defined in HaXPath.Schematic

Associated Types

type NonSchematic (DocumentRoot' sc s) Source #

ToNonSchematic (Node' n s) Source # 
Instance details

Defined in HaXPath.Schematic

Associated Types

type NonSchematic (Node' n s) Source #

ToNonSchematic (Number' as s) Source # 
Instance details

Defined in HaXPath.Schematic

Associated Types

type NonSchematic (Number' as s) Source #

ToNonSchematic (Text' as s) Source # 
Instance details

Defined in HaXPath.Schematic

Associated Types

type NonSchematic (Text' as s) Source #

Methods

toNonSchematic :: Text' as s -> NonSchematic (Text' as s) Source #

ToNonSchematic (Path' c axis n rn s) Source # 
Instance details

Defined in HaXPath.Schematic

Associated Types

type NonSchematic (Path' c axis n rn s) Source #

Methods

toNonSchematic :: Path' c axis n rn s -> NonSchematic (Path' c axis n rn s) Source #

data Bool' (as :: [Type]) s Source #

The type of boolean expressions which depend on the value of the attribute(s) as and can be showed as the string type s.

Instances

Instances details
ToNonSchematic (Bool' as s) Source # 
Instance details

Defined in HaXPath.Schematic

Associated Types

type NonSchematic (Bool' as s) Source #

Methods

toNonSchematic :: Bool' as s -> NonSchematic (Bool' as s) Source #

type NonSchematic (Bool' as s) Source # 
Instance details

Defined in HaXPath.Schematic

type NonSchematic (Bool' as s) = Bool' s

type Bool as = Bool' as String Source #

Bool' specialised so it can be shown as String.

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

XPath false() value.

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

XPath true() value.

data Number' (as :: [Type]) s Source #

The type of simple numeric expressions which depend on the value of the attribute(s) as and can be showed as the string type s.

Instances

Instances details
ToNonSchematic (Number' as s) Source # 
Instance details

Defined in HaXPath.Schematic

Associated Types

type NonSchematic (Number' as s) Source #

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

Defined in HaXPath.Schematic

Methods

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

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

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

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

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

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

fromInteger :: Integer -> Number' a s #

type NonSchematic (Number' as s) Source # 
Instance details

Defined in HaXPath.Schematic

type NonSchematic (Number' as s) = Number' s

type Number as = Number' as String Source #

Number' specialised so it can be shown as String

data Text' (as :: [Type]) s Source #

The type of simple text expressions which depend on the value of the attribute(s) as and can be showed as the string type s.

Instances

Instances details
ToNonSchematic (Text' as s) Source # 
Instance details

Defined in HaXPath.Schematic

Associated Types

type NonSchematic (Text' as s) Source #

Methods

toNonSchematic :: Text' as s -> NonSchematic (Text' as s) Source #

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

Defined in HaXPath.Schematic

Methods

fromString :: String -> Text' as s #

type NonSchematic (Text' as s) Source # 
Instance details

Defined in HaXPath.Schematic

type NonSchematic (Text' as s) = Text' s

type Text as = Text' as String Source #

Text' specialised so it can be shown as String

text :: forall (as :: [Type]) s. IsString s => Text' as s Source #

The XPath text() function.

Nodes

data Node' (n :: Type) s Source #

Type of an XPath node of type n which can be showed as the string type s.

Instances

Instances details
ToNonSchematic (Node' n s) Source # 
Instance details

Defined in HaXPath.Schematic

Associated Types

type NonSchematic (Node' n s) Source #

type NonSchematic (Node' n s) Source # 
Instance details

Defined in HaXPath.Schematic

type NonSchematic (Node' n s) = Node' s

type Node n = Node' n String Source #

Node' specialised so it can be shown as String.

class IsNode n where Source #

Type class of node types.

Methods

nodeName :: IsString s => proxy n -> s Source #

Return the name of the node.

namedNode :: forall n s. (IsNode n, IsString s) => Node' n s Source #

Create a node expression of the given type.

data DocumentRoot' sc s Source #

Type of the document root for the schema sc which can be showed as the string type s. Useful in forming an XPaths which must begin from the root.

Instances

Instances details
ToNonSchematic (DocumentRoot' sc s) Source # 
Instance details

Defined in HaXPath.Schematic

Associated Types

type NonSchematic (DocumentRoot' sc s) Source #

type NonSchematic (DocumentRoot' sc s) Source # 
Instance details

Defined in HaXPath.Schematic

type Relatives (DocumentRoot' sc s) Ancestor Source # 
Instance details

Defined in HaXPath.Schematic

type Relatives (DocumentRoot' sc s) Ancestor = '[] :: [Type]
type Relatives (DocumentRoot' sc s) Following Source # 
Instance details

Defined in HaXPath.Schematic

type Relatives (DocumentRoot' sc s) Following = '[] :: [Type]
type Relatives (DocumentRoot' sc s) FollowingSibling Source # 
Instance details

Defined in HaXPath.Schematic

type Relatives (DocumentRoot' sc s) Parent Source # 
Instance details

Defined in HaXPath.Schematic

type Relatives (DocumentRoot' sc s) Parent = '[] :: [Type]

root' :: DocumentRoot' sc s Source #

The root of the document for the schema s.

type DocumentRoot sc = DocumentRoot' sc String Source #

DocumentRoot' specialised so it can be shown as String.

root :: DocumentRoot sc Source #

root' specialised so it can be shown as String.

type family Attributes n :: [Type] Source #

Type family which contrains the possible attributes a node of type n may have.

type family AttributesUsed t where ... Source #

Type family which returns the node attribute(s) used within a given expression.

Equations

AttributesUsed (Bool' as s) = as 
AttributesUsed (Text' as s) = as 
AttributesUsed (Number' as s) = as 

class IsAttribute a where Source #

Type class for node attributes.

Methods

attributeName :: IsString s => proxy a -> s Source #

Return the name of the attribute.

at :: (IsAttribute a, Member a as, IsString s) => proxy a -> Text' as s Source #

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

Basic combinators

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

The XPath not() function.

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

The XPath and operator.

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

The XPath or operator.

(=.) :: (ToNonSchematic t, Eq (NonSchematic t), IsString (Showed (NonSchematic t))) => t -> t -> Bool' (AttributesUsed t) (Showed (NonSchematic t)) infix 4 Source #

The XPath = operator.

(/=.) :: (ToNonSchematic t, Eq (NonSchematic t), IsString (Showed (NonSchematic t))) => t -> t -> Bool' (AttributesUsed t) (Showed (NonSchematic t)) infix 4 Source #

The XPath != operator.

(<.) :: (ToNonSchematic t, Ord (NonSchematic t), IsString (Showed (NonSchematic t))) => t -> t -> Bool' (AttributesUsed t) (Showed (NonSchematic t)) infix 4 Source #

The XPath < operator.

(<=.) :: (ToNonSchematic t, Ord (NonSchematic t), IsString (Showed (NonSchematic t))) => t -> t -> Bool' (AttributesUsed t) (Showed (NonSchematic t)) infix 4 Source #

The XPath <= operator.

(>.) :: (ToNonSchematic t, Ord (NonSchematic t), IsString (Showed (NonSchematic t))) => t -> t -> Bool' (AttributesUsed t) (Showed (NonSchematic t)) infix 4 Source #

The XPath > operator.

(>=.) :: (ToNonSchematic t, Ord (NonSchematic t), IsString (Showed (NonSchematic t))) => t -> t -> Bool' (AttributesUsed t) (Showed (NonSchematic t)) infix 4 Source #

The XPath >= operator.

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

The XPath contains() function.

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

The opposite of contains.

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

The XPath position() function.

Paths

data Path' c axis n rn s Source #

The type of path expressions which can be showed as the string type s and are formed by these steps:

  1. Starting from the context c and moving through the given axis.
  2. Selecting node(s) of type n.
  3. Performing zero or more location steps.
  4. Finally returning the node(s) of type rn.

Instances

Instances details
ToNonSchematic (Path' c axis n rn s) Source # 
Instance details

Defined in HaXPath.Schematic

Associated Types

type NonSchematic (Path' c axis n rn s) Source #

Methods

toNonSchematic :: Path' c axis n rn s -> NonSchematic (Path' c axis n rn s) Source #

type NonSchematic (Path' c axis n rn s) Source # 
Instance details

Defined in HaXPath.Schematic

type NonSchematic (Path' c axis n rn s) = Path' c s

type Path c axis n rn = Path' c axis n rn String Source #

Path' specialised so it can be shown as String.

type AbsolutePath' sc rn = Path' RootContext Self (DocumentRoot sc) rn Source #

An XPath beginning from the document root for the schema sc, returning a node of type rn.

type AbsolutePath sc rn = AbsolutePath' sc rn String Source #

AbsolutePath' specialised so it can be shown as String

type RelativePath' = Path' CurrentContext Source #

An XPath beginning from the current context.

type RelativePath axis n rn = RelativePath' axis n rn String Source #

RelativePath' specialised so it can be shown as String

type PathLike p = (ToNonSchematic p, PathLike (NonSchematic p)) Source #

Constraint for types from which a path can be inferred.

type family SelectNode p where ... Source #

Type family to infer the type of the node selected by the first location step in a path.

Equations

SelectNode (Path' c axis n rn s) = n 
SelectNode (Node' n s) = n 
SelectNode (DocumentRoot' sc s) = DocumentRoot' sc s 

type family ReturnNode p where ... Source #

Type family to infer the node selected by the last location step in a path.

Equations

ReturnNode (Path' c axis n rn s) = rn 
ReturnNode (Node' n s) = n 
ReturnNode (DocumentRoot' sc s) = DocumentRoot' sc s 

type family Relatives n axis :: [Type] Source #

Type family to constrain the possible relatives of nodes of type n through the given axis.

Instances

Instances details
type Relatives (DocumentRoot' sc s) Ancestor Source # 
Instance details

Defined in HaXPath.Schematic

type Relatives (DocumentRoot' sc s) Ancestor = '[] :: [Type]
type Relatives (DocumentRoot' sc s) Following Source # 
Instance details

Defined in HaXPath.Schematic

type Relatives (DocumentRoot' sc s) Following = '[] :: [Type]
type Relatives (DocumentRoot' sc s) FollowingSibling Source # 
Instance details

Defined in HaXPath.Schematic

type Relatives (DocumentRoot' sc s) Parent Source # 
Instance details

Defined in HaXPath.Schematic

type Relatives (DocumentRoot' sc s) Parent = '[] :: [Type]

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

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

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

show' specialised to generate Strings.

Axes

type family Axis p where ... Source #

Type family to infer of the axis of a location step based on the type of the step.

Equations

Axis (Path' c axis n rn s) = axis 
Axis (Node' n s) = Child 
Axis (DocumentRoot' sc s) = Self 

data Ancestor Source #

Type of the XPath ancestor:: axis.

Instances

Instances details
type Relatives (DocumentRoot' sc s) Ancestor Source # 
Instance details

Defined in HaXPath.Schematic

type Relatives (DocumentRoot' sc s) Ancestor = '[] :: [Type]

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

The XPath ancestor:: axis.

data Child Source #

Type of the XPath child:: axis.

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

The XPath child:: axis.

data Descendant Source #

Type of the XPath descendant:: axis.

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

The XPath descendant:: axis.

data DescendantOrSelf Source #

Type of the XPath descendant-or-self:: axis.

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

The XPath descendant-or-self:: axis.

data Following Source #

Type of the XPath following:: axis.

Instances

Instances details
type Relatives (DocumentRoot' sc s) Following Source # 
Instance details

Defined in HaXPath.Schematic

type Relatives (DocumentRoot' sc s) Following = '[] :: [Type]

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

The XPath following:: axis.

data FollowingSibling Source #

Type of the XPath following-sibling:: axis.

Instances

Instances details
type Relatives (DocumentRoot' sc s) FollowingSibling Source # 
Instance details

Defined in HaXPath.Schematic

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

The XPath following-sibling:: axis.

data Parent Source #

Type of the XPath parent:: axis.

Instances

Instances details
type Relatives (DocumentRoot' sc s) Parent Source # 
Instance details

Defined in HaXPath.Schematic

type Relatives (DocumentRoot' sc s) Parent = '[] :: [Type]

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

The XPath parent:: axis.

Path combinators

(/.) :: (Member (SelectNode q) (Relatives (ReturnNode p) (Axis q)), PathLike p, PathLike q, SlashOperator (NonSchematic p) (NonSchematic q)) => p -> q -> Path' (Context (NonSchematic p)) (Axis p) (SelectNode p) (ReturnNode q) (Showed (NonSchematic q)) infixl 8 Source #

The XPath / operator.

(#) :: (PathLike p, ToNonSchematic p, FromNonSchematic (NonSchematic p) p, Filterable (NonSchematic p)) => p -> [Bool' (Attributes (ReturnNode p)) (Showed (NonSchematic p))] -> p infixl 9 Source #

Filter the path-like expression using the given predicate(s). The predicates must only make use of the attributes of the type of node selected by the path, otherwise it will not type check.

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

The XPath count() function.

Utilities

type Member x xs = HMember x xs 'True Source #

Type level membership constraint indicating that the type x is a member of the type-level list xs.