Update command tests to distinguish stderr and test exit status.
This commit is contained in:
parent
7df29e495f
commit
9e0d146837
16 changed files with 60 additions and 38 deletions
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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]
|
||||
|
|
|
@ -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
|
||||
<p><a href="">click here</a></p>
|
||||
```
|
||||
|
||||
|
|
|
@ -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
|
||||
```
|
||||
|
|
|
@ -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
|
||||
```
|
||||
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -2,7 +2,7 @@
|
|||
% pandoc -f html -t native --verbose
|
||||
<iframe src=""></iframe>
|
||||
^D
|
||||
[INFO] Skipped '<iframe src></iframe>' at input line 1 column 16
|
||||
2> [INFO] Skipped '<iframe src></iframe>' at input line 1 column 16
|
||||
[]
|
||||
```
|
||||
|
||||
|
@ -10,9 +10,9 @@
|
|||
% pandoc -f html -t native --verbose
|
||||
<iframe src="h:invalid@url"></iframe>
|
||||
^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 '<iframe src="h:invalid@url"></iframe>' 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 '<iframe src="h:invalid@url"></iframe>' at input line 1 column 29
|
||||
[]
|
||||
```
|
||||
|
|
|
@ -2,4 +2,5 @@
|
|||
% pandoc -d command/defaults6 2>&1
|
||||
^D
|
||||
Error: Circular defaults file reference in 'command/defaults7.yaml'
|
||||
=> 63
|
||||
```
|
||||
|
|
|
@ -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".
|
||||
<p><span class="foobar zip" style="color:blue">span</span></p>
|
||||
```
|
||||
|
|
|
@ -67,7 +67,7 @@ The table on level 3 is thus converted to level 2 and a warning is produced
|
|||
</body>
|
||||
</html>
|
||||
^D
|
||||
[INFO] Not rendering Table ("",[],[]) (Caption Nothing []) [(AlignDefault,ColWidth 0.5),(AlignDefault,ColWidth 0.5)] (TableHead ("",[],[]) []) [TableBody ("",[],[]) (RowHeadColumns 0) [] [Row ("",[],[]) [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "a1"]],Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Table ("",[],[]) (Caption Nothing []) [(AlignDefault,ColWidthDefault),(AlignDefault,ColWidthDefault)] (TableHead ("",[],[]) []) [TableBody ("",[],[]) (RowHeadColumns 0) [] [Row ("",[],[]) [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "1"]],Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "2"]]]]] (TableFoot ("",[],[]) [])]]]] (TableFoot ("",[],[]) [])
|
||||
2> [INFO] Not rendering Table ("",[],[]) (Caption Nothing []) [(AlignDefault,ColWidth 0.5),(AlignDefault,ColWidth 0.5)] (TableHead ("",[],[]) []) [TableBody ("",[],[]) (RowHeadColumns 0) [] [Row ("",[],[]) [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "a1"]],Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Table ("",[],[]) (Caption Nothing []) [(AlignDefault,ColWidthDefault),(AlignDefault,ColWidthDefault)] (TableHead ("",[],[]) []) [TableBody ("",[],[]) (RowHeadColumns 0) [] [Row ("",[],[]) [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "1"]],Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) [Plain [Str "2"]]]]] (TableFoot ("",[],[]) [])]]]] (TableFoot ("",[],[]) [])
|
||||
[width="100%",cols="50%,50%",]
|
||||
|===
|
||||
a|
|
||||
|
|
|
@ -15,6 +15,6 @@ references:
|
|||
|
||||
[@bar]
|
||||
^D
|
||||
[WARNING] Citeproc: citation bar not found
|
||||
2> [WARNING] Citeproc: citation bar not found
|
||||
(**bar?**)
|
||||
```
|
||||
|
|
|
@ -47,7 +47,7 @@ References {#references .unnumbered}
|
|||
[^3]: Like a citation without author: [-@item1], and now Doe with a
|
||||
locator [-@item2 p. 44].
|
||||
^D
|
||||
[WARNING] Citeproc: citation nonexistent not found
|
||||
2> [WARNING] Citeproc: citation nonexistent not found
|
||||
# Pandoc with citeproc-hs
|
||||
|
||||
([**nonexistent?**](#ref-nonexistent))
|
||||
|
|
|
@ -48,7 +48,7 @@ References {#references .unnumbered}
|
|||
[^3]: Like a citation without author: [-@item1], and again
|
||||
[-@item1], and now Doe with a locator [-@item2 p. 44].
|
||||
^D
|
||||
[WARNING] Citeproc: citation nonexistent not found
|
||||
2> [WARNING] Citeproc: citation nonexistent not found
|
||||
# Pandoc with citeproc-hs
|
||||
|
||||
[^1]
|
||||
|
|
|
@ -48,7 +48,7 @@ References {#references .unnumbered}
|
|||
[^3]: Like a citation without author: [-@item1], and now Doe with a
|
||||
locator [-@item2 p. 44].
|
||||
^D
|
||||
[WARNING] Citeproc: citation nonexistent not found
|
||||
2> [WARNING] Citeproc: citation nonexistent not found
|
||||
# Pandoc with citeproc-hs
|
||||
|
||||
[**nonexistent?**](#ref-nonexistent)
|
||||
|
|
|
@ -2,7 +2,7 @@
|
|||
% pandoc -f latex -t icml
|
||||
\includegraphics{command/corrupt.svg}
|
||||
^D
|
||||
[WARNING] Could not determine image size for command/corrupt.svg: could not determine image type
|
||||
2> [WARNING] Could not determine image size for command/corrupt.svg: could not determine image type
|
||||
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
|
||||
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
|
||||
<Rectangle Self="uec" StrokeWeight="0" ItemTransform="1 0 0 1 150 -100">
|
||||
|
|
Loading…
Reference in a new issue