xml-indexed-cursor-0.1.0.0: Indexed XML cursors similar to 'Text.XML.Cursor' from xml-conduit

CopyrightDennis Gosnell 2017
LicenseBSD3
MaintainerDennis Gosnell (cdep.illabout@gmail.com)
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Text.XML.Cursor.Indexed

Contents

Description

This module provides indexed Cursors. It has a very similar API to Text.XML.Cursor.

The big difference is in the Cursor type. Cursor wraps around a Node, while this module's Cursor type wraps around an IndexedNode.

An IndexedNode is a data type that contains both a Node and a NodeIndex. The NodeIndex gives a way to figure out how two IndexedNodes compare to each other in the Document. It gives the ability to figure out which IndexedNode comes earlier in the Document. This gives the ability to sort lists of IndexedNodes, based on their location in the Document. See NodeIndex for more information.

Synopsis

Cursor

type IndexedCursor = Cursor IndexedNode Source #

This is similar to Cursor except for IndexedNode.

type IndexedAxis = Axis IndexedNode Source #

This is similar to 'Text.XML.Cursor.Axis except for IndexedNode.

NodeIndex and IndexedNode

newtype NodeIndex Source #

Index for a Node in a Document.

The root element has a value of '[]'. Every child element is given an Int index as the first element of the list, and the grandchild elements are given an Int index as the second element of the list, and so on. If there are multiple root elements, then '[]' acts as a "virtual" root element that contains all actual root elements.

The index of the first child of the root be [0]

The index of the second child of the root would be [1].

The index of the third child of the root would be [2].

The index of the first child of the first child of the root would be [0, 0].

The index of the second child of the first child of the root would be [0, 1] (since the [Int] is stored reversed).

The index of the third child of the fifth child of the root would be [4, 2].

Constructors

NodeIndex 

Fields

Instances

Eq NodeIndex Source # 
Data NodeIndex Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NodeIndex -> c NodeIndex #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NodeIndex #

toConstr :: NodeIndex -> Constr #

dataTypeOf :: NodeIndex -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NodeIndex) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NodeIndex) #

gmapT :: (forall b. Data b => b -> b) -> NodeIndex -> NodeIndex #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NodeIndex -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NodeIndex -> r #

gmapQ :: (forall d. Data d => d -> u) -> NodeIndex -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NodeIndex -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NodeIndex -> m NodeIndex #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NodeIndex -> m NodeIndex #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NodeIndex -> m NodeIndex #

Ord NodeIndex Source # 
Read NodeIndex Source # 
Show NodeIndex Source # 
HasNodeIndex NodeIndex Source # 

class HasNodeIndex a where Source #

Minimal complete definition

nodeIndexLens

Methods

nodeIndexLens :: Functor f => (NodeIndex -> f NodeIndex) -> a -> f a Source #

This is basically Lens' a NodeIndex.

rootIndex :: NodeIndex Source #

Index to use for the root NodeIndex. Should be '[]'.

data IndexedNode Source #

IndexedNode just wraps together a Node and a NodeIndex for that Node.

Instances

Eq IndexedNode Source # 
Data IndexedNode Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IndexedNode -> c IndexedNode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IndexedNode #

toConstr :: IndexedNode -> Constr #

dataTypeOf :: IndexedNode -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c IndexedNode) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IndexedNode) #

gmapT :: (forall b. Data b => b -> b) -> IndexedNode -> IndexedNode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IndexedNode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IndexedNode -> r #

gmapQ :: (forall d. Data d => d -> u) -> IndexedNode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IndexedNode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IndexedNode -> m IndexedNode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IndexedNode -> m IndexedNode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IndexedNode -> m IndexedNode #

Show IndexedNode Source # 
HasNodeIndex IndexedNode Source # 

toChildIndex Source #

Arguments

:: NodeIndex

Parent NodeIndex.

-> Int

Child index.

-> NodeIndex 

Create a NodeIndex for the Int child below the input parent NodeIndex.

childNodeToIndexedNode :: NodeIndex -> Int -> Node -> IndexedNode Source #

In childNodeToIndexedNode parentIndex childIndexInt childNode, create an IndexedNode out of childNode, creating its NodeIndex using toChildIndex.

childNodesToIndexedNodes :: NodeIndex -> [Node] -> [IndexedNode] Source #

In 'childNodesToIndexedNodes parentIndex childNodes convert a list of Node childNodes to a list of IndexNodes using the NodeIndex parentIndex@.

Converting

fromDocument :: Document -> IndexedCursor Source #

