diff options
Diffstat (limited to 'test/Tests')
-rw-r--r-- | test/Tests/Old.hs | 4 | ||||
-rw-r--r-- | test/Tests/Readers/Man.hs | 83 |
2 files changed, 87 insertions, 0 deletions
diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs index b426ffd07..842e0f656 100644 --- a/test/Tests/Old.hs +++ b/test/Tests/Old.hs @@ -171,6 +171,10 @@ tests = [ testGroup "markdown" , test "tables" ["-f", "native", "-t", "../data/sample.lua"] "tables.native" "tables.custom" ] + , testGroup "man" + [ test "reader" ["-r", "man", "-w", "native", "-s"] + "man-reader.man" "man-reader.native" + ] ] -- makes sure file is fully closed after reading diff --git a/test/Tests/Readers/Man.hs b/test/Tests/Readers/Man.hs new file mode 100644 index 000000000..9dbfbab4d --- /dev/null +++ b/test/Tests/Readers/Man.hs @@ -0,0 +1,83 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Man (tests) where + +import Prelude +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" + =?> (para $ strong "foo") + , "Italic" =: + ".I bar\n" + =?> (para $ emph "bar") + , "BoldItalic" =: + ".BI foo bar" + =?> (para $ strong $ emph $ str "foo bar") + , "H1" =: + ".SH The header\n" + =?> header 2 (str "The" <> space <> str "header") + , "H2" =: + ".SS \"The header 2\"" + =?> header 3 (str "The header 2") + , "Macro args" =: + ".B \"single arg with \"\"Q\"\"\"" + =?> (para $ strong $ str "single arg with \"Q\"") + , "comment" =: + ".\\\"bla\naaa" + =?> (para $ space <> str "aaa") + , "link" =: + ".BR aa (1)" + =?> (para $ link "../1/aa.1" "aa" (strong $ str "aa") <> (strong $ str " (1)")) + ], + testGroup "Escapes" [ + "fonts" =: + "aa\\fIbb\\fRcc" + =?> (para $ str "aa" <> (emph $ str "bb") <> str "cc") + , "skip" =: + "a\\%\\{\\}\\\n\\:b\\0" + =?> (para $ str "ab") + , "replace" =: + "\\-\\ \\\\\\[lq]\\[rq]\\[em]\\[en]\\*(lq\\*(rq" + =?> (para $ str "- \\“”—–«»") + , "replace2" =: + "\\t\\e\\`\\^\\|\\'" + =?> (para $ str "\t\\` `") + ], + testGroup "Lists" [ + "bullet" =: + ".IP\nfirst\n.IP\nsecond" + =?> bulletList [plain $ str "first", plain $ str "second"] + , "odrered" =: + ".IP 1 a\nfirst\n.IP 2 a\nsecond" + =?> orderedListWith (1,Decimal,DefaultDelim) [plain $ str "first", plain $ str "second"] + , "upper" =: + ".IP A a\nfirst\n.IP B a\nsecond" + =?> orderedListWith (1,UpperAlpha,DefaultDelim) [plain $ str "first", plain $ str "second"] + , "nested" =: + ".IP\nfirst\n.RS\n.IP\n1a\n.IP\n1b\n.RE" + =?> bulletList [(plain $ str "first") <> (bulletList [plain $ str "1a", plain $ str "1b"])] + ], + testGroup "CodeBlocks" [ + "cb1"=: + ".nf\naa\n\tbb\n.fi" + =?> codeBlock "aa\n\tbb" + ] + ] |