[Haskell-cafe] How do I insert an element in HaXml?

Jeremy Shaw jeremy.shaw at linspireinc.com
Sat May 19 16:46:13 EDT 2007


Hello,

How do I create a HaXml filter that adds a new element as a child of
an existing element. For example, let's say I have the XML document:

<a>
 <b/>
 <c/>
</a>

How do I add a new element under <a /> so that I have the document:

<a>
 <newElement/>
 <b/>
 <c/>
</a>

The following works, but it seems very hackish because I have to use
the underlying HaXml data types. I think I could possibly use the
filters in Text.XML.HaXml.Xtract.Combinators, but that seems like
overkill for such a seemingly simple (and common?) operation.

import Text.XML.HaXml
import Text.XML.HaXml.Types
import Text.XML.HaXml.Pretty

insertNewElement = extract (\(CElem (Elem name _as cs)) -> mkElem name [mkElem "newElement" [] , const cs])
    where
      extract :: (Content -> CFilter) -> CFilter
      extract f = \c -> f c undefined

-- these are just helper functions to invoke my filter. But, I'll
-- happily accept improvements to these functions as well ;)

main = print $ document $ runFilter "<a><b /><c /></a>" insertNewElement

runFilter :: String -> CFilter -> Document
runFilter xmlStr cfilter =
    let (Document p s e m) = xmlParse "" xmlStr
    in case (cfilter (CElem e)) of
            [CElem e'] -> Document p s e' m
            []           -> error "produced no output"
            _            -> error "produced more than one output"

thanks!
j.


More information about the Haskell-Cafe mailing list