hxt-8.3.1: A collection of tools for processing XML with Haskell.Source codeContentsIndex
Text.XML.HXT.Arrow.XPathSimple
Portabilityportable
Stabilityexperimental
MaintainerUwe Schmidt (uwe@fh-wedel.de)
Description

XPath selection for simple XPath expressions with list arrows instead of navigable trees.

It is recommended, that this module is imported qualified, e.g like Text.XML.HXT.Arrow.XPathSimple as XS.

The arrows defined in this module have the same functionality as the functions in Text.XML.HXT.Arrow.XPath.

The computation model in XPath is a navigable tree, that means a tree which can be traversed in arbitrary directions, not only from the root to the leafs. Sometimes this model leads to inefficient XPath processing for simple queries, which only need a top down tree traversal.

When evaluating an XPath expression with these functions, first an attempt is made to map the XPath expression to a pure arrow. If this is possible due to the simplicity of the XPath expressions, the result is computed directly, else the query is processed by the corresponding function in Text.XML.HXT.Arrow.XPath.

The simple evaluation is possible, when in the XPath expression only the top down axes (self, child, descendant, descendant or self) are used, when no built-in functions concerning the position of a node are used, and no comparison of nodes e.g. in node set union is required.

Synopsis
getXPathTreesInDoc :: ArrowXml a => String -> a XmlTree XmlTree
getXPathTreesInDocWithNsEnv :: ArrowXml a => Attributes -> String -> a XmlTree XmlTree
getXPathTrees :: ArrowXml a => String -> a XmlTree XmlTree
getXPathTreesWithNsEnv :: ArrowXml a => Attributes -> String -> a XmlTree XmlTree
tryGetXPath :: ArrowXml a => Attributes -> String -> a XmlTree XmlTree
getXPathTreesWithNsEnvSimple :: ArrowXml a => Attributes -> String -> a XmlTree XmlTree
getXP :: NsEnv -> String -> LA XmlTree XmlTree
type XPArrow b c = Maybe (LA b c)
mk :: LA b c -> XPArrow b c
unwrap :: XPArrow b b -> LA b b
(>>>>) :: XPArrow b b -> XPArrow b b -> XPArrow b b
(&&&&) :: XPArrow b b -> XPArrow b b -> XPArrow b (b, b)
(<+>>) :: XPArrow b b -> XPArrow b b -> XPArrow b b
guards' :: XPArrow b b -> XPArrow b b -> XPArrow b b
this' :: XPArrow b b
this'' :: XPArrow b b
toThis :: XPArrow b b -> XPArrow b b
getChildren' :: XPArrow XmlTree XmlTree -> XPArrow XmlTree XmlTree
getAttrl' :: XPArrow XmlTree XmlTree -> XPArrow XmlTree XmlTree
multi' :: XPArrow XmlTree XmlTree -> XPArrow XmlTree XmlTree
deep' :: XPArrow XmlTree XmlTree -> XPArrow XmlTree XmlTree
xIndex :: Int -> LA [b] b
xString :: XPArrow XmlTree XmlTree -> LA XmlTree String
xNumber' :: XPArrow XmlTree XmlTree -> LA XmlTree XPNumber
deadEndStreet :: Monad m => m a
compXPath :: MonadPlus m => Expr -> m (LA XmlTree XmlTree)
compXP :: MonadPlus m => Expr -> m (XPArrow XmlTree XmlTree)
compFP :: MonadPlus m => [Expr] -> XPArrow XmlTree XmlTree -> m (XPArrow XmlTree XmlTree)
compLP :: MonadPlus m => [XStep] -> XPArrow XmlTree XmlTree -> m (XPArrow XmlTree XmlTree)
compXS :: MonadPlus m => XStep -> XPArrow XmlTree XmlTree -> m (XPArrow XmlTree XmlTree)
compNTE :: Monad m => NodeTest -> m (XPArrow XmlTree XmlTree)
compNTA :: Monad m => NodeTest -> m (XPArrow XmlTree XmlTree)
compNameT :: Monad m => LA XmlTree XmlTree -> QName -> m (XPArrow XmlTree XmlTree)
compNT :: Monad m => NodeTest -> m (XPArrow XmlTree XmlTree)
compPred :: MonadPlus m => [Expr] -> XPArrow XmlTree XmlTree -> m (XPArrow XmlTree XmlTree)
compPred1 :: MonadPlus m => Expr -> XPArrow XmlTree XmlTree -> m (XPArrow XmlTree XmlTree)
compRelPathExpr :: MonadPlus m => Expr -> m (XPArrow XmlTree XmlTree)
compStringExpr :: MonadPlus m => Expr -> m String
compNumberExpr :: MonadPlus m => Expr -> m XPNumber
compIntExpr :: MonadPlus m => Expr -> m Int
compBoolExpr :: MonadPlus m => Expr -> m Bool
compGenExpr :: MonadPlus m => Expr -> m (XPArrow XmlTree XmlTree)
compString :: MonadPlus m => Op -> Expr -> Expr -> m (XPArrow XmlTree XmlTree)
compNumber :: MonadPlus m => Op -> Expr -> Expr -> m (XPArrow XmlTree XmlTree)
compBool :: MonadPlus m => Op -> Expr -> Expr -> m (XPArrow XmlTree XmlTree)
compPath :: MonadPlus m => Op -> Expr -> Expr -> m (XPArrow XmlTree XmlTree)
toNumber :: String -> XPNumber
equalNodeSet :: Eq a => [a] -> [a] -> [a]
Documentation
getXPathTreesInDoc :: ArrowXml a => String -> a XmlTree XmlTreeSource
Same Functionality as Text.XML.HXT.Arrow.XPath.getXPathTreesInDoc
getXPathTreesInDocWithNsEnv :: ArrowXml a => Attributes -> String -> a XmlTree XmlTreeSource
Same Functionality as Text.XML.HXT.Arrow.XPath.getXPathTreesInDocWithNsEnv
getXPathTrees :: ArrowXml a => String -> a XmlTree XmlTreeSource
Same Functionality as Text.XML.HXT.Arrow.XPath.getXPathTrees
getXPathTreesWithNsEnv :: ArrowXml a => Attributes -> String -> a XmlTree XmlTreeSource
Same Functionality as Text.XML.HXT.Arrow.XPath.getXPathTreesWithNsEnv
tryGetXPath :: ArrowXml a => Attributes -> String -> a XmlTree XmlTreeSource
getXPathTreesWithNsEnvSimple :: ArrowXml a => Attributes -> String -> a XmlTree XmlTreeSource

The xpath interpreter for simple xpath expressions.

In case of a too complicated or illegal xpath expression an error node is returned, else the list of selected XML trees

getXP :: NsEnv -> String -> LA XmlTree XmlTreeSource
type XPArrow b c = Maybe (LA b c)Source
mk :: LA b c -> XPArrow b cSource
unwrap :: XPArrow b b -> LA b bSource
(>>>>) :: XPArrow b b -> XPArrow b b -> XPArrow b bSource
(&&&&) :: XPArrow b b -> XPArrow b b -> XPArrow b (b, b)Source
(<+>>) :: XPArrow b b -> XPArrow b b -> XPArrow b bSource
guards' :: XPArrow b b -> XPArrow b b -> XPArrow b bSource
this' :: XPArrow b bSource
this'' :: XPArrow b bSource
toThis :: XPArrow b b -> XPArrow b bSource
getChildren' :: XPArrow XmlTree XmlTree -> XPArrow XmlTree XmlTreeSource
getAttrl' :: XPArrow XmlTree XmlTree -> XPArrow XmlTree XmlTreeSource
multi' :: XPArrow XmlTree XmlTree -> XPArrow XmlTree XmlTreeSource
deep' :: XPArrow XmlTree XmlTree -> XPArrow XmlTree XmlTreeSource
xIndex :: Int -> LA [b] bSource
xString :: XPArrow XmlTree XmlTree -> LA XmlTree StringSource
xNumber' :: XPArrow XmlTree XmlTree -> LA XmlTree XPNumberSource
deadEndStreet :: Monad m => m aSource
compXPath :: MonadPlus m => Expr -> m (LA XmlTree XmlTree)Source
compXP :: MonadPlus m => Expr -> m (XPArrow XmlTree XmlTree)Source
compFP :: MonadPlus m => [Expr] -> XPArrow XmlTree XmlTree -> m (XPArrow XmlTree XmlTree)Source
compLP :: MonadPlus m => [XStep] -> XPArrow XmlTree XmlTree -> m (XPArrow XmlTree XmlTree)Source
compXS :: MonadPlus m => XStep -> XPArrow XmlTree XmlTree -> m (XPArrow XmlTree XmlTree)Source
compNTE :: Monad m => NodeTest -> m (XPArrow XmlTree XmlTree)Source
compNTA :: Monad m => NodeTest -> m (XPArrow XmlTree XmlTree)Source
compNameT :: Monad m => LA XmlTree XmlTree -> QName -> m (XPArrow XmlTree XmlTree)Source
compNT :: Monad m => NodeTest -> m (XPArrow XmlTree XmlTree)Source
compPred :: MonadPlus m => [Expr] -> XPArrow XmlTree XmlTree -> m (XPArrow XmlTree XmlTree)Source
compPred1 :: MonadPlus m => Expr -> XPArrow XmlTree XmlTree -> m (XPArrow XmlTree XmlTree)Source
compRelPathExpr :: MonadPlus m => Expr -> m (XPArrow XmlTree XmlTree)Source
compStringExpr :: MonadPlus m => Expr -> m StringSource
compNumberExpr :: MonadPlus m => Expr -> m XPNumberSource
compIntExpr :: MonadPlus m => Expr -> m IntSource
compBoolExpr :: MonadPlus m => Expr -> m BoolSource
compGenExpr :: MonadPlus m => Expr -> m (XPArrow XmlTree XmlTree)Source
compString :: MonadPlus m => Op -> Expr -> Expr -> m (XPArrow XmlTree XmlTree)Source
compNumber :: MonadPlus m => Op -> Expr -> Expr -> m (XPArrow XmlTree XmlTree)Source
compBool :: MonadPlus m => Op -> Expr -> Expr -> m (XPArrow XmlTree XmlTree)Source
compPath :: MonadPlus m => Op -> Expr -> Expr -> m (XPArrow XmlTree XmlTree)Source
toNumber :: String -> XPNumberSource
equalNodeSet :: Eq a => [a] -> [a] -> [a]Source
Produced by Haddock version 2.4.2