Only run lhs tests if 'lhs' argument passed to RunTests.hs.

Reason:  these tests assume highlighting support has been
compiled in.  So, to avoid unexpected failures, we shouldn't
run them by default.


git-svn-id: https://pandoc.googlecode.com/svn/trunk@1541 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
fiddlosopher 2009-02-14 16:10:19 +00:00
parent 6033ea729c
commit 1a15c46eef

View file

@ -2,6 +2,12 @@
-- RunTests.hs - run test suite for pandoc -- RunTests.hs - run test suite for pandoc
-- This script is designed to be run from the tests directory. -- This script is designed to be run from the tests directory.
-- It assumes the pandoc executable is in dist/build/pandoc. -- It assumes the pandoc executable is in dist/build/pandoc.
--
-- runhaskell -i.. RunTests.hs [lhs]
--
-- If the lhs argument is provided, tests for lhs support will be
-- run. These presuppose that pandoc has been compiled with the
-- -fhighlighting flag, so these tests are not run by default.
module Main where module Main where
import System.Exit import System.Exit
@ -11,6 +17,7 @@ import Prelude hiding ( putStrLn, putStr, readFile )
import System.Process ( runProcess, waitForProcess ) import System.Process ( runProcess, waitForProcess )
import System.FilePath ( (</>), (<.>) ) import System.FilePath ( (</>), (<.>) )
import System.Directory import System.Directory
import System.Environment
import System.Exit import System.Exit
import Text.Printf import Text.Printf
import Diff import Diff
@ -68,6 +75,8 @@ lhsReaderFormats = [ "markdown+lhs"
main :: IO () main :: IO ()
main = do main = do
args <- getArgs
let runLhsTests = "lhs" `elem` args
r1s <- mapM runWriterTest writerFormats r1s <- mapM runWriterTest writerFormats
r2 <- runS5WriterTest "basic" ["-s"] "s5" r2 <- runS5WriterTest "basic" ["-s"] "s5"
r3 <- runS5WriterTest "fancy" ["-s","-m","-i"] "s5" r3 <- runS5WriterTest "fancy" ["-s","-m","-i"] "s5"
@ -88,8 +97,12 @@ main = do
"latex-reader.latex" "latex-reader.native" "latex-reader.latex" "latex-reader.native"
r11 <- runTest "native reader" ["-r", "native", "-w", "native", "-s"] r11 <- runTest "native reader" ["-r", "native", "-w", "native", "-s"]
"testsuite.native" "testsuite.native" "testsuite.native" "testsuite.native"
r12s <- mapM runLhsWriterTest lhsWriterFormats r12s <- if runLhsTests
r13s <- mapM runLhsReaderTest lhsReaderFormats then mapM runLhsWriterTest lhsWriterFormats
else return []
r13s <- if runLhsTests
then mapM runLhsReaderTest lhsReaderFormats
else return []
let results = r1s ++ [r2, r3, r4, r5, r6, r7, r7a, r8, r9, r10, r11] ++ r12s ++ r13s let results = r1s ++ [r2, r3, r4, r5, r6, r7, r7a, r8, r9, r10, r11] ++ r12s ++ r13s
if all id results if all id results
then do then do