
Hi.
I've got a problem with the Haskell XML Toolkit (hxt). I want to write a little app that performs REST requests from a certain (rather simple) XML format.
A example procedure Call looks like testData defined below.
What I'd like to do is to transform this xml tree into a GET variable string using an XmlArrow. The task sounds easy, and it has to be easy, but I've been sitting here for about a day now, staring at my code.
It looks like this (the transformation should be done by the arrow "mkGetStr"):
-- Rest.hs
-- This is also on HPaste: http://hpaste.org/fastcgi/hpaste.fcgi/view?id=3210#a3210
{-# LANGUAGE NoMonomorphismRestriction #-}
module Rest where
import Text.XML.HXT.Arrow
import Data.List
getParamsA = hasName "param" >>> getChildren >>> isElem
>>> (getName &&& (getChildren >>> getText)) >>> arr2 mkGetPair
mkMethodStr = ("method=" ++)
mkGetPair k v = k ++ "=" ++ v
getMethodA = hasName "method" >>> getChildren >>> getText >>> arr mkMethodStr
mkGetStr = isElem
>>> (getMethodA <+> getParamsA)
>>. intercalate "&"
-- Try it with: runX (testData >>> mkGetStr) >>= print
testData = xread <<< constA (
"<method>my.Method</method>"
++ "<param>"
++ "