{-# LANGUAGE OverloadedStrings #-} {- | Module : Tests.Readers.HTML Copyright : © 2006-2024 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane Stability : alpha Portability : portable Tests for the HTML reader. -} module Tests.Readers.HTML (tests) where import Data.Text (Text) import qualified Data.Text as T import Test.Tasty import Test.Tasty.QuickCheck import Test.Tasty.Options (IsOption(defaultValue)) import Tests.Helpers import Text.Pandoc import Text.Pandoc.Shared (isHeaderBlock) import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder import Text.Pandoc.Walk (walk) html :: Text -> Pandoc html = purely $ readHtml def htmlNativeDivs :: Text -> Pandoc htmlNativeDivs = purely $ readHtml def { readerExtensions = enableExtension Ext_native_divs $ readerExtensions def } makeRoundTrip :: Block -> Block makeRoundTrip CodeBlock{} = Para [Str "code block was here"] makeRoundTrip LineBlock{} = Para [Str "line block was here"] makeRoundTrip RawBlock{} = Para [Str "raw block was here"] makeRoundTrip (Div attr bs) = Div attr $ filter (not . isHeaderBlock) bs -- avoids round-trip failures related to makeSections -- e.g. with [Div ("loc",[],[("a","11"),("b_2","a b c")]) [Header 3 ("",[],[]) []]] makeRoundTrip Table{} = Para [Str "table block was here"] makeRoundTrip x = x removeRawInlines :: Inline -> Inline removeRawInlines RawInline{} = Str "raw inline was here" removeRawInlines x = x roundTrip :: Blocks -> Bool roundTrip b = d'' == d''' where d = walk removeRawInlines $ walk makeRoundTrip $ Pandoc nullMeta $ toList b d' = rewrite d d'' = rewrite d' d''' = rewrite d'' rewrite = html . (`T.snoc` '\n') . purely (writeHtml5String def { writerWrapText = WrapPreserve }) tests :: [TestTree] tests = [ testGroup "base tag" [ test html "simple" $ "\"Stickman\"" =?> plain (image "http://www.w3schools.com/images/stickman.gif" "" (text "Stickman")) , test html "slash at end of base" $ "\"Stickman\"" =?> plain (image "http://www.w3schools.com/images/stickman.gif" "" (text "Stickman")) , test html "slash at beginning of href" $ "\"Stickman\"" =?> plain (image "http://www.w3schools.com/stickman.gif" "" (text "Stickman")) , test html "absolute URL" $ "\"Stickman\"" =?> plain (image "http://example.com/stickman.gif" "" (text "Stickman")) ] , testGroup "anchors" [ test html "anchor without href" $ "" =?> plain (spanWith ("anchor",[],[]) mempty) ] , testGroup "img" [ test html "data-external attribute" $ "" =?> plain (imageWith ("", [], [("external", "1")]) "http://example.com/stickman.gif" "" "") , test html "title" $ "" =?> plain (imageWith ("", [], []) "http://example.com/stickman.gif" "The title" "") ] , testGroup "lang" [ test html "lang on " $ "hola" =?> setMeta "lang" (text "es") (doc (plain (text "hola"))) , test html "xml:lang on " $ "hola" =?> setMeta "lang" (text "es") (doc (plain (text "hola"))) ] , testGroup "main" [ test htmlNativeDivs "
contents are parsed" $ "
ignore me