Difference between revisions of "HXT"

From HaskellWiki
Jump to navigation Jump to search
m
Line 110: Line 110:
 
When processing trees, there's often the case, that no, exactly one, or more than one result is possible. These functions, returning a set of results are often a bit imprecisely called ''nondeterministic'' functions. These functions, e.g. selecting all children of a node or all grandchildren, are exactly our filters. In this context lists instead of sets of values are the appropriate result type, because the ordering in XML is important and duplicates are possible.
 
When processing trees, there's often the case, that no, exactly one, or more than one result is possible. These functions, returning a set of results are often a bit imprecisely called ''nondeterministic'' functions. These functions, e.g. selecting all children of a node or all grandchildren, are exactly our filters. In this context lists instead of sets of values are the appropriate result type, because the ordering in XML is important and duplicates are possible.
   
''Working with filters is rather similar to working with binary relations, and working with relations is rather natural and comfortable, database people do know this very well.''
+
Working with filters is rather similar to working with binary relations, and working with relations is rather natural and comfortable, database people do know this very well.
   
 
Two first examples for working with ''nondeterministic'' functions are selecting the children and the grandchildren of an XmlTree which can be implemented by
 
Two first examples for working with ''nondeterministic'' functions are selecting the children and the grandchildren of an XmlTree which can be implemented by
Line 123: Line 123:
 
= concat [ getChildren c | c <- cs ]
 
= concat [ getChildren c | c <- cs ]
 
</haskell>
 
</haskell>
  +
  +
=== Filter combinators ===
  +
  +
Composition of filters (like function composition) is the most important combinator. We will use the infix operator <hask>(>>>)</hask> for filter composition and reverse the arguments, so we can read composition sequences from left to right, like with pipes in Unix. Composition is defined as follows:
  +
  +
<haskell>
  +
(>>>) :: XmlFilter -> XmlFilter -> XmlFilter
  +
  +
(f >>> g) t = concat [g t' | t' <- f t]
  +
</haskell>
  +
  +
This definition corresponds 1-1 to the composition of binary relations. With help of the <hask>(>>>)</hask> operator the definition of <hask>getGrandChildren</hask> becomes rather simple:
  +
  +
<haskell>
  +
getGrandChildren :: XmlFilter
  +
getGrandChildren = getChildren >>> getChilden
  +
</haskell>
  +
  +
Selecting all text nodes of the children of an element can also be formulated very easily with the help of <hask>(>>>)</hask>
  +
  +
<haskell>
  +
getTextChildren :: XmlFilter
  +
getTextChildren = getChildren >>> isText
  +
</haskell>
  +
  +
In case of predicate filter the <hask>(>>>)</hask> serves as a logical and operator, or from the relational view as an intersection operator: <hask>isA p1 >>> isA p2</hask> selects all values for which p1 and p2 both hold.
  +
  +
The dual operator to <hask>(>>>)</hask> is the locical or, (thinking in sets: The union operator). For this we define a sum operator <hask>(<+>)</hask>. The sum of two filters is defined as follows:
  +
  +
<haskell>
  +
(<+>) :: XmlFilter -> XmlFilter -> XmlFilter
  +
  +
(f <+> g) t = f t ++ g t
  +
</haskell>
  +
  +
Example: <hask>isA p1 <+> isA p2</hask> is the locical or for filter.
  +
  +
Combining elementary filters with (>>>) and (<+>) leads to more complex functionality. For example, selecting all text nodes within two levels of depth (in left to right order) can be formulated with:
  +
  +
<haskell>
  +
getTextChildren2 :: XmlFilter
  +
getTextChildren2 = getChildren >>> ( isText <+> ( getChildren >>> isText ) )
  +
</haskell>
  +
  +
'''Exercise:''' Are these filters equivalent or what's the difference between the two filters?
  +
  +
<haskell>
  +
getChildren >>> ( isText <+> ( getChildren >>> isText ) )
  +
  +
( getChildren >>> isText ) <+> ( getChildren >>> getChildren >>> isText )
  +
</haskell>
  +
  +
Of course we need choice combinators. The first idea is an if-then-else filter,
  +
built up from three simpler filters. But often it's easier and more elegant to work with simpler binary combinators for choice. So we will introduce the simpler ones first.
  +
  +
One of these choice combinators is called <hask>orElse</hask> and is defined as
  +
