hxt-8.2.0: A collection of tools for processing XML with Haskell.Source codeContentsIndex
Data.Tree.NTree.Filter
Portabilityportable
Stabilityexperimental
MaintainerUwe Schmidt (uwe\@fh-wedel.de)
Contents
Filter
Monadic Filter
Description

Version : $Id: Filter.hs,v 1.6 20061112 14:52:59 hxml Exp $

Filter for n-ary tree structure with filter combinators copied and modified from HxXml (http://www.cs.york.ac.uk/fp/HaXml/)

Similar but more flexible functions for tree processing are defined in the arrow classes Control.Arrow.ArrowList, Control.Arrow.ArrowIf, Control.Arrow.ArrowTree and Control.Arrow.ArrowState. For new applications, especially for XML processing, it's recommended to use the arrow interface Text.XML.HXT.Arrow instead of this filter approach as part of the api Text.XML.HXT.Parser

Synopsis
module Data.Tree.NTree.TypeDefs
type TFilter node = NTree node -> NTrees node
type TSFilter node = NTrees node -> NTrees node
satisfies :: (a -> [b]) -> a -> Bool
none :: a -> [b]
this :: a -> [a]
isOf :: (a -> Bool) -> a -> [a]
isOfNode :: (node -> Bool) -> TFilter node
mkNTree :: NTree node -> TFilter node
replaceNode :: node -> TFilter node
replaceChildren :: NTrees node -> TFilter node
modifyNode :: (node -> Maybe node) -> TFilter node
modifyNode0 :: (node -> node) -> TFilter node
modifyChildren :: TSFilter node -> TFilter node
substChildren :: TFilter node -> TFilter node
processChildren :: TFilter node -> TFilter node
o :: (a -> [b]) -> (c -> [a]) -> c -> [b]
(.>) :: (a -> [b]) -> (b -> [c]) -> a -> [c]
seqF :: [a -> [a]] -> a -> [a]
(..>) :: (a -> [b]) -> (a -> b -> [d]) -> a -> [d]
(+++) :: (a -> [b]) -> (a -> [b]) -> a -> [b]
cat :: [a -> [b]] -> a -> [b]
orElse :: (a -> [b]) -> (a -> [b]) -> a -> [b]
iff :: (a -> [c]) -> (a -> [b]) -> (a -> [b]) -> a -> [b]
choice :: [IfThen (a -> [c]) (a -> [b])] -> a -> [b]
data IfThen a b = a :-> b
when :: (a -> [a]) -> (a -> [a]) -> a -> [a]
whenNot :: (a -> [a]) -> (a -> [a]) -> a -> [a]
guards :: (a -> [b]) -> (a -> [b]) -> a -> [b]
neg :: (a -> [c]) -> a -> [a]
containing :: (a -> [b]) -> (b -> [c]) -> a -> [b]
notContaining :: (a -> [b]) -> (b -> [c]) -> a -> [b]
(/>) :: TFilter node -> TFilter node -> TFilter node
(</) :: TFilter node -> TFilter node -> TFilter node
deep :: TFilter node -> TFilter node
deepest :: TFilter node -> TFilter node
multi :: TFilter node -> TFilter node
processBottomUp :: TFilter node -> TFilter node
processBottomUpIfNot :: TFilter node -> TFilter node -> TFilter node
processTopDown :: TFilter node -> TFilter node
processTopDownUntil :: TFilter node -> TFilter node
insertChildrenAt :: Int -> TFilter node -> TFilter node
insertChildrenAfter :: TFilter node -> TFilter node -> TFilter node
thisM :: Monad m => a -> m [a]
noneM :: Monad m => a -> m [b]
(.>>) :: Monad m => (a -> m [b]) -> (b -> m [c]) -> a -> m [c]
seqM :: Monad m => [a -> m [a]] -> a -> m [a]
(+++>>) :: Monad m => (a -> m [b]) -> (a -> m [b]) -> a -> m [b]
catM :: Monad m => [a -> m [b]] -> a -> m [b]
ifM :: Monad m => (a -> [b]) -> (a -> m [c]) -> (a -> m [c]) -> a -> m [c]
choiceM :: Monad m => [IfThen (a -> [c]) (a -> m [b])] -> a -> m [b]
whenM :: Monad m => (a -> m [a]) -> (a -> [b]) -> a -> m [a]
whenNotM :: Monad m => (a -> m [a]) -> (a -> [b]) -> a -> m [a]
guardsM :: Monad m => (a -> [b]) -> (a -> m [c]) -> a -> m [c]
containingM :: Monad m => (a -> m [b]) -> (b -> [c]) -> a -> m [b]
processChildrenM :: Monad m => (NTree node -> m [NTree node]) -> NTree node -> m [NTree node]
processTopDownM :: Monad m => (NTree node -> m [NTree node]) -> NTree node -> m [NTree node]
processBottomUpM :: Monad m => (NTree node -> m [NTree node]) -> NTree node -> m [NTree node]
liftMf :: Monad m => (a -> [b]) -> a -> m [b]
($$) :: (a -> [b]) -> [a] -> [b]
($$<) :: Monad m => (a -> m [b]) -> [a] -> m [b]
performAction :: Monad m => (a -> m b) -> a -> m [a]
Documentation
module Data.Tree.NTree.TypeDefs
type TFilter node = NTree node -> NTrees nodeSource

tree filter type: a function mapping a tree onto a list of trees

filter can be used in various ways, as predicates, selectors, transformers, ...

type TSFilter node = NTrees node -> NTrees nodeSource
a filter for sequences
satisfies :: (a -> [b]) -> a -> BoolSource

satisfies converts a result of a predicate filter into a boolean

is a shortcut for not . null

typical use in guards or ifs: if (satisfies f) t then ... else ...

  • 1.parameter f : the predicate filter
  • 2.parameter t : the tree to be tested
  • returns : b = not (null (f t))
Filter
none :: a -> [b]Source
the null filter, returns the empty list
this :: a -> [a]Source
the unit filter, returns the single element list containing the argument
isOf :: (a -> Bool) -> a -> [a]Source

conversion from predicate function to filter

  • 1.parameter p : the predicate for testing the tree
  • returns : this or none depending on the predicate
isOfNode :: (node -> Bool) -> TFilter nodeSource

select filter, selects trees with node values with a specific property

  • 1.parameter p : the predicate for testing the node value
  • returns : [] or [t] depending on p t

a special case of isOf filter

mkNTree :: NTree node -> TFilter nodeSource

filter for substituting an arbitray tree by a constant

  • 1.parameter t : the result tree, the input tree is ignored
  • returns : the filter
replaceNode :: node -> TFilter nodeSource

filter for replacing the node

  • 1.parameter n : the new node
  • returns : the editing filter
replaceChildren :: NTrees node -> TFilter nodeSource

filter for replacing the children

  • 1.parameter cs : cs the list of children
  • returns : the filter
modifyNode :: (node -> Maybe node) -> TFilter nodeSource
modifyNode0 :: (node -> node) -> TFilter nodeSource

filter for editing the node

  • 1.parameter nf : the XNode editing funtion
  • returns : the filter
modifyChildren :: TSFilter node -> TFilter nodeSource

filter for editing the children

all children are processed with a filter mapping lists to lists, this enables not only elementwise editing by lifting a normal filter to a list filter with (f $$) (see '($$)') but also manipulation of the order of the elements, e.g. reverse is an appropriate childen editing function.

  • 1.parameter csf : the children editing function
  • returns : the filter

see also : processChildren

substChildren :: TFilter node -> TFilter nodeSource
filter for substituting the children of a tree by a new list of childen computed by applying a filter to the input tree. modifyChildren can be expressed by substChildren: modifyChildren f t is equal to substChildren (f . getChildren)
processChildren :: TFilter node -> TFilter nodeSource

Filter for editing the children of a tree element wise

  • 1.parameter cf : the filter applied to the children
  • returns : the editing filter

see also : modifyChildren

o :: (a -> [b]) -> (c -> [a]) -> c -> [b]Source

sequential composition of filters, usually written in infix notation f2 o f1.

for predicate filter the logical AND

  • 1.parameter f2 : the 2. filter
  • 2.parameter f1 : the 1. filter
  • returns : the fiter applying first f1 to n and then f2 to the result (like function composition)
(.>) :: (a -> [b]) -> (b -> [c]) -> a -> [c]Source

pronounced "followed by", defined as: f .> g = g `o` f.

allows filter composition in a more readable way from left to right

  • 1.parameter f1 : the 1. filter
  • 2.parameter f2 : the 2. filter
  • returns : the composition of f1 and f2

see also : o, '(..>)'

seqF :: [a -> [a]] -> a -> [a]Source

apply a list of filters sequentially with '(.>)', for predicate filters the generalized AND

see also : '(.>)'

(..>) :: (a -> [b]) -> (a -> b -> [d]) -> a -> [d]Source

special sequential composition.

filter f is applied to an argument t. then filter g is applied to all elements of the result list, but the argument t is also passed as extra parameter to g.

This allows for step by step transformations of a tree with access to the original tree in every transformation step.

see also : '(.>)', o

(+++) :: (a -> [b]) -> (a -> [b]) -> a -> [b]Source

binary parallel composition, the logical OR for predicate filter

  • 1.parameter f1 : the 1. filter
  • 2.parameter f2 : the 2. filter
  • returns : the filter for applying f1 and f2 both to an argument tree and concatenating the results
cat :: [a -> [b]] -> a -> [b]Source

apply a list of filters, a "union" for lists, for predicate filters the generalized OR

  • 1.parameter fs : the list of filters
  • returns : the composing filter
orElse :: (a -> [b]) -> (a -> [b]) -> a -> [b]Source

directional choice, usually written in infix notation as f orElse g

  • 1.parameter f : the 1. filter
  • 2.parameter g : the 2. filter
  • 3.parameter t : the tree
  • returns : the filter, that applies f to t, if the result is not the empty list, the result is found, else g t is the result
iff :: (a -> [c]) -> (a -> [b]) -> (a -> [b]) -> a -> [b]Source

if then else lifted to filters

  • 1.parameter p : the predicate filter
  • 2.parameter t : the "then" filter
  • 3.parameter e : the "else" filter
  • returns : the resulting conditional filter
choice :: [IfThen (a -> [c]) (a -> [b])] -> a -> [b]Source

multiway branch. The list of cases f :-> g is processed sequentially, in the first case for that f holds g is applied, if no case matches, none is applied. This filter can be used like a case expression: choice [ p1 :-> f1, p2 :-> f2, ... , this :-> defaultFilter]

see also : iff, choiceM

data IfThen a b Source
auxiliary datatype for cases within choice filter
Constructors
a :-> b
when :: (a -> [a]) -> (a -> [a]) -> a -> [a]Source

when the predicate p holds, f is applied, else the identity filter this

  • 1.parameter f : the conditinally applied filter
  • 2.parameter p : the predicate
  • returns : the conditional filter

see also : iff, whenNot, guards, whenM

whenNot :: (a -> [a]) -> (a -> [a]) -> a -> [a]Source

the complementary filter of when

shortcut for f when neg g

see also : iff, when, whenNotM, neg

guards :: (a -> [b]) -> (a -> [b]) -> a -> [b]Source

when the predicate p holds, f is applied, else the null filter none

  • 1.parameter p : the predicate filter
  • 2.parameter f : the conditionally applied filter
  • returns : the conditional filter

see also : iff, when, guardsM

neg :: (a -> [c]) -> a -> [a]Source

negation lifted to filters

  • 1.parameter f : the predicate filter
  • returns : the filter, that succeeds, when f failed
containing :: (a -> [b]) -> (b -> [c]) -> a -> [b]Source

pruning: keep only those results from f for which g holds, usually written in infix notation as f containing g

  • 1.parameter f : the processing filter
  • 2.parameter g : the predicate filter
  • 3.parameter t : the tree
  • returns : all trees r from f t, for which g r holds (is not the empty list)

see also : notContaining

notContaining :: (a -> [b]) -> (b -> [c]) -> a -> [b]Source

pruning: keep only those results from f for which g does not hold

see also : containing

(/>) :: TFilter node -> TFilter node -> TFilter nodeSource
pronounced "slash", meaning g inside f
(</) :: TFilter node -> TFilter node -> TFilter nodeSource
pronounced "outside" meaning f containing g
deep :: TFilter node -> TFilter nodeSource

top down search.

search terminates, when filter f succeeds can e.g. be used for finding all outermost tag node of a specific kind

deepest :: TFilter node -> TFilter nodeSource

bottom up search.

first the children are processed, if this does not succeed, the node itself is processed can e.g. be used for finding all innermost tag nodes of a specific kind

multi :: TFilter node -> TFilter nodeSource

process all nodes of the whole tree.

can e.g. be used for finding all nodes of a specific kind

processBottomUp :: TFilter node -> TFilter nodeSource

bottom up transformation

  • 1.parameter f : the simple transforming filter
  • returns : the filter that applies f to all subtrees and the tree itself in a deepth first left to right manner

see also : processTopDown, processBottomUpIfNot

processBottomUpIfNot :: TFilter node -> TFilter node -> TFilter nodeSource

guarded bottom up transformation, stops at subtrees for which a predicate p holds

  • 1.parameter f : the transforming filter
  • 2.parameter p : the predicate filter for the guard
  • returns : the filter for processing all (sub-)trees

see also : processBottomUp

processTopDown :: TFilter node -> TFilter nodeSource

top down transformation

  • 1.parameter f : the simple transforming filter
  • returns : the filter that applies f first to the tree and then recursively to all subtrees of the result

see also : processBottomUp

processTopDownUntil :: TFilter node -> TFilter nodeSource

top down transformation until a node to be transformed is found

  • 1.parameter f : the simple transforming filter
  • returns : the filter that applies f first to the tree and, if the filter does not succeed, recursively to all children of the input tree.

Example:

processTopDownUntil none

is the identity filter (maybe a bit more inefficient).

Example:

processTopDownUntil (add1Attr "border" "2" `containing` isTag "table")

is a filter for adding an attribute border="2" in all top level table tags. The content of table tags will remain unchanged.

see also : processTopDown, processBottomUp

insertChildrenAt :: Int -> TFilter node -> TFilter nodeSource

insertion of trees into the list of children at a given position

useful for inserting something into the list of children at a given position the list of children is split with the splitAt function the nodes are inserted between these two sublists.

examples: insertChildrenAt 0 ins t inserts all elements computed with ins t in front of the childen of t, insertChildrenAt 1 ins t behind the first child

see also: insertChildrenAfter

insertChildrenAfter :: TFilter node -> TFilter node -> TFilter nodeSource

insertion of trees into the list of children after specific elements

useful for inserting something into the list of children of a node the list of children is split with the span function and the filter p as predicate the nodes are inserted between these two sublists

examples: insertChildrenAfter none ins t inserts all elements computed with ins t in front of the childen of t, insertChildrenAfter this ins t appends the elements to the children

see also: insertChildrenAt

Monadic Filter
thisM :: Monad m => a -> m [a]Source

the monadic version of the identity filter this.

see also : this

noneM :: Monad m => a -> m [b]Source

the monadic version of the null filter none.

see also : none

(.>>) :: Monad m => (a -> m [b]) -> (b -> m [c]) -> a -> m [c]Source

sequential composition of monadic filters, monadic version of ".>".

  • 1.parameter f1 : the 1. monadic filter
  • 2.parameter f2 : the 2. monadic filter
  • returns : the monadic fiter applying first f1 to n and then f2 to the result (like function composition)

see also : '(.>)'

seqM :: Monad m => [a -> m [a]] -> a -> m [a]Source
generalized sequential composition of monadic filters
(+++>>) :: Monad m => (a -> m [b]) -> (a -> m [b]) -> a -> m [b]Source

binary parallel composition, the logical OR for predicate filter

  • 1.parameter f1 : the 1. filter
  • 2.parameter f2 : the 2. filter
  • returns : the filter for applying f1 and f2 both to an argument tree and concatenating the results see also: cat, +++, catM
catM :: Monad m => [a -> m [b]] -> a -> m [b]Source

apply a list of monadic filters

  • 1.parameter fs : the list of filters
  • returns : the composing filter see also: cat, +++, +++>>
ifM :: Monad m => (a -> [b]) -> (a -> m [c]) -> (a -> m [c]) -> a -> m [c]Source

monadic if-then-else.

  • 1.parameter p : the predicate
  • 2.parameter thenP : the then part: the monadic filter, that is applied if p holds for the input tree
  • 3.parameter elseP : the else part
  • returns : the monadic filter for the conditional
choiceM :: Monad m => [IfThen (a -> [c]) (a -> m [b])] -> a -> m [b]Source

monadic version of multiway branch. The list of cases f :-> g is processed sequentially, in the first case for that f holds g is applied, if no case matches, noneM is applied. This filter can be used like a case expression: choiceM [ p1 :-> f1, p2 :-> f2, ... , thisM :-> defaultFilter]

see also : choice, ifM

whenM :: Monad m => (a -> m [a]) -> (a -> [b]) -> a -> m [a]Source

when the predicate p holds, the monadic filter f is applied, else the identity filter.

  • 1.parameter f : the conditinally applied monadic filter
  • 2.parameter p : the simple predicate
  • returns : the conditional filter

see also : ifM, when, guardsM, whenNotM

whenNotM :: Monad m => (a -> m [a]) -> (a -> [b]) -> a -> m [a]Source

the complementary filter of whenM.

see also : ifM, whenM, whenNot

guardsM :: Monad m => (a -> [b]) -> (a -> m [c]) -> a -> m [c]Source

when the predicate p holds, the monadic filter f is applied, else the null filter.

  • 1.parameter p : the simple predicate filter
  • 2.parameter f : the conditionally applied monadic filter
  • returns : the conditional filter

see also : ifM, guards, whenM

containingM :: Monad m => (a -> m [b]) -> (b -> [c]) -> a -> m [b]Source

pruning: monadic version of containing, usually written in infix notation as f containingM g

  • 1.parameter f : the monadic processing filter
  • 2.parameter g : the predicate filter
  • 3.parameter t : the tree
  • returns : all trees r from f t, for which g r holds (is not the empty list)

see also : notContaining

processChildrenM :: Monad m => (NTree node -> m [NTree node]) -> NTree node -> m [NTree node]Source

Filter for editing the children of a tree with a monadic filter

  • 1.parameter cf : the monadic filter applied to the children
  • returns : the monadic editing filter

see also : processChildren

processTopDownM :: Monad m => (NTree node -> m [NTree node]) -> NTree node -> m [NTree node]Source
monadic variant of processTopDown
processBottomUpM :: Monad m => (NTree node -> m [NTree node]) -> NTree node -> m [NTree node]Source
monadic variant of processBottomUp
liftMf :: Monad m => (a -> [b]) -> a -> m [b]Source

lift a filter to a monadic filter

  • 1.parameter f : the simple filter
  • returns : the lifted monadic version
($$) :: (a -> [b]) -> [a] -> [b]Source

infix operator for applying a filter to a list of trees

  • 1.parameter f : the filter
  • 2.parameter ts : the list of trees
  • returns : the concatenated list of results
($$<) :: Monad m => (a -> m [b]) -> [a] -> m [b]Source

infix operator for applying a monadic filter to a list of trees, typically used in do-notation for processing of intermediate results.

  • 1.parameter f : the monadic filter
  • 2.parameter ts : the list of trees
  • returns : the concatenated list of results

see also : '($$)'

performAction :: Monad m => (a -> m b) -> a -> m [a]Source

run an arbitray command on a tree t and return the tree, used for inserting arbitray commands in a filter pipeline

  • 1.parameter cmd : the command
  • 2.parameter t : the argument tree
  • returns : the unchanged tree as a single element list
Produced by Haddock version 2.4.2