import Test.HUnit hiding (Node) import Text.XML.Expat.Pickle import Text.XML.Expat.Tree import Text.XML.Expat.Format import Control.Exception.Extensible as E import Control.Parallel.Strategies import qualified Data.ByteString.Lazy as L import qualified Data.ByteString as B import Data.ByteString.Internal (c2w) import qualified Data.Map as M import Control.Arrow -- | Tests where input and XML output differ u2 :: (NFData a, Eq a, Show a) => String -> String -> String -> Either String a -> PU (UNodes String) a -> IO () u2 title inXML chkXML inEVal inPU = do let inTree = parseTreeThrowing (Just UTF8) (L.pack $ map c2w inXML) inTreeXML = formatTree' inTree eVal = unpickleTree' (xpRoot inPU) inTree assertEqual (title++" - strict unpickle") inEVal eVal case eVal of Right val -> do -- Make sure that the lazy unpickler gives the same result assertEqual (title++" - lazy unpickle") val (unpickleTree (xpRoot inPU) inTree) let chkTree = parseTreeThrowing (Just UTF8) (L.pack $ map c2w chkXML) :: UNode String chkTreeXML = formatTree' chkTree outXML = pickleXML' (xpRoot inPU) val assertEqual (title++" - pickle") chkTreeXML outXML Left err -> -- Make sure that the lazy unpickler also fails, but we don't care -- what the message is (it won't be the same) E.catch (do let val2 = unpickleTree (xpRoot inPU) inTree rnf val2 `seq` assertFailure $ title++" - lazy unpickle didn't throw expected exception ("++err++")" ) (\exc -> return (exc::SomeException) >> return ()) -- | Tests where input and output XML are the same u title inXML inEVal inPU = u2 title inXML inXML inEVal inPU main = runTestTT $ TestList $ map TestCase $ [ u "xpUnit" "" (Right ()) $ xpElemNodes "top" xpUnit, u "xpUnit" "" (Left "in , got xpZero" :: Either String ()) $ xpElemNodes "top" xpZero, u "xpLift" "" (Right "banana") $ xpElemNodes "top" $ xpLift "banana", u "xpElem" "applecat" (Right ("apple","cat")) $ xpElemNodes "top" $ xpPair (xpElemNodes "fruit" $ xpContent xpText) (xpElemNodes "pet" $ xpContent xpText), u2 "xpElem - with elements out of order" "applecat" "catapple" (Right ("cat","apple")) $ xpElemNodes "top" $ xpPair (xpElemNodes "pet" $ xpContent xpText) (xpElemNodes "fruit" $ xpContent xpText), u2 "xpElem - Check ignoring of extra elements" "onionapplechaircat" "applecat" (Right ("apple","cat")) $ xpElemNodes "top" $ xpPair (xpElemNodes "fruit" $ xpContent xpText) (xpElemNodes "pet" $ xpContent xpText), u2 "xpElem - Check ignoring of extra text" "OnionapplechairChaircat" "applecat" (Right ("apple","cat")) $ xpElemNodes "top" $ xpPair (xpElemNodes "fruit" $ xpContent xpText) (xpElemNodes "pet" $ xpContent xpText), u "xpElem - check missing element" "apple" (Left "in , in 2nd of pair, can't find ") $ xpElemNodes "top" $ xpPair (xpElemNodes "fruit" $ xpContent xpText) (xpElemNodes "pet" $ xpContent xpText), u "xpAttr" "" (Right ("apple", "cat")) $ xpElemAttrs "top" $ xpPair (xpAttr "fruit" xpText0) (xpAttr "pet" xpText), u2 "xpAttr - Attributes out of order" "" "" (Right ("apple", "cat")) $ xpElemAttrs "top" $ xpPair (xpAttr "fruit" xpText0) (xpAttr "pet" xpText), u2 "xpAttr - Ignore extra attributes" "" "" (Right ("apple", "cat")) $ xpElemAttrs "top" $ xpPair (xpAttr "fruit" xpText0) (xpAttr "pet" xpText), u "xpAttr - Missing attribute" "" (Left "in , in 1st of pair, can't find attribute fruit") $ xpElemAttrs "top" $ xpPair (xpAttr "fruit" xpText0) (xpAttr "pet" xpText), u "xpAttrImplied - Nothing value" "" (Right Nothing) $ xpElemAttrs "top" $ xpAttrImplied "missing" xpText0, u "xpAttrImplied - Just value" "" (Right $ Just "not missing") $ xpElemAttrs "top" $ xpAttrImplied "missing" xpText0, u "xpAttrFixed" "" (Right ()) $ xpElemAttrs "top" $ xpAttrFixed "fixed" "horse", u "xpAttrFixed - missing attribute on unpickle" "" (Left "in , can't find attribute fixed") $ xpElemAttrs "top" $ xpAttrFixed "fixed" "horse", u "xpAddFixedAttr" "" (Right "sheep") $ xpElemAttrs "top" $ xpAddFixedAttr "fixed" "horse" $ xpAttr "unfixed" xpText0, u "xpContent xpText0" "Shoe" (Right "Shoe") $ xpElemNodes "top" $ xpContent $ xpText0, u "xpAttr .. xpText0" "" (Right "Shoe") $ xpElemAttrs "top" $ xpAttr "clothes" xpText0, u "xpContent xpText0 - empty string" "" (Right "") $ xpElemNodes "top" $ xpContent $ xpText0, u "xpAttr .. xpText0 - empty string" "" (Right "") $ xpElemAttrs "top" $ xpAttr "clothes" xpText0, u "xpContent xpText" "Shoe" (Right "Shoe") $ xpElemNodes "top" $ xpContent $ xpText, u "xpAttr .. xpText" "" (Right "Shoe") $ xpElemAttrs "top" $ xpAttr "clothes" xpText, u "xpContent xpText - empty string" "" (Left "in , empty text") $ xpElemNodes "top" $ xpContent $ xpText, u "xpAttr .. xpText - empty string" "" (Left "in , in attribute clothes, empty text") $ xpElemAttrs "top" $ xpAttr "clothes" xpText, u "xpPrim" "1234" (Right 1234 :: Either String Int) $ xpElemNodes "top" $ xpContent $ xpPrim, u "xpPrim" "1234!" (Left "in , failed to read text: 1234!" :: Either String Int) $ xpElemNodes "top" $ xpContent $ xpPrim, u "xpPair" "12" (Right (1,2) :: Either String (Int,Int)) $ xpElemNodes "top" $ xpPair (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpContent xpPrim), u "xpPair - failure in 1st" "12" (Left "in , in 1st of pair, in , got xpZero" :: Either String (Int,Int)) $ xpElemNodes "top" $ xpPair (xpElemNodes "a" $ xpZero) (xpElemNodes "b" $ xpContent xpPrim), u "xpPair - failure in 2nd" "12" (Left "in , in 2nd of pair, in , got xpZero" :: Either String (Int,Int)) $ xpElemNodes "top" $ xpPair (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpZero), u "xpTriple" "123" (Right (1,2,3) :: Either String (Int,Int,Int)) $ xpElemNodes "top" $ xpTriple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpContent xpPrim), u "xpTriple - failure in 1st" "123" (Left "in , in 1st of triple, in , got xpZero" :: Either String (Int,Int,Int)) $ xpElemNodes "top" $ xpTriple (xpElemNodes "a" $ xpZero) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpContent xpPrim), u "xpTriple - failure in 2nd" "123" (Left "in , in 2nd of triple, in , got xpZero" :: Either String (Int,Int,Int)) $ xpElemNodes "top" $ xpTriple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpZero) (xpElemNodes "c" $ xpContent xpPrim), u "xpTriple - failure in 3rd" "123" (Left "in , in 3rd of triple, in , got xpZero" :: Either String (Int,Int,Int)) $ xpElemNodes "top" $ xpTriple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpZero), u "xp4Tuple" "1234" (Right (1,2,3,4) :: Either String (Int,Int,Int,Int)) $ xpElemNodes "top" $ xp4Tuple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpContent xpPrim) (xpElemNodes "d" $ xpContent xpPrim), u "xp4Tuple - failure in 1st" "1234" (Left "in , in 1st of 4-tuple, in , got xpZero" :: Either String (Int,Int,Int,Int)) $ xpElemNodes "top" $ xp4Tuple (xpElemNodes "a" $ xpZero) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpContent xpPrim) (xpElemNodes "d" $ xpContent xpPrim), u "xp4Tuple - failure in 2nd" "1234" (Left "in , in 2nd of 4-tuple, in , got xpZero" :: Either String (Int,Int,Int,Int)) $ xpElemNodes "top" $ xp4Tuple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpZero) (xpElemNodes "c" $ xpContent xpPrim) (xpElemNodes "d" $ xpContent xpPrim), u "xp4Tuple - failure in 3rd" "1234" (Left "in , in 3rd of 4-tuple, in , got xpZero" :: Either String (Int,Int,Int,Int)) $ xpElemNodes "top" $ xp4Tuple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpZero) (xpElemNodes "d" $ xpContent xpPrim), u "xp4Tuple - failure in 4th" "1234" (Left "in , in 4th of 4-tuple, in , got xpZero" :: Either String (Int,Int,Int,Int)) $ xpElemNodes "top" $ xp4Tuple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpContent xpPrim) (xpElemNodes "d" $ xpZero), u "xp5Tuple" "12345" (Right (1,2,3,4,5) :: Either String (Int,Int,Int,Int,Int)) $ xpElemNodes "top" $ xp5Tuple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpContent xpPrim) (xpElemNodes "d" $ xpContent xpPrim) (xpElemNodes "e" $ xpContent xpPrim), u "xp5Tuple - failure in 1st" "12345" (Left "in , in 1st of 5-tuple, in , got xpZero" :: Either String (Int,Int,Int,Int,Int)) $ xpElemNodes "top" $ xp5Tuple (xpElemNodes "a" $ xpZero) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpContent xpPrim) (xpElemNodes "d" $ xpContent xpPrim) (xpElemNodes "e" $ xpContent xpPrim), u "xp5Tuple - failure in 2nd" "12345" (Left "in , in 2nd of 5-tuple, in , got xpZero" :: Either String (Int,Int,Int,Int,Int)) $ xpElemNodes "top" $ xp5Tuple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpZero) (xpElemNodes "c" $ xpContent xpPrim) (xpElemNodes "d" $ xpContent xpPrim) (xpElemNodes "e" $ xpContent xpPrim), u "xp5Tuple - failure in 3rd" "12345" (Left "in , in 3rd of 5-tuple, in , got xpZero" :: Either String (Int,Int,Int,Int,Int)) $ xpElemNodes "top" $ xp5Tuple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpZero) (xpElemNodes "d" $ xpContent xpPrim) (xpElemNodes "e" $ xpContent xpPrim), u "xp5Tuple - failure in 4th" "12345" (Left "in , in 4th of 5-tuple, in , got xpZero" :: Either String (Int,Int,Int,Int,Int)) $ xpElemNodes "top" $ xp5Tuple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpContent xpPrim) (xpElemNodes "d" $ xpZero) (xpElemNodes "e" $ xpContent xpPrim), u "xp5Tuple - failure in 5th" "12345" (Left "in , in 5th of 5-tuple, in , got xpZero" :: Either String (Int,Int,Int,Int,Int)) $ xpElemNodes "top" $ xp5Tuple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpContent xpPrim) (xpElemNodes "d" $ xpContent xpPrim) (xpElemNodes "e" $ xpZero), u "xp6Tuple" "123456" (Right (1,2,3,4,5,6) :: Either String (Int,Int,Int,Int,Int,Int)) $ xpElemNodes "top" $ xp6Tuple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpContent xpPrim) (xpElemNodes "d" $ xpContent xpPrim) (xpElemNodes "e" $ xpContent xpPrim) (xpElemNodes "f" $ xpContent xpPrim), u "xp6Tuple - failure in 1st" "123456" (Left "in , in 1st of 6-tuple, in , got xpZero" :: Either String (Int,Int,Int,Int,Int,Int)) $ xpElemNodes "top" $ xp6Tuple (xpElemNodes "a" $ xpZero) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpContent xpPrim) (xpElemNodes "d" $ xpContent xpPrim) (xpElemNodes "e" $ xpContent xpPrim) (xpElemNodes "f" $ xpContent xpPrim), u "xp6Tuple - failure in 2nd" "123456" (Left "in , in 2nd of 6-tuple, in , got xpZero" :: Either String (Int,Int,Int,Int,Int,Int)) $ xpElemNodes "top" $ xp6Tuple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpZero) (xpElemNodes "c" $ xpContent xpPrim) (xpElemNodes "d" $ xpContent xpPrim) (xpElemNodes "e" $ xpContent xpPrim) (xpElemNodes "f" $ xpContent xpPrim), u "xp6Tuple - failure in 3rd" "123456" (Left "in , in 3rd of 6-tuple, in , got xpZero" :: Either String (Int,Int,Int,Int,Int,Int)) $ xpElemNodes "top" $ xp6Tuple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpZero) (xpElemNodes "d" $ xpContent xpPrim) (xpElemNodes "e" $ xpContent xpPrim) (xpElemNodes "f" $ xpContent xpPrim), u "xp6Tuple - failure in 4th" "123456" (Left "in , in 4th of 6-tuple, in , got xpZero" :: Either String (Int,Int,Int,Int,Int,Int)) $ xpElemNodes "top" $ xp6Tuple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpContent xpPrim) (xpElemNodes "d" $ xpZero) (xpElemNodes "e" $ xpContent xpPrim) (xpElemNodes "f" $ xpContent xpPrim), u "xp6Tuple - failure in 5th" "123456" (Left "in , in 5th of 6-tuple, in , got xpZero" :: Either String (Int,Int,Int,Int,Int,Int)) $ xpElemNodes "top" $ xp6Tuple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpContent xpPrim) (xpElemNodes "d" $ xpContent xpPrim) (xpElemNodes "e" $ xpZero) (xpElemNodes "f" $ xpContent xpPrim), u "xp6Tuple - failure in 6th" "123456" (Left "in , in 6th of 6-tuple, in , got xpZero" :: Either String (Int,Int,Int,Int,Int,Int)) $ xpElemNodes "top" $ xp6Tuple (xpElemNodes "a" $ xpContent xpPrim) (xpElemNodes "b" $ xpContent xpPrim) (xpElemNodes "c" $ xpContent xpPrim) (xpElemNodes "d" $ xpContent xpPrim) (xpElemNodes "e" $ xpContent xpPrim) (xpElemNodes "f" $ xpZero), u "xpList0" "MatthewStephen" (Right ["Matthew", "Stephen"]) $ xpElemNodes "top" $ xpList0 $ xpElemNodes "name" $ xpContent xpText0, u "xpList0 with failure in element" "MatthewStephen" (Left "in , in list, can't find ") $ xpElemNodes "top" $ xpList0 $ xpElemNodes "name" $ xpContent xpText0, u "xpList0 with empty list" "" (Right []) $ xpElemNodes "top" $ xpList0 $ xpElemNodes "name" $ xpContent xpText0, u "xpList" "MatthewStephen" (Right ["Matthew", "Stephen"]) $ xpElemNodes "top" $ xpList $ xpElemNodes "name" $ xpContent xpText0, u2 "xpList with failure in element" "MatthewStephen" "Matthew" (Right ["Matthew"]) $ xpElemNodes "top" $ xpList $ xpElemNodes "name" $ xpContent xpText0, u "xpList with empty list" "" (Right []) $ xpElemNodes "top" $ xpList $ xpElemNodes "name" $ xpContent xpText0, u "xpListMinLength (len 2)" "MatthewStephen" (Right ["Matthew", "Stephen"]) $ xpElemNodes "top" $ xpListMinLen 1 $ xpElemNodes "name" $ xpContent xpText0, u "xpListMinLength (len 1)" "Matthew" (Right ["Matthew"]) $ xpElemNodes "top" $ xpListMinLen 1 $ xpElemNodes "name" $ xpContent xpText0, u "xpListMinLength (len 0)" "" (Left "in , Expecting at least 1 elements") $ xpElemNodes "top" $ xpListMinLen 1 $ xpElemNodes "name" $ xpContent xpText0, u2 "xpListMinLength error in 2nd elt" "MatthewStephen" "Matthew" (Right ["Matthew"]) $ xpElemNodes "top" $ xpListMinLen 1 $ xpElemNodes "name" $ xpContent xpText0, u "xpListMinLength error in 1st elt" "MatthewStephen" (Left "in , Expecting at least 1 elements") $ xpElemNodes "top" $ xpListMinLen 1 $ xpElemNodes "name" $ xpContent xpText0, u2 "xpMap" "480" "408" (Right $ M.fromList [("dog",4),("spider",8),("fish",0)] :: Either String (M.Map String Int)) $ xpElemNodes "top" $ xpMap "animal" "name" xpText0 (xpContent xpickle), u "xpMap - empty" "" (Right $ M.empty :: Either String (M.Map String Int)) $ xpElemNodes "top" $ xpMap "animal" "name" xpText0 (xpContent xpickle), u2 "xpMap - error in elt" "43780" "4" (Right $ M.fromList [("dog",4)] :: Either String (M.Map String Int)) $ xpElemNodes "top" $ xpMap "animal" "name" xpText0 (xpContent xpickle), u "xpWrap" "480" (Right [("_dog",400),("_spider",800),("_fish",0)] :: Either String [(String,Int)]) $ xpElemNodes "top" $ xpList $ xpWrap (('_':) *** (*100), tail *** (`div` 100)) $ xpElem "animal" (xpAttr "name" xpText0) (xpContent xpickle), u "xpWrapMaybe" "480" (Right [("_dog",400),("_spider",800),("_fish",0)] :: Either String [(String,Int)]) $ xpElemNodes "top" $ xpList $ xpWrapMaybe (Just . (('_':) *** (*100)), tail *** (`div` 100)) $ xpElem "animal" (xpAttr "name" xpText0) (xpContent xpickle), u2 "xpWrapMaybe failure with xpList" "480" "4" (Right [("_dog",400)] :: Either String [(String,Int)]) $ xpElemNodes "top" $ xpList $ xpWrapMaybe (\(a,b) -> if b < 6 then Just (('_':a),b*100) else Nothing, tail *** (`div` 100)) $ xpElem "animal" (xpAttr "name" xpText0) (xpContent xpickle), u "xpWrapMaybe with xpList0" "480" (Right [("_dog",400),("_spider",800),("_fish",0)] :: Either String [(String,Int)]) $ xpElemNodes "top" $ xpList0 $ xpWrapMaybe (Just . (('_':) *** (*100)), tail *** (`div` 100)) $ xpElem "animal" (xpAttr "name" xpText0) (xpContent xpickle), u "xpWrapMaybe failure with xpList0" "480" (Left "in , in list, xpWrapMaybe can't encode Nothing value" :: Either String [(String,Int)]) $ xpElemNodes "top" $ xpList0 $ xpWrapMaybe (\(a,b) -> if b < 6 then Just (('_':a),b*100) else Nothing, tail *** (`div` 100)) $ xpElem "animal" (xpAttr "name" xpText0) (xpContent xpickle), u "xpWrapMaybe_ failure with xpList0" "480" (Left "in , in list, no invertebrates, please" :: Either String [(String,Int)]) $ xpElemNodes "top" $ xpList0 $ xpWrapMaybe_ "no invertebrates, please" (\(a,b) -> if b < 6 then Just (('_':a),b*100) else Nothing, tail *** (`div` 100)) $ xpElem "animal" (xpAttr "name" xpText0) (xpContent xpickle), u "xpWrapEither" "480" (Right [("_dog",400),("_spider",800),("_fish",0)] :: Either String [(String,Int)]) $ xpElemNodes "top" $ xpList0 $ xpWrapEither (Right . (('_':) *** (*100)), tail *** (`div` 100)) $ xpElem "animal" (xpAttr "name" xpText0) (xpContent xpickle), u "xpWrapEither failure" "480" (Left "in , in list, no invertibrates, I said" :: Either String [(String,Int)]) $ xpElemNodes "top" $ xpList0 $ xpWrapEither (\(a,b) -> if b < 6 then Right (('_':a),b*100) else Left "no invertibrates, I said", tail *** (`div` 100)) $ xpElem "animal" (xpAttr "name" xpText0) (xpContent xpickle), u "xpOption present" "salt" (Right $ Just "salt") $ xpElemNodes "top" $ xpOption $ xpElemNodes "mineral" $ xpContent xpText0, u "xpOption absent" "" (Right $ Nothing) $ xpElemNodes "top" $ xpOption $ xpElemNodes "mineral" $ xpContent xpText0, u "xpDefault present" "salt" (Right $ "salt") $ xpElemNodes "top" $ xpDefault "quartz" $ xpElemNodes "mineral" $ xpContent xpText0, u "xpDefault absent" "" -- omits default if it matches (Right $ "quartz") $ xpElemNodes "top" $ xpDefault "quartz" $ xpElemNodes "mineral" $ xpContent xpText0, u "xpWithDefault present" "salt" (Right $ "salt") $ xpElemNodes "top" $ xpDefault "quartz" $ xpElemNodes "mineral" $ xpContent xpText0, u2 "xpWithDefault absent" "" "quartz" -- encodes default on pickle (Right $ "quartz") $ xpElemNodes "top" $ xpWithDefault "quartz" $ xpElemNodes "mineral" $ xpContent xpText0, u "xpAlt" "" (Right $ [1,0,2] :: Either String [Int]) $ xpElemNodes "top" $ xpList0 $ xpAlt id [xpElemNodes "pukeko" $ xpContent $ xpLift 0, xpElemNodes "duck" $ xpContent $ xpLift 1, xpElemNodes "swan" $ xpContent $ xpLift 2], u2 "xpTryCatch" "five" "4" (Right 4 :: Either String Int) $ xpElemNodes "top" $ xpContent $ xpTryCatch xpPrim (xpWrap (length, const "x") xpText0), u "xpThrow" "" (Left "in , Oh!" :: Either String Int) $ xpElemNodes "top" $ xpThrow "Oh!", u "xpAttrs" "" (Right [("name", "Stephen"),("favouriteColour","green")]) $ xpElemAttrs "top" xpAttrs, u "xpTree" "hello" (Right (Element "top" [("test","1")] [Text "hello"])) $ xpTree, u "xpTrees" "hello" (Right [Element "top" [("test","1")] [Text "hello"]]) $ xpTrees ]