aboutsummaryrefslogtreecommitdiff
path: root/tests/RunTests.hs
blob: 6579077f157a2e1f3abb3ff034bd7de16705d090 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
{-# OPTIONS_GHC -Wall #-}
-- RunTests.hs - run test suite for pandoc
-- This script is designed to be run from the tests directory.
-- It assumes the pandoc executable is in dist/build/pandoc.

module Main where
import System.Exit
import System.IO.UTF8
import System.IO ( openTempFile, stderr )
import Prelude hiding ( putStrLn, putStr, readFile )
import System.Process ( runProcess, waitForProcess )
import System.FilePath ( (</>), (<.>) )
import System.Directory
import System.Exit
import Text.Printf
import Diff

pandocPath :: FilePath
pandocPath = ".." </> "dist" </> "build" </> "pandoc" </> "pandoc"

data TestResult = TestPassed
                | TestError ExitCode
                | TestFailed [(DI, String)]
     deriving (Eq)

instance Show TestResult where
  show TestPassed     = "PASSED"
  show (TestError ec) = "ERROR " ++ show ec
  show (TestFailed d) = "FAILED\n" ++ showDiff d

showDiff :: [(DI, String)] -> String
showDiff []             = ""
showDiff ((F, ln) : ds) = "|TEST| " ++ ln ++ "\n" ++ showDiff ds
showDiff ((S, ln) : ds) = "|NORM| " ++ ln ++ "\n" ++ showDiff ds
showDiff ((B, _ ) : ds) = showDiff ds

writerFormats :: [String]
writerFormats = [ "native"
                , "html"
                , "docbook"
                , "opendocument"
                , "latex"
                , "context"
                , "texinfo"
                , "man"
                , "markdown"
                , "rst"
                , "mediawiki"
                , "rtf"
                ]

main :: IO ()
main = do
  r1s <- mapM runWriterTest writerFormats
  r2 <- runS5WriterTest "basic" ["-s"] "s5"
  r3 <- runS5WriterTest "fancy" ["-s","-m","-i"] "s5"
  r4 <- runS5WriterTest "fragment" [] "html"
  r5 <- runS5WriterTest "inserts"  ["-s", "-H", "insert",
            "-B", "insert", "-A", "insert", "-c", "main.css"] "html"
  r6 <- runTest "markdown reader" ["-r", "markdown", "-w", "native", "-s", "-S"]
             "testsuite.txt" "testsuite.native"
  r7 <- runTest "markdown reader (tables)" ["-r", "markdown", "-w", "native"]
             "tables.txt" "tables.native"
  r7a <- runTest "markdown reader (more)" ["-r", "markdown", "-w", "native"]
             "markdown-reader-more.txt" "markdown-reader-more.native"
  r8 <- runTest "rst reader" ["-r", "rst", "-w", "native", "-s", "-S"]
             "rst-reader.rst" "rst-reader.native"
  r9 <- runTest "html reader" ["-r", "html", "-w", "native", "-s"]
             "html-reader.html" "html-reader.native"
  r10 <- runTest "latex reader" ["-r", "latex", "-w", "native", "-s", "-R"]
             "latex-reader.latex" "latex-reader.native"
  r11 <- runTest "native reader" ["-r", "native", "-w", "native", "-s"]
             "testsuite.native" "testsuite.native"
  let results = r1s ++ [r2, r3, r4, r5, r6, r7, r7a, r8, r9, r10, r11]
  if all id results
     then do
       putStrLn "\nAll tests passed."
       exitWith ExitSuccess
     else do
       let failures = length $ filter not results
       putStrLn $ "\n" ++ show failures ++ " tests failed."
       exitWith (ExitFailure failures)

-- makes sure file is fully closed after reading
readFile' :: FilePath -> IO String
readFile' f = do s <- readFile f
                 return $! (length s `seq` s)

runWriterTest :: String -> IO Bool
runWriterTest format = do
  r1 <- runTest (format ++ " writer") ["-r", "native", "-s", "-w", format] "testsuite.native" ("writer" <.> format)
  r2 <- runTest (format ++ " writer (tables)") ["-r", "native", "-w", format] "tables.native" ("tables" <.> format)
  return (r1 && r2)

runS5WriterTest :: String -> [String] -> String -> IO Bool
runS5WriterTest modifier opts format = runTest (format ++ " writer (" ++ modifier ++ ")")
                     (["-r", "native", "-w", format] ++ opts) "s5.native"  ("s5." ++ modifier <.> "html")

-- | Run a test, return True if test passed.
runTest  :: String                      -- ^ Title of test
         -> [String]                    -- ^ Options to pass to pandoc
         -> String                      -- ^ Input filepath
         -> FilePath                    -- ^ Norm (for test results) filepath
         -> IO Bool
runTest testname opts inp norm = do
  (outputPath, hOut) <- openTempFile "" "pandoc-test"
  let inpPath = inp
  let normPath = norm
  -- Note: COLUMNS must be set for markdown table reader
  ph <- runProcess pandocPath (opts ++ [inpPath]) Nothing (Just [("COLUMNS", "80")]) Nothing (Just hOut) (Just stderr)
  ec <- waitForProcess ph
  result  <- if ec == ExitSuccess
                then do
                  -- filter \r so the tests will work on Windows machines
                  outputContents <- readFile' outputPath >>= return . filter (/='\r')
                  normContents <- readFile' normPath >>= return . filter (/='\r')
                  if outputContents == normContents
                     then return TestPassed
                     else return $ TestFailed $ getDiff (lines outputContents) (lines normContents)
                else return $ TestError ec
  removeFile outputPath
  putStrLn $ printf "%-28s ---> %s" testname (show result)
  return (result == TestPassed)