diff --git a/test/Tests/Command.hs b/test/Tests/Command.hs index 021486231..0fa06be8c 100644 --- a/test/Tests/Command.hs +++ b/test/Tests/Command.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE BangPatterns #-} {- | Module : Tests.Command Copyright : © 2006-2022 John MacFarlane @@ -8,6 +9,27 @@ Portability : portable Run commands, and test results, defined in markdown files. + +A command test is a code block with the following format: + +> ``` +> % pandoc -f markdown -t latex +> *hi* +> ^D +> \emph{hi} +> ``` + +- The first line, after "%", should contain a command to run. +- Then comes zero or more lines of text which will be passed + to the command as stdin. +- The stdin terminates with a line containing "^D". +- The following lines are typically the expected output + on stdout. +- If any output on stderr is expected, it should come first + and each stderr line should be preceded by the string "2> ". +- If a nonzero exit status is expected, the last line should + contain "=> " followed by the exit status. + -} module Tests.Command (runTest, tests) where @@ -39,13 +61,14 @@ execTest :: String -- ^ Path to test executable execTest testExePath cmd inp = do env' <- setupEnvironment testExePath let pr = (shell (pandocToEmulate True cmd)){ env = Just env' } - (ec, out', err') <- readCreateProcessWithExitCode pr inp + (!ec, out', err') <- readCreateProcessWithExitCode pr inp + let err = unlines . map ("2> " ++) . lines $ err' -- filter \r so the tests will work on Windows machines - let out = filter (/= '\r') $ err' ++ out' - case ec of - ExitFailure _ -> hPutStr stderr err' - ExitSuccess -> return () - return (ec, out) + let out'' = filter (/= '\r') $ err ++ out' + let out' = out'' ++ case ec of + ExitFailure !n -> "=> " ++ show n ++ "\n" + ExitSuccess -> "" + return (ec, out') pandocToEmulate :: Bool -> String -> String pandocToEmulate True ('p':'a':'n':'d':'o':'c':cs) = @@ -63,15 +86,11 @@ runTest :: String -- ^ Path to test executable -> String -- ^ Expected output -> TestTree runTest testExePath testname cmd inp norm = testCase testname $ do - (ec, out) <- execTest testExePath cmd inp - result <- if ec == ExitSuccess - then - if out == norm - then return TestPassed - else return - $ TestFailed cmd "expected" - $ getDiff (lines out) (lines norm) - else return $ TestError ec + (_ec, out) <- execTest testExePath cmd inp + result <- if out == norm + then return TestPassed + else return $ TestFailed cmd "expected" + $ getDiff (lines out) (lines norm) assertBool (show result) (result == TestPassed) tests :: TestTree diff --git a/test/command/1718.md b/test/command/1718.md index c93067869..a6722b1e4 100644 --- a/test/command/1718.md +++ b/test/command/1718.md @@ -6,7 +6,7 @@ Note[^1]. [^2]: the second, unused, note. ^D -[WARNING] Note with key '2' defined at line 5 column 1 but not used. +2> [WARNING] Note with key '2' defined at line 5 column 1 but not used. [ Para [ Str "Note" , Note diff --git a/test/command/3752.md b/test/command/3752.md index bac81b1a1..b7b67cc70 100644 --- a/test/command/3752.md +++ b/test/command/3752.md @@ -1,9 +1,9 @@ ``` % pandoc command/chap1/text.md command/chap2/text.md -f markdown+rebase_relative_paths --verbose -t docx -o - | pandoc -f docx -t plain ^D -[INFO] Loaded command/chap1/spider.png from command/chap1/spider.png -[INFO] Loaded command/chap2/spider.png from command/chap2/spider.png -[INFO] Loaded command/chap1/../../lalune.jpg from command/chap1/../../lalune.jpg +2> [INFO] Loaded command/chap1/spider.png from command/chap1/spider.png +2> [INFO] Loaded command/chap2/spider.png from command/chap2/spider.png +2> [INFO] Loaded command/chap1/../../lalune.jpg from command/chap1/../../lalune.jpg Chapter one A spider: [spider] diff --git a/test/command/512.md b/test/command/512.md index 21b3ea9a7..20053d9cd 100644 --- a/test/command/512.md +++ b/test/command/512.md @@ -37,7 +37,7 @@ Loop detection: __ link1_ ^D -[WARNING] Circular reference 'link1' at line 1 column 15 +2> [WARNING] Circular reference 'link1' at line 1 column 15
``` diff --git a/test/command/5876.md b/test/command/5876.md index 7671a89cf..a8ede1887 100644 --- a/test/command/5876.md +++ b/test/command/5876.md @@ -48,11 +48,13 @@ Pandoc % pandoc -s -t native --data-dir=command/5876 --metadata-file=does-not-exist.yaml Hello ^D -Could not find metadata file does-not-exist.yaml +2> Could not find metadata file does-not-exist.yaml +=> 98 ``` ``` % pandoc -s -t native --metadata-file=does-not-exist.yaml Hello ^D -Could not find metadata file does-not-exist.yaml +2> Could not find metadata file does-not-exist.yaml +=> 98 ``` diff --git a/test/command/6837.md b/test/command/6837.md index cb35e19a1..f3f800bbb 100644 --- a/test/command/6837.md +++ b/test/command/6837.md @@ -14,9 +14,9 @@ Hi % pandoc -t markdown+lhs # Hi ^D -[WARNING] Rendering heading 'Hi' as a paragraph. - ATX headings cannot be used in literate Haskell, because '#' is not - allowed in column 1. Consider using --markdown-headings=setext. +2> [WARNING] Rendering heading 'Hi' as a paragraph. +2> ATX headings cannot be used in literate Haskell, because '#' is not +2> allowed in column 1. Consider using --markdown-headings=setext. Hi ``` diff --git a/test/command/6873.md b/test/command/6873.md index 20667d64c..394b53037 100644 --- a/test/command/6873.md +++ b/test/command/6873.md @@ -2,7 +2,7 @@ % pandoc -f latex -t native --citeproc \cite[„Etwas […{]} auslassen“]{key} ^D -[WARNING] Citeproc: citation key not found +2> [WARNING] Citeproc: citation key not found [ Para [ Cite [ Citation diff --git a/test/command/7099.md b/test/command/7099.md index 467b22a16..5dcaa64eb 100644 --- a/test/command/7099.md +++ b/test/command/7099.md @@ -2,7 +2,7 @@ % pandoc -f html -t native --verbose ^D -[INFO] Skipped '' at input line 1 column 16 +2> [INFO] Skipped '' at input line 1 column 16 [] ``` @@ -10,9 +10,9 @@ % pandoc -f html -t native --verbose ^D -[INFO] Fetching h:invalid@url... -[WARNING] Could not fetch resource h:invalid@url: Could not fetch h:invalid@url - InvalidUrlException "h:invalid@url" "Invalid scheme" -[INFO] Skipped '' at input line 1 column 29 +2> [INFO] Fetching h:invalid@url... +2> [WARNING] Could not fetch resource h:invalid@url: Could not fetch h:invalid@url +2> InvalidUrlException "h:invalid@url" "Invalid scheme" +2> [INFO] Skipped '' at input line 1 column 29 [] ``` diff --git a/test/command/defaults-inheritance-2.md b/test/command/defaults-inheritance-2.md index c639655d3..e50332cb0 100644 --- a/test/command/defaults-inheritance-2.md +++ b/test/command/defaults-inheritance-2.md @@ -2,4 +2,5 @@ % pandoc -d command/defaults6 2>&1 ^D Error: Circular defaults file reference in 'command/defaults7.yaml' +=> 63 ``` diff --git a/test/command/duplicate_attributes.md b/test/command/duplicate_attributes.md index b6e8a4c21..4eec0be45 100644 --- a/test/command/duplicate_attributes.md +++ b/test/command/duplicate_attributes.md @@ -2,6 +2,6 @@ % pandoc [span]{.foobar style="color:blue" class="zip" style="color:red"} ^D -[WARNING] Ignoring duplicate attribute style="color:red". +2> [WARNING] Ignoring duplicate attribute style="color:red".``` diff --git a/test/command/nested-table-to-asciidoc-6942.md b/test/command/nested-table-to-asciidoc-6942.md index baf11fdf7..2b0f13487 100644 --- a/test/command/nested-table-to-asciidoc-6942.md +++ b/test/command/nested-table-to-asciidoc-6942.md @@ -67,7 +67,7 @@ The table on level 3 is thus converted to level 2 and a warning is produced