diff options
Diffstat (limited to 'test/Tests/Writers/HTML.hs.orig')
-rw-r--r-- | test/Tests/Writers/HTML.hs.orig | 44 |
1 files changed, 44 insertions, 0 deletions
diff --git a/test/Tests/Writers/HTML.hs.orig b/test/Tests/Writers/HTML.hs.orig new file mode 100644 index 000000000..23ff718d3 --- /dev/null +++ b/test/Tests/Writers/HTML.hs.orig @@ -0,0 +1,44 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.HTML (tests) where + +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 + +{- + "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 "@&" =?> "<code>@&</code>" + , "haskell" =: codeWith ("",["haskell"],[]) ">>=" + =?> "<code class=\"sourceCode haskell\"><span class=\"fu\">>>=</span></code>" + , "nolanguage" =: codeWith ("",["nolanguage"],[]) ">>=" + =?> "<code class=\"nolanguage\">>>=</code>" + ] + , testGroup "images" + [ "alt with formatting" =: + image "/url" "title" ("my " <> emph "image") + =?> "<img src=\"/url\" title=\"title\" alt=\"my image\" />" + ] + ] |