Convert a Document to a Cursor. It will point to the document root.

"check" functions

check :: Boolean b => (Cursor a -> b) -> Axis a Source #

Filter cursors that don't pass a check.

checkIndexedNode :: Boolean b => (IndexedNode -> b) -> IndexedAxis Source #

Filter nodes that don't pass a check.

checkElement :: Boolean b => (Element -> b) -> IndexedAxis Source #

Filter elements that don't pass a check, and remove all non-elements.

checkName :: Boolean b => (Name -> b) -> IndexedAxis Source #

Filter elements that don't pass a name check, and remove all non-elements.

XPath-style functions

element :: Name -> IndexedAxis Source #

Select only those elements with a matching tag name.

XPath: /A node test that is a QName is true if and only if the type of the node (see [5 Data Model]) is the principal node type and has an expanded-name equal to the expanded-name specified by the QName./

content :: IndexedCursor -> [Text] Source #

Select only text nodes, and directly give the Content values.

XPath: The node test text() is true for any text node.

Note that this is not strictly an Axis, but will work with most combinators.

>>> let cursor = indexedCursorFromText_ "<foo>hello<bar/>bye</foo>"
>>> cursor $| child >=> content
["hello","bye"]
>>> cursor $| child >=> child >=> content
[]

attribute :: Name -> IndexedCursor -> [Text] Source #

Select attributes on the current element (or nothing if it is not an element).

XPath: /the attribute axis contains the attributes of the context node; the axis will be empty unless the context node is an element/

Note that this is not strictly an Axis, but will work with most combinators.

The return list of the generalised axis contains as elements lists of Content elements, each full list representing an attribute value.

>>> let cursor = indexedCursorFromText_ "<foo hello='cat' bar='3'>hello world</foo>"
>>> cursor $| attribute "hello"
["cat"]
>>> cursor $| attribute "doesntexist"
[]
>>> cursor $| child >=> attribute "attroftext"
[]

attributeMay :: Name -> IndexedCursor -> Maybe Text Source #

Similar to attribute but return a Maybe instead of a list.

>>> let cursor = indexedCursorFromText_ "<foo hello='cat' bar='3'>hello world</foo>"
>>> cursor $| attributeMay "hello"
Just "cat"
>>> cursor $| attributeMay "doesntexist"
Nothing

laxAttribute :: Text -> IndexedCursor -> [Text] Source #

Select attributes on the current element (or nothing if it is not an element). Namespace and case are ignored.

XPath: /the attribute axis contains the attributes of the context node; the axis will be empty unless the context node is an element/

Note that this is not strictly an Axis, but will work with most combinators.

The return list of the generalised axis contains as elements lists of Content elements, each full list representing an attribute value.

>>> let cursor = indexedCursorFromText_ "<foo HellO='cat'/>"
>>> cursor $| laxAttribute "HellO"
["cat"]
>>> cursor $| laxAttribute "Hello"
["cat"]
>>> cursor $| laxAttribute "hello"
["cat"]
>>> cursor $| laxAttribute "bye"
[]

hasAttribute :: Name -> IndexedAxis Source #

Select only those element nodes with the given attribute.

attributeIs :: Name -> Text -> IndexedAxis Source #

Select only those element nodes containing the given attribute key/value pair.

descendantElementsNamed :: Name -> IndexedAxis Source #

For a given Name, find all descendant Elements with that Name.

ancestorElementsNamed :: Name -> IndexedAxis Source #

For a given Name, find all ancestor Elements. with that Name.

descendantElementsNamedWithAttr :: Name -> Name -> Text -> IndexedAxis Source #

In descendantElementsNamedWithAttr elemName attrKey attrVal, find all descendant Elements with elemName that have an attribute called attrKey with a value of attrVal.

descendantContent :: IndexedCursor -> [Text] Source #

Find all content in all descendants.

>>> let cursor = indexedCursorFromText_ "<foo>hello<bar>lala</bar>bye</foo>"
>>> descendantContent cursor
["hello","lala","bye"]
>>> let cursor = indexedCursorFromText_ "<foo/>"
>>> descendantContent cursor
[]

attrValForElemCursor :: Name -> IndexedCursor -> Maybe Text Source #

Find attribute with Name on the element IndexedCursor is pointing to.

>>> let cursor = indexedCursorFromText_ "<foo hello='3'/>"
>>> attrValForElemCursor "hello" cursor
Just "3"
>>> attrValForElemCursor "bye" cursor
Nothing

Parse directly into IndexedCursor

Patterns