Hi Henry,

> I have just spent many hours staring at code and losing some hair.  My
> hope is to save you the same experience someday.  Here was my goal:
>
> Take some XML, like <photo url="somewhere" align="left" alt=""/> and
> replace the align attribute with a class attribute, but only if the
> value of the align attribute was not null.  This led to to followed
> (hugely condensed) attempts:

you could try the following:

------------------------------------

module Align where

import Text.XML.HXT.Core

doc = concat $
      [ "<collection>"
      , "<photo url='somewhere' align='left' alt=''/>"
      , "<photo url='somewhere' align='' alt=''/>"
      , "</collection>"
      ]

main =
 runX ( constA doc
        >>>
        readFromString []
        >>>
        writeDocument [withIndent yes] ""
        >>>
        modifyAlt
        >>>
        writeDocument [withIndent yes] ""
      )

modifyAlt
    = processTopDownUntil
      (isPhotoWithNonEmptyAlign `guards` addClassAttr)

isPhotoWithNonEmptyAlign
    = hasName "photo"
      >>>
      hasAttrValue "align" (not .null)

addClassAttr
    = addAttr "class" "someclass"
      >>>
      removeAttr "align"



------------------------------------

Cheers,

    Uwe


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to