{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} module Tests.Writers.HTML (tests) where import Prelude import Data.Text (unpack) import Test.Tasty import Tests.Helpers import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder html :: (ToPandoc a) => a -> String html = unpack . purely (writeHtml4String def{ writerWrapText = WrapNone }) . toPandoc htmlQTags :: (ToPandoc a) => a -> String htmlQTags = unpack . purely (writeHtml4String def{ writerWrapText = WrapNone, writerHtmlQTags = True }) . toPandoc {- "my test" =: X =?> Y is shorthand for test html "my test" $ X =?> Y which is in turn shorthand for test html "my test" (X,Y) -} infix 4 =: (=:) :: (ToString a, ToPandoc a) => String -> (a, String) -> TestTree (=:) = test html tests :: [TestTree] tests = [ testGroup "inline code" [ "basic" =: code "@&" =?> "@&" , "haskell" =: codeWith ("",["haskell"],[]) ">>=" =?> ">>=" , "nolanguage" =: codeWith ("",["nolanguage"],[]) ">>=" =?> ">>=" ] , testGroup "images" [ "alt with formatting" =: image "/url" "title" ("my " <> emph "image") =?> "\"my" ] , testGroup "blocks" [ "definition list with empty
" =: definitionList [(mempty, [para $ text "foo bar"])] =?> "

foo bar

" ] , testGroup "quotes" [ "quote with cite attribute (without q-tags)" =: doubleQuoted (spanWith ("", [], [("cite", "http://example.org")]) (str "examples")) =?> "“examples”" , tQ "quote with cite attribute (with q-tags)" $ doubleQuoted (spanWith ("", [], [("cite", "http://example.org")]) (str "examples")) =?> "examples" ] , testGroup "sample" [ "sample should be rendered correctly" =: plain (codeWith ("",["sample"],[]) "Answer is 42") =?> "Answer is 42" ] , testGroup "variable" [ "variable should be rendered correctly" =: plain (codeWith ("",["variable"],[]) "result") =?> "result" ] , testGroup "sample with style" [ "samp should wrap highlighted code" =: codeWith ("",["sample","haskell"],[]) ">>=" =?> ("" ++ ">>=") ] , testGroup "variable with style" [ "var should wrap highlighted code" =: codeWith ("",["haskell","variable"],[]) ">>=" =?> ("" ++ ">>=") ] ] where tQ :: (ToString a, ToPandoc a) => String -> (a, String) -> TestTree tQ = test htmlQTags