diff options
Diffstat (limited to 'src/Tests')
-rw-r--r-- | src/Tests/Old.hs | 35 | ||||
-rw-r--r-- | src/Tests/Writers/ConTeXt.hs | 2 | ||||
-rw-r--r-- | src/Tests/Writers/LaTeX.hs | 35 |
3 files changed, 67 insertions, 5 deletions
diff --git a/src/Tests/Old.hs b/src/Tests/Old.hs index a26e435a0..3315bb74e 100644 --- a/src/Tests/Old.hs +++ b/src/Tests/Old.hs @@ -99,13 +99,27 @@ tests = [ testGroup "markdown" , test "reader" ["-r", "textile", "-w", "native", "-s"] "textile-reader.textile" "textile-reader.native" ] + , testGroup "docbook" + [ testGroup "writer" $ writerTests "docbook" + , test "reader" ["-r", "docbook", "-w", "native", "-s"] + "docbook-reader.docbook" "docbook-reader.native" + ] , testGroup "native" [ testGroup "writer" $ writerTests "native" , test "reader" ["-r", "native", "-w", "native", "-s"] "testsuite.native" "testsuite.native" ] + , testGroup "fb2" + [ fb2WriterTest "basic" [] "fb2.basic.markdown" "fb2.basic.fb2" + , fb2WriterTest "titles" [] "fb2.titles.markdown" "fb2.titles.fb2" + , fb2WriterTest "images" [] "fb2.images.markdown" "fb2.images.fb2" + , fb2WriterTest "images-embedded" [] "fb2.images-embedded.html" "fb2.images-embedded.fb2" + , fb2WriterTest "tables" [] "tables.native" "tables.fb2" + , fb2WriterTest "math" [] "fb2.math.markdown" "fb2.math.fb2" + , fb2WriterTest "testsuite" [] "testsuite.native" "writer.fb2" + ] , testGroup "other writers" $ map (\f -> testGroup f $ writerTests f) - [ "docbook", "opendocument" , "context" , "texinfo" + [ "opendocument" , "context" , "texinfo" , "man" , "plain" , "mediawiki", "rtf", "org", "asciidoc" ] ] @@ -139,14 +153,27 @@ writerTests format opts = ["-r", "native", "-w", format, "--columns=78"] s5WriterTest :: String -> [String] -> String -> Test -s5WriterTest modifier opts format +s5WriterTest modifier opts format = test (format ++ " writer (" ++ modifier ++ ")") - (["-r", "native", "-w", format] ++ opts) + (["-r", "native", "-w", format] ++ opts) "s5.native" ("s5." ++ modifier <.> "html") +fb2WriterTest :: String -> [String] -> String -> String -> Test +fb2WriterTest title opts inputfile normfile = + testWithNormalize (ignoreBinary . formatXML) + title (["-t", "fb2"]++opts) inputfile normfile + where + formatXML xml = splitTags $ zip xml (drop 1 xml) + splitTags [] = [] + splitTags [end] = fst end : snd end : [] + splitTags (('>','<'):rest) = ">\n" ++ splitTags rest + splitTags ((c,_):rest) = c : splitTags rest + ignoreBinary = unlines . filter (not . startsWith "<binary ") . lines + startsWith tag str = all (uncurry (==)) $ zip tag str + markdownCitationTests :: [Test] markdownCitationTests - = map styleToTest ["chicago-author-date","ieee","mhra"] + = map styleToTest ["chicago-author-date","ieee","mhra"] ++ [test "natbib" wopts "markdown-citations.txt" "markdown-citations.txt"] where diff --git a/src/Tests/Writers/ConTeXt.hs b/src/Tests/Writers/ConTeXt.hs index 506ff698f..beb6411f0 100644 --- a/src/Tests/Writers/ConTeXt.hs +++ b/src/Tests/Writers/ConTeXt.hs @@ -33,7 +33,7 @@ infix 4 =: tests :: [Test] tests = [ testGroup "inline code" - [ "with '}'" =: code "}" =?> "\\mono{\\letterclosebrace{}}" + [ "with '}'" =: code "}" =?> "\\mono{\\}}" , "without '}'" =: code "]" =?> "\\type{]}" , property "code property" $ \s -> null s || if '{' `elem` s || '}' `elem` s diff --git a/src/Tests/Writers/LaTeX.hs b/src/Tests/Writers/LaTeX.hs new file mode 100644 index 000000000..7987716f3 --- /dev/null +++ b/src/Tests/Writers/LaTeX.hs @@ -0,0 +1,35 @@ +{-# LANGUAGE OverloadedStrings, QuasiQuotes #-} +module Tests.Writers.LaTeX (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Tests.Arbitrary() + +latex :: (ToString a, ToPandoc a) => a -> String +latex = writeLaTeX defaultWriterOptions . toPandoc + +{- + "my test" =: X =?> Y + +is shorthand for + + test latex "my test" $ X =?> Y + +which is in turn shorthand for + + test latex "my test" (X,Y) +-} + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> Test +(=:) = test latex + +tests :: [Test] +tests = [ testGroup "code blocks" + [ "in footnotes" =: note (para "hi" <> codeBlock "hi") =?> + "\\footnote{hi\n\n\\begin{Verbatim}\nhi\n\\end{Verbatim}\n}" + ] + ] |