aboutsummaryrefslogtreecommitdiff
path: root/tests/Tests/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Tests/Writers')
-rw-r--r--tests/Tests/Writers/AsciiDoc.hs25
-rw-r--r--tests/Tests/Writers/LaTeX.hs4
-rw-r--r--tests/Tests/Writers/Plain.hs21
3 files changed, 46 insertions, 4 deletions
diff --git a/tests/Tests/Writers/AsciiDoc.hs b/tests/Tests/Writers/AsciiDoc.hs
index 118e648d3..f9e6bd154 100644
--- a/tests/Tests/Writers/AsciiDoc.hs
+++ b/tests/Tests/Writers/AsciiDoc.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.AsciiDoc (tests) where
import Test.Framework
@@ -12,7 +11,27 @@ asciidoc :: (ToString a, ToPandoc a) => a -> String
asciidoc = writeAsciiDoc def{ writerWrapText = False } . toPandoc
tests :: [Test]
-tests = [ testGroup "tables"
+tests = [ testGroup "emphasis"
+ [ test asciidoc "emph word before" $
+ para (text "foo" <> emph (text "bar")) =?>
+ "foo__bar__"
+ , test asciidoc "emph word after" $
+ para (emph (text "foo") <> text "bar") =?>
+ "__foo__bar"
+ , test asciidoc "emph quoted" $
+ para (doubleQuoted (emph (text "foo"))) =?>
+ "``__foo__''"
+ , test asciidoc "strong word before" $
+ para (text "foo" <> strong (text "bar")) =?>
+ "foo**bar**"
+ , test asciidoc "strong word after" $
+ para (strong (text "foo") <> text "bar") =?>
+ "**foo**bar"
+ , test asciidoc "strong quoted" $
+ para (singleQuoted (strong (text "foo"))) =?>
+ "`**foo**'"
+ ]
+ , testGroup "tables"
[ test asciidoc "empty cells" $
simpleTable [] [[mempty],[mempty]] =?> unlines
[ "[cols=\"\",]"
@@ -22,7 +41,7 @@ tests = [ testGroup "tables"
, "|===="
]
, test asciidoc "multiblock cells" $
- simpleTable [] [[para "Para 1" <> para "Para 2"]]
+ simpleTable [] [[para (text "Para 1") <> para (text "Para 2")]]
=?> unlines
[ "[cols=\"\",]"
, "|====="
diff --git a/tests/Tests/Writers/LaTeX.hs b/tests/Tests/Writers/LaTeX.hs
index 6db6542a0..8ce73c099 100644
--- a/tests/Tests/Writers/LaTeX.hs
+++ b/tests/Tests/Writers/LaTeX.hs
@@ -46,7 +46,7 @@ tests = [ testGroup "code blocks"
]
, testGroup "math"
[ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?>
- "$\\sigma|_{\\{x\\}}$"
+ "\\(\\sigma|_{\\{x\\}}\\)"
]
, testGroup "headers"
[ "unnumbered header" =:
@@ -63,5 +63,7 @@ tests = [ testGroup "code blocks"
strikeout (code "foo" <> space
<> str "bar") =?>
"\\sout{\\texttt{foo} bar}"
+ , "single quotes" =:
+ code "dog's" =?> "\\texttt{dog\\textquotesingle{}s}"
]
]
diff --git a/tests/Tests/Writers/Plain.hs b/tests/Tests/Writers/Plain.hs
new file mode 100644
index 000000000..f8f1d3d90
--- /dev/null
+++ b/tests/Tests/Writers/Plain.hs
@@ -0,0 +1,21 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.Plain (tests) where
+
+import Test.Framework
+import Text.Pandoc.Builder
+import Text.Pandoc
+import Tests.Helpers
+import Tests.Arbitrary()
+
+
+infix 4 =:
+(=:) :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> Test
+(=:) = test (writePlain def . toPandoc)
+
+
+tests :: [Test]
+tests = [ "strongly emphasized text to uppercase"
+ =: strong "Straße"
+ =?> "STRASSE"
+ ]