aboutsummaryrefslogtreecommitdiff
path: root/test/Tests/Readers/Man.hs
diff options
context:
space:
mode:
Diffstat (limited to 'test/Tests/Readers/Man.hs')
-rw-r--r--test/Tests/Readers/Man.hs31
1 files changed, 31 insertions, 0 deletions
diff --git a/test/Tests/Readers/Man.hs b/test/Tests/Readers/Man.hs
new file mode 100644
index 000000000..007935be1
--- /dev/null
+++ b/test/Tests/Readers/Man.hs
@@ -0,0 +1,31 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Readers.Man (tests) where
+
+import Data.Text (Text)
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+import Text.Pandoc.Readers.Man
+
+man :: Text -> Pandoc
+man = purely $ readMan def
+
+infix 4 =:
+(=:) :: ToString c
+ => String -> (Text, c) -> TestTree
+(=:) = test man
+
+tests :: [TestTree]
+tests = [
+ -- .SH "HEllo bbb" "aaa"" as"
+ testGroup "Macros" [
+ "Bold" =:
+ ".B foo\n"
+ =?> strong "foo"
+ , "Italic" =:
+ ".I foo\n"
+ =?> emph "foo"
+ ]
+ ]