Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
This module defines the notion of filters and filter combinators for processing XML documents.
These XML transformation combinators are described in the paper ``Haskell and XML: Generic Combinators or Type-Based Translation?'' Malcolm Wallace and Colin Runciman, Proceedings ICFP'99.
- type CFilter i = Content i -> [Content i]
- keep :: a -> [a]
- none :: a -> [b]
- children :: CFilter i
- childrenBy :: CFilter i -> CFilter i
- position :: Int -> CFilter i -> CFilter i
- elm :: CFilter i
- txt :: CFilter i
- tag :: String -> CFilter i
- attr :: String -> CFilter i
- attrval :: Attribute -> CFilter i
- tagWith :: (String -> Bool) -> CFilter i
- find :: String -> (String -> CFilter i) -> CFilter i
- iffind :: String -> (String -> CFilter i) -> CFilter i -> CFilter i
- ifTxt :: (String -> CFilter i) -> CFilter i -> CFilter i
- o :: CFilter i -> CFilter i -> CFilter i
- union :: (a -> [b]) -> (a -> [b]) -> a -> [b]
- cat :: [a -> [b]] -> a -> [b]
- andThen :: (a -> c) -> (c -> a -> b) -> a -> b
- (|>|) :: (a -> [b]) -> (a -> [b]) -> a -> [b]
- with :: CFilter i -> CFilter i -> CFilter i
- without :: CFilter i -> CFilter i -> CFilter i
- (/>) :: CFilter i -> CFilter i -> CFilter i
- (</) :: CFilter i -> CFilter i -> CFilter i
- et :: (String -> CFilter i) -> CFilter i -> CFilter i
- path :: [CFilter i] -> CFilter i
- deep :: CFilter i -> CFilter i
- deepest :: CFilter i -> CFilter i
- multi :: CFilter i -> CFilter i
- when :: CFilter i -> CFilter i -> CFilter i
- guards :: CFilter i -> CFilter i -> CFilter i
- chip :: CFilter i -> CFilter i
- inplace :: CFilter i -> CFilter i
- recursivelyInPlace :: CFilter i -> CFilter i
- foldXml :: CFilter i -> CFilter i
- mkElem :: String -> [CFilter i] -> CFilter i
- mkElemAttr :: String -> [(String, CFilter i)] -> [CFilter i] -> CFilter i
- literal :: String -> CFilter i
- cdata :: String -> CFilter i
- replaceTag :: String -> CFilter i
- replaceAttrs :: [(String, String)] -> CFilter i
- addAttribute :: String -> String -> CFilter a
- data ThenElse a = a :> a
- (?>) :: (a -> [b]) -> ThenElse (a -> [b]) -> a -> [b]
- type LabelFilter i a = Content i -> [(a, Content i)]
- oo :: (a -> CFilter i) -> LabelFilter i a -> CFilter i
- x :: (CFilter i -> LabelFilter i a) -> (CFilter i -> LabelFilter i b) -> CFilter i -> LabelFilter i (a, b)
- numbered :: CFilter i -> LabelFilter i Int
- interspersed :: String -> CFilter i -> String -> LabelFilter i String
- tagged :: CFilter i -> LabelFilter i String
- attributed :: String -> CFilter i -> LabelFilter i String
- textlabelled :: CFilter i -> LabelFilter i (Maybe String)
- extracted :: (Content i -> a) -> CFilter i -> LabelFilter i a
The content filter type.
Simple filters.
Selection filters.
In the algebra of combinators, none
is the zero, and keep
the identity.
(They have a more general type than just CFilter.)
childrenBy :: CFilter i -> CFilter i Source
Process children using specified filters.
Predicate filters.
These filters either keep or throw away some content based on
a simple test. For instance, elm
keeps only a tagged element,
txt
keeps only non-element text, tag
keeps only an element
with the named tag, attr
keeps only an element with the named
attribute, attrval
keeps only an element with the given
attribute value, tagWith
keeps only an element whose tag name
satisfies the given predicate.
Search filters.
find :: String -> (String -> CFilter i) -> CFilter i Source
For a mandatory attribute field, find key cont
looks up the value of
the attribute name key
, and applies the continuation cont
to
the value.
iffind :: String -> (String -> CFilter i) -> CFilter i -> CFilter i Source
When an attribute field may be absent, use iffind key yes no
to lookup
its value. If the attribute is absent, it acts as the no
filter,
otherwise it applies the yes
filter.
ifTxt :: (String -> CFilter i) -> CFilter i -> CFilter i Source
ifTxt yes no
processes any textual content with the yes
filter,
but otherwise is the same as the no
filter.
Filter combinators
Basic combinators.
union :: (a -> [b]) -> (a -> [b]) -> a -> [b] infixr 5 Source
Binary parallel composition. Each filter uses a copy of the input, rather than one filter using the result of the other. (Has a more general type than just CFilter.)
cat :: [a -> [b]] -> a -> [b] Source
Glue a list of filters together. (A list version of union; also has a more general type than just CFilter.)
andThen :: (a -> c) -> (c -> a -> b) -> a -> b infixr 5 Source
A special form of filter composition where the second filter works over the same data as the first, but also uses the first's result.
(|>|) :: (a -> [b]) -> (a -> [b]) -> a -> [b] infixl 5 Source
Directional choice:
in f |>| g
give g-productions only if no f-productions
with :: CFilter i -> CFilter i -> CFilter i infixl 6 Source
Pruning: in f
,
keep only those f-productions which have at least one g-productionwith
g
without :: CFilter i -> CFilter i -> CFilter i infixl 6 Source
Pruning: in f
,
keep only those f-productions which have no g-productionswithout
g
(/>) :: CFilter i -> CFilter i -> CFilter i infixl 5 Source
Pronounced slash, f /> g
means g inside f
(</) :: CFilter i -> CFilter i -> CFilter i infixl 5 Source
Pronounced outside, f </ g
means f containing g
et :: (String -> CFilter i) -> CFilter i -> CFilter i Source
Join an element-matching filter with a text-only filter
path :: [CFilter i] -> CFilter i Source
Express a list of filters like an XPath query, e.g.
path [children, tag "name1", attr "attr1", children, tag "name2"]
is like the XPath query /name1[@attr1]/name2
.
Recursive search.
Recursive search has three variants: deep
does a breadth-first
search of the tree, deepest
does a depth-first search, multi
returns
content at all tree-levels, even those strictly contained within results
that have already been returned.
Interior editing.
when :: CFilter i -> CFilter i -> CFilter i infixr 4 Source
Interior editing:
f
applies when
gf
only when the predicate g
succeeds,
otherwise the content is unchanged.
guards :: CFilter i -> CFilter i -> CFilter i infixr 4 Source
Interior editing:
g
applies guards
ff
only when the predicate g
succeeds,
otherwise the content is discarded.
chip :: CFilter i -> CFilter i Source
Process CHildren In Place. The filter is applied to any children of an element content, and the element rebuilt around the results.
inplace :: CFilter i -> CFilter i Source
Process an element In Place. The filter is applied to the element itself, and then the original element rebuilt around the results.
recursivelyInPlace :: CFilter i -> CFilter i Source
Recursively process an element in place. That is, the filter is applied to the element itself, then recursively to the results of the filter, all the way to the bottom, then the original element rebuilt around the final results.
foldXml :: CFilter i -> CFilter i Source
Recursive application of filters: a fold-like operator. Defined
as f
.o
chip (foldXml f)
Constructive filters.
The constructive filters are primitive filters for building new elements, or editing existing elements.
mkElem :: String -> [CFilter i] -> CFilter i Source
Build an element with the given tag name - its content is the results of the given list of filters.
mkElemAttr :: String -> [(String, CFilter i)] -> [CFilter i] -> CFilter i Source
Build an element with the given name, attributes, and content.
replaceTag :: String -> CFilter i Source
Rename an element tag (leaving attributes in place).
replaceAttrs :: [(String, String)] -> CFilter i Source
Replace the attributes of an element (leaving tag the same).
addAttribute :: String -> String -> CFilter a Source
Add the desired attribute name and value to the topmost element, without changing the element in any other way.
C-like conditionals.
These definitions provide C-like conditionals, lifted to the filter level.
The (cond ? yes : no)
style in C becomes (cond ?> yes :> no)
in Haskell.
(?>) :: (a -> [b]) -> ThenElse (a -> [b]) -> a -> [b] infixr 3 Source
Select between the two branches of a joined conditional.
Filters with labelled results.
type LabelFilter i a = Content i -> [(a, Content i)] Source
A LabelFilter is like a CFilter except that it pairs up a polymorphic value (label) with each of its results.
Using and combining labelled filters.
oo :: (a -> CFilter i) -> LabelFilter i a -> CFilter i infixr 5 Source
Compose a label-processing filter with a label-generating filter.
x :: (CFilter i -> LabelFilter i a) -> (CFilter i -> LabelFilter i b) -> CFilter i -> LabelFilter i (a, b) Source
Combine labels. Think of this as a pair-wise zip on labels.
e.g. (numbered
x
tagged)
Some label-generating filters.
numbered :: CFilter i -> LabelFilter i Int Source
Number the results from 1 upwards.
interspersed :: String -> CFilter i -> String -> LabelFilter i String Source
In interspersed a f b
, label each result of f
with the string a
,
except for the last one which is labelled with the string b
.
tagged :: CFilter i -> LabelFilter i String Source
Label each element in the result with its tag name. Non-element results get an empty string label.
attributed :: String -> CFilter i -> LabelFilter i String Source
Label each element in the result with the value of the named attribute. Elements without the attribute, and non-element results, get an empty string label.
textlabelled :: CFilter i -> LabelFilter i (Maybe String) Source
Label each textual part of the result with its text. Element results get an empty string label.
extracted :: (Content i -> a) -> CFilter i -> LabelFilter i a Source
Label each content with some information extracted from itself.