{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE OverloadedStrings #-} import Test.Hspec import Test.Hspec.HUnit import Test.HUnit hiding (Test) import Data.XML.Types import qualified Text.XML.Enumerator.Document as D import Text.XML.Enumerator.Parse (decodeEntities) import qualified Text.XML.Enumerator.Parse as P import qualified Data.Map as Map import qualified Data.ByteString.Lazy.Char8 as L import Control.Monad.IO.Class (liftIO) main :: IO () main = hspec $ describe "XML parsing and rendering" [ it "is idempotent to parse and render a document" documentParseRender , it "has valid parser combinators" combinators , it "has working ignoreSiblings function" testIgnoreSiblings ] documentParseRender = mapM_ go docs where go x = x @=? D.parseLBS_ (D.renderLBS x) decodeEntities docs = [ Document (Prologue [] Nothing []) (Element "foo" Map.empty []) [] , D.parseLBS_ "\n\n" decodeEntities , D.parseLBS_ "\n\n&ignore;" decodeEntities , D.parseLBS_ "]]>" decodeEntities , D.parseLBS_ "" decodeEntities , D.parseLBS_ "" decodeEntities , D.parseLBS_ "" decodeEntities ] combinators = P.parseLBS_ input decodeEntities $ do P.force "need hello" $ P.tagName "hello" (P.requireAttr "world") $ \world -> do liftIO $ world @?= "true" P.force "need child1" $ P.tagNoAttr "{mynamespace}child1" $ return () P.force "need child2" $ P.tagNoAttr "child2" $ return () P.force "need child3" $ P.tagNoAttr "child3" $ do x <- P.contentMaybe liftIO $ x @?= Just "combine &content" where input = L.concat [ "\n" , "\n" , "" , "" , "" , "" , " " , "combine <all> \n" , "" ] testIgnoreSiblings = P.parseLBS_ input decodeEntities $ do P.force "need hello" $ P.tagNoAttr "hello" $ do P.ignoreSiblings return () where input = L.concat [ "\n" , "\n" , "" , "" , "" , "" , "" , "" , "\n" , "" ]