follows:
  +
  +
<haskell>
  +
orElse :: XmlFilter -> XmlFilter -> XmlFilter
  +
orElse f g t
  +
| null res1 = g t
  +
| otherwise = res1
  +
where
  +
res1 = f t
  +
</haskell>
  +
  +
The meaning is the following: If f computes a none empty list as result, f succeeds and this list is the result, else g is applied to the input and this yields the result. There are two other simple choice combinators usually written in infix notation, <hask> g `guards` f</hask> and <hask>f `when` g</hask>:
  +
  +
<haskell>
  +
guards :: XmlFilter -> XmlFilter -> XmlFilter
  +
guards g f t
  +
| null (g t) = []
  +
| otherwise = f t
  +
  +
when :: XmlFilter -> XmlFilter -> XmlFilter
  +
when f g t
  +
| null (g t) = [t]
  +
| otherwise = f t
  +
</haskell>
  +
  +
These choice operators become useful when transforming and manipulation trees.

Revision as of 14:53, 15 September 2006

The Haskell XML Toolbox (HXT) is a collection of tools for processing XML with Haskell. The core component of the Haskell XML Toolbox is a domain specific language, consisting of a set of combinators, for processing XML trees in a simple and elegant way. The combinator library is based on the concept of arrows. The main component is a validating and namespace aware XML-Parser that supports almost fully the XML 1.0 Standard. Extensions are a validator for RelaxNG and an XPath evaluator.

Background

The Haskell XML Toolbox bases on the ideas of HaXml and HXML but introduces a more general approach for processing XML with Haskell. HXT uses a generic data model for representing XML documents, including the DTD subset, entity references, CData parts and processing instructions. This data model makes it possible to use tree transformation functions as a uniform design of XML processing steps from parsing, DTD processing, entity processing, validation, namespace propagation, content processing and output.

The basic concepts

The basic data strutures

Processing of XML is a task of processing tree structures. This is can be done in Haskell in a very elegant way by defining an appropriate tree data type, a Haskell DOM (document object model) structure. The tree structure in HXT is a rose tree with a special XNode data type for storing the XML node information.

The generally useful tree structure (NTree) is separated from the node type (XNode). This allows for reusing the tree structure and the tree traversal and maipulation functions in other applications.

type NTree a  = NTree a [NTree a]     -- rose tree

data XNode    = XText String          -- plain text node
              | ...
              | XTag QName XmlTrees   -- element name and list of attributes
              | XAttr QName           -- attribute name
              | ...

type QName    = ...                   -- qualified name

type XmlTree  = NTree XNode

type XmlTrees = [XmlTree]

The concept of filters

Selecting, transforming and generating trees often requires routines, which compute not only a single result tree, but a (possibly empty) list of (sub-)trees. This leads to the idea of XML filters like in HaXml. Filters are functions, which take an XML tree as input and compute a list of result trees.

type XmlFilter = XmlTree -> [XmlTree]

More generally we can define a filter as

type Filter a b = a -> [b]

We will do this abstraction later, when introducing arrows. Many of the functions in the following motivating examples can be generalised this way. But for getting the idea, the XmlFilter is sufficient.

The filter functions are used so frequently, that the idea of defining a domain specific language with filters as the basic processing units comes up. In such a DSL the basic filters are predicates, selectors, constructors and transformers, all working on the HXT DOM tree structure. For a DSL it becomes neccessary to define an appropriate set of combinators for building more complex functions from simpler ones. Of course filter composition, like (.) becomes one of the most frequently used combinators. there are more complex filters for traversal of a whole tree and selection or transformation of several nodes. We will see a few first examples in the following part.

The first task is to build filters from pure functions, to define a lift operator. Pure functions are liftet to filters in the following way:

Predicates are lifted by mapping False to the empty list and True to the single element list, containing the input tree.

p   :: XmlTree -> Bool		-- pure function
p t =  ...

pf  :: XmlTree -> [XmlTree]	-- or XmlFilter
pf t
  | p t       = [t]
  | otherwise = []

The combinator for this type of lifting is called isA, it works on any type and is defined as

isA  :: (a -> Bool) -> (a -> [a])
isA p x
  | p x       = [x]
  | otherwise = []

A predicate for filtering text nodes looks like this

isText		              :: XmlFilter       -- XmlTree -> [XmlTrees]
isText t@(NTree (XText _) _) =  [t]
isText _                     =  []

Transformers, function that map a tree into another tree, are lifted in a trivial way:

f	:: XmlTree -> XmlTree
f t	=  exp(t)

ff	:: XmlTree -> [XmlTree]
ff t	= [exp(t)]

This basic function is called arr, it comes from the Control.Arrow module of the basic library package of ghc.

Partial functions, functions that can't always compute a result, are usually liftet to totally defined filters:

f	:: XmlTree -> XmlTree
f t
  | p t	      =  expr(t)
  | otherwise = error "f not defined"

ff	:: XmlFilter
ff t
  | p t       = [expr(t)]
  | otherwise = []

This is a rather comfotable situation, with these filters we don't have to deal with illegal argument errors. Illegal arguments are just mapped to the empty list.

When processing trees, there's often the case, that no, exactly one, or more than one result is possible. These functions, returning a set of results are often a bit imprecisely called nondeterministic functions. These functions, e.g. selecting all children of a node or all grandchildren, are exactly our filters. In this context lists instead of sets of values are the appropriate result type, because the ordering in XML is important and duplicates are possible.

Working with filters is rather similar to working with binary relations, and working with relations is rather natural and comfortable, database people do know this very well.

Two first examples for working with nondeterministic functions are selecting the children and the grandchildren of an XmlTree which can be implemented by

getChildren	 :: XmlFilter
getChildren (NTree n cs)
  = cs

getGrandChildren :: XmlFilter
getGrandChildren (NTree n cs)
  = concat [ getChildren c | c <- cs ]

Filter combinators

Composition of filters (like function composition) is the most important combinator. We will use the infix operator (>>>) for filter composition and reverse the arguments, so we can read composition sequences from left to right, like with pipes in Unix. Composition is defined as follows:

(>>>)	    :: XmlFilter -> XmlFilter -> XmlFilter

(f >>> g) t =  concat [g t' | t' <- f t]

This definition corresponds 1-1 to the composition of binary relations. With help of the (>>>) operator the definition of getGrandChildren becomes rather simple:

getGrandChildren :: XmlFilter
getGrandChildren = getChildren >>> getChilden

Selecting all text nodes of the children of an element can also be formulated very easily with the help of (>>>)

getTextChildren :: XmlFilter
getTextChildren = getChildren >>> isText

In case of predicate filter the (>>>) serves as a logical and operator, or from the relational view as an intersection operator: isA p1 >>> isA p2 selects all values for which p1 and p2 both hold.

The dual operator to (>>>) is the locical or, (thinking in sets: The union operator). For this we define a sum operator (<+>). The sum of two filters is defined as follows:

(<+>)	    :: XmlFilter -> XmlFilter -> XmlFilter

(f <+> g) t =  f t ++ g t

Example: isA p1 <+> isA p2 is the locical or for filter.

Combining elementary filters with (>>>) and (<+>) leads to more complex functionality. For example, selecting all text nodes within two levels of depth (in left to right order) can be formulated with:

getTextChildren2 :: XmlFilter
getTextChildren2 = getChildren >>> ( isText <+> ( getChildren >>> isText ) )

Exercise: Are these filters equivalent or what's the difference between the two filters?

getChildren >>> ( isText <+> ( getChildren >>> isText ) )

( getChildren >>> isText ) <+> ( getChildren >>> getChildren >>> isText )

Of course we need choice combinators. The first idea is an if-then-else filter, built up from three simpler filters. But often it's easier and more elegant to work with simpler binary combinators for choice. So we will introduce the simpler ones first.

One of these choice combinators is called orElse and is defined as follows:

orElse	:: XmlFilter -> XmlFilter -> XmlFilter
orElse f g t
  | null res1 = g t
  | otherwise = res1
  where
  res1 = f t

The meaning is the following: If f computes a none empty list as result, f succeeds and this list is the result, else g is applied to the input and this yields the result. There are two other simple choice combinators usually written in infix notation, g `guards` f and f `when` g:

guards	:: XmlFilter -> XmlFilter -> XmlFilter
guards g f t
  | null (g t) = []
  | otherwise  = f t

when	:: XmlFilter -> XmlFilter -> XmlFilter
when f g t
  | null (g t) = [t]
  | otherwise  = f t

These choice operators become useful when transforming and manipulation trees.