Test suite: a more robust way of testing the executable.
Mmny of our tests require running the pandoc
executable. This is problematic for a few different reasons.
First, cabal-install will sometimes run the test suite
after building the library but before building the executable,
which means the executable isn't in place for the tests.
One can work around that by first building, then building
and running the tests, but that's fragile. Second,
we have to find the executable. So far, we've done that
using a function findPandoc that attempts to locate it
relative to the test executable (which can be located
using findExecutablePath). But the logic here is delicate
and work with every combination of options.
To solve both problems, we add an `--emulate` option to
the `test-pandoc` executable. When `--emulate` occurs
as the first argument passed to `test-pandoc`, the
program simply emulates the regular pandoc executable,
using the rest of the arguments (after `--emulate`).
Thus,
test-pandoc --emulate -f markdown -t latex
is just like
pandoc -f markdown -t latex
Since all the work is done by library functions,
implementing this emulation just takes a couple lines
of code and should be entirely reliable.
With this change, we can test the pandoc executable
by running the test program itself (locatable using
findExecutablePath) with the `--emulate` option.
This removes the need for the fragile `findPandoc`
step, and it means we can run our integration tests
even when we're just building the library, not the
executable.
Part of this change involved simplifying some complex
handling to set environment variables for dynamic
library paths. I have tested a build with
`--enable-dynamic-executable`, and it works, but
further testing may be needed.
2021-02-03 02:09:16 +01:00
|
|
|
{-# LANGUAGE TupleSections #-}
|
2019-02-04 22:52:31 +01:00
|
|
|
{- |
|
|
|
|
Module : Tests.Old
|
2021-01-08 18:38:20 +01:00
|
|
|
Copyright : © 2006-2021 John MacFarlane
|
2019-02-04 22:52:31 +01:00
|
|
|
License : GNU GPL, version 2 or above
|
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley@edu>
|
|
|
|
Stability : alpha
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
"Old" style tests (comparing output to golden files).
|
|
|
|
-}
|
2011-01-12 19:10:56 +01:00
|
|
|
module Tests.Old (tests) where
|
2011-01-12 13:11:08 +01:00
|
|
|
|
2017-03-04 13:03:41 +01:00
|
|
|
import Data.Algorithm.Diff
|
2011-01-12 13:11:08 +01:00
|
|
|
import System.Exit
|
2021-02-03 06:09:10 +01:00
|
|
|
import System.FilePath ((<.>), (</>))
|
2020-05-19 07:46:14 +02:00
|
|
|
import qualified System.Environment as Env
|
Test suite: a more robust way of testing the executable.
Mmny of our tests require running the pandoc
executable. This is problematic for a few different reasons.
First, cabal-install will sometimes run the test suite
after building the library but before building the executable,
which means the executable isn't in place for the tests.
One can work around that by first building, then building
and running the tests, but that's fragile. Second,
we have to find the executable. So far, we've done that
using a function findPandoc that attempts to locate it
relative to the test executable (which can be located
using findExecutablePath). But the logic here is delicate
and work with every combination of options.
To solve both problems, we add an `--emulate` option to
the `test-pandoc` executable. When `--emulate` occurs
as the first argument passed to `test-pandoc`, the
program simply emulates the regular pandoc executable,
using the rest of the arguments (after `--emulate`).
Thus,
test-pandoc --emulate -f markdown -t latex
is just like
pandoc -f markdown -t latex
Since all the work is done by library functions,
implementing this emulation just takes a couple lines
of code and should be entirely reliable.
With this change, we can test the pandoc executable
by running the test program itself (locatable using
findExecutablePath) with the `--emulate` option.
This removes the need for the fragile `findPandoc`
step, and it means we can run our integration tests
even when we're just building the library, not the
executable.
Part of this change involved simplifying some complex
handling to set environment variables for dynamic
library paths. I have tested a build with
`--enable-dynamic-executable`, and it works, but
further testing may be needed.
2021-02-03 02:09:16 +01:00
|
|
|
import System.Environment.Executable (getExecutablePath)
|
2019-02-01 02:25:36 +01:00
|
|
|
import Text.Pandoc.Process (pipeProcess)
|
2017-03-14 17:05:36 +01:00
|
|
|
import Test.Tasty (TestTree, testGroup)
|
2017-03-15 00:27:39 +01:00
|
|
|
import Test.Tasty.Golden.Advanced (goldenTest)
|
2017-03-04 13:03:41 +01:00
|
|
|
import Tests.Helpers hiding (test)
|
2017-02-04 21:54:41 +01:00
|
|
|
import qualified Text.Pandoc.UTF8 as UTF8
|
2011-01-12 13:11:08 +01:00
|
|
|
|
2019-02-01 05:56:20 +01:00
|
|
|
tests :: FilePath -> [TestTree]
|
|
|
|
tests pandocPath =
|
|
|
|
[ testGroup "markdown"
|
|
|
|
[ testGroup "writer"
|
|
|
|
$ writerTests' "markdown" ++ lhsWriterTests' "markdown"
|
|
|
|
, testGroup "reader"
|
|
|
|
[ test' "basic" ["-r", "markdown", "-w", "native", "-s"]
|
|
|
|
"testsuite.txt" "testsuite.native"
|
|
|
|
, test' "tables" ["-r", "markdown", "-w", "native", "--columns=80"]
|
|
|
|
"tables.txt" "tables.native"
|
|
|
|
, test' "pipe tables" ["-r", "markdown", "-w", "native", "--columns=80"]
|
|
|
|
"pipe-tables.txt" "pipe-tables.native"
|
|
|
|
, test' "more" ["-r", "markdown", "-w", "native", "-s"]
|
|
|
|
"markdown-reader-more.txt" "markdown-reader-more.native"
|
|
|
|
, lhsReaderTest' "markdown+lhs"
|
|
|
|
]
|
|
|
|
, testGroup "citations"
|
|
|
|
[ test' "citations" ["-r", "markdown", "-w", "native"]
|
|
|
|
"markdown-citations.txt" "markdown-citations.native"
|
|
|
|
]
|
|
|
|
]
|
|
|
|
, testGroup "rst"
|
|
|
|
[ testGroup "writer" (writerTests' "rst" ++ lhsWriterTests' "rst")
|
|
|
|
, testGroup "reader"
|
|
|
|
[ test' "basic" ["-r", "rst+smart", "-w", "native",
|
|
|
|
"-s", "--columns=80"] "rst-reader.rst" "rst-reader.native"
|
|
|
|
, test' "tables" ["-r", "rst", "-w", "native", "--columns=80"]
|
|
|
|
"tables.rst" "tables-rstsubset.native"
|
|
|
|
, lhsReaderTest' "rst+lhs"
|
|
|
|
]
|
|
|
|
]
|
|
|
|
, testGroup "latex"
|
|
|
|
[ testGroup "writer"
|
2020-12-21 03:04:54 +01:00
|
|
|
(extWriterTests' "latex" ++ lhsWriterTests' "latex")
|
2019-02-01 05:56:20 +01:00
|
|
|
, testGroup "reader"
|
|
|
|
[ test' "basic" ["-r", "latex+raw_tex", "-w", "native", "-s"]
|
|
|
|
"latex-reader.latex" "latex-reader.native"
|
|
|
|
, lhsReaderTest' "latex+lhs"
|
|
|
|
]
|
|
|
|
]
|
|
|
|
, testGroup "html"
|
2020-09-10 18:47:40 +02:00
|
|
|
[ testGroup "writer" $ mconcat
|
|
|
|
[ extWriterTests' "html4"
|
|
|
|
, extWriterTests' "html5"
|
|
|
|
, lhsWriterTests' "html"
|
|
|
|
]
|
2019-02-01 05:56:20 +01:00
|
|
|
, test' "reader" ["-r", "html", "-w", "native", "-s"]
|
|
|
|
"html-reader.html" "html-reader.native"
|
|
|
|
]
|
|
|
|
, testGroup "s5"
|
|
|
|
[ s5WriterTest' "basic" ["-s"] "s5"
|
|
|
|
, s5WriterTest' "fancy" ["-s","--mathjax","-i"] "s5"
|
|
|
|
, s5WriterTest' "fragment" [] "html4"
|
|
|
|
, s5WriterTest' "inserts" ["-s", "-H", "insert",
|
|
|
|
"-B", "insert", "-A", "insert", "-c", "main.css"] "html4"
|
|
|
|
]
|
|
|
|
, testGroup "textile"
|
|
|
|
[ testGroup "writer" $ writerTests' "textile"
|
|
|
|
, test' "reader" ["-r", "textile", "-w", "native", "-s"]
|
|
|
|
"textile-reader.textile" "textile-reader.native"
|
|
|
|
]
|
|
|
|
, testGroup "docbook"
|
|
|
|
[ testGroup "writer" $ writerTests' "docbook4"
|
|
|
|
, test' "reader" ["-r", "docbook", "-w", "native", "-s"]
|
|
|
|
"docbook-reader.docbook" "docbook-reader.native"
|
2019-10-30 16:51:33 +01:00
|
|
|
, test' "reader" ["-r", "docbook", "-w", "native", "-s"]
|
|
|
|
"docbook-chapter.docbook" "docbook-chapter.native"
|
2019-02-01 05:56:20 +01:00
|
|
|
, test' "reader" ["-r", "docbook", "-w", "native", "-s"]
|
|
|
|
"docbook-xref.docbook" "docbook-xref.native"
|
|
|
|
]
|
|
|
|
, testGroup "docbook5"
|
|
|
|
[ testGroup "writer" $ writerTests' "docbook5"
|
|
|
|
]
|
|
|
|
, testGroup "jats"
|
2020-02-13 05:36:02 +01:00
|
|
|
[ testGroup "writer"
|
|
|
|
[ testGroup "jats_archiving" $
|
2020-11-17 17:18:15 +01:00
|
|
|
extWriterTests' "jats_archiving"
|
2020-02-13 05:36:02 +01:00
|
|
|
, testGroup "jats_articleauthoring" $
|
|
|
|
writerTests' "jats_articleauthoring"
|
|
|
|
, testGroup "jats_publishing" $
|
|
|
|
writerTests' "jats_publishing"
|
|
|
|
]
|
2019-02-01 05:56:20 +01:00
|
|
|
, test' "reader" ["-r", "jats", "-w", "native", "-s"]
|
|
|
|
"jats-reader.xml" "jats-reader.native"
|
|
|
|
]
|
2019-06-05 23:52:23 +02:00
|
|
|
, testGroup "jira"
|
|
|
|
[ testGroup "writer" $ writerTests' "jira"
|
2019-12-18 06:07:46 +01:00
|
|
|
, test' "reader" ["-r", "jira", "-w", "native", "-s"]
|
|
|
|
"jira-reader.jira" "jira-reader.native"
|
2019-06-05 23:52:23 +02:00
|
|
|
]
|
2019-02-01 05:56:20 +01:00
|
|
|
, 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' "math" [] "fb2/math.markdown" "fb2/math.fb2"
|
|
|
|
, fb2WriterTest' "meta" [] "fb2/meta.markdown" "fb2/meta.fb2"
|
|
|
|
, fb2WriterTest' "tables" [] "tables.native" "tables.fb2"
|
|
|
|
, fb2WriterTest' "testsuite" [] "testsuite.native" "writer.fb2"
|
|
|
|
]
|
|
|
|
, testGroup "mediawiki"
|
|
|
|
[ testGroup "writer" $ writerTests' "mediawiki"
|
|
|
|
, test' "reader" ["-r", "mediawiki", "-w", "native", "-s"]
|
|
|
|
"mediawiki-reader.wiki" "mediawiki-reader.native"
|
|
|
|
]
|
|
|
|
, testGroup "vimwiki"
|
|
|
|
[ test' "reader" ["-r", "vimwiki", "-w", "native", "-s"]
|
|
|
|
"vimwiki-reader.wiki" "vimwiki-reader.native"
|
|
|
|
]
|
|
|
|
, testGroup "dokuwiki"
|
|
|
|
[ testGroup "writer" $ writerTests' "dokuwiki"
|
|
|
|
, test' "inline_formatting" ["-r", "native", "-w", "dokuwiki", "-s"]
|
|
|
|
"dokuwiki_inline_formatting.native" "dokuwiki_inline_formatting.dokuwiki"
|
|
|
|
, test' "multiblock table" ["-r", "native", "-w", "dokuwiki", "-s"]
|
|
|
|
"dokuwiki_multiblock_table.native" "dokuwiki_multiblock_table.dokuwiki"
|
|
|
|
, test' "external images" ["-r", "native", "-w", "dokuwiki", "-s"]
|
|
|
|
"dokuwiki_external_images.native" "dokuwiki_external_images.dokuwiki"
|
|
|
|
]
|
|
|
|
, testGroup "opml"
|
|
|
|
[ test' "basic" ["-r", "native", "-w", "opml", "--columns=78", "-s"]
|
|
|
|
"testsuite.native" "writer.opml"
|
|
|
|
, test' "reader" ["-r", "opml", "-w", "native", "-s"]
|
|
|
|
"opml-reader.opml" "opml-reader.native"
|
|
|
|
]
|
|
|
|
, testGroup "haddock"
|
|
|
|
[ testGroup "writer" $ writerTests' "haddock"
|
|
|
|
, test' "reader" ["-r", "haddock", "-w", "native", "-s"]
|
|
|
|
"haddock-reader.haddock" "haddock-reader.native"
|
|
|
|
]
|
|
|
|
, testGroup "txt2tags"
|
|
|
|
[ test' "reader" ["-r", "t2t", "-w", "native", "-s"]
|
|
|
|
"txt2tags.t2t" "txt2tags.native" ]
|
|
|
|
, testGroup "epub" [
|
|
|
|
test' "features" ["-r", "epub", "-w", "native"]
|
|
|
|
"epub/features.epub" "epub/features.native"
|
|
|
|
, test' "wasteland" ["-r", "epub", "-w", "native"]
|
|
|
|
"epub/wasteland.epub" "epub/wasteland.native"
|
|
|
|
, test' "formatting" ["-r", "epub", "-w", "native"]
|
|
|
|
"epub/formatting.epub" "epub/formatting.native"
|
|
|
|
]
|
|
|
|
, testGroup "twiki"
|
|
|
|
[ test' "reader" ["-r", "twiki", "-w", "native", "-s"]
|
|
|
|
"twiki-reader.twiki" "twiki-reader.native" ]
|
|
|
|
, testGroup "tikiwiki"
|
|
|
|
[ test' "reader" ["-r", "tikiwiki", "-w", "native", "-s"]
|
|
|
|
"tikiwiki-reader.tikiwiki" "tikiwiki-reader.native" ]
|
|
|
|
, testGroup "other writers" $ map (\f -> testGroup f $ writerTests' f)
|
|
|
|
[ "opendocument" , "context" , "texinfo", "icml", "tei"
|
2019-04-03 02:11:35 +02:00
|
|
|
, "man" , "plain" , "rtf", "org", "asciidoc", "asciidoctor"
|
|
|
|
, "xwiki", "zimwiki"
|
2019-02-01 05:56:20 +01:00
|
|
|
]
|
|
|
|
, testGroup "writers-lang-and-dir"
|
|
|
|
[ test' "latex" ["-f", "native", "-t", "latex", "-s"]
|
|
|
|
"writers-lang-and-dir.native" "writers-lang-and-dir.latex"
|
|
|
|
, test' "context" ["-f", "native", "-t", "context", "-s"]
|
|
|
|
"writers-lang-and-dir.native" "writers-lang-and-dir.context"
|
|
|
|
]
|
|
|
|
, testGroup "muse"
|
|
|
|
[ testGroup "writer" $ writerTests' "muse"
|
|
|
|
]
|
|
|
|
, testGroup "ms"
|
|
|
|
[ testGroup "writer" $ writerTests' "ms"
|
|
|
|
]
|
|
|
|
, testGroup "creole"
|
|
|
|
[ test' "reader" ["-r", "creole", "-w", "native", "-s"]
|
|
|
|
"creole-reader.txt" "creole-reader.native"
|
|
|
|
]
|
|
|
|
, testGroup "custom writer"
|
|
|
|
[ test' "basic" ["-f", "native", "-t", "../data/sample.lua"]
|
|
|
|
"testsuite.native" "writer.custom"
|
|
|
|
, 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"
|
|
|
|
]
|
|
|
|
, testGroup "org"
|
|
|
|
[ test' "reader" ["-r", "org", "-w", "native", "-s"]
|
|
|
|
"org-select-tags.org" "org-select-tags.native"
|
|
|
|
]
|
2019-02-09 23:53:30 +01:00
|
|
|
, testGroup "ipynb"
|
2019-03-10 01:53:53 +01:00
|
|
|
[ test' "reader" ["-f", "ipynb-raw_html-raw_tex+raw_attribute",
|
|
|
|
"-t", "native", "-s"]
|
2019-02-09 23:53:30 +01:00
|
|
|
"ipynb/simple.ipynb" "ipynb/simple.out.native"
|
2020-11-15 00:09:44 +01:00
|
|
|
, test' "writer" ["-f", "native",
|
|
|
|
"--markdown-headings=setext", "-t",
|
2019-03-10 01:53:53 +01:00
|
|
|
"ipynb-raw_html-raw_tex+raw_attribute", "-s"]
|
2019-02-09 23:53:30 +01:00
|
|
|
"ipynb/simple.in.native" "ipynb/simple.ipynb"
|
|
|
|
]
|
2019-02-01 05:56:20 +01:00
|
|
|
]
|
|
|
|
where
|
|
|
|
test' = test pandocPath
|
|
|
|
writerTests' = writerTests pandocPath
|
|
|
|
s5WriterTest' = s5WriterTest pandocPath
|
|
|
|
fb2WriterTest' = fb2WriterTest pandocPath
|
|
|
|
lhsWriterTests' = lhsWriterTests pandocPath
|
|
|
|
lhsReaderTest' = lhsReaderTest pandocPath
|
2020-09-10 18:47:40 +02:00
|
|
|
extWriterTests' = extendedWriterTests pandocPath
|
2011-01-12 13:11:08 +01:00
|
|
|
|
|
|
|
-- makes sure file is fully closed after reading
|
|
|
|
readFile' :: FilePath -> IO String
|
2017-02-04 21:54:41 +01:00
|
|
|
readFile' f = do s <- UTF8.readFile f
|
2011-01-12 13:11:08 +01:00
|
|
|
return $! (length s `seq` s)
|
|
|
|
|
2019-02-01 05:56:20 +01:00
|
|
|
lhsWriterTests :: FilePath -> String -> [TestTree]
|
|
|
|
lhsWriterTests pandocPath format
|
2011-01-12 13:11:08 +01:00
|
|
|
= [ t "lhs to normal" format
|
|
|
|
, t "lhs to lhs" (format ++ "+lhs")
|
|
|
|
]
|
|
|
|
where
|
2019-02-01 05:56:20 +01:00
|
|
|
t n f = test pandocPath
|
2020-11-15 00:09:44 +01:00
|
|
|
n ["--wrap=preserve", "-r", "native", "-s",
|
|
|
|
"--markdown-headings=setext", "-w", f]
|
2011-12-22 22:21:44 +01:00
|
|
|
"lhs-test.native" ("lhs-test" <.> f)
|
2011-01-12 13:11:08 +01:00
|
|
|
|
2019-02-01 05:56:20 +01:00
|
|
|
lhsReaderTest :: FilePath -> String -> TestTree
|
|
|
|
lhsReaderTest pandocPath format =
|
|
|
|
test pandocPath "lhs" ["-r", format, "-w", "native"]
|
2012-10-30 06:45:52 +01:00
|
|
|
("lhs-test" <.> format) norm
|
2016-12-11 22:09:33 +01:00
|
|
|
where norm = if format == "markdown+lhs"
|
2012-10-30 06:45:52 +01:00
|
|
|
then "lhs-test-markdown.native"
|
|
|
|
else "lhs-test.native"
|
2011-01-12 13:11:08 +01:00
|
|
|
|
2019-02-01 05:56:20 +01:00
|
|
|
writerTests :: FilePath -> String -> [TestTree]
|
|
|
|
writerTests pandocPath format
|
|
|
|
= [ test pandocPath
|
|
|
|
"basic" (opts ++ ["-s"]) "testsuite.native" ("writer" <.> format)
|
|
|
|
, test pandocPath
|
|
|
|
"tables" opts "tables.native" ("tables" <.> format)
|
2011-01-12 13:11:08 +01:00
|
|
|
]
|
|
|
|
where
|
2015-10-18 20:52:32 +02:00
|
|
|
opts = ["-r", "native", "-w", format, "--columns=78",
|
|
|
|
"--variable", "pandoc-version="]
|
2011-01-12 13:11:08 +01:00
|
|
|
|
2020-09-10 18:47:40 +02:00
|
|
|
extendedWriterTests :: FilePath -> String -> [TestTree]
|
|
|
|
extendedWriterTests pandocPath format
|
|
|
|
= writerTests pandocPath format ++
|
2020-09-12 20:44:15 +02:00
|
|
|
let testForTable name =
|
|
|
|
test pandocPath
|
|
|
|
(name ++ " table")
|
|
|
|
opts
|
|
|
|
("tables" </> name <.> "native")
|
|
|
|
("tables" </> name <.> format)
|
2020-09-13 23:20:26 +02:00
|
|
|
in map testForTable ["planets", "nordics", "students"]
|
2020-09-10 18:47:40 +02:00
|
|
|
where
|
|
|
|
opts = ["-r", "native", "-w", format, "--columns=78",
|
|
|
|
"--variable", "pandoc-version="]
|
|
|
|
|
2019-02-01 05:56:20 +01:00
|
|
|
s5WriterTest :: FilePath -> String -> [String] -> String -> TestTree
|
|
|
|
s5WriterTest pandocPath modifier opts format
|
|
|
|
= test pandocPath (format ++ " writer (" ++ modifier ++ ")")
|
2012-04-19 03:03:32 +02:00
|
|
|
(["-r", "native", "-w", format] ++ opts)
|
2014-08-13 20:16:50 +02:00
|
|
|
"s5.native" ("s5-" ++ modifier <.> "html")
|
2011-01-12 13:11:08 +01:00
|
|
|
|
2019-02-01 05:56:20 +01:00
|
|
|
fb2WriterTest :: FilePath -> String -> [String] -> String -> String -> TestTree
|
|
|
|
fb2WriterTest pandocPath title opts inputfile normfile =
|
|
|
|
testWithNormalize (ignoreBinary . formatXML) pandocPath
|
2012-04-19 03:03:32 +02:00
|
|
|
title (["-t", "fb2"]++opts) inputfile normfile
|
|
|
|
where
|
|
|
|
formatXML xml = splitTags $ zip xml (drop 1 xml)
|
2017-03-04 13:03:41 +01:00
|
|
|
splitTags [] = []
|
2020-09-13 16:48:14 +02:00
|
|
|
splitTags [end] = [fst end, snd end]
|
2012-04-19 03:03:32 +02:00
|
|
|
splitTags (('>','<'):rest) = ">\n" ++ splitTags rest
|
2017-03-04 13:03:41 +01:00
|
|
|
splitTags ((c,_):rest) = c : splitTags rest
|
2012-04-19 03:03:32 +02:00
|
|
|
ignoreBinary = unlines . filter (not . startsWith "<binary ") . lines
|
|
|
|
startsWith tag str = all (uncurry (==)) $ zip tag str
|
|
|
|
|
2011-01-12 13:11:08 +01:00
|
|
|
-- | Run a test without normalize function, return True if test passed.
|
2019-02-01 05:56:20 +01:00
|
|
|
test :: FilePath -- ^ Path of pandoc executable
|
|
|
|
-> String -- ^ Title of test
|
2011-01-12 13:11:08 +01:00
|
|
|
-> [String] -- ^ Options to pass to pandoc
|
|
|
|
-> String -- ^ Input filepath
|
|
|
|
-> FilePath -- ^ Norm (for test results) filepath
|
2017-03-14 17:05:36 +01:00
|
|
|
-> TestTree
|
2011-01-12 13:11:08 +01:00
|
|
|
test = testWithNormalize id
|
|
|
|
|
|
|
|
-- | Run a test with normalize function, return True if test passed.
|
|
|
|
testWithNormalize :: (String -> String) -- ^ Normalize function for output
|
2019-02-01 05:56:20 +01:00
|
|
|
-> FilePath -- ^ Path to pandoc executable
|
2011-01-12 13:11:08 +01:00
|
|
|
-> String -- ^ Title of test
|
|
|
|
-> [String] -- ^ Options to pass to pandoc
|
|
|
|
-> String -- ^ Input filepath
|
|
|
|
-> FilePath -- ^ Norm (for test results) filepath
|
2017-03-14 17:05:36 +01:00
|
|
|
-> TestTree
|
2019-02-01 05:56:20 +01:00
|
|
|
testWithNormalize normalizer pandocPath testname opts inp norm =
|
2017-03-15 00:27:39 +01:00
|
|
|
goldenTest testname getExpected getActual
|
|
|
|
(compareValues norm options) updateGolden
|
|
|
|
where getExpected = normalizer <$> readFile' norm
|
2019-02-01 02:25:36 +01:00
|
|
|
getActual = do
|
2020-05-19 07:46:14 +02:00
|
|
|
mldpath <- Env.lookupEnv "LD_LIBRARY_PATH"
|
|
|
|
mdyldpath <- Env.lookupEnv "DYLD_LIBRARY_PATH"
|
Test suite: a more robust way of testing the executable.
Mmny of our tests require running the pandoc
executable. This is problematic for a few different reasons.
First, cabal-install will sometimes run the test suite
after building the library but before building the executable,
which means the executable isn't in place for the tests.
One can work around that by first building, then building
and running the tests, but that's fragile. Second,
we have to find the executable. So far, we've done that
using a function findPandoc that attempts to locate it
relative to the test executable (which can be located
using findExecutablePath). But the logic here is delicate
and work with every combination of options.
To solve both problems, we add an `--emulate` option to
the `test-pandoc` executable. When `--emulate` occurs
as the first argument passed to `test-pandoc`, the
program simply emulates the regular pandoc executable,
using the rest of the arguments (after `--emulate`).
Thus,
test-pandoc --emulate -f markdown -t latex
is just like
pandoc -f markdown -t latex
Since all the work is done by library functions,
implementing this emulation just takes a couple lines
of code and should be entirely reliable.
With this change, we can test the pandoc executable
by running the test program itself (locatable using
findExecutablePath) with the `--emulate` option.
This removes the need for the fragile `findPandoc`
step, and it means we can run our integration tests
even when we're just building the library, not the
executable.
Part of this change involved simplifying some complex
handling to set environment variables for dynamic
library paths. I have tested a build with
`--enable-dynamic-executable`, and it works, but
further testing may be needed.
2021-02-03 02:09:16 +01:00
|
|
|
let env = ("TMP",".") :
|
|
|
|
("LANG","en_US.UTF-8") :
|
|
|
|
("HOME", "./") :
|
|
|
|
maybe [] ((:[]) . ("LD_LIBRARY_PATH",)) mldpath ++
|
|
|
|
maybe [] ((:[]) . ("DYLD_LIBRARY_PATH",)) mdyldpath
|
|
|
|
|
|
|
|
(ec, out) <- pipeProcess (Just env) pandocPath
|
|
|
|
("--emulate":options) mempty
|
2017-03-15 00:27:39 +01:00
|
|
|
if ec == ExitSuccess
|
2019-02-01 02:25:36 +01:00
|
|
|
then return $ filter (/='\r') . normalizer
|
|
|
|
$ UTF8.toStringLazy out
|
2017-03-15 00:27:39 +01:00
|
|
|
-- filter \r so the tests will work on Windows machines
|
2019-02-01 02:25:36 +01:00
|
|
|
else fail $ "Pandoc failed with error code " ++ show ec
|
2017-03-15 00:27:39 +01:00
|
|
|
updateGolden = UTF8.writeFile norm
|
2019-03-14 01:44:07 +01:00
|
|
|
options = ["--data-dir=../data","--quiet"] ++ [inp] ++ opts
|
2017-03-15 00:27:39 +01:00
|
|
|
|
|
|
|
compareValues :: FilePath -> [String] -> String -> String -> IO (Maybe String)
|
|
|
|
compareValues norm options expected actual = do
|
Test suite: a more robust way of testing the executable.
Mmny of our tests require running the pandoc
executable. This is problematic for a few different reasons.
First, cabal-install will sometimes run the test suite
after building the library but before building the executable,
which means the executable isn't in place for the tests.
One can work around that by first building, then building
and running the tests, but that's fragile. Second,
we have to find the executable. So far, we've done that
using a function findPandoc that attempts to locate it
relative to the test executable (which can be located
using findExecutablePath). But the logic here is delicate
and work with every combination of options.
To solve both problems, we add an `--emulate` option to
the `test-pandoc` executable. When `--emulate` occurs
as the first argument passed to `test-pandoc`, the
program simply emulates the regular pandoc executable,
using the rest of the arguments (after `--emulate`).
Thus,
test-pandoc --emulate -f markdown -t latex
is just like
pandoc -f markdown -t latex
Since all the work is done by library functions,
implementing this emulation just takes a couple lines
of code and should be entirely reliable.
With this change, we can test the pandoc executable
by running the test program itself (locatable using
findExecutablePath) with the `--emulate` option.
This removes the need for the fragile `findPandoc`
step, and it means we can run our integration tests
even when we're just building the library, not the
executable.
Part of this change involved simplifying some complex
handling to set environment variables for dynamic
library paths. I have tested a build with
`--enable-dynamic-executable`, and it works, but
further testing may be needed.
2021-02-03 02:09:16 +01:00
|
|
|
testExePath <- getExecutablePath
|
|
|
|
let cmd = testExePath ++ " --emulate " ++ unwords options
|
2017-03-15 00:27:39 +01:00
|
|
|
let dash = replicate 72 '-'
|
|
|
|
let diff = getDiff (lines actual) (lines expected)
|
|
|
|
if expected == actual
|
|
|
|
then return Nothing
|
|
|
|
else return $ Just $
|
|
|
|
'\n' : dash ++
|
|
|
|
"\n--- " ++ norm ++
|
|
|
|
"\n+++ " ++ cmd ++ "\n" ++
|
|
|
|
showDiff (1,1) diff ++ dash
|