[Haskell-cafe] Processing XML with HXT

Uwe Schmidt uwe at fh-wedel.de
Wed Apr 23 12:55:00 EDT 2008


Hi Rodrigo,

> Just one more question, I didn't find any example describing how to get the 
> text information of a XML element in the picklers tutorial. So, if the use case 
> element is described as follwing:
> ...

here is a complete example for your use case.

Take the following XML data in file "uc.xml"

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

<useCaseModel name="firstUseCaseModel">
  <useCase>
    <id>UC_01</id>
    <name>Opening ...</name>
    <description>This use case describes how...</description>
  </useCase>
</useCaseModel>

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

and the following picker and test

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

module Main
where

import Text.XML.HXT.Arrow


type Id = String
type Name = String
type Description = String

data UseCaseModel
    = UCM Name [UseCase]
      deriving (Show)

data UseCase
    = UseCase Id Name Description
      deriving (Show)

instance XmlPickler UseCase where
    xpickle = xpUseCase

xpUseCaseModel :: PU  UseCaseModel
xpUseCaseModel =
    xpElem "useCaseModel" $
    xpWrap ( uncurry UCM
	   , \ (UCM n ucs) -> (n, ucs) ) $
    xpPair ( xpAttr "name" xpText )
	   ( xpList xpUseCase )

xpUseCase :: PU UseCase
xpUseCase =
    xpElem "useCase" $
    xpWrap ( uncurry3 UseCase
           ,  \ (UseCase i n d) -> (i, n, d) )  $
    xpTriple (xpElem "id"          xpText)
             (xpElem "name"        xpText)
             (xpElem "description" xpText)


main	:: IO ()
main
    = do
      runX ( xunpickleDocument xpUseCaseModel
	              [ (a_validate,v_0)
		      , (a_trace, v_1)
		      , (a_remove_whitespace,v_1)  -- !!!!!!!!!! throw away whitespace
		      , (a_preserve_comment, v_0)  -- !!!!!!!!!! throw away comments
		      ] "uc.xml"
	     >>>
	     processUseCaseModel
	     >>>
	     xpickleDocument xpUseCaseModel
	              [ (a_indent, v_1)
		      ] "new-uc.xml"
	   )
      return ()
 
-- the dummy for processing the unpickled data
 
processUseCaseModel	:: IOSArrow UseCaseModel UseCaseModel
processUseCaseModel
    = arrIO ( \ x -> do {print x ; return x})

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

This program will print the internal haskell value and
writes the data to "new-uc.xml"

Cheers

Uwe

-- 

Uwe Schmidt
Web: http://www.fh-wedel.de/~si/


More information about the Haskell-Cafe mailing list