Hets - the Heterogeneous Tool Set
Copyright(c) Christian Maeder DFKI GmbH 2010
LicenseGPLv2 or higher, see LICENSE.txt
MaintainerChristian.Maeder@dfki.de
Stabilityprovisional
Portabilityportable
Safe HaskellSafe

Common.XPath

Description

XPath utilities independent of xml package. references: http://www.w3.org/TR/xpath/ http://www.galiel.net/el/study/XPath_Overview.html http://www.fh-wedel.de/~si/HXmlToolbox/hxpath/diplomarbeit.pdf http://hackage.haskell.org/package/hxt-xpath (modules XPathParser, XPathDataTypes) http://hackage.haskell.org/package/hxt-8.5.0 (modules Text.XML.HXT.DOM.Unicode, Text.XML.HXT.Parser.XmlCharParser) http://www.w3.org/TR/REC-xml/#NT-Name

Unicode is not fully supported. A qualified name is an ncName or two ncNames separated by a colon (different from OWL uris).

Synopsis

data types and pretty printing (via show)

data Axis Source #

axis specifier

Constructors

Ancestor Bool

or self?

Attribute 
Child 
Descendant Bool

or self?

Following Bool

sibling?

Namespace 
Parent 
Preceding Bool

sibling?

Self 

Instances

Instances details
Show Axis Source # 
Instance details

Defined in Common.XPath

Methods

showsPrec :: Int -> Axis -> ShowS

show :: Axis -> String

showList :: [Axis] -> ShowS

allAxis :: [Axis] Source #

all possible values

lowerShow :: Show a => a -> String Source #

utility to show (constant) constructors as lower case strings

showAxis :: Axis -> String Source #

proper string representation (do not use show)

data NodeTest Source #

testing attribute, namespace or element nodes (usually) by name

Constructors

NameTest String

optional prefix and local part (possibly a * wildcard)

PI String

processing-instruction node type with optional literal

Node

true for any node (therefore rarely used)

Comment

true for comment nodes

Text

true for text nodes

Instances

Instances details
Show NodeTest Source # 
Instance details

Defined in Common.XPath

Methods

showsPrec :: Int -> NodeTest -> ShowS

show :: NodeTest -> String

showList :: [NodeTest] -> ShowS

nodeTypes :: [NodeTest] Source #

all node types without processing-instruction

pIS :: String Source #

the processing-instruction string

paren :: String -> String Source #

put parens arount a string

showNodeTest :: NodeTest -> String Source #

proper string representation (do not use show)

data Step Source #

the stuff of a path between the slashes

Constructors

Step Axis NodeTest [Expr]

with predicate list

Instances

Instances details
Show Step Source # 
Instance details

Defined in Common.XPath

Methods

showsPrec :: Int -> Step -> ShowS

show :: Step -> String

showList :: [Step] -> ShowS

showStep :: Step -> String Source #

string representation considering abbreviations

isDescOrSelfNode :: Step -> Bool Source #

test for descendant-or-self::node() step

data Path Source #

only absolute paths may be empty

Constructors

Path Bool [Step]

absolute?

Instances

Instances details
Show Path Source # 
Instance details

Defined in Common.XPath

Methods

showsPrec :: Int -> Path -> ShowS

show :: Path -> String

showList :: [Path] -> ShowS

showSteps :: Bool -> [Step] -> String Source #

show a path abbreviating /descendant-or-self::node()/

data PrimKind Source #

indicator for primary expressions

Constructors

Var

leading dollar

Literal

single or double quotes

Number

digits possibly with decimal point

data Expr Source #

expressions where function calls, unary and infix expressions are generic

Constructors

GenExpr Bool String [Expr]

infix?, op or fct, and arguments

PathExpr (Maybe Expr) Path

optional filter and path

FilterExpr Expr [Expr]

primary expression with predicates

PrimExpr PrimKind String 

Instances

Instances details
Show Expr Source # 
Instance details

Defined in Common.XPath

Methods

showsPrec :: Int -> Expr -> ShowS

show :: Expr -> String

showList :: [Expr] -> ShowS

showPred :: Expr -> String Source #

put square brackets around an expression

showExpr :: Expr -> String Source #

show expression with minimal parens

showInfixExpr :: String -> [Expr] -> String Source #

show arguments with minimal parens interspersed with the infix operator. Also treat the unary minus where the argument list is a singleton. Alphanumeric operators are shown with spaces, which looks bad for mod and div in conjunction with additive, relational, or equality operators. The unary minus gets a leading blank if the preceding character is a ncNameChar.

parenExpr :: Bool -> Maybe Int -> Expr -> String Source #

put parens around arguments that have a lower precedence or equal precendence if they are a right argument.

isPrimExpr :: Expr -> Bool Source #

test if expression is primary

infix operators

eqOps :: [String] Source #

unequal (!=) and equal (=)

relOps :: [String] Source #

the four other comparisons

addOps :: [String] Source #

+ and -, where - is allowed within names and as unary operator

multOps :: [String] Source #

*, div and mod, where * is also used as wildcard for node names

inOps :: [[String]] Source #

all infix operators. Lowest precedence for or followed by and, highest is union(|). Only these three operators may get more than two arguments.

parsers

skips :: Parser a -> Parser a Source #

skip trailing spaces

symbol :: String -> Parser String Source #

parse keyword and skip spaces

lpar :: Parser () Source #

skip left paren

rpar :: Parser () Source #

skip right paren

axis :: Parser Axis Source #

non-abbreviated axis parser

abbrAxis :: Parser Axis Source #

the axis specifier parser

ncNameStart :: Char -> Bool Source #

starting name character (no unicode)

ncNameChar :: Char -> Bool Source #

name character (without +) including centered dot (and no other unicode)

ncName :: Parser String Source #

non-colon xml names (non-skipping)

literal :: Parser String Source #

literal string within single or double quotes (skipping)

localName :: Parser String Source #

ncName or wild-card (*) (skipping)

nodeTest :: Parser NodeTest Source #

the node test parser

abbrStep :: Parser Step Source #

parent or self abbreviated steps

predicate :: Parser Expr Source #

the predicate (expression in square brackets) parser

step :: Parser Step Source #

the step (stuff between slashes) parser

descOrSelfStep :: Step Source #

the implicit descendant-or-self::node() step constant

doubleSlash :: Parser Bool Source #

a double or single slash

slashStep :: Parser [Step] Source #

a step starting with a single or double slash, the latter yielding two steps.

relPath :: Parser [Step] Source #

parse the steps of a relative path

path :: Parser Path Source #

a (possibly empty) absolute or (non-empty) relative path

number :: Parser String Source #

at least one digit and at most one decimal point (skipping)

qualName :: Parser String Source #

a qualified name (prefixed or unprefixed)

primExpr :: Parser Expr Source #

parse a primary expression (including fct or expr in parens)

fct :: Parser Expr Source #

parse a function call by checking the qname and the left paren

filterExpr :: Parser Expr Source #

parse a filter expresssion as primary expression followed by predicates

pathExpr :: Parser Expr Source #

a path expression is either a filter expression followed by a (non-empty) absoulte path or an ordinary path.

singleInfixExpr :: Parser Expr -> String -> Parser Expr Source #

parse multiple argument expressions separated by an infix symbol

unionExpr :: Parser Expr Source #

pathExpr are arguments of union expression

unaryExpr :: Parser Expr Source #

unionExpr can be prefixed by the unary minus

leftAssocExpr :: Parser Expr -> [String] -> Parser Expr Source #

parse as many arguments separated by any infix symbol as possible but construct left-associative binary application trees.

all final infix parsers using leftAssocExpr or singleInfixExpr

multExpr :: Parser Expr Source #

addExpr :: Parser Expr Source #

relExpr :: Parser Expr Source #

eqExpr :: Parser Expr Source #

andExpr :: Parser Expr Source #

expr :: Parser Expr Source #

the top-level expressions interspersed by or.

checking sanity of paths

data PrincipalNodeType Source #

Instances

Instances details
Eq PrincipalNodeType Source # 
Instance details

Defined in Common.XPath

isElementNode :: Step -> Bool Source #

may this step have further steps

isLegalPath :: [Step] -> Bool Source #

finalStep :: Path -> Maybe Step Source #

type FctEnv = [(String, (BasicType, [BasicType]))] Source #

type VarEnv = [(String, BasicType)] Source #

isPathExpr :: Expr -> Bool Source #

parseExpr :: String -> Either String Expr Source #

parse string