{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
import Control.Exception (Exception, toException,
fromException)
import Control.Monad.IO.Class (liftIO)
import qualified Data.ByteString.Char8 as S
import qualified Data.ByteString.Lazy.Char8 as L
import Data.Typeable (Typeable)
import Data.XML.Types
import Test.Hspec
import Test.HUnit hiding (Test)
import qualified Text.XML as Res
import qualified Text.XML.Cursor as Cu
import Text.XML.Stream.Parse (def)
import qualified Text.XML.Stream.Parse as P
import qualified Text.XML.Unresolved as D
import Control.Monad
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as T
import Text.XML.Cursor (($.//), ($/), ($//), ($|),
(&.//), (&/), (&//))
import qualified Control.Monad.Trans.Resource as C
import Data.Conduit ((.|), runConduit,
runConduitRes, ConduitT)
import Data.Conduit.Attoparsec (ParseError(..))
import qualified Data.Conduit as C
import qualified Data.Conduit.List as CL
import qualified Data.Map as Map
import Text.Blaze (toMarkup)
import Text.Blaze.Renderer.String (renderMarkup)
main :: IO ()
main = hspec $ do
describe "XML parsing and rendering" $ do
it "is idempotent to parse and render a document" documentParseRender
it "has valid parser combinators" combinators
context "has working choose function" testChoose
it "has working many function" testMany
it "has working many' function" testMany'
it "has working manyYield function" testManyYield
it "has working takeContent function" testTakeContent
it "has working takeTree function" testTakeTree
it "has working takeAnyTreeContent function" testTakeAnyTreeContent
it "has working orE" testOrE
it "is idempotent to parse and pretty render a document" documentParsePrettyRender
it "ignores the BOM" parseIgnoreBOM
it "strips duplicated attributes" stripDuplicateAttributes
it "displays comments" testRenderComments
it "conduit parser" testConduitParser
it "can omit the XML declaration" omitXMLDeclaration
it "doesn't hang on malformed entity declarations" malformedEntityDeclaration
it "escapes <>'\"& as necessary" caseEscapesAsNecessary
it "preserves the order of attributes" casePreservesAttrOrder
context "correctly parses hexadecimal entities" hexEntityParsing
it "normalizes line endings" crlfToLfConversion
it "normalizes \\r at the end of a content" crlfToLfConversionCrAtEnd
it "normalizes multiple \\rs and \\r\\ns" crlfToLfConversionCrCrCr
describe "XML Cursors" $ do
it "has correct parent" cursorParent
it "has correct ancestor" cursorAncestor
it "has correct orSelf" cursorOrSelf
it "has correct preceding" cursorPreceding
it "has correct following" cursorFollowing
it "has correct precedingSibling" cursorPrecedingSib
it "has correct followingSibling" cursorFollowingSib
it "has correct descendant" cursorDescendant
it "has correct check" cursorCheck
it "has correct check with lists" cursorPredicate
it "has correct checkNode" cursorCheckNode
it "has correct checkElement" cursorCheckElement
it "has correct checkName" cursorCheckName
it "has correct anyElement" cursorAnyElement
it "has correct element" cursorElement
it "has correct laxElement" cursorLaxElement
it "has correct content" cursorContent
it "has correct attribute" cursorAttribute
it "has correct laxAttribute" cursorLaxAttribute
it "has correct &* and $* operators" cursorDeep
it "has correct force" cursorForce
it "has correct forceM" cursorForceM
it "has correct hasAttribute" cursorHasAttribute
it "has correct attributeIs" cursorAttributeIs
describe "resolved" $ do
it "identifies unresolved entities" resolvedIdentifies
it "decodeHtmlEntities" testHtmlEntities
it "works for resolvable entities" resolvedAllGood
it "ignores custom entities when psResolveEntities is False" dontResolveEntities
it "merges adjacent content nodes" resolvedMergeContent
it "understands inline entity declarations" resolvedInline
it "understands complex inline with markup" resolvedInlineComplex
it "can expand inline entities recursively" resolvedInlineRecursive
it "doesn't explode with an inline entity loop" resolvedInlineLoop
it "doesn't explode with the billion laughs attack" billionLaughs
it "allows entity expansion size limit to be adjusted" thousandLaughs
it "ignores parameter entity declarations" parameterEntity
it "doesn't break on [] in doctype comments" doctypeComment
it "skips element declarations in doctype" doctypeElements
it "skips processing instructions in doctype" doctypePI
describe "pretty" $ do
it "works" casePretty
describe "top level namespaces" $ do
it "works" caseTopLevelNamespace
it "works with prefix" caseTopLevelNamespacePrefix
it "handles conflicts" caseTLNConflict
describe "blaze-html instances" $ do
it "works" caseBlazeHtml
describe "attribute reordering" $ do
it "works" caseAttrReorder
describe "ordering attributes explicitly" $ do
it "works" caseOrderAttrs
it "parsing CDATA" caseParseCdata
it "retains namespaces when asked" caseRetainNamespaces
it "handles iso-8859-1" caseIso8859_1
it "renders CDATA when asked" caseRenderCDATA
it "escapes CDATA closing tag in CDATA" caseEscapesCDATA
documentParseRender :: IO ()
documentParseRender =
mapM_ go docs
where
go x = x @=? D.parseLBS_ def (D.renderLBS def x)
docs =
[ Document (Prologue [] Nothing [])
(Element "foo" [] [])
[]
, D.parseLBS_ def
"\n