{-# LANGUAGE OverloadedStrings #-} import Test.HUnit hiding (Test) import Test.Hspec import Data.ByteString.Lazy.Char8 () import qualified Text.HTML.DOM as H import qualified Text.XML as X import qualified Data.Map as Map main :: IO () main = hspec $ do describe "parses" $ do it "well-formed document" $ X.parseLBS_ X.def "baz" @=? H.parseLBS "baz" it "adds missing close tags" $ X.parseLBS_ X.def "baz" @=? H.parseLBS "baz" it "void tags" $ X.parseLBS_ X.def "foo" @=? H.parseLBS "foo" it "xml entities" $ X.parseLBS_ X.def "baz>" @=? H.parseLBS "baz>" it "html entities" $ X.parseLBS_ X.def "baz " @=? H.parseLBS "baz " it "decimal entities" $ X.parseLBS_ X.def "baz " @=? H.parseLBS "baz " it "hex entities" $ X.parseLBS_ X.def "bazŠ" @=? H.parseLBS "bazŠ" it "invalid entities" $ X.parseLBS_ X.def "baz&foobar;" @=? H.parseLBS "baz&foobar;" it "multiple root elements" $ X.parseLBS_ X.def "baz&foobar;" @=? H.parseLBS "baz&foobar;" describe "HTML parsing" $ do it "XHTML" $ let html = "foo

Hello World

" doc = X.Document (X.Prologue [] Nothing []) root [] root = X.Element "html" Map.empty [ X.NodeElement $ X.Element "head" Map.empty [ X.NodeElement $ X.Element "title" Map.empty [X.NodeContent "foo"] ] , X.NodeElement $ X.Element "body" Map.empty [ X.NodeElement $ X.Element "p" Map.empty [X.NodeContent "Hello World"] ] ] in H.parseLBS html @?= doc it "HTML" $ let html = "foo

Hello World

" doc = X.Document (X.Prologue [] Nothing []) root [] root = X.Element "html" Map.empty [ X.NodeElement $ X.Element "head" Map.empty [ X.NodeElement $ X.Element "title" Map.empty [X.NodeContent "foo"] ] , X.NodeElement $ X.Element "body" Map.empty [ X.NodeElement $ X.Element "br" Map.empty [] , X.NodeElement $ X.Element "p" Map.empty [X.NodeContent "Hello World"] ] ] in H.parseLBS html @?= doc