aboutsummaryrefslogtreecommitdiff
path: root/test/Tests/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'test/Tests/Writers')
-rw-r--r--test/Tests/Writers/AsciiDoc.hs21
-rw-r--r--test/Tests/Writers/ConTeXt.hs8
2 files changed, 18 insertions, 11 deletions
diff --git a/test/Tests/Writers/AsciiDoc.hs b/test/Tests/Writers/AsciiDoc.hs
index ea61ed044..75f6e5e97 100644
--- a/test/Tests/Writers/AsciiDoc.hs
+++ b/test/Tests/Writers/AsciiDoc.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.AsciiDoc (tests) where
import Prelude
@@ -12,29 +13,35 @@ import Text.Pandoc.Builder
asciidoc :: (ToPandoc a) => a -> String
asciidoc = unpack . purely (writeAsciiDoc def{ writerWrapText = WrapNone }) . toPandoc
+testAsciidoc :: (ToString a, ToPandoc a)
+ => String
+ -> (a, String)
+ -> TestTree
+testAsciidoc = test asciidoc
+
tests :: [TestTree]
tests = [ testGroup "emphasis"
- [ test asciidoc "emph word before" $
+ [ testAsciidoc "emph word before" $
para (text "foo" <> emph (text "bar")) =?>
"foo__bar__"
- , test asciidoc "emph word after" $
+ , testAsciidoc "emph word after" $
para (emph (text "foo") <> text "bar") =?>
"__foo__bar"
- , test asciidoc "emph quoted" $
+ , testAsciidoc "emph quoted" $
para (doubleQuoted (emph (text "foo"))) =?>
"``__foo__''"
- , test asciidoc "strong word before" $
+ , testAsciidoc "strong word before" $
para (text "foo" <> strong (text "bar")) =?>
"foo**bar**"
- , test asciidoc "strong word after" $
+ , testAsciidoc "strong word after" $
para (strong (text "foo") <> text "bar") =?>
"**foo**bar"
- , test asciidoc "strong quoted" $
+ , testAsciidoc "strong quoted" $
para (singleQuoted (strong (text "foo"))) =?>
"`**foo**'"
]
, testGroup "tables"
- [ test asciidoc "empty cells" $
+ [ testAsciidoc "empty cells" $
simpleTable [] [[mempty],[mempty]] =?> unlines
[ "[cols=\"\",]"
, "|==="
diff --git a/test/Tests/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs
index c11e409f8..082ff12fe 100644
--- a/test/Tests/Writers/ConTeXt.hs
+++ b/test/Tests/Writers/ConTeXt.hs
@@ -3,7 +3,7 @@
module Tests.Writers.ConTeXt (tests) where
import Prelude
-import Data.Text (unpack)
+import Data.Text (unpack, pack)
import Test.Tasty
import Test.Tasty.QuickCheck
import Tests.Helpers
@@ -46,9 +46,9 @@ tests = [ testGroup "inline code"
, "without '}'" =: code "]" =?> "\\type{]}"
, testProperty "code property" $ \s -> null s || '\n' `elem` s ||
if '{' `elem` s || '}' `elem` s
- then context' (code s) == "\\mono{" ++
- context' (str s) ++ "}"
- else context' (code s) == "\\type{" ++ s ++ "}"
+ then context' (code $ pack s) == "\\mono{" ++
+ context' (str $ pack s) ++ "}"
+ else context' (code $ pack s) == "\\type{" ++ s ++ "}"
]
, testGroup "headers"
[ "level 1" =: