aboutsummaryrefslogtreecommitdiff
path: root/tests/test-pandoc.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2011-01-11 17:36:58 -0800
committerNathan Gass <gass@search.ch>2011-01-12 11:35:10 +0100
commiteb1d0148596b91c2887233e034411763196490a5 (patch)
tree2a3ca115e319249d4edd4a17ce7327cef17406d7 /tests/test-pandoc.hs
parent3bc0a55af0994f34c1d7b2ebdc8b960f0f713ebf (diff)
downloadpandoc-eb1d0148596b91c2887233e034411763196490a5.tar.gz
Improvements to test suite.
+ You can now specify glob patterns after 'cabal test'; e.g. 'cabal test latex' will only run the latex tests. + Instead of detecting highlighting support in Setup.hs, we now detect it in test-pandoc, by looking to see if 'languages' is null. + We now verify the lhs readers against the lhs-test.native, normalizing with 'normalize'. This makes more sense than verifying against HTML, which also brings in the HTML writer. + Added lhsn-test.nohl.{html,html+lhs}, so we can do the lhs tests whether or not highlighting has been installed.
Diffstat (limited to 'tests/test-pandoc.hs')
-rw-r--r--tests/test-pandoc.hs24
1 files changed, 14 insertions, 10 deletions
diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs
index 6c77b984c..c7ec67705 100644
--- a/tests/test-pandoc.hs
+++ b/tests/test-pandoc.hs
@@ -12,7 +12,9 @@ import System.FilePath ( (</>), (<.>) )
import System.Directory
import System.Exit
import Data.Algorithm.Diff
-import Text.Pandoc.Shared ( substitute )
+import Text.Pandoc.Shared ( substitute, normalize, defaultWriterOptions )
+import Text.Pandoc.Writers.Native ( writeNative )
+import Text.Pandoc.Highlighting ( languages )
import Prelude hiding ( readFile )
import qualified Data.ByteString.Lazy as B
import Data.ByteString.Lazy.UTF8 (toString)
@@ -105,13 +107,15 @@ lhsWriterTests format
, t "lhs to lhs" (format ++ "+lhs")
]
where
- t n f = test n ["--columns=78", "-r", "native", "-s", "-w", f]
- "lhs-test.native" ("lhs-test" <.> f)
+ t n f = test n ["--columns=78", "-r", "native", "-s", "-w", f] "lhs-test.native" ("lhs-test" <.> ext f)
+ ext f = if null languages && format == "html"
+ then "nohl" <.> f
+ else f
lhsReaderTest :: String -> Test
lhsReaderTest format =
- test "lhs" ["-r", format, "-w", "html+lhs"] ("lhs-test" <.> format) "lhs-test.fragment.html+lhs"
-
+ testWithNormalize normalizer "lhs" ["-r", format, "-w", "native"] ("lhs-test" <.> format) "lhs-test.native"
+ where normalizer = writeNative defaultWriterOptions . normalize . read
latexCitationTests :: String -> Test
latexCitationTests n
@@ -124,8 +128,8 @@ latexCitationTests n
where
o = ["--bibliography", "biblio.bib", "--csl", "chicago-author-date.csl", "--no-citeproc", "--" ++ n]
f = n ++ "-citations.latex"
- normalize = substitute "\160" " " . substitute "\8211" "-"
- t = testWithNormalize normalize
+ normalizer = substitute "\160" " " . substitute "\8211" "-"
+ t = testWithNormalize normalizer
writerTests :: String -> [Test]
writerTests format
@@ -165,7 +169,7 @@ testWithNormalize :: (String -> String) -- ^ Normalize function for output
-> String -- ^ Input filepath
-> FilePath -- ^ Norm (for test results) filepath
-> Test
-testWithNormalize normalize testname opts inp norm = testCase testname $ do
+testWithNormalize normalizer testname opts inp norm = testCase testname $ do
(outputPath, hOut) <- openTempFile "" "pandoc-test"
let inpPath = inp
let normPath = norm
@@ -175,8 +179,8 @@ testWithNormalize normalize testname opts inp norm = testCase testname $ do
result <- if ec == ExitSuccess
then do
-- filter \r so the tests will work on Windows machines
- outputContents <- readFile' outputPath >>= return . filter (/='\r') . normalize
- normContents <- readFile' normPath >>= return . filter (/='\r')
+ outputContents <- readFile' outputPath >>= return . filter (/='\r') . normalizer
+ normContents <- readFile' normPath >>= return . filter (/='\r') . normalizer
if outputContents == normContents
then return TestPassed
else return $ TestFailed $ getDiff (lines outputContents) (lines normContents)