hxt-9.3.1.16: A collection of tools for processing XML with Haskell.

CopyrightCopyright (C) 2010 Uwe Schmidt
LicenseMIT
MaintainerUwe Schmidt (uwe\@fh-wedel.de)
Stabilitystable
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Control.Arrow.ArrowTree

Description

List arrows for tree processing.

Trees that implement the Data.Tree.Class interface, can be processed with these arrows.

Synopsis

Documentation

class (ArrowPlus a, ArrowIf a) => ArrowTree a where Source #

The interface for tree arrows

all functions have default implementations

Methods

mkLeaf :: Tree t => b -> a c (t b) Source #

construct a leaf

mkTree :: Tree t => b -> [t b] -> a c (t b) Source #

construct an inner node

getChildren :: Tree t => a (t b) (t b) Source #

select the children of the root of a tree

getNode :: Tree t => a (t b) b Source #

select the node info of the root of a tree

hasNode :: Tree t => (b -> Bool) -> a (t b) (t b) Source #

select the attribute of the root of a tree

setChildren :: Tree t => [t b] -> a (t b) (t b) Source #

substitute the children of the root of a tree

setNode :: Tree t => b -> a (t b) (t b) Source #

substitute the attribute of the root of a tree

changeChildren :: Tree t => ([t b] -> [t b]) -> a (t b) (t b) Source #

edit the children of the root of a tree

changeNode :: Tree t => (b -> b) -> a (t b) (t b) Source #

edit the attribute of the root of a tree

processChildren :: Tree t => a (t b) (t b) -> a (t b) (t b) Source #

apply an arrow element wise to all children of the root of a tree collect these results and substitute the children with this result

example: processChildren isText deletes all subtrees, for which isText does not hold

example: processChildren (none `when` isCmt) removes all children, for which isCmt holds

replaceChildren :: Tree t => a (t b) (t b) -> a (t b) (t b) Source #

similar to processChildren, but the new children are computed by processing the whole input tree

example: replaceChildren (deep isText) selects all subtrees for which isText holds and substitutes the children component of the root node with this list

(/>) :: Tree t => a b (t c) -> a (t c) d -> a b d infixl 5 Source #

pronounced "slash", meaning g inside f

defined as f /> g = f >>> getChildren >>> g

example: hasName "html" /> hasName "body" /> hasName "h1"

This expression selects all "h1" elements in the "body" element of an "html" element, an expression, that corresponds 1-1 to the XPath selection path "html/body/h1"

(//>) :: Tree t => a b (t c) -> a (t c) d -> a b d infixl 5 Source #

pronounced "double slash", meaning g arbitrarily deep inside f

defined as f //> g = f >>> getChildren >>> deep g

example: hasName "html" //> hasName "table"

This expression selects all top level "table" elements within an "html" element, an expression. Attention: This does not correspond to the XPath selection path "html//table". The latter on matches all table elements even nested ones, but //> gives in many cases the appropriate functionality.

(</) :: Tree t => a (t b) (t b) -> a (t b) (t b) -> a (t b) (t b) infixl 5 Source #

pronounced "outside" meaning f containing g

defined as f </ g = f `containing` (getChildren >>> g)

deep :: Tree t => a (t b) c -> a (t b) c Source #

recursively searches a whole tree for subtrees, for which a predicate holds. The search is performed top down. When a tree is found, this becomes an element of the result list. The tree found is not further examined for any subtress, for which the predicate also could hold. See multi for this kind of search.

example: deep isHtmlTable selects all top level table elements in a document (with an appropriate definition for isHtmlTable) but no tables occuring within a table cell.

deepest :: Tree t => a (t b) c -> a (t b) c Source #

recursively searches a whole tree for subrees, for which a predicate holds. The search is performed bottom up.

example: deepest isHtmlTable selects all innermost table elements in a document but no table elements containing tables. See deep and multi for other search strategies.

multi :: Tree t => a (t b) c -> a (t b) c Source #

recursively searches a whole tree for subtrees, for which a predicate holds. The search is performed top down. All nodes of the tree are searched, even within the subtrees of trees for which the predicate holds.

example: multi isHtmlTable selects all table elements, even nested ones.

processBottomUp :: Tree t => a (t b) (t b) -> a (t b) (t b) Source #

recursively transforms a whole tree by applying an arrow to all subtrees, this is done bottom up depth first, leaves first, root as last tree

example: processBottomUp (getChildren `when` isHtmlFont) removes all font tags in a HTML document, even nested ones (with an appropriate definition of isHtmlFont)

processTopDown :: Tree t => a (t b) (t b) -> a (t b) (t b) Source #

similar to processBottomUp, but recursively transforms a whole tree by applying an arrow to all subtrees with a top down depth first traversal strategie. In many cases processBottomUp and processTopDown give same results.

processBottomUpWhenNot :: Tree t => a (t b) (t b) -> a (t b) (t b) -> a (t b) (t b) Source #

recursively transforms a whole tree by applying an arrow to all subtrees, but transformation stops when a predicte does not hold for a subtree, leaves are transformed first

processTopDownUntil :: Tree t => a (t b) (t b) -> a (t b) (t b) Source #

recursively transforms a whole tree by applying an arrow to all subtrees, but transformation stops when a tree is successfully transformed. the transformation is done top down

example: processTopDownUntil (isHtmlTable `guards` tranformTable) transforms all top level table elements into something else, but inner tables remain unchanged

insertChildrenAt :: Tree t => Int -> a (t b) (t b) -> a (t b) (t b) Source #

computes a list of trees by applying an arrow to the input and inserts this list in front of index i in the list of children

example: insertChildrenAt 0 (deep isCmt) selects all subtrees for which isCmt holds and copies theses in front of the existing children

insertChildrenAfter :: Tree t => a (t b) (t b) -> a (t b) (t b) -> a (t b) (t b) Source #

similar to insertChildrenAt, but the insertion position is searched with a predicate

insertTreeTemplate :: Tree t => a (t b) (t b) -> [IfThen (a (t b) c) (a (t b) (t b))] -> a (t b) (t b) Source #

an arrow for inserting a whole subtree with some holes in it (a template) into a document. The holes can be filled with contents from the input.

Example

insertTreeTemplateTest :: ArrowXml a => a b XmlTree
insertTreeTemplateTest
    = doc
      >>>
      insertTreeTemplate template pattern
    where
    doc                                                                -- the input data
       = constA "<x><y>The Title</y><z>The content</z></x>"
         >>> xread
    template                                                           -- the output template with 2 holes: xxx and yyy
       = constA "<html><head><title>xxx</title></head><body><h1>yyy</h1></body></html>"
         >>> xread
    pattern
       = [ hasText (== "xxx")                                          -- fill the xxx hole with the input contents from element "x/y"
           :-> ( getChildren >>> hasName "y" >>> deep isText )

         , hasText (== "yyy")                                          -- fill the yyy hole with the input contents from element "x/z"
           :-> ( getChildren >>> hasName "z" >>> getChildren )
         ]

computes the XML tree for the following document

"<html><head><title>The Title</title></head><body><h1>The content</h1></body></html>"

Instances

ArrowTree LA Source # 

Methods

mkLeaf :: Tree t => b -> LA c (t b) Source #

mkTree :: Tree t => b -> [t b] -> LA c (t b) Source #

getChildren :: Tree t => LA (t b) (t b) Source #

getNode :: Tree t => LA (t b) b Source #

hasNode :: Tree t => (b -> Bool) -> LA (t b) (t b) Source #

setChildren :: Tree t => [t b] -> LA (t b) (t b) Source #

setNode :: Tree t => b -> LA (t b) (t b) Source #

changeChildren :: Tree t => ([t b] -> [t b]) -> LA (t b) (t b) Source #

changeNode :: Tree t => (b -> b) -> LA (t b) (t b) Source #

processChildren :: Tree t => LA (t b) (t b) -> LA (t b) (t b) Source #

replaceChildren :: Tree t => LA (t b) (t b) -> LA (t b) (t b) Source #

(/>) :: Tree t => LA b (t c) -> LA (t c) d -> LA b d Source #

(//>) :: Tree t => LA b (t c) -> LA (t c) d -> LA b d Source #

(</) :: Tree t => LA (t b) (t b) -> LA (t b) (t b) -> LA (t b) (t b) Source #

deep :: Tree t => LA (t b) c -> LA (t b) c Source #

deepest :: Tree t => LA (t b) c -> LA (t b) c Source #

multi :: Tree t => LA (t b) c -> LA (t b) c Source #

processBottomUp :: Tree t => LA (t b) (t b) -> LA (t b) (t b) Source #

processTopDown :: Tree t => LA (t b) (t b) -> LA (t b) (t b) Source #

processBottomUpWhenNot :: Tree t => LA (t b) (t b) -> LA (t b) (t b) -> LA (t b) (t b) Source #

processTopDownUntil :: Tree t => LA (t b) (t b) -> LA (t b) (t b) Source #

insertChildrenAt :: Tree t => Int -> LA (t b) (t b) -> LA (t b) (t b) Source #

insertChildrenAfter :: Tree t => LA (t b) (t b) -> LA (t b) (t b) -> LA (t b) (t b) Source #

insertTreeTemplate :: Tree t => LA (t b) (t b) -> [IfThen (LA (t b) c) (LA (t b) (t b))] -> LA (t b) (t b) Source #

ArrowTree IOLA Source # 

Methods

mkLeaf :: Tree t => b -> IOLA c (t b) Source #

mkTree :: Tree t => b -> [t b] -> IOLA c (t b) Source #

getChildren :: Tree t => IOLA (t b) (t b) Source #

getNode :: Tree t => IOLA (t b) b Source #

hasNode :: Tree t => (b -> Bool) -> IOLA (t b) (t b) Source #

setChildren :: Tree t => [t b] -> IOLA (t b) (t b) Source #

setNode :: Tree t => b -> IOLA (t b) (t b) Source #

changeChildren :: Tree t => ([t b] -> [t b]) -> IOLA (t b) (t b) Source #

changeNode :: Tree t => (b -> b) -> IOLA (t b) (t b) Source #

processChildren :: Tree t => IOLA (t b) (t b) -> IOLA (t b) (t b) Source #

replaceChildren :: Tree t => IOLA (t b) (t b) -> IOLA (t b) (t b) Source #

(/>) :: Tree t => IOLA b (t c) -> IOLA (t c) d -> IOLA b d Source #

(//>) :: Tree t => IOLA b (t c) -> IOLA (t c) d -> IOLA b d Source #

(</) :: Tree t => IOLA (t b) (t b) -> IOLA (t b) (t b) -> IOLA (t b) (t b) Source #

deep :: Tree t => IOLA (t b) c -> IOLA (t b) c Source #

deepest :: Tree t => IOLA (t b) c -> IOLA (t b) c Source #

multi :: Tree t => IOLA (t b) c -> IOLA (t b) c Source #

processBottomUp :: Tree t => IOLA (t b) (t b) -> IOLA (t b) (t b) Source #

processTopDown :: Tree t => IOLA (t b) (t b) -> IOLA (t b) (t b) Source #

processBottomUpWhenNot :: Tree t => IOLA (t b) (t b) -> IOLA (t b) (t b) -> IOLA (t b) (t b) Source #

processTopDownUntil :: Tree t => IOLA (t b) (t b) -> IOLA (t b) (t b) Source #

insertChildrenAt :: Tree t => Int -> IOLA (t b) (t b) -> IOLA (t b) (t b) Source #

insertChildrenAfter :: Tree t => IOLA (t b) (t b) -> IOLA (t b) (t b) -> IOLA (t b) (t b) Source #

insertTreeTemplate :: Tree t => IOLA (t b) (t b) -> [IfThen (IOLA (t b) c) (IOLA (t b) (t b))] -> IOLA (t b) (t b) Source #

ArrowTree (SLA s) Source # 

Methods

mkLeaf :: Tree t => b -> SLA s c (t b) Source #

mkTree :: Tree t => b -> [t b] -> SLA s c (t b) Source #

getChildren :: Tree t => SLA s (t b) (t b) Source #

getNode :: Tree t => SLA s (t b) b Source #

hasNode :: Tree t => (b -> Bool) -> SLA s (t b) (t b) Source #

setChildren :: Tree t => [t b] -> SLA s (t b) (t b) Source #

setNode :: Tree t => b -> SLA s (t b) (t b) Source #

changeChildren :: Tree t => ([t b] -> [t b]) -> SLA s (t b) (t b) Source #

changeNode :: Tree t => (b -> b) -> SLA s (t b) (t b) Source #

processChildren :: Tree t => SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

replaceChildren :: Tree t => SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

(/>) :: Tree t => SLA s b (t c) -> SLA s (t c) d -> SLA s b d Source #

(//>) :: Tree t => SLA s b (t c) -> SLA s (t c) d -> SLA s b d Source #

(</) :: Tree t => SLA s (t b) (t b) -> SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

deep :: Tree t => SLA s (t b) c -> SLA s (t b) c Source #

deepest :: Tree t => SLA s (t b) c -> SLA s (t b) c Source #

multi :: Tree t => SLA s (t b) c -> SLA s (t b) c Source #

processBottomUp :: Tree t => SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

processTopDown :: Tree t => SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

processBottomUpWhenNot :: Tree t => SLA s (t b) (t b) -> SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

processTopDownUntil :: Tree t => SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

insertChildrenAt :: Tree t => Int -> SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

insertChildrenAfter :: Tree t => SLA s (t b) (t b) -> SLA s (t b) (t b) -> SLA s (t b) (t b) Source #

insertTreeTemplate :: Tree t => SLA s (t b) (t b) -> [IfThen (SLA s (t b) c) (SLA s (t b) (t b))] -> SLA s (t b) (t b) Source #

ArrowTree (IOSLA s) Source # 

Methods

mkLeaf :: Tree t => b -> IOSLA s c (t b) Source #

mkTree :: Tree t => b -> [t b] -> IOSLA s c (t b) Source #

getChildren :: Tree t => IOSLA s (t b) (t b) Source #

getNode :: Tree t => IOSLA s (t b) b Source #

hasNode :: Tree t => (b -> Bool) -> IOSLA s (t b) (t b) Source #

setChildren :: Tree t => [t b] -> IOSLA s (t b) (t b) Source #

setNode :: Tree t => b -> IOSLA s (t b) (t b) Source #

changeChildren :: Tree t => ([t b] -> [t b]) -> IOSLA s (t b) (t b) Source #

changeNode :: Tree t => (b -> b) -> IOSLA s (t b) (t b) Source #

processChildren :: Tree t => IOSLA s (t b) (t b) -> IOSLA s (t b) (t b) Source #

replaceChildren :: Tree t => IOSLA s (t b) (t b) -> IOSLA s (t b) (t b) Source #

(/>) :: Tree t => IOSLA s b (t c) -> IOSLA s (t c) d -> IOSLA s b d Source #

(//>) :: Tree t => IOSLA s b (t c) -> IOSLA s (t c) d -> IOSLA s b d Source #

(</) :: Tree t => IOSLA s (t b) (t b) -> IOSLA s (t b) (t b) -> IOSLA s (t b) (t b) Source #

deep :: Tree t => IOSLA s (t b) c -> IOSLA s (t b) c Source #

deepest :: Tree t => IOSLA s (t b) c -> IOSLA s (t b) c Source #

multi :: Tree t => IOSLA s (t b) c -> IOSLA s (t b) c Source #

processBottomUp :: Tree t => IOSLA s (t b) (t b) -> IOSLA s (t b) (t b) Source #

processTopDown :: Tree t => IOSLA s (t b) (t b) -> IOSLA s (t b) (t b) Source #

processBottomUpWhenNot :: Tree t => IOSLA s (t b) (t b) -> IOSLA s (t b) (t b) -> IOSLA s (t b) (t b) Source #

processTopDownUntil :: Tree t => IOSLA s (t b) (t b) -> IOSLA s (t b) (t b) Source #

insertChildrenAt :: Tree t => Int -> IOSLA s (t b) (t b) -> IOSLA s (t b) (t b) Source #

insertChildrenAfter :: Tree t => IOSLA s (t b) (t b) -> IOSLA s (t b) (t b) -> IOSLA s (t b) (t b) Source #

insertTreeTemplate :: Tree t => IOSLA s (t b) (t b) -> [IfThen (IOSLA s (t b) c) (IOSLA s (t b) (t b))] -> IOSLA s (t b) (t b) Source #

class Tree t Source #

The interface for trees

Instances

Tree NTree Source #

Implementation of Data.Tree.Class interface for rose trees

Methods

mkTree :: a -> [NTree a] -> NTree a Source #

mkLeaf :: a -> NTree a Source #

isLeaf :: NTree a -> Bool Source #

isInner :: NTree a -> Bool Source #

getNode :: NTree a -> a Source #

getChildren :: NTree a -> [NTree a] Source #

changeNode :: (a -> a) -> NTree a -> NTree a Source #

changeChildren :: ([NTree a] -> [NTree a]) -> NTree a -> NTree a Source #

setNode :: a -> NTree a -> NTree a Source #

setChildren :: [NTree a] -> NTree a -> NTree a Source #

foldTree :: (a -> [b] -> b) -> NTree a -> b Source #

nodesTree :: NTree a -> [a] Source #

depthTree :: NTree a -> Int Source #

cardTree :: NTree a -> Int Source #

formatTree :: (a -> String) -> NTree a -> String Source #

Tree NTZipper Source #