aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authordespresc <[email protected]>2019-11-09 13:27:40 -0500
committerdespresc <[email protected]>2019-11-09 13:27:40 -0500
commita0441ad3db3420a66b21ab3a87cfc4f3a679f87b (patch)
tree414ab4c4618da452682f5a838a956ec508d22d3b
parent2c05a6d6a4f37ee6daed41b62a7e5bc35e49f238 (diff)
Switch Tests.Helpers and Tests.Writers.* to Text
-rw-r--r--test/Tests/Helpers.hs8
-rw-r--r--test/Tests/Writers/AsciiDoc.hs23
-rw-r--r--test/Tests/Writers/ConTeXt.hs10
3 files changed, 24 insertions, 17 deletions
diff --git a/test/Tests/Helpers.hs b/test/Tests/Helpers.hs
index bc9d097ea..85bd518b3 100644
--- a/test/Tests/Helpers.hs
+++ b/test/Tests/Helpers.hs
@@ -35,10 +35,10 @@ import System.FilePath
import Test.Tasty
import Test.Tasty.HUnit
import Text.Pandoc.Builder (Blocks, Inlines, doc, plain)
-import Text.Pandoc.Legacy.Class
+import Text.Pandoc.Class
import Text.Pandoc.Definition
-import Text.Pandoc.Legacy.Options
-import Text.Pandoc.Legacy.Shared (trimr)
+import Text.Pandoc.Options
+import Text.Pandoc.Shared (trimr)
import Text.Pandoc.Writers.Native (writeNative)
import Text.Printf
@@ -142,7 +142,7 @@ instance ToString Blocks where
toString = unpack . purely (writeNative def) . toPandoc
instance ToString Inlines where
- toString = trimr . unpack . purely (writeNative def) . toPandoc
+ toString = unpack . trimr . purely (writeNative def) . toPandoc
instance ToString String where
toString = id
diff --git a/test/Tests/Writers/AsciiDoc.hs b/test/Tests/Writers/AsciiDoc.hs
index 679367ae2..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
@@ -7,34 +8,40 @@ import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
-import Text.Pandoc.Legacy.Builder -- TODO text: remove Legacy
+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 b0474b469..082ff12fe 100644
--- a/test/Tests/Writers/ConTeXt.hs
+++ b/test/Tests/Writers/ConTeXt.hs
@@ -3,13 +3,13 @@
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
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
-import Text.Pandoc.Legacy.Builder -- TODO text: remove Legacy
+import Text.Pandoc.Builder
context :: (ToPandoc a) => a -> String
context = unpack . purely (writeConTeXt def) . toPandoc
@@ -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" =: