From c0700987ba30de0cd7aa697da144eb19a58147ab Mon Sep 17 00:00:00 2001 From: Nathan Gass <gass@search.ch> Date: Tue, 4 Jan 2011 01:00:01 +0100 Subject: [PATCH 01/28] Changed test-pandoc to use test-framework and HUnit. --- Setup.hs | 2 +- pandoc.cabal | 2 +- src/test-pandoc.hs | 207 +++++++++++++++++++++------------------------ 3 files changed, 100 insertions(+), 111 deletions(-) diff --git a/Setup.hs b/Setup.hs index b68435216..432746070 100644 --- a/Setup.hs +++ b/Setup.hs @@ -46,7 +46,7 @@ runTestSuite _ _ pkg lbi = do let isHighlightingKate (Dependency (PackageName "highlighting-kate") _) = True isHighlightingKate _ = False let highlightingSupport = any isHighlightingKate $ buildDepends pkg - let testArgs = ["lhs" | highlightingSupport] + let testArgs = if highlightingSupport then [] else ["-t", "!lhs"] inDirectory "tests" $ rawSystem (testDir' </> "test-pandoc") testArgs >>= exitWith else do diff --git a/pandoc.cabal b/pandoc.cabal index d41e608ee..bb9a3e323 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -295,5 +295,5 @@ Executable test-pandoc Buildable: False else Ghc-Options: -Wall - Build-Depends: base >= 4 && < 5, Diff + Build-Depends: base >= 4 && < 5, Diff, test-framework, test-framework-hunit, HUnit Other-Modules: Text.Pandoc.Shared diff --git a/src/test-pandoc.hs b/src/test-pandoc.hs index 9b6d96510..43b8a2afa 100644 --- a/src/test-pandoc.hs +++ b/src/test-pandoc.hs @@ -13,18 +13,22 @@ -- cabal install Diff module Main where -import System.IO ( openTempFile, stderr, stdout, hFlush ) + +import Test.Framework (defaultMain, testGroup, Test ) +import Test.Framework.Providers.HUnit + +import Test.HUnit hiding ( Test ) + +import System.IO ( openTempFile, stderr ) import System.Process ( runProcess, waitForProcess ) import System.FilePath ( (</>), (<.>) ) import System.Directory -import System.Environment import System.Exit -import Text.Printf import Data.Algorithm.Diff import Text.Pandoc.Shared ( substitute ) import Prelude hiding ( readFile ) import qualified Data.ByteString.Lazy as B -import Data.ByteString.Lazy.UTF8 (toString, fromString) +import Data.ByteString.Lazy.UTF8 (toString) readFileUTF8 :: FilePath -> IO String readFileUTF8 f = B.readFile f >>= return . toString @@ -48,24 +52,6 @@ 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" - , "plain" - , "markdown" - , "rst" - , "mediawiki" - , "textile" - , "rtf" - , "org" - ] - lhsWriterFormats :: [String] lhsWriterFormats = [ "markdown" , "markdown+lhs" @@ -83,100 +69,106 @@ lhsReaderFormats = [ "markdown+lhs" , "latex+lhs" ] -main :: IO () -main = do - args <- getArgs - let runLhsTests = "lhs" `elem` args - 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", "-S"] - "markdown-reader-more.txt" "markdown-reader-more.native" - r8 <- runTest "rst reader" ["-r", "rst", "-w", "native", "-s", "-S"] - "rst-reader.rst" "rst-reader.native" - r8a <- runTest "rst reader (tables)" ["-r", "rst", "-w", "native"] - "tables.rst" "tables-rstsubset.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" - rTextile1 <- runTest "textile reader" ["-r", "textile", "-w", "native", "-s"] - "textile-reader.textile" "textile-reader.native" - r11 <- runTest "native reader" ["-r", "native", "-w", "native", "-s"] - "testsuite.native" "testsuite.native" - r14s <- mapM (\style -> runTest ("markdown reader (citations) (" ++ style ++ ")") ["-r", "markdown", "-w", "markdown", "--bibliography", "biblio.bib", "--csl", style ++ ".csl", "--no-wrap"] "markdown-citations.txt" ("markdown-citations." ++ style ++ ".txt")) ["chicago-author-date","ieee","mhra"] - let citopts = ["--bibliography", "biblio.bib", "--csl", "chicago-author-date.csl", "--no-citeproc"] - r15 <- runTest "markdown writer (citations)" (["-r", "markdown", "-w", "markdown", "--no-wrap"] ++ citopts) - "markdown-citations.txt" "markdown-citations.txt" - r16s <- runLatexCitationTests citopts "biblatex" - r17s <- runLatexCitationTests citopts "natbib" - r12s <- if runLhsTests - then mapM runLhsWriterTest lhsWriterFormats - else putStrLn "Skipping lhs writer tests because they presuppose highlighting support" >> return [] - r13s <- if runLhsTests - then mapM runLhsReaderTest lhsReaderFormats - else putStrLn "Skipping lhs reader tests because they presuppose highlighting support" >> return [] - let results = r1s ++ +markdownCitationTest :: Test +markdownCitationTest + = testGroup "citations" $ map styleToTest ["chicago-author-date","ieee","mhra"] + ++ [runTest "no-citeproc" wopts "markdown-citations.txt" "markdown-citations.txt"] + where + ropts = ["-r", "markdown", "-w", "markdown", "--bibliography", "biblio.bib", "--no-wrap"] + wopts = ropts ++ ["--no-citeproc"] + styleToTest style = runTest style (ropts ++ ["--csl", style ++ ".csl"]) + "markdown-citations.txt" ("markdown-citations." ++ style ++ ".txt") - [ r2, r3, r4, r5 -- S5 - , r6, r7, r7a -- markdown reader - , r8, r8a -- rst - , r9 -- html - , r10 -- latex - , rTextile1 -- textile - , r11 -- native - , r15 -- markdown citations - ] ++ r12s ++ r13s ++ r14s ++ r16s ++ r17s - 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) + +tests :: [Test] +tests = [ testGroup "markdown" [ runWriterTest "" "markdown" + , runTest "reader" ["-r", "markdown", "-w", "native", "-s", "-S"] + "testsuite.txt" "testsuite.native" + , runTest "reader (tables)" ["-r", "markdown", "-w", "native"] + "tables.txt" "tables.native" + , runTest "reader (more)" ["-r", "markdown", "-w", "native", "-S"] + "markdown-reader-more.txt" "markdown-reader-more.native" + , markdownCitationTest + ] + , testGroup "rst" [ runWriterTest "" "rst" + , runTest "reader" ["-r", "rst", "-w", "native", "-s", "-S"] + "rst-reader.rst" "rst-reader.native" + , runTest "reader (tables)" ["-r", "rst", "-w", "native"] + "tables.rst" "tables-rstsubset.native" + ] + , testGroup "latex" [ runWriterTest "" "latex" + , runTest "reader" ["-r", "latex", "-w", "native", "-s", "-R"] + "latex-reader.latex" "latex-reader.native" + , runLatexCitationTests "biblatex" + , runLatexCitationTests "natbib" + ] + , testGroup "html" [ runWriterTest "" "html" + , runTest "reader" ["-r", "html", "-w", "native", "-s"] + "html-reader.html" "html-reader.native" + ] + , testGroup "s5" [ runS5WriterTest "basic" ["-s"] "s5" + , runS5WriterTest "fancy" ["-s","-m","-i"] "s5" + , runS5WriterTest "fragment" [] "html" + , runS5WriterTest "inserts" ["-s", "-H", "insert", + "-B", "insert", "-A", "insert", "-c", "main.css"] "html" + ] + , testGroup "textile" [ runWriterTest "" "textile" + , runTest "reader" ["-r", "textile", "-w", "native", "-s"] + "textile-reader.textile" "textile-reader.native" + ] + , testGroup "native" [ runWriterTest "" "native" + , runTest "reader" ["-r", "native", "-w", "native", "-s"] + "testsuite.native" "testsuite.native" + ] + , testGroup "other writers" $ map (\f -> runWriterTest f f) [ "docbook", "opendocument" , "context" , "texinfo" + , "man" , "plain" , "mediawiki", "rtf", "org" + ] + , testGroup "lhs" [ testGroup "writer" $ map runLhsWriterTest lhsWriterFormats + , testGroup "reader" $ map runLhsReaderTest lhsReaderFormats + ] + ] + +main :: IO () +main = defaultMain tests -- makes sure file is fully closed after reading readFile' :: FilePath -> IO String readFile' f = do s <- readFileUTF8 f return $! (length s `seq` s) -runLhsWriterTest :: String -> IO Bool +runLhsWriterTest :: String -> Test runLhsWriterTest format = - runTest ("(lhs) " ++ format ++ " writer") ["--columns=78", "-r", "native", "-s", "-w", format] "lhs-test.native" ("lhs-test" <.> format) + runTest format ["--columns=78", "-r", "native", "-s", "-w", format] "lhs-test.native" ("lhs-test" <.> format) -runLhsReaderTest :: String -> IO Bool +runLhsReaderTest :: String -> Test runLhsReaderTest format = - runTest ("(lhs) " ++ format ++ " reader") ["-r", format, "-w", "html+lhs"] ("lhs-test" <.> format) "lhs-test.fragment.html+lhs" + runTest format ["-r", format, "-w", "html+lhs"] ("lhs-test" <.> format) "lhs-test.fragment.html+lhs" -runLatexCitationTests :: [String] -> String -> IO [Bool] -runLatexCitationTests o n - = sequence [ rt ("latex reader (" ++ n ++ " citations)") (["-r", "latex", "-w", "markdown", "-s", "--no-wrap"] ++ o') - f "markdown-citations.txt" - , rt ("latex writer (" ++ n ++ " citations)") (["-r", "markdown", "-w", "latex", "-s", "--no-wrap"] ++ o') - "markdown-citations.txt" f - ] - where - o' = o ++ ["--" ++ n] - f = n ++ "-citations.latex" - normalize = substitute "\160" " " . substitute "\8211" "-" - rt = runTestWithNormalize normalize +runLatexCitationTests :: String -> Test +runLatexCitationTests n + = testGroup (n ++ " citations") + [ rt ("latex reader (" ++ n ++ " citations)") (["-r", "latex", "-w", "markdown", "-s", "--no-wrap"] ++ o) + f "markdown-citations.txt" + , rt ("latex writer (" ++ n ++ " citations)") (["-r", "markdown", "-w", "latex", "-s", "--no-wrap"] ++ o) + "markdown-citations.txt" f + ] + where + o = ["--bibliography", "biblio.bib", "--csl", "chicago-author-date.csl", "--no-citeproc", "--" ++ n] + f = n ++ "-citations.latex" + normalize = substitute "\160" " " . substitute "\8211" "-" + rt = runTestWithNormalize normalize -runWriterTest :: String -> IO Bool -runWriterTest format = do - r1 <- runTest (format ++ " writer") ["-r", "native", "-s", "-w", format, "--columns=78"] "testsuite.native" ("writer" <.> format) - r2 <- runTest (format ++ " writer (tables)") ["-r", "native", "-w", format, "--columns=78"] "tables.native" ("tables" <.> format) - return (r1 && r2) +runWriterTest :: String -> String -> Test +runWriterTest prefix format + = testGroup name [ runTest "basic" (opts ++ ["-s"]) "testsuite.native" ("writer" <.> format) + , runTest "tables" opts "tables.native" ("tables" <.> format) + ] + where + name = if (null prefix) then "writer" else prefix ++ " writer" + opts = ["-r", "native", "-w", format, "--columns=78"] -runS5WriterTest :: String -> [String] -> String -> IO Bool +runS5WriterTest :: String -> [String] -> String -> Test runS5WriterTest modifier opts format = runTest (format ++ " writer (" ++ modifier ++ ")") (["-r", "native", "-w", format] ++ opts) "s5.native" ("s5." ++ modifier <.> "html") @@ -186,7 +178,7 @@ runTest :: String -- ^ Title of test -> [String] -- ^ Options to pass to pandoc -> String -- ^ Input filepath -> FilePath -- ^ Norm (for test results) filepath - -> IO Bool + -> Test runTest = runTestWithNormalize id -- | Run a test with normalize function, return True if test passed. @@ -195,13 +187,11 @@ runTestWithNormalize :: (String -> String) -- ^ Normalize function for output -> [String] -- ^ Options to pass to pandoc -> String -- ^ Input filepath -> FilePath -- ^ Norm (for test results) filepath - -> IO Bool -runTestWithNormalize normalize testname opts inp norm = do - putStr $ printf "%-28s ---> " testname + -> Test +runTestWithNormalize normalize testname opts inp norm = testCase testname $ do (outputPath, hOut) <- openTempFile "" "pandoc-test" let inpPath = inp let normPath = norm - hFlush stdout ph <- runProcess pandocPath (["--columns=80"] ++ [inpPath] ++ ["--data-dir", ".."] ++ opts) Nothing (Just [("LANG","en_US.UTF-8"),("HOME", "./")]) Nothing (Just hOut) (Just stderr) ec <- waitForProcess ph @@ -215,5 +205,4 @@ runTestWithNormalize normalize testname opts inp norm = do else return $ TestFailed $ getDiff (lines outputContents) (lines normContents) else return $ TestError ec removeFile outputPath - B.putStrLn (fromString $ show result) - return (result == TestPassed) + assertBool (show result) (result == TestPassed) From e06899ef1fb4a0b6a034cceb4b9ec11725720efa Mon Sep 17 00:00:00 2001 From: Nathan Gass <gass@search.ch> Date: Tue, 11 Jan 2011 20:41:34 +0100 Subject: [PATCH 02/28] Add reader groups for markdown and rst reader tests. --- src/test-pandoc.hs | 22 ++++++++++++---------- 1 file changed, 12 insertions(+), 10 deletions(-) diff --git a/src/test-pandoc.hs b/src/test-pandoc.hs index 43b8a2afa..0c0218ae8 100644 --- a/src/test-pandoc.hs +++ b/src/test-pandoc.hs @@ -82,19 +82,21 @@ markdownCitationTest tests :: [Test] tests = [ testGroup "markdown" [ runWriterTest "" "markdown" - , runTest "reader" ["-r", "markdown", "-w", "native", "-s", "-S"] - "testsuite.txt" "testsuite.native" - , runTest "reader (tables)" ["-r", "markdown", "-w", "native"] - "tables.txt" "tables.native" - , runTest "reader (more)" ["-r", "markdown", "-w", "native", "-S"] - "markdown-reader-more.txt" "markdown-reader-more.native" + , testGroup "reader" [ runTest "basic" ["-r", "markdown", "-w", "native", "-s", "-S"] + "testsuite.txt" "testsuite.native" + , runTest "tables" ["-r", "markdown", "-w", "native"] + "tables.txt" "tables.native" + , runTest "more" ["-r", "markdown", "-w", "native", "-S"] + "markdown-reader-more.txt" "markdown-reader-more.native" + ] , markdownCitationTest ] , testGroup "rst" [ runWriterTest "" "rst" - , runTest "reader" ["-r", "rst", "-w", "native", "-s", "-S"] - "rst-reader.rst" "rst-reader.native" - , runTest "reader (tables)" ["-r", "rst", "-w", "native"] - "tables.rst" "tables-rstsubset.native" + , testGroup "reader" [ runTest "basic" ["-r", "rst", "-w", "native", "-s", "-S"] + "rst-reader.rst" "rst-reader.native" + , runTest "tables" ["-r", "rst", "-w", "native"] + "tables.rst" "tables-rstsubset.native" + ] ] , testGroup "latex" [ runWriterTest "" "latex" , runTest "reader" ["-r", "latex", "-w", "native", "-s", "-R"] From a2153acfffecd969a513bf2fc3d940f99ec3dfee Mon Sep 17 00:00:00 2001 From: Nathan Gass <gass@search.ch> Date: Tue, 11 Jan 2011 21:10:36 +0100 Subject: [PATCH 03/28] Include lhs tests in existing testGroup structure. --- src/test-pandoc.hs | 71 ++++++++++++++++++++-------------------------- 1 file changed, 30 insertions(+), 41 deletions(-) diff --git a/src/test-pandoc.hs b/src/test-pandoc.hs index 0c0218ae8..fde0715c9 100644 --- a/src/test-pandoc.hs +++ b/src/test-pandoc.hs @@ -52,23 +52,6 @@ showDiff ((F, ln) : ds) = "|TEST| " ++ ln ++ "\n" ++ showDiff ds showDiff ((S, ln) : ds) = "|NORM| " ++ ln ++ "\n" ++ showDiff ds showDiff ((B, _ ) : ds) = showDiff ds -lhsWriterFormats :: [String] -lhsWriterFormats = [ "markdown" - , "markdown+lhs" - , "rst" - , "rst+lhs" - , "latex" - , "latex+lhs" - , "html" - , "html+lhs" - ] - -lhsReaderFormats :: [String] -lhsReaderFormats = [ "markdown+lhs" - , "rst+lhs" - , "latex+lhs" - ] - markdownCitationTest :: Test markdownCitationTest = testGroup "citations" $ map styleToTest ["chicago-author-date","ieee","mhra"] @@ -81,30 +64,34 @@ markdownCitationTest tests :: [Test] -tests = [ testGroup "markdown" [ runWriterTest "" "markdown" +tests = [ testGroup "markdown" [ testGroup "writer" (runWriterTests "markdown" ++ runLhsWriterTests "markdown") , testGroup "reader" [ runTest "basic" ["-r", "markdown", "-w", "native", "-s", "-S"] "testsuite.txt" "testsuite.native" , runTest "tables" ["-r", "markdown", "-w", "native"] "tables.txt" "tables.native" , runTest "more" ["-r", "markdown", "-w", "native", "-S"] "markdown-reader-more.txt" "markdown-reader-more.native" + , runLhsReaderTest "markdown+lhs" ] , markdownCitationTest ] - , testGroup "rst" [ runWriterTest "" "rst" + , testGroup "rst" [ testGroup "writer" (runWriterTests "rst" ++ runLhsWriterTests "rst") , testGroup "reader" [ runTest "basic" ["-r", "rst", "-w", "native", "-s", "-S"] "rst-reader.rst" "rst-reader.native" , runTest "tables" ["-r", "rst", "-w", "native"] "tables.rst" "tables-rstsubset.native" + , runLhsReaderTest "rst+lhs" ] ] - , testGroup "latex" [ runWriterTest "" "latex" - , runTest "reader" ["-r", "latex", "-w", "native", "-s", "-R"] - "latex-reader.latex" "latex-reader.native" + , testGroup "latex" [ testGroup "writer" (runWriterTests "latex" ++ runLhsWriterTests "latex") + , testGroup "reader" [ runTest "basic" ["-r", "latex", "-w", "native", "-s", "-R"] + "latex-reader.latex" "latex-reader.native" + , runLhsReaderTest "latex+lhs" + ] , runLatexCitationTests "biblatex" , runLatexCitationTests "natbib" ] - , testGroup "html" [ runWriterTest "" "html" + , testGroup "html" [ testGroup "writer" (runWriterTests "html" ++ runLhsWriterTests "html") , runTest "reader" ["-r", "html", "-w", "native", "-s"] "html-reader.html" "html-reader.native" ] @@ -114,20 +101,18 @@ tests = [ testGroup "markdown" [ runWriterTest "" "markdown" , runS5WriterTest "inserts" ["-s", "-H", "insert", "-B", "insert", "-A", "insert", "-c", "main.css"] "html" ] - , testGroup "textile" [ runWriterTest "" "textile" + , testGroup "textile" [ testGroup "writer" $ runWriterTests "textile" , runTest "reader" ["-r", "textile", "-w", "native", "-s"] "textile-reader.textile" "textile-reader.native" ] - , testGroup "native" [ runWriterTest "" "native" + , testGroup "native" [ testGroup "writer" $ runWriterTests "native" , runTest "reader" ["-r", "native", "-w", "native", "-s"] "testsuite.native" "testsuite.native" ] - , testGroup "other writers" $ map (\f -> runWriterTest f f) [ "docbook", "opendocument" , "context" , "texinfo" - , "man" , "plain" , "mediawiki", "rtf", "org" - ] - , testGroup "lhs" [ testGroup "writer" $ map runLhsWriterTest lhsWriterFormats - , testGroup "reader" $ map runLhsReaderTest lhsReaderFormats - ] + , testGroup "other writers" $ map (\f -> testGroup f $ runWriterTests f) + [ "docbook", "opendocument" , "context" , "texinfo" + , "man" , "plain" , "mediawiki", "rtf", "org" + ] ] main :: IO () @@ -138,13 +123,18 @@ readFile' :: FilePath -> IO String readFile' f = do s <- readFileUTF8 f return $! (length s `seq` s) -runLhsWriterTest :: String -> Test -runLhsWriterTest format = - runTest format ["--columns=78", "-r", "native", "-s", "-w", format] "lhs-test.native" ("lhs-test" <.> format) +runLhsWriterTests :: String -> [Test] +runLhsWriterTests format + = [ t "lhs to normal" format + , t "lhs to lhs" (format ++ "+lhs") + ] + where + t n f = runTest n ["--columns=78", "-r", "native", "-s", "-w", f] + "lhs-test.native" ("lhs-test" <.> f) runLhsReaderTest :: String -> Test runLhsReaderTest format = - runTest format ["-r", format, "-w", "html+lhs"] ("lhs-test" <.> format) "lhs-test.fragment.html+lhs" + runTest "lhs" ["-r", format, "-w", "html+lhs"] ("lhs-test" <.> format) "lhs-test.fragment.html+lhs" runLatexCitationTests :: String -> Test @@ -161,13 +151,12 @@ runLatexCitationTests n normalize = substitute "\160" " " . substitute "\8211" "-" rt = runTestWithNormalize normalize -runWriterTest :: String -> String -> Test -runWriterTest prefix format - = testGroup name [ runTest "basic" (opts ++ ["-s"]) "testsuite.native" ("writer" <.> format) - , runTest "tables" opts "tables.native" ("tables" <.> format) - ] +runWriterTests :: String -> [Test] +runWriterTests format + = [ runTest "basic" (opts ++ ["-s"]) "testsuite.native" ("writer" <.> format) + , runTest "tables" opts "tables.native" ("tables" <.> format) + ] where - name = if (null prefix) then "writer" else prefix ++ " writer" opts = ["-r", "native", "-w", format, "--columns=78"] runS5WriterTest :: String -> [String] -> String -> Test From f3ee73607fd33a4ea6292ca02ba195ede075278b Mon Sep 17 00:00:00 2001 From: Nathan Gass <gass@search.ch> Date: Tue, 11 Jan 2011 21:30:19 +0100 Subject: [PATCH 04/28] Removed run prefix from all test functions. --- src/test-pandoc.hs | 138 ++++++++++++++++++++++----------------------- 1 file changed, 68 insertions(+), 70 deletions(-) diff --git a/src/test-pandoc.hs b/src/test-pandoc.hs index fde0715c9..78b2b8e4f 100644 --- a/src/test-pandoc.hs +++ b/src/test-pandoc.hs @@ -16,8 +16,7 @@ module Main where import Test.Framework (defaultMain, testGroup, Test ) import Test.Framework.Providers.HUnit - -import Test.HUnit hiding ( Test ) +import Test.HUnit ( assertBool ) import System.IO ( openTempFile, stderr ) import System.Process ( runProcess, waitForProcess ) @@ -52,64 +51,53 @@ showDiff ((F, ln) : ds) = "|TEST| " ++ ln ++ "\n" ++ showDiff ds showDiff ((S, ln) : ds) = "|NORM| " ++ ln ++ "\n" ++ showDiff ds showDiff ((B, _ ) : ds) = showDiff ds -markdownCitationTest :: Test -markdownCitationTest - = testGroup "citations" $ map styleToTest ["chicago-author-date","ieee","mhra"] - ++ [runTest "no-citeproc" wopts "markdown-citations.txt" "markdown-citations.txt"] - where - ropts = ["-r", "markdown", "-w", "markdown", "--bibliography", "biblio.bib", "--no-wrap"] - wopts = ropts ++ ["--no-citeproc"] - styleToTest style = runTest style (ropts ++ ["--csl", style ++ ".csl"]) - "markdown-citations.txt" ("markdown-citations." ++ style ++ ".txt") - - tests :: [Test] -tests = [ testGroup "markdown" [ testGroup "writer" (runWriterTests "markdown" ++ runLhsWriterTests "markdown") - , testGroup "reader" [ runTest "basic" ["-r", "markdown", "-w", "native", "-s", "-S"] +tests = [ testGroup "markdown" [ testGroup "writer" (writerTests "markdown" ++ lhsWriterTests "markdown") + , testGroup "reader" [ test "basic" ["-r", "markdown", "-w", "native", "-s", "-S"] "testsuite.txt" "testsuite.native" - , runTest "tables" ["-r", "markdown", "-w", "native"] + , test "tables" ["-r", "markdown", "-w", "native"] "tables.txt" "tables.native" - , runTest "more" ["-r", "markdown", "-w", "native", "-S"] + , test "more" ["-r", "markdown", "-w", "native", "-S"] "markdown-reader-more.txt" "markdown-reader-more.native" - , runLhsReaderTest "markdown+lhs" + , lhsReaderTest "markdown+lhs" ] - , markdownCitationTest + , testGroup "citations" markdownCitationTests ] - , testGroup "rst" [ testGroup "writer" (runWriterTests "rst" ++ runLhsWriterTests "rst") - , testGroup "reader" [ runTest "basic" ["-r", "rst", "-w", "native", "-s", "-S"] + , testGroup "rst" [ testGroup "writer" (writerTests "rst" ++ lhsWriterTests "rst") + , testGroup "reader" [ test "basic" ["-r", "rst", "-w", "native", "-s", "-S"] "rst-reader.rst" "rst-reader.native" - , runTest "tables" ["-r", "rst", "-w", "native"] + , test "tables" ["-r", "rst", "-w", "native"] "tables.rst" "tables-rstsubset.native" - , runLhsReaderTest "rst+lhs" + , lhsReaderTest "rst+lhs" ] ] - , testGroup "latex" [ testGroup "writer" (runWriterTests "latex" ++ runLhsWriterTests "latex") - , testGroup "reader" [ runTest "basic" ["-r", "latex", "-w", "native", "-s", "-R"] + , testGroup "latex" [ testGroup "writer" (writerTests "latex" ++ lhsWriterTests "latex") + , testGroup "reader" [ test "basic" ["-r", "latex", "-w", "native", "-s", "-R"] "latex-reader.latex" "latex-reader.native" - , runLhsReaderTest "latex+lhs" + , lhsReaderTest "latex+lhs" ] - , runLatexCitationTests "biblatex" - , runLatexCitationTests "natbib" + , latexCitationTests "biblatex" + , latexCitationTests "natbib" ] - , testGroup "html" [ testGroup "writer" (runWriterTests "html" ++ runLhsWriterTests "html") - , runTest "reader" ["-r", "html", "-w", "native", "-s"] + , testGroup "html" [ testGroup "writer" (writerTests "html" ++ lhsWriterTests "html") + , test "reader" ["-r", "html", "-w", "native", "-s"] "html-reader.html" "html-reader.native" ] - , testGroup "s5" [ runS5WriterTest "basic" ["-s"] "s5" - , runS5WriterTest "fancy" ["-s","-m","-i"] "s5" - , runS5WriterTest "fragment" [] "html" - , runS5WriterTest "inserts" ["-s", "-H", "insert", + , testGroup "s5" [ s5WriterTest "basic" ["-s"] "s5" + , s5WriterTest "fancy" ["-s","-m","-i"] "s5" + , s5WriterTest "fragment" [] "html" + , s5WriterTest "inserts" ["-s", "-H", "insert", "-B", "insert", "-A", "insert", "-c", "main.css"] "html" ] - , testGroup "textile" [ testGroup "writer" $ runWriterTests "textile" - , runTest "reader" ["-r", "textile", "-w", "native", "-s"] + , testGroup "textile" [ testGroup "writer" $ writerTests "textile" + , test "reader" ["-r", "textile", "-w", "native", "-s"] "textile-reader.textile" "textile-reader.native" ] - , testGroup "native" [ testGroup "writer" $ runWriterTests "native" - , runTest "reader" ["-r", "native", "-w", "native", "-s"] + , testGroup "native" [ testGroup "writer" $ writerTests "native" + , test "reader" ["-r", "native", "-w", "native", "-s"] "testsuite.native" "testsuite.native" ] - , testGroup "other writers" $ map (\f -> testGroup f $ runWriterTests f) + , testGroup "other writers" $ map (\f -> testGroup f $ writerTests f) [ "docbook", "opendocument" , "context" , "texinfo" , "man" , "plain" , "mediawiki", "rtf", "org" ] @@ -123,63 +111,73 @@ readFile' :: FilePath -> IO String readFile' f = do s <- readFileUTF8 f return $! (length s `seq` s) -runLhsWriterTests :: String -> [Test] -runLhsWriterTests format +lhsWriterTests :: String -> [Test] +lhsWriterTests format = [ t "lhs to normal" format , t "lhs to lhs" (format ++ "+lhs") ] where - t n f = runTest n ["--columns=78", "-r", "native", "-s", "-w", f] + t n f = test n ["--columns=78", "-r", "native", "-s", "-w", f] "lhs-test.native" ("lhs-test" <.> f) -runLhsReaderTest :: String -> Test -runLhsReaderTest format = - runTest "lhs" ["-r", format, "-w", "html+lhs"] ("lhs-test" <.> format) "lhs-test.fragment.html+lhs" +lhsReaderTest :: String -> Test +lhsReaderTest format = + test "lhs" ["-r", format, "-w", "html+lhs"] ("lhs-test" <.> format) "lhs-test.fragment.html+lhs" -runLatexCitationTests :: String -> Test -runLatexCitationTests n +latexCitationTests :: String -> Test +latexCitationTests n = testGroup (n ++ " citations") - [ rt ("latex reader (" ++ n ++ " citations)") (["-r", "latex", "-w", "markdown", "-s", "--no-wrap"] ++ o) + [ t ("latex reader (" ++ n ++ " citations)") (["-r", "latex", "-w", "markdown", "-s", "--no-wrap"] ++ o) f "markdown-citations.txt" - , rt ("latex writer (" ++ n ++ " citations)") (["-r", "markdown", "-w", "latex", "-s", "--no-wrap"] ++ o) + , t ("latex writer (" ++ n ++ " citations)") (["-r", "markdown", "-w", "latex", "-s", "--no-wrap"] ++ o) "markdown-citations.txt" f ] where o = ["--bibliography", "biblio.bib", "--csl", "chicago-author-date.csl", "--no-citeproc", "--" ++ n] f = n ++ "-citations.latex" normalize = substitute "\160" " " . substitute "\8211" "-" - rt = runTestWithNormalize normalize + t = testWithNormalize normalize -runWriterTests :: String -> [Test] -runWriterTests format - = [ runTest "basic" (opts ++ ["-s"]) "testsuite.native" ("writer" <.> format) - , runTest "tables" opts "tables.native" ("tables" <.> format) +writerTests :: String -> [Test] +writerTests format + = [ test "basic" (opts ++ ["-s"]) "testsuite.native" ("writer" <.> format) + , test "tables" opts "tables.native" ("tables" <.> format) ] where opts = ["-r", "native", "-w", format, "--columns=78"] -runS5WriterTest :: String -> [String] -> String -> Test -runS5WriterTest modifier opts format = runTest (format ++ " writer (" ++ modifier ++ ")") - (["-r", "native", "-w", format] ++ opts) "s5.native" ("s5." ++ modifier <.> "html") +s5WriterTest :: String -> [String] -> String -> Test +s5WriterTest modifier opts format + = test (format ++ " writer (" ++ modifier ++ ")") (["-r", "native", "-w", format] ++ opts) + "s5.native" ("s5." ++ modifier <.> "html") +markdownCitationTests :: [Test] +markdownCitationTests + = map styleToTest ["chicago-author-date","ieee","mhra"] + ++ [test "no-citeproc" wopts "markdown-citations.txt" "markdown-citations.txt"] + where + ropts = ["-r", "markdown", "-w", "markdown", "--bibliography", "biblio.bib", "--no-wrap"] + wopts = ropts ++ ["--no-citeproc"] + styleToTest style = test style (ropts ++ ["--csl", style ++ ".csl"]) + "markdown-citations.txt" ("markdown-citations." ++ style ++ ".txt") -- | Run a test without normalize function, 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 - -> Test -runTest = runTestWithNormalize id +test :: String -- ^ Title of test + -> [String] -- ^ Options to pass to pandoc + -> String -- ^ Input filepath + -> FilePath -- ^ Norm (for test results) filepath + -> Test +test = testWithNormalize id -- | Run a test with normalize function, return True if test passed. -runTestWithNormalize :: (String -> String) -- ^ Normalize function for output - -> String -- ^ Title of test - -> [String] -- ^ Options to pass to pandoc - -> String -- ^ Input filepath - -> FilePath -- ^ Norm (for test results) filepath - -> Test -runTestWithNormalize normalize testname opts inp norm = testCase testname $ do +testWithNormalize :: (String -> String) -- ^ Normalize function for output + -> String -- ^ Title of test + -> [String] -- ^ Options to pass to pandoc + -> String -- ^ Input filepath + -> FilePath -- ^ Norm (for test results) filepath + -> Test +testWithNormalize normalize testname opts inp norm = testCase testname $ do (outputPath, hOut) <- openTempFile "" "pandoc-test" let inpPath = inp let normPath = norm From e8fa72c6a7c40f21ad31998acd4da769e8b5f41c Mon Sep 17 00:00:00 2001 From: Nathan Gass <gass@search.ch> Date: Tue, 11 Jan 2011 21:49:49 +0100 Subject: [PATCH 05/28] Moved test-pandoc.hs to tests directory. --- pandoc.cabal | 2 +- {src => tests}/test-pandoc.hs | 0 2 files changed, 1 insertion(+), 1 deletion(-) rename {src => tests}/test-pandoc.hs (100%) diff --git a/pandoc.cabal b/pandoc.cabal index bb9a3e323..1a3dd8506 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -289,7 +289,7 @@ Executable markdown2pdf Buildable: False Executable test-pandoc - Hs-Source-Dirs: src + Hs-Source-Dirs: tests, src Main-Is: test-pandoc.hs if !flag(tests) Buildable: False diff --git a/src/test-pandoc.hs b/tests/test-pandoc.hs similarity index 100% rename from src/test-pandoc.hs rename to tests/test-pandoc.hs From 3bc0a55af0994f34c1d7b2ebdc8b960f0f713ebf Mon Sep 17 00:00:00 2001 From: Nathan Gass <gass@search.ch> Date: Tue, 11 Jan 2011 22:37:41 +0100 Subject: [PATCH 06/28] Removed outdated comments. --- tests/test-pandoc.hs | 12 ------------ 1 file changed, 12 deletions(-) diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs index 78b2b8e4f..6c77b984c 100644 --- a/tests/test-pandoc.hs +++ b/tests/test-pandoc.hs @@ -1,16 +1,4 @@ {-# 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. --- --- 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. --- --- This program assumes that the Diff package has been installed: --- cabal install Diff module Main where From eb1d0148596b91c2887233e034411763196490a5 Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Tue, 11 Jan 2011 17:36:58 -0800 Subject: [PATCH 07/28] 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. --- Setup.hs | 11 +++------- pandoc.cabal | 7 ++++++- tests/lhs-test.native | 4 ++-- tests/lhs-test.nohl.html | 39 ++++++++++++++++++++++++++++++++++++ tests/lhs-test.nohl.html+lhs | 39 ++++++++++++++++++++++++++++++++++++ tests/test-pandoc.hs | 24 +++++++++++++--------- 6 files changed, 103 insertions(+), 21 deletions(-) create mode 100644 tests/lhs-test.nohl.html create mode 100644 tests/lhs-test.nohl.html+lhs diff --git a/Setup.hs b/Setup.hs index 432746070..6dbc119e2 100644 --- a/Setup.hs +++ b/Setup.hs @@ -38,17 +38,12 @@ main = do -- | Run test suite. runTestSuite :: Args -> Bool -> PackageDescription -> LocalBuildInfo -> IO a -runTestSuite _ _ pkg lbi = do +runTestSuite args _ pkg lbi = do let testDir = buildDir lbi </> "test-pandoc" testDir' <- canonicalizePath testDir + let testArgs = concatMap (\arg -> ["-t",arg]) args if any id [buildable (buildInfo exe) | exe <- executables pkg, exeName exe == "test-pandoc"] - then do - let isHighlightingKate (Dependency (PackageName "highlighting-kate") _) = True - isHighlightingKate _ = False - let highlightingSupport = any isHighlightingKate $ buildDepends pkg - let testArgs = if highlightingSupport then [] else ["-t", "!lhs"] - inDirectory "tests" $ rawSystem (testDir' </> "test-pandoc") - testArgs >>= exitWith + then inDirectory "tests" $ rawSystem (testDir' </> "test-pandoc") testArgs >>= exitWith else do putStrLn "Build pandoc with the 'tests' flag to run tests" exitWith $ ExitFailure 3 diff --git a/pandoc.cabal b/pandoc.cabal index 1a3dd8506..71cb0135b 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -136,6 +136,8 @@ Extra-Source-Files: tests/lhs-test.latex+lhs, tests/lhs-test.html, tests/lhs-test.html+lhs, + tests/lhs-test.nohl.html, + tests/lhs-test.nohl.html+lhs, tests/lhs-test.fragment.html+lhs Extra-Tmp-Files: man/man1/pandoc.1, man/man1/markdown2pdf.1 @@ -291,9 +293,12 @@ Executable markdown2pdf Executable test-pandoc Hs-Source-Dirs: tests, src Main-Is: test-pandoc.hs + if flag(highlighting) + cpp-options: -D_HIGHLIGHTING if !flag(tests) Buildable: False else Ghc-Options: -Wall + Extensions: CPP Build-Depends: base >= 4 && < 5, Diff, test-framework, test-framework-hunit, HUnit - Other-Modules: Text.Pandoc.Shared + Other-Modules: Text.Pandoc.Shared, Text.Pandoc.Highlighting, Text.Pandoc.Writers.Native diff --git a/tests/lhs-test.native b/tests/lhs-test.native index 94150f069..e1127c9db 100644 --- a/tests/lhs-test.native +++ b/tests/lhs-test.native @@ -1,10 +1,10 @@ Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []}) [ Header 1 [Str "lhs",Space,Str "test"] -, Para [Code "unsplit",Space,Str "is",Space,Str "an",Space,Str "arrow",Space,Str "that",Space,Str "takes",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "and",Space,Str "combines",Space,Str "them",Space,Str "to",Space,Str "return",Space,Str "a",Space,Str "single",Space,Str "value:"] +, Para [Code "unsplit",Space,Str "is",Space,Str "an",Space,Str "arrow",Space,Str "that",Space,Str "takes",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "and",Space,Str "combines",Space,Str "them",Space,Str "to",Space,Str "return",Space,Str "a",Space,Str "single",Space,Str "value",Str ":"] , CodeBlock ("",["sourceCode","literate","haskell"],[]) "unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d\nunsplit = arr . uncurry \n -- arr (\\op (x,y) -> x `op` y) " , Para [Code "(***)",Space,Str "combines",Space,Str "two",Space,Str "arrows",Space,Str "into",Space,Str "a",Space,Str "new",Space,Str "arrow",Space,Str "by",Space,Str "running",Space,Str "the",Space,Str "two",Space,Str "arrows",Space,Str "on",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "(one",Space,Str "arrow",Space,Str "on",Space,Str "the",Space,Str "first",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair",Space,Str "and",Space,Str "one",Space,Str "arrow",Space,Str "on",Space,Str "the",Space,Str "second",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair)",Str "."] , CodeBlock ("",[],[]) "f *** g = first f >>> second g" -, Para [Str "Block",Space,Str "quote:"] +, Para [Str "Block",Space,Str "quote",Str ":"] , BlockQuote [ Para [Str "foo",Space,Str "bar"] ] ] diff --git a/tests/lhs-test.nohl.html b/tests/lhs-test.nohl.html new file mode 100644 index 000000000..feee89d4e --- /dev/null +++ b/tests/lhs-test.nohl.html @@ -0,0 +1,39 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml"> +<head> + <title></title> + <meta http-equiv="Content-Type" content="text/html; charset=utf-8" /> + <meta name="generator" content="pandoc" /> +</head> +<body> +<h1 id="lhs-test" +>lhs test</h1 +><p +><code + >unsplit</code + > is an arrow that takes a pair of values and combines them to return a single value:</p +><pre class="sourceCode haskell" +><code + >unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d +unsplit = arr . uncurry + -- arr (\op (x,y) -> x `op` y) +</code + ></pre +><p +><code + >(***)</code + > combines two arrows into a new arrow by running the two arrows on a pair of values (one arrow on the first item of the pair and one arrow on the second item of the pair).</p +><pre +><code + >f *** g = first f >>> second g +</code + ></pre +><p +>Block quote:</p +><blockquote +><p + >foo bar</p + ></blockquote +> +</body> +</html> diff --git a/tests/lhs-test.nohl.html+lhs b/tests/lhs-test.nohl.html+lhs new file mode 100644 index 000000000..ec364e796 --- /dev/null +++ b/tests/lhs-test.nohl.html+lhs @@ -0,0 +1,39 @@ +<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> +<html xmlns="http://www.w3.org/1999/xhtml"> +<head> + <title></title> + <meta http-equiv="Content-Type" content="text/html; charset=utf-8" /> + <meta name="generator" content="pandoc" /> +</head> +<body> +<h1 id="lhs-test" +>lhs test</h1 +><p +><code + >unsplit</code + > is an arrow that takes a pair of values and combines them to return a single value:</p +><pre class="sourceCode literate haskell" +><code + >> unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d +> unsplit = arr . uncurry +> -- arr (\op (x,y) -> x `op` y) +</code + ></pre +><p +><code + >(***)</code + > combines two arrows into a new arrow by running the two arrows on a pair of values (one arrow on the first item of the pair and one arrow on the second item of the pair).</p +><pre +><code + >f *** g = first f >>> second g +</code + ></pre +><p +>Block quote:</p +><blockquote +><p + >foo bar</p + ></blockquote +> +</body> +</html> 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) From 715e33705f9c857c1bfd82f1f333b381d62feed4 Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Tue, 11 Jan 2011 18:02:50 -0800 Subject: [PATCH 08/28] test-pandoc: More diff-like diffs in case of test failure. --- tests/test-pandoc.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs index c7ec67705..0c70760dc 100644 --- a/tests/test-pandoc.hs +++ b/tests/test-pandoc.hs @@ -27,18 +27,18 @@ pandocPath = ".." </> "dist" </> "build" </> "pandoc" </> "pandoc" data TestResult = TestPassed | TestError ExitCode - | TestFailed [(DI, String)] + | TestFailed FilePath [(DI, String)] deriving (Eq) instance Show TestResult where show TestPassed = "PASSED" show (TestError ec) = "ERROR " ++ show ec - show (TestFailed d) = "FAILED\n" ++ showDiff d + show (TestFailed f d) = f ++ "\n--- expected test result\n+++ actual test result\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 ((F, ln) : ds) = "- " ++ ln ++ "\n" ++ showDiff ds +showDiff ((S, ln) : ds) = "+ " ++ ln ++ "\n" ++ showDiff ds showDiff ((B, _ ) : ds) = showDiff ds tests :: [Test] @@ -183,7 +183,7 @@ testWithNormalize normalizer testname opts inp norm = testCase testname $ do normContents <- readFile' normPath >>= return . filter (/='\r') . normalizer if outputContents == normContents then return TestPassed - else return $ TestFailed $ getDiff (lines outputContents) (lines normContents) + else return $ TestFailed normPath $ getDiff (lines outputContents) (lines normContents) else return $ TestError ec removeFile outputPath assertBool (show result) (result == TestPassed) From 51d9d8b674ea21c821113ec2bf92bb5e8a1cf067 Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Tue, 11 Jan 2011 18:10:46 -0800 Subject: [PATCH 09/28] test-pandoc: Fixed + and - in diff output, which were reversed. --- tests/test-pandoc.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs index 0c70760dc..9773966b6 100644 --- a/tests/test-pandoc.hs +++ b/tests/test-pandoc.hs @@ -37,8 +37,8 @@ instance Show TestResult where showDiff :: [(DI, String)] -> String showDiff [] = "" -showDiff ((F, ln) : ds) = "- " ++ ln ++ "\n" ++ showDiff ds -showDiff ((S, ln) : ds) = "+ " ++ ln ++ "\n" ++ showDiff ds +showDiff ((F, ln) : ds) = "+ " ++ ln ++ "\n" ++ showDiff ds +showDiff ((S, ln) : ds) = "- " ++ ln ++ "\n" ++ showDiff ds showDiff ((B, _ ) : ds) = showDiff ds tests :: [Test] From 046c9c7d3b1c928b003497e05038e1cdaee85e50 Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Tue, 11 Jan 2011 18:15:24 -0800 Subject: [PATCH 10/28] test-pandoc: Relocated --columns=80 to just where it's needed. We only need it for certain table tests, because of the relative alignments. --- tests/test-pandoc.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs index 9773966b6..ad581307b 100644 --- a/tests/test-pandoc.hs +++ b/tests/test-pandoc.hs @@ -45,7 +45,7 @@ tests :: [Test] tests = [ testGroup "markdown" [ testGroup "writer" (writerTests "markdown" ++ lhsWriterTests "markdown") , testGroup "reader" [ test "basic" ["-r", "markdown", "-w", "native", "-s", "-S"] "testsuite.txt" "testsuite.native" - , test "tables" ["-r", "markdown", "-w", "native"] + , test "tables" ["-r", "markdown", "-w", "native", "--columns=80"] "tables.txt" "tables.native" , test "more" ["-r", "markdown", "-w", "native", "-S"] "markdown-reader-more.txt" "markdown-reader-more.native" @@ -54,9 +54,9 @@ tests = [ testGroup "markdown" [ testGroup "writer" (writerTests "markdown" ++ l , testGroup "citations" markdownCitationTests ] , testGroup "rst" [ testGroup "writer" (writerTests "rst" ++ lhsWriterTests "rst") - , testGroup "reader" [ test "basic" ["-r", "rst", "-w", "native", "-s", "-S"] + , testGroup "reader" [ test "basic" ["-r", "rst", "-w", "native", "-s", "-S", "--columns=80"] "rst-reader.rst" "rst-reader.native" - , test "tables" ["-r", "rst", "-w", "native"] + , test "tables" ["-r", "rst", "-w", "native", "--columns=80"] "tables.rst" "tables-rstsubset.native" , lhsReaderTest "rst+lhs" ] @@ -173,7 +173,7 @@ testWithNormalize normalizer testname opts inp norm = testCase testname $ do (outputPath, hOut) <- openTempFile "" "pandoc-test" let inpPath = inp let normPath = norm - ph <- runProcess pandocPath (["--columns=80"] ++ [inpPath] ++ ["--data-dir", ".."] ++ opts) Nothing + ph <- runProcess pandocPath ([inpPath] ++ ["--data-dir", ".."] ++ opts) Nothing (Just [("LANG","en_US.UTF-8"),("HOME", "./")]) Nothing (Just hOut) (Just stderr) ec <- waitForProcess ph result <- if ec == ExitSuccess From 530e3edc0f734dea454c7a542ca4e59a03cbe3fe Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Tue, 11 Jan 2011 18:29:38 -0800 Subject: [PATCH 11/28] test-pandoc: More informative diff output on test failure. Now the test suite tells you the exact command that was run, and the file containing the expected output. --- tests/test-pandoc.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs index ad581307b..586b807c2 100644 --- a/tests/test-pandoc.hs +++ b/tests/test-pandoc.hs @@ -27,13 +27,14 @@ pandocPath = ".." </> "dist" </> "build" </> "pandoc" </> "pandoc" data TestResult = TestPassed | TestError ExitCode - | TestFailed FilePath [(DI, String)] + | TestFailed String FilePath [(DI, String)] deriving (Eq) instance Show TestResult where show TestPassed = "PASSED" show (TestError ec) = "ERROR " ++ show ec - show (TestFailed f d) = f ++ "\n--- expected test result\n+++ actual test result\n" ++ showDiff d + show (TestFailed cmd file d) = cmd ++ "\n--- expected (" ++ file ++ ")" ++ + "\n+++ actual\n" ++ showDiff d showDiff :: [(DI, String)] -> String showDiff [] = "" @@ -173,7 +174,9 @@ testWithNormalize normalizer testname opts inp norm = testCase testname $ do (outputPath, hOut) <- openTempFile "" "pandoc-test" let inpPath = inp let normPath = norm - ph <- runProcess pandocPath ([inpPath] ++ ["--data-dir", ".."] ++ opts) Nothing + let options = ["--data-dir", ".."] ++ [inpPath] ++ opts + let cmd = pandocPath ++ " " ++ unwords options + ph <- runProcess pandocPath options Nothing (Just [("LANG","en_US.UTF-8"),("HOME", "./")]) Nothing (Just hOut) (Just stderr) ec <- waitForProcess ph result <- if ec == ExitSuccess @@ -183,7 +186,7 @@ testWithNormalize normalizer testname opts inp norm = testCase testname $ do normContents <- readFile' normPath >>= return . filter (/='\r') . normalizer if outputContents == normContents then return TestPassed - else return $ TestFailed normPath $ getDiff (lines outputContents) (lines normContents) + else return $ TestFailed cmd normPath $ getDiff (lines outputContents) (lines normContents) else return $ TestError ec removeFile outputPath assertBool (show result) (result == TestPassed) From cf5e8a824fe44ad65f1a3eb6255457667ba0cf70 Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Tue, 11 Jan 2011 19:10:35 -0800 Subject: [PATCH 12/28] test-pandoc: Improved header for diff output. --- tests/test-pandoc.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs index 586b807c2..7b585a921 100644 --- a/tests/test-pandoc.hs +++ b/tests/test-pandoc.hs @@ -33,8 +33,8 @@ data TestResult = TestPassed instance Show TestResult where show TestPassed = "PASSED" show (TestError ec) = "ERROR " ++ show ec - show (TestFailed cmd file d) = cmd ++ "\n--- expected (" ++ file ++ ")" ++ - "\n+++ actual\n" ++ showDiff d + show (TestFailed cmd file d) = "\n--- " ++ file ++ + "\n+++ " ++ cmd ++ "\n" ++ showDiff d showDiff :: [(DI, String)] -> String showDiff [] = "" From 4f6099f350a878420b403af5413a806c06694207 Mon Sep 17 00:00:00 2001 From: Nathan Gass <gass@search.ch> Date: Wed, 12 Jan 2011 13:11:08 +0100 Subject: [PATCH 13/28] Started implementing splitted test suite. Moved old tests into Old.hs and added new simple test-pandoc.hs for loading and grouping together tests from different files. Later commits will add more testfiles to the suite with more modular tests. --- tests/Old.hs | 188 +++++++++++++++++++++++++++++++++++++++++++ tests/test-pandoc.hs | 184 +----------------------------------------- 2 files changed, 191 insertions(+), 181 deletions(-) create mode 100644 tests/Old.hs diff --git a/tests/Old.hs b/tests/Old.hs new file mode 100644 index 000000000..af8cbbe3c --- /dev/null +++ b/tests/Old.hs @@ -0,0 +1,188 @@ + +module Old (tests) where + +import Test.Framework (testGroup, Test ) +import Test.Framework.Providers.HUnit +import Test.HUnit ( assertBool ) + +import System.IO ( openTempFile, stderr ) +import System.Process ( runProcess, waitForProcess ) +import System.FilePath ( (</>), (<.>) ) +import System.Directory +import System.Exit +import Data.Algorithm.Diff +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) + +readFileUTF8 :: FilePath -> IO String +readFileUTF8 f = B.readFile f >>= return . toString + +pandocPath :: FilePath +pandocPath = ".." </> "dist" </> "build" </> "pandoc" </> "pandoc" + +data TestResult = TestPassed + | TestError ExitCode + | TestFailed String FilePath [(DI, String)] + deriving (Eq) + +instance Show TestResult where + show TestPassed = "PASSED" + show (TestError ec) = "ERROR " ++ show ec + show (TestFailed cmd file d) = "\n--- " ++ file ++ + "\n+++ " ++ cmd ++ "\n" ++ showDiff d + +showDiff :: [(DI, String)] -> String +showDiff [] = "" +showDiff ((F, ln) : ds) = "+ " ++ ln ++ "\n" ++ showDiff ds +showDiff ((S, ln) : ds) = "- " ++ ln ++ "\n" ++ showDiff ds +showDiff ((B, _ ) : ds) = showDiff ds + +tests :: [Test] +tests = [ testGroup "markdown" [ testGroup "writer" (writerTests "markdown" ++ lhsWriterTests "markdown") + , testGroup "reader" [ test "basic" ["-r", "markdown", "-w", "native", "-s", "-S"] + "testsuite.txt" "testsuite.native" + , test "tables" ["-r", "markdown", "-w", "native", "--columns=80"] + "tables.txt" "tables.native" + , test "more" ["-r", "markdown", "-w", "native", "-S"] + "markdown-reader-more.txt" "markdown-reader-more.native" + , lhsReaderTest "markdown+lhs" + ] + , testGroup "citations" markdownCitationTests + ] + , testGroup "rst" [ testGroup "writer" (writerTests "rst" ++ lhsWriterTests "rst") + , testGroup "reader" [ test "basic" ["-r", "rst", "-w", "native", "-s", "-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" (writerTests "latex" ++ lhsWriterTests "latex") + , testGroup "reader" [ test "basic" ["-r", "latex", "-w", "native", "-s", "-R"] + "latex-reader.latex" "latex-reader.native" + , lhsReaderTest "latex+lhs" + ] + , latexCitationTests "biblatex" + , latexCitationTests "natbib" + ] + , testGroup "html" [ testGroup "writer" (writerTests "html" ++ lhsWriterTests "html") + , test "reader" ["-r", "html", "-w", "native", "-s"] + "html-reader.html" "html-reader.native" + ] + , testGroup "s5" [ s5WriterTest "basic" ["-s"] "s5" + , s5WriterTest "fancy" ["-s","-m","-i"] "s5" + , s5WriterTest "fragment" [] "html" + , s5WriterTest "inserts" ["-s", "-H", "insert", + "-B", "insert", "-A", "insert", "-c", "main.css"] "html" + ] + , testGroup "textile" [ testGroup "writer" $ writerTests "textile" + , test "reader" ["-r", "textile", "-w", "native", "-s"] + "textile-reader.textile" "textile-reader.native" + ] + , testGroup "native" [ testGroup "writer" $ writerTests "native" + , test "reader" ["-r", "native", "-w", "native", "-s"] + "testsuite.native" "testsuite.native" + ] + , testGroup "other writers" $ map (\f -> testGroup f $ writerTests f) + [ "docbook", "opendocument" , "context" , "texinfo" + , "man" , "plain" , "mediawiki", "rtf", "org" + ] + ] + +-- makes sure file is fully closed after reading +readFile' :: FilePath -> IO String +readFile' f = do s <- readFileUTF8 f + return $! (length s `seq` s) + +lhsWriterTests :: String -> [Test] +lhsWriterTests format + = [ t "lhs to normal" 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" <.> ext f) + ext f = if null languages && format == "html" + then "nohl" <.> f + else f + +lhsReaderTest :: String -> Test +lhsReaderTest format = + testWithNormalize normalizer "lhs" ["-r", format, "-w", "native"] ("lhs-test" <.> format) "lhs-test.native" + where normalizer = writeNative defaultWriterOptions . normalize . read + +latexCitationTests :: String -> Test +latexCitationTests n + = testGroup (n ++ " citations") + [ t ("latex reader (" ++ n ++ " citations)") (["-r", "latex", "-w", "markdown", "-s", "--no-wrap"] ++ o) + f "markdown-citations.txt" + , t ("latex writer (" ++ n ++ " citations)") (["-r", "markdown", "-w", "latex", "-s", "--no-wrap"] ++ o) + "markdown-citations.txt" f + ] + where + o = ["--bibliography", "biblio.bib", "--csl", "chicago-author-date.csl", "--no-citeproc", "--" ++ n] + f = n ++ "-citations.latex" + normalizer = substitute "\160" " " . substitute "\8211" "-" + t = testWithNormalize normalizer + +writerTests :: String -> [Test] +writerTests format + = [ test "basic" (opts ++ ["-s"]) "testsuite.native" ("writer" <.> format) + , test "tables" opts "tables.native" ("tables" <.> format) + ] + where + opts = ["-r", "native", "-w", format, "--columns=78"] + +s5WriterTest :: String -> [String] -> String -> Test +s5WriterTest modifier opts format + = test (format ++ " writer (" ++ modifier ++ ")") (["-r", "native", "-w", format] ++ opts) + "s5.native" ("s5." ++ modifier <.> "html") + +markdownCitationTests :: [Test] +markdownCitationTests + = map styleToTest ["chicago-author-date","ieee","mhra"] + ++ [test "no-citeproc" wopts "markdown-citations.txt" "markdown-citations.txt"] + where + ropts = ["-r", "markdown", "-w", "markdown", "--bibliography", "biblio.bib", "--no-wrap"] + wopts = ropts ++ ["--no-citeproc"] + styleToTest style = test style (ropts ++ ["--csl", style ++ ".csl"]) + "markdown-citations.txt" ("markdown-citations." ++ style ++ ".txt") + +-- | Run a test without normalize function, return True if test passed. +test :: String -- ^ Title of test + -> [String] -- ^ Options to pass to pandoc + -> String -- ^ Input filepath + -> FilePath -- ^ Norm (for test results) filepath + -> Test +test = testWithNormalize id + +-- | Run a test with normalize function, return True if test passed. +testWithNormalize :: (String -> String) -- ^ Normalize function for output + -> String -- ^ Title of test + -> [String] -- ^ Options to pass to pandoc + -> String -- ^ Input filepath + -> FilePath -- ^ Norm (for test results) filepath + -> Test +testWithNormalize normalizer testname opts inp norm = testCase testname $ do + (outputPath, hOut) <- openTempFile "" "pandoc-test" + let inpPath = inp + let normPath = norm + let options = ["--data-dir", ".."] ++ [inpPath] ++ opts + let cmd = pandocPath ++ " " ++ unwords options + ph <- runProcess pandocPath options Nothing + (Just [("LANG","en_US.UTF-8"),("HOME", "./")]) 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') . normalizer + normContents <- readFile' normPath >>= return . filter (/='\r') . normalizer + if outputContents == normContents + then return TestPassed + else return $ TestFailed cmd normPath $ getDiff (lines outputContents) (lines normContents) + else return $ TestError ec + removeFile outputPath + assertBool (show result) (result == TestPassed) diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs index 7b585a921..ae367fc53 100644 --- a/tests/test-pandoc.hs +++ b/tests/test-pandoc.hs @@ -2,191 +2,13 @@ module Main where -import Test.Framework (defaultMain, testGroup, Test ) -import Test.Framework.Providers.HUnit -import Test.HUnit ( assertBool ) +import Test.Framework -import System.IO ( openTempFile, stderr ) -import System.Process ( runProcess, waitForProcess ) -import System.FilePath ( (</>), (<.>) ) -import System.Directory -import System.Exit -import Data.Algorithm.Diff -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) - -readFileUTF8 :: FilePath -> IO String -readFileUTF8 f = B.readFile f >>= return . toString - -pandocPath :: FilePath -pandocPath = ".." </> "dist" </> "build" </> "pandoc" </> "pandoc" - -data TestResult = TestPassed - | TestError ExitCode - | TestFailed String FilePath [(DI, String)] - deriving (Eq) - -instance Show TestResult where - show TestPassed = "PASSED" - show (TestError ec) = "ERROR " ++ show ec - show (TestFailed cmd file d) = "\n--- " ++ file ++ - "\n+++ " ++ cmd ++ "\n" ++ showDiff d - -showDiff :: [(DI, String)] -> String -showDiff [] = "" -showDiff ((F, ln) : ds) = "+ " ++ ln ++ "\n" ++ showDiff ds -showDiff ((S, ln) : ds) = "- " ++ ln ++ "\n" ++ showDiff ds -showDiff ((B, _ ) : ds) = showDiff ds +import qualified Old tests :: [Test] -tests = [ testGroup "markdown" [ testGroup "writer" (writerTests "markdown" ++ lhsWriterTests "markdown") - , testGroup "reader" [ test "basic" ["-r", "markdown", "-w", "native", "-s", "-S"] - "testsuite.txt" "testsuite.native" - , test "tables" ["-r", "markdown", "-w", "native", "--columns=80"] - "tables.txt" "tables.native" - , test "more" ["-r", "markdown", "-w", "native", "-S"] - "markdown-reader-more.txt" "markdown-reader-more.native" - , lhsReaderTest "markdown+lhs" - ] - , testGroup "citations" markdownCitationTests - ] - , testGroup "rst" [ testGroup "writer" (writerTests "rst" ++ lhsWriterTests "rst") - , testGroup "reader" [ test "basic" ["-r", "rst", "-w", "native", "-s", "-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" (writerTests "latex" ++ lhsWriterTests "latex") - , testGroup "reader" [ test "basic" ["-r", "latex", "-w", "native", "-s", "-R"] - "latex-reader.latex" "latex-reader.native" - , lhsReaderTest "latex+lhs" - ] - , latexCitationTests "biblatex" - , latexCitationTests "natbib" - ] - , testGroup "html" [ testGroup "writer" (writerTests "html" ++ lhsWriterTests "html") - , test "reader" ["-r", "html", "-w", "native", "-s"] - "html-reader.html" "html-reader.native" - ] - , testGroup "s5" [ s5WriterTest "basic" ["-s"] "s5" - , s5WriterTest "fancy" ["-s","-m","-i"] "s5" - , s5WriterTest "fragment" [] "html" - , s5WriterTest "inserts" ["-s", "-H", "insert", - "-B", "insert", "-A", "insert", "-c", "main.css"] "html" - ] - , testGroup "textile" [ testGroup "writer" $ writerTests "textile" - , test "reader" ["-r", "textile", "-w", "native", "-s"] - "textile-reader.textile" "textile-reader.native" - ] - , testGroup "native" [ testGroup "writer" $ writerTests "native" - , test "reader" ["-r", "native", "-w", "native", "-s"] - "testsuite.native" "testsuite.native" - ] - , testGroup "other writers" $ map (\f -> testGroup f $ writerTests f) - [ "docbook", "opendocument" , "context" , "texinfo" - , "man" , "plain" , "mediawiki", "rtf", "org" - ] +tests = [ testGroup "Old" Old.tests ] main :: IO () main = defaultMain tests - --- makes sure file is fully closed after reading -readFile' :: FilePath -> IO String -readFile' f = do s <- readFileUTF8 f - return $! (length s `seq` s) - -lhsWriterTests :: String -> [Test] -lhsWriterTests format - = [ t "lhs to normal" 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" <.> ext f) - ext f = if null languages && format == "html" - then "nohl" <.> f - else f - -lhsReaderTest :: String -> Test -lhsReaderTest format = - testWithNormalize normalizer "lhs" ["-r", format, "-w", "native"] ("lhs-test" <.> format) "lhs-test.native" - where normalizer = writeNative defaultWriterOptions . normalize . read - -latexCitationTests :: String -> Test -latexCitationTests n - = testGroup (n ++ " citations") - [ t ("latex reader (" ++ n ++ " citations)") (["-r", "latex", "-w", "markdown", "-s", "--no-wrap"] ++ o) - f "markdown-citations.txt" - , t ("latex writer (" ++ n ++ " citations)") (["-r", "markdown", "-w", "latex", "-s", "--no-wrap"] ++ o) - "markdown-citations.txt" f - ] - where - o = ["--bibliography", "biblio.bib", "--csl", "chicago-author-date.csl", "--no-citeproc", "--" ++ n] - f = n ++ "-citations.latex" - normalizer = substitute "\160" " " . substitute "\8211" "-" - t = testWithNormalize normalizer - -writerTests :: String -> [Test] -writerTests format - = [ test "basic" (opts ++ ["-s"]) "testsuite.native" ("writer" <.> format) - , test "tables" opts "tables.native" ("tables" <.> format) - ] - where - opts = ["-r", "native", "-w", format, "--columns=78"] - -s5WriterTest :: String -> [String] -> String -> Test -s5WriterTest modifier opts format - = test (format ++ " writer (" ++ modifier ++ ")") (["-r", "native", "-w", format] ++ opts) - "s5.native" ("s5." ++ modifier <.> "html") - -markdownCitationTests :: [Test] -markdownCitationTests - = map styleToTest ["chicago-author-date","ieee","mhra"] - ++ [test "no-citeproc" wopts "markdown-citations.txt" "markdown-citations.txt"] - where - ropts = ["-r", "markdown", "-w", "markdown", "--bibliography", "biblio.bib", "--no-wrap"] - wopts = ropts ++ ["--no-citeproc"] - styleToTest style = test style (ropts ++ ["--csl", style ++ ".csl"]) - "markdown-citations.txt" ("markdown-citations." ++ style ++ ".txt") - --- | Run a test without normalize function, return True if test passed. -test :: String -- ^ Title of test - -> [String] -- ^ Options to pass to pandoc - -> String -- ^ Input filepath - -> FilePath -- ^ Norm (for test results) filepath - -> Test -test = testWithNormalize id - --- | Run a test with normalize function, return True if test passed. -testWithNormalize :: (String -> String) -- ^ Normalize function for output - -> String -- ^ Title of test - -> [String] -- ^ Options to pass to pandoc - -> String -- ^ Input filepath - -> FilePath -- ^ Norm (for test results) filepath - -> Test -testWithNormalize normalizer testname opts inp norm = testCase testname $ do - (outputPath, hOut) <- openTempFile "" "pandoc-test" - let inpPath = inp - let normPath = norm - let options = ["--data-dir", ".."] ++ [inpPath] ++ opts - let cmd = pandocPath ++ " " ++ unwords options - ph <- runProcess pandocPath options Nothing - (Just [("LANG","en_US.UTF-8"),("HOME", "./")]) 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') . normalizer - normContents <- readFile' normPath >>= return . filter (/='\r') . normalizer - if outputContents == normContents - then return TestPassed - else return $ TestFailed cmd normPath $ getDiff (lines outputContents) (lines normContents) - else return $ TestError ec - removeFile outputPath - assertBool (show result) (result == TestPassed) From ec4deb25327cd525d188093918330149d0ead4e7 Mon Sep 17 00:00:00 2001 From: Nathan Gass <gass@search.ch> Date: Wed, 12 Jan 2011 14:16:35 +0100 Subject: [PATCH 14/28] Added some basic testing infrastructure and some latex reader tests. --- pandoc.cabal | 5 ++++- tests/Helpers.hs | 37 +++++++++++++++++++++++++++++++++++++ tests/Latex/Reader.hs | 35 +++++++++++++++++++++++++++++++++++ tests/test-pandoc.hs | 3 +++ 4 files changed, 79 insertions(+), 1 deletion(-) create mode 100644 tests/Helpers.hs create mode 100644 tests/Latex/Reader.hs diff --git a/pandoc.cabal b/pandoc.cabal index 71cb0135b..da855a07d 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -298,7 +298,10 @@ Executable test-pandoc if !flag(tests) Buildable: False else - Ghc-Options: -Wall + if impl(ghc >= 6.12) + Ghc-Options: -O2 -Wall -fno-warn-unused-do-bind + else + Ghc-Options: -O2 -Wall Extensions: CPP Build-Depends: base >= 4 && < 5, Diff, test-framework, test-framework-hunit, HUnit Other-Modules: Text.Pandoc.Shared, Text.Pandoc.Highlighting, Text.Pandoc.Writers.Native diff --git a/tests/Helpers.hs b/tests/Helpers.hs new file mode 100644 index 000000000..c61207153 --- /dev/null +++ b/tests/Helpers.hs @@ -0,0 +1,37 @@ +module Helpers where + +import Text.Pandoc + +import Test.Framework +import Test.Framework.Providers.HUnit +import Test.HUnit hiding (Test) + +data Expect = Inline Inline + | Inlines [Inline] + | Block Block + | Blocks [Block] + +assertPandoc :: Expect -> Pandoc -> Assertion +assertPandoc (Inline e) (Pandoc _ [Para [g]]) = e @=? g +assertPandoc (Inlines e) (Pandoc _ [Para g] ) = e @=? g +assertPandoc (Block e) (Pandoc _ [g] ) = e @=? g +assertPandoc (Blocks e) (Pandoc _ g ) = e @=? g +assertPandoc _ _ = assertFailure "Wrong structur of Pandoc document." + +latexTest :: String-> String -> Expect -> Test +latexTest = latexTestWithState defaultParserState + +latexTestWithState :: ParserState -> String -> String -> Expect -> Test +latexTestWithState state name string exp = testCase name $ exp `assertPandoc` readLaTeX state string + +blocks :: [Block] -> Pandoc +blocks bs = Pandoc (Meta { docTitle = [], docAuthors = [], docDate = [] }) bs + +block :: Block -> Pandoc +block b = blocks [b] + +inlines :: [Inline] -> Pandoc +inlines is = block $ Para is + +inline :: Inline -> Pandoc +inline i = inlines [i] diff --git a/tests/Latex/Reader.hs b/tests/Latex/Reader.hs new file mode 100644 index 000000000..d313b33eb --- /dev/null +++ b/tests/Latex/Reader.hs @@ -0,0 +1,35 @@ +module Latex.Reader (tests) where + +import Text.Pandoc.Definition + +import Test.Framework +import Helpers + +tests :: [Test] +tests = [ testGroup "basic" [ latexTest "simplest" "word" + (Inline $ Str "word") + + , latexTest "space" "some text" + (Inlines $ [Str "some", Space, Str "text"]) + + , latexTest "emphasis" "\\emph{emphasized}" + (Inline $ Emph [Str "emphasized"]) + ] + + , testGroup "headers" [ latexTest "1. level" "\\section{header}" + $ Block $ Header 1 [Str "header"] + + , latexTest "2. level" "\\subsection{header}" + $ Block $ Header 2 [Str "header"] + + , latexTest "3. level" "\\subsubsection{header}" + $ Block $ Header 3 [Str "header"] + + , latexTest "with emphasis" "\\section{text \\emph{emph}}" + $ Block $ Header 1 [Str "text", Space, Emph [Str "emph"]] + + , latexTest "with link" "\\section{text \\href{/url}{link}}" + $ Block $ Header 1 [Str "text", Space, Link [Str "link"] ("/url", "")] + ] + ] + diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs index ae367fc53..cf7a7e5e4 100644 --- a/tests/test-pandoc.hs +++ b/tests/test-pandoc.hs @@ -5,9 +5,12 @@ module Main where import Test.Framework import qualified Old +import qualified Latex.Reader tests :: [Test] tests = [ testGroup "Old" Old.tests + , testGroup "Latex" [ testGroup "Reader" Latex.Reader.tests + ] ] main :: IO () From ff74c51b532f05303343b4c9de3a8c392298c014 Mon Sep 17 00:00:00 2001 From: Nathan Gass <gass@search.ch> Date: Wed, 12 Jan 2011 14:44:32 +0100 Subject: [PATCH 15/28] Remove some accidentally commited functions. Fixed a type and alignment. --- tests/Helpers.hs | 19 ++++--------------- 1 file changed, 4 insertions(+), 15 deletions(-) diff --git a/tests/Helpers.hs b/tests/Helpers.hs index c61207153..a8732fa7a 100644 --- a/tests/Helpers.hs +++ b/tests/Helpers.hs @@ -12,11 +12,11 @@ data Expect = Inline Inline | Blocks [Block] assertPandoc :: Expect -> Pandoc -> Assertion -assertPandoc (Inline e) (Pandoc _ [Para [g]]) = e @=? g +assertPandoc (Inline e) (Pandoc _ [Para [g]]) = e @=? g assertPandoc (Inlines e) (Pandoc _ [Para g] ) = e @=? g -assertPandoc (Block e) (Pandoc _ [g] ) = e @=? g -assertPandoc (Blocks e) (Pandoc _ g ) = e @=? g -assertPandoc _ _ = assertFailure "Wrong structur of Pandoc document." +assertPandoc (Block e) (Pandoc _ [g] ) = e @=? g +assertPandoc (Blocks e) (Pandoc _ g ) = e @=? g +assertPandoc _ _ = assertFailure "Wrong structure of Pandoc document." latexTest :: String-> String -> Expect -> Test latexTest = latexTestWithState defaultParserState @@ -24,14 +24,3 @@ latexTest = latexTestWithState defaultParserState latexTestWithState :: ParserState -> String -> String -> Expect -> Test latexTestWithState state name string exp = testCase name $ exp `assertPandoc` readLaTeX state string -blocks :: [Block] -> Pandoc -blocks bs = Pandoc (Meta { docTitle = [], docAuthors = [], docDate = [] }) bs - -block :: Block -> Pandoc -block b = blocks [b] - -inlines :: [Inline] -> Pandoc -inlines is = block $ Para is - -inline :: Inline -> Pandoc -inline i = inlines [i] From a2f562719d858f56dbbcdf783900cde6a41d01df Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Wed, 12 Jan 2011 08:17:38 -0800 Subject: [PATCH 16/28] Updated lhs tests for new positioning of <title>. --- tests/lhs-test.html | 2 +- tests/lhs-test.html+lhs | 2 +- tests/lhs-test.nohl.html | 2 +- tests/lhs-test.nohl.html+lhs | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/tests/lhs-test.html b/tests/lhs-test.html index 5a0f27af7..2c4bedc00 100644 --- a/tests/lhs-test.html +++ b/tests/lhs-test.html @@ -1,9 +1,9 @@ <!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> <html xmlns="http://www.w3.org/1999/xhtml"> <head> - <title></title> <meta http-equiv="Content-Type" content="text/html; charset=utf-8" /> <meta name="generator" content="pandoc" /> + <title></title> <style type="text/css"> table.sourceCode, tr.sourceCode, td.lineNumbers, td.sourceCode, table.sourceCode pre { margin: 0; padding: 0; border: 0; vertical-align: baseline; border: none; } diff --git a/tests/lhs-test.html+lhs b/tests/lhs-test.html+lhs index d5a7b8196..536490af5 100644 --- a/tests/lhs-test.html+lhs +++ b/tests/lhs-test.html+lhs @@ -1,9 +1,9 @@ <!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> <html xmlns="http://www.w3.org/1999/xhtml"> <head> - <title></title> <meta http-equiv="Content-Type" content="text/html; charset=utf-8" /> <meta name="generator" content="pandoc" /> + <title></title> <style type="text/css"> table.sourceCode, tr.sourceCode, td.lineNumbers, td.sourceCode, table.sourceCode pre { margin: 0; padding: 0; border: 0; vertical-align: baseline; border: none; } diff --git a/tests/lhs-test.nohl.html b/tests/lhs-test.nohl.html index feee89d4e..cb03679f3 100644 --- a/tests/lhs-test.nohl.html +++ b/tests/lhs-test.nohl.html @@ -1,9 +1,9 @@ <!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> <html xmlns="http://www.w3.org/1999/xhtml"> <head> - <title></title> <meta http-equiv="Content-Type" content="text/html; charset=utf-8" /> <meta name="generator" content="pandoc" /> + <title></title> </head> <body> <h1 id="lhs-test" diff --git a/tests/lhs-test.nohl.html+lhs b/tests/lhs-test.nohl.html+lhs index ec364e796..8b972a044 100644 --- a/tests/lhs-test.nohl.html+lhs +++ b/tests/lhs-test.nohl.html+lhs @@ -1,9 +1,9 @@ <!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd"> <html xmlns="http://www.w3.org/1999/xhtml"> <head> - <title></title> <meta http-equiv="Content-Type" content="text/html; charset=utf-8" /> <meta name="generator" content="pandoc" /> + <title></title> </head> <body> <h1 id="lhs-test" From 3ebfcd0ceaccfb7ee0d7c4d2310890e08919e303 Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Wed, 12 Jan 2011 08:29:13 -0800 Subject: [PATCH 17/28] Added line numbers to diff output in tests. --- tests/Old.hs | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/tests/Old.hs b/tests/Old.hs index af8cbbe3c..1d9540fdd 100644 --- a/tests/Old.hs +++ b/tests/Old.hs @@ -17,6 +17,7 @@ import Text.Pandoc.Highlighting ( languages ) import Prelude hiding ( readFile ) import qualified Data.ByteString.Lazy as B import Data.ByteString.Lazy.UTF8 (toString) +import Text.Printf readFileUTF8 :: FilePath -> IO String readFileUTF8 f = B.readFile f >>= return . toString @@ -33,13 +34,13 @@ instance Show TestResult where show TestPassed = "PASSED" show (TestError ec) = "ERROR " ++ show ec show (TestFailed cmd file d) = "\n--- " ++ file ++ - "\n+++ " ++ cmd ++ "\n" ++ showDiff d + "\n+++ " ++ cmd ++ "\n" ++ showDiff (1,1) d -showDiff :: [(DI, String)] -> String -showDiff [] = "" -showDiff ((F, ln) : ds) = "+ " ++ ln ++ "\n" ++ showDiff ds -showDiff ((S, ln) : ds) = "- " ++ ln ++ "\n" ++ showDiff ds -showDiff ((B, _ ) : ds) = showDiff ds +showDiff :: (Int,Int) -> [(DI, String)] -> String +showDiff _ [] = "" +showDiff (l,r) ((F, ln) : ds) = printf "%4d +" l ++ ln ++ "\n" ++ showDiff (l+1,r) ds +showDiff (l,r) ((S, ln) : ds) = printf "%4d -" r ++ ln ++ "\n" ++ showDiff (l,r+1) ds +showDiff (l,r) ((B, _ ) : ds) = showDiff (l+1,r+1) ds tests :: [Test] tests = [ testGroup "markdown" [ testGroup "writer" (writerTests "markdown" ++ lhsWriterTests "markdown") From e9f1de639d80330b940c1b733a94bd9bf2ac8631 Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Wed, 12 Jan 2011 09:59:06 -0800 Subject: [PATCH 18/28] test diff output: put +/- at beginning of line. --- tests/Old.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/tests/Old.hs b/tests/Old.hs index 1d9540fdd..ef04f4a4e 100644 --- a/tests/Old.hs +++ b/tests/Old.hs @@ -38,9 +38,12 @@ instance Show TestResult where showDiff :: (Int,Int) -> [(DI, String)] -> String showDiff _ [] = "" -showDiff (l,r) ((F, ln) : ds) = printf "%4d +" l ++ ln ++ "\n" ++ showDiff (l+1,r) ds -showDiff (l,r) ((S, ln) : ds) = printf "%4d -" r ++ ln ++ "\n" ++ showDiff (l,r+1) ds -showDiff (l,r) ((B, _ ) : ds) = showDiff (l+1,r+1) ds +showDiff (l,r) ((F, ln) : ds) = + printf "+%4d " l ++ ln ++ "\n" ++ showDiff (l+1,r) ds +showDiff (l,r) ((S, ln) : ds) = + printf "-%4d " r ++ ln ++ "\n" ++ showDiff (l,r+1) ds +showDiff (l,r) ((B, _ ) : ds) = + showDiff (l+1,r+1) ds tests :: [Test] tests = [ testGroup "markdown" [ testGroup "writer" (writerTests "markdown" ++ lhsWriterTests "markdown") From e61348dc11f743289e9cb8cb4981eaba1d4fccdc Mon Sep 17 00:00:00 2001 From: Nathan Gass <gass@search.ch> Date: Wed, 12 Jan 2011 19:10:56 +0100 Subject: [PATCH 19/28] Reordered test files. --- tests/{ => Tests}/Old.hs | 2 +- tests/{Latex/Reader.hs => Tests/Readers/LaTeX.hs} | 4 ++-- tests/{Helpers.hs => Tests/Shared.hs} | 2 +- tests/test-pandoc.hs | 10 +++++----- 4 files changed, 9 insertions(+), 9 deletions(-) rename tests/{ => Tests}/Old.hs (99%) rename tests/{Latex/Reader.hs => Tests/Readers/LaTeX.hs} (95%) rename tests/{Helpers.hs => Tests/Shared.hs} (97%) diff --git a/tests/Old.hs b/tests/Tests/Old.hs similarity index 99% rename from tests/Old.hs rename to tests/Tests/Old.hs index 1d9540fdd..c7dca6ec1 100644 --- a/tests/Old.hs +++ b/tests/Tests/Old.hs @@ -1,5 +1,5 @@ -module Old (tests) where +module Tests.Old (tests) where import Test.Framework (testGroup, Test ) import Test.Framework.Providers.HUnit diff --git a/tests/Latex/Reader.hs b/tests/Tests/Readers/LaTeX.hs similarity index 95% rename from tests/Latex/Reader.hs rename to tests/Tests/Readers/LaTeX.hs index d313b33eb..58a27f09b 100644 --- a/tests/Latex/Reader.hs +++ b/tests/Tests/Readers/LaTeX.hs @@ -1,9 +1,9 @@ -module Latex.Reader (tests) where +module Tests.Readers.LaTeX (tests) where import Text.Pandoc.Definition import Test.Framework -import Helpers +import Tests.Shared tests :: [Test] tests = [ testGroup "basic" [ latexTest "simplest" "word" diff --git a/tests/Helpers.hs b/tests/Tests/Shared.hs similarity index 97% rename from tests/Helpers.hs rename to tests/Tests/Shared.hs index a8732fa7a..3cf8d5689 100644 --- a/tests/Helpers.hs +++ b/tests/Tests/Shared.hs @@ -1,4 +1,4 @@ -module Helpers where +module Tests.Shared where import Text.Pandoc diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs index cf7a7e5e4..b67998177 100644 --- a/tests/test-pandoc.hs +++ b/tests/test-pandoc.hs @@ -4,13 +4,13 @@ module Main where import Test.Framework -import qualified Old -import qualified Latex.Reader +import qualified Tests.Old +import qualified Tests.Readers.LaTeX tests :: [Test] -tests = [ testGroup "Old" Old.tests - , testGroup "Latex" [ testGroup "Reader" Latex.Reader.tests - ] +tests = [ testGroup "Old" Tests.Old.tests + , testGroup "Readers" [ testGroup "LaTeX" Tests.Readers.LaTeX.tests + ] ] main :: IO () From 6fbd446cbef4021838c7101e27a6737ca0713efd Mon Sep 17 00:00:00 2001 From: Nathan Gass <gass@search.ch> Date: Wed, 12 Jan 2011 19:11:11 +0100 Subject: [PATCH 20/28] Removed copy-pasted -O2. --- pandoc.cabal | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/pandoc.cabal b/pandoc.cabal index da855a07d..30cbf190f 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -299,9 +299,9 @@ Executable test-pandoc Buildable: False else if impl(ghc >= 6.12) - Ghc-Options: -O2 -Wall -fno-warn-unused-do-bind + Ghc-Options: -Wall -fno-warn-unused-do-bind else - Ghc-Options: -O2 -Wall + Ghc-Options: -Wall Extensions: CPP Build-Depends: base >= 4 && < 5, Diff, test-framework, test-framework-hunit, HUnit Other-Modules: Text.Pandoc.Shared, Text.Pandoc.Highlighting, Text.Pandoc.Writers.Native From 2dadb67b25638a8e51effdae09c6534562f2920e Mon Sep 17 00:00:00 2001 From: Nathan Gass <gass@search.ch> Date: Wed, 12 Jan 2011 19:32:26 +0100 Subject: [PATCH 21/28] Generalized latexTestWithState to readerTestWithState. --- tests/Tests/Shared.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/tests/Tests/Shared.hs b/tests/Tests/Shared.hs index 3cf8d5689..f5b13986d 100644 --- a/tests/Tests/Shared.hs +++ b/tests/Tests/Shared.hs @@ -19,8 +19,8 @@ assertPandoc (Blocks e) (Pandoc _ g ) = e @=? g assertPandoc _ _ = assertFailure "Wrong structure of Pandoc document." latexTest :: String-> String -> Expect -> Test -latexTest = latexTestWithState defaultParserState +latexTest = readerTestWithState defaultParserState readLaTeX -latexTestWithState :: ParserState -> String -> String -> Expect -> Test -latexTestWithState state name string exp = testCase name $ exp `assertPandoc` readLaTeX state string +readerTestWithState :: ParserState -> (ParserState -> String -> Pandoc) -> String -> String -> Expect -> Test +readerTestWithState state reader name string exp = testCase name $ exp `assertPandoc` reader state string From 99c361d2b433a90525e3dea002cd8700e6596a09 Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Thu, 13 Jan 2011 10:58:58 -0800 Subject: [PATCH 22/28] Fixed bug in markdown-citations.mhra.txt expected test output. This failing test was a test suite bug, not a pandoc or citeproc bug. --- tests/markdown-citations.mhra.txt | 2 -- 1 file changed, 2 deletions(-) diff --git a/tests/markdown-citations.mhra.txt b/tests/markdown-citations.mhra.txt index 3add1cfdd..56eb147a3 100644 --- a/tests/markdown-citations.mhra.txt +++ b/tests/markdown-citations.mhra.txt @@ -58,6 +58,4 @@ Doe, John, and Jenny Roe, ‘Why Water Is Wet’, in *Third Book*, ed by Sam Smi [^11]: Like a citation without author: First Book, and now Doe with a locator Article, 33-34 (p. 44). -[^11]: Like a citation without author: First Book, and now Doe with a locator Article, 33-34 (p. 44). - [^12]: *See* Doe, First Book, p. 32. From 4ccd30fe3ec899389e8159cc51e830c9edd9f875 Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Thu, 13 Jan 2011 10:59:44 -0800 Subject: [PATCH 23/28] Moved Tests.Shared -> Tests.Helpers. Tests.Shared would be the natural place to put tests for functions in Text.Pandoc.Shared. --- tests/Tests/{Shared.hs => Helpers.hs} | 2 +- tests/Tests/Readers/LaTeX.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) rename tests/Tests/{Shared.hs => Helpers.hs} (97%) diff --git a/tests/Tests/Shared.hs b/tests/Tests/Helpers.hs similarity index 97% rename from tests/Tests/Shared.hs rename to tests/Tests/Helpers.hs index f5b13986d..272fa16bc 100644 --- a/tests/Tests/Shared.hs +++ b/tests/Tests/Helpers.hs @@ -1,4 +1,4 @@ -module Tests.Shared where +module Tests.Helpers where import Text.Pandoc diff --git a/tests/Tests/Readers/LaTeX.hs b/tests/Tests/Readers/LaTeX.hs index 58a27f09b..093ff07e5 100644 --- a/tests/Tests/Readers/LaTeX.hs +++ b/tests/Tests/Readers/LaTeX.hs @@ -3,7 +3,7 @@ module Tests.Readers.LaTeX (tests) where import Text.Pandoc.Definition import Test.Framework -import Tests.Shared +import Tests.Helpers tests :: [Test] tests = [ testGroup "basic" [ latexTest "simplest" "word" From 75e8ab25ef003fb50a81e0aaf36997ce17b48c3c Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Thu, 13 Jan 2011 11:11:55 -0800 Subject: [PATCH 24/28] Adjusted source to 80-column limit. --- tests/Tests/Helpers.hs | 2 + tests/Tests/Old.hs | 142 ++++++++++++++++++++--------------- tests/Tests/Readers/LaTeX.hs | 41 +++++----- 3 files changed, 106 insertions(+), 79 deletions(-) diff --git a/tests/Tests/Helpers.hs b/tests/Tests/Helpers.hs index 272fa16bc..e6d3640d9 100644 --- a/tests/Tests/Helpers.hs +++ b/tests/Tests/Helpers.hs @@ -1,3 +1,5 @@ +-- Utility functions for the test suite. + module Tests.Helpers where import Text.Pandoc diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs index 3c4c9572a..7d1df3758 100644 --- a/tests/Tests/Old.hs +++ b/tests/Tests/Old.hs @@ -1,4 +1,3 @@ - module Tests.Old (tests) where import Test.Framework (testGroup, Test ) @@ -46,51 +45,62 @@ showDiff (l,r) ((B, _ ) : ds) = showDiff (l+1,r+1) ds tests :: [Test] -tests = [ testGroup "markdown" [ testGroup "writer" (writerTests "markdown" ++ lhsWriterTests "markdown") - , testGroup "reader" [ test "basic" ["-r", "markdown", "-w", "native", "-s", "-S"] - "testsuite.txt" "testsuite.native" - , test "tables" ["-r", "markdown", "-w", "native", "--columns=80"] - "tables.txt" "tables.native" - , test "more" ["-r", "markdown", "-w", "native", "-S"] - "markdown-reader-more.txt" "markdown-reader-more.native" - , lhsReaderTest "markdown+lhs" - ] - , testGroup "citations" markdownCitationTests - ] - , testGroup "rst" [ testGroup "writer" (writerTests "rst" ++ lhsWriterTests "rst") - , testGroup "reader" [ test "basic" ["-r", "rst", "-w", "native", "-s", "-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" (writerTests "latex" ++ lhsWriterTests "latex") - , testGroup "reader" [ test "basic" ["-r", "latex", "-w", "native", "-s", "-R"] - "latex-reader.latex" "latex-reader.native" - , lhsReaderTest "latex+lhs" - ] - , latexCitationTests "biblatex" - , latexCitationTests "natbib" - ] - , testGroup "html" [ testGroup "writer" (writerTests "html" ++ lhsWriterTests "html") - , test "reader" ["-r", "html", "-w", "native", "-s"] - "html-reader.html" "html-reader.native" - ] - , testGroup "s5" [ s5WriterTest "basic" ["-s"] "s5" - , s5WriterTest "fancy" ["-s","-m","-i"] "s5" - , s5WriterTest "fragment" [] "html" - , s5WriterTest "inserts" ["-s", "-H", "insert", - "-B", "insert", "-A", "insert", "-c", "main.css"] "html" - ] - , testGroup "textile" [ testGroup "writer" $ writerTests "textile" - , test "reader" ["-r", "textile", "-w", "native", "-s"] - "textile-reader.textile" "textile-reader.native" - ] - , testGroup "native" [ testGroup "writer" $ writerTests "native" - , test "reader" ["-r", "native", "-w", "native", "-s"] - "testsuite.native" "testsuite.native" - ] +tests = [ testGroup "markdown" + [ testGroup "writer" + $ writerTests "markdown" ++ lhsWriterTests "markdown" + , testGroup "reader" + [ test "basic" ["-r", "markdown", "-w", "native", "-s", "-S"] + "testsuite.txt" "testsuite.native" + , test "tables" ["-r", "markdown", "-w", "native", "--columns=80"] + "tables.txt" "tables.native" + , test "more" ["-r", "markdown", "-w", "native", "-S"] + "markdown-reader-more.txt" "markdown-reader-more.native" + , lhsReaderTest "markdown+lhs" + ] + , testGroup "citations" markdownCitationTests + ] + , testGroup "rst" + [ testGroup "writer" (writerTests "rst" ++ lhsWriterTests "rst") + , testGroup "reader" + [ test "basic" ["-r", "rst", "-w", "native", + "-s", "-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" (writerTests "latex" ++ lhsWriterTests "latex") + , testGroup "reader" + [ test "basic" ["-r", "latex", "-w", "native", "-s", "-R"] + "latex-reader.latex" "latex-reader.native" + , lhsReaderTest "latex+lhs" + ] + , latexCitationTests "biblatex" + , latexCitationTests "natbib" + ] + , testGroup "html" + [ testGroup "writer" (writerTests "html" ++ lhsWriterTests "html") + , test "reader" ["-r", "html", "-w", "native", "-s"] + "html-reader.html" "html-reader.native" + ] + , testGroup "s5" + [ s5WriterTest "basic" ["-s"] "s5" + , s5WriterTest "fancy" ["-s","-m","-i"] "s5" + , s5WriterTest "fragment" [] "html" + , s5WriterTest "inserts" ["-s", "-H", "insert", + "-B", "insert", "-A", "insert", "-c", "main.css"] "html" + ] + , testGroup "textile" + [ testGroup "writer" $ writerTests "textile" + , test "reader" ["-r", "textile", "-w", "native", "-s"] + "textile-reader.textile" "textile-reader.native" + ] + , testGroup "native" + [ testGroup "writer" $ writerTests "native" + , test "reader" ["-r", "native", "-w", "native", "-s"] + "testsuite.native" "testsuite.native" + ] , testGroup "other writers" $ map (\f -> testGroup f $ writerTests f) [ "docbook", "opendocument" , "context" , "texinfo" , "man" , "plain" , "mediawiki", "rtf", "org" @@ -108,26 +118,31 @@ 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" <.> ext 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 = - testWithNormalize normalizer "lhs" ["-r", format, "-w", "native"] ("lhs-test" <.> format) "lhs-test.native" + testWithNormalize normalizer "lhs" ["-r", format, "-w", "native"] + ("lhs-test" <.> format) "lhs-test.native" where normalizer = writeNative defaultWriterOptions . normalize . read latexCitationTests :: String -> Test latexCitationTests n = testGroup (n ++ " citations") - [ t ("latex reader (" ++ n ++ " citations)") (["-r", "latex", "-w", "markdown", "-s", "--no-wrap"] ++ o) + [ t ("latex reader (" ++ n ++ " citations)") + (["-r", "latex", "-w", "markdown", "-s", "--no-wrap"] ++ o) f "markdown-citations.txt" - , t ("latex writer (" ++ n ++ " citations)") (["-r", "markdown", "-w", "latex", "-s", "--no-wrap"] ++ o) + , t ("latex writer (" ++ n ++ " citations)") + (["-r", "markdown", "-w", "latex", "-s", "--no-wrap"] ++ o) "markdown-citations.txt" f ] where - o = ["--bibliography", "biblio.bib", "--csl", "chicago-author-date.csl", "--no-citeproc", "--" ++ n] + o = ["--bibliography", "biblio.bib", "--csl", "chicago-author-date.csl", + "--no-citeproc", "--" ++ n] f = n ++ "-citations.latex" normalizer = substitute "\160" " " . substitute "\8211" "-" t = testWithNormalize normalizer @@ -142,18 +157,22 @@ writerTests format s5WriterTest :: String -> [String] -> String -> Test s5WriterTest modifier opts format - = test (format ++ " writer (" ++ modifier ++ ")") (["-r", "native", "-w", format] ++ opts) + = test (format ++ " writer (" ++ modifier ++ ")") + (["-r", "native", "-w", format] ++ opts) "s5.native" ("s5." ++ modifier <.> "html") markdownCitationTests :: [Test] markdownCitationTests = map styleToTest ["chicago-author-date","ieee","mhra"] - ++ [test "no-citeproc" wopts "markdown-citations.txt" "markdown-citations.txt"] + ++ [test "no-citeproc" wopts "markdown-citations.txt" + "markdown-citations.txt"] where - ropts = ["-r", "markdown", "-w", "markdown", "--bibliography", "biblio.bib", "--no-wrap"] + ropts = ["-r", "markdown", "-w", "markdown", "--bibliography", + "biblio.bib", "--no-wrap"] wopts = ropts ++ ["--no-citeproc"] styleToTest style = test style (ropts ++ ["--csl", style ++ ".csl"]) - "markdown-citations.txt" ("markdown-citations." ++ style ++ ".txt") + "markdown-citations.txt" + ("markdown-citations." ++ style ++ ".txt") -- | Run a test without normalize function, return True if test passed. test :: String -- ^ Title of test @@ -177,16 +196,21 @@ testWithNormalize normalizer testname opts inp norm = testCase testname $ do let options = ["--data-dir", ".."] ++ [inpPath] ++ opts let cmd = pandocPath ++ " " ++ unwords options ph <- runProcess pandocPath options Nothing - (Just [("LANG","en_US.UTF-8"),("HOME", "./")]) Nothing (Just hOut) (Just stderr) + (Just [("LANG","en_US.UTF-8"),("HOME", "./")]) 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') . normalizer - normContents <- readFile' normPath >>= return . filter (/='\r') . normalizer + outputContents <- readFile' outputPath >>= + return . filter (/='\r') . normalizer + normContents <- readFile' normPath >>= + return . filter (/='\r') . normalizer if outputContents == normContents then return TestPassed - else return $ TestFailed cmd normPath $ getDiff (lines outputContents) (lines normContents) + else return + $ TestFailed cmd normPath + $ getDiff (lines outputContents) (lines normContents) else return $ TestError ec removeFile outputPath assertBool (show result) (result == TestPassed) diff --git a/tests/Tests/Readers/LaTeX.hs b/tests/Tests/Readers/LaTeX.hs index 093ff07e5..99ccb3fe2 100644 --- a/tests/Tests/Readers/LaTeX.hs +++ b/tests/Tests/Readers/LaTeX.hs @@ -6,30 +6,31 @@ import Test.Framework import Tests.Helpers tests :: [Test] -tests = [ testGroup "basic" [ latexTest "simplest" "word" - (Inline $ Str "word") - - , latexTest "space" "some text" - (Inlines $ [Str "some", Space, Str "text"]) - - , latexTest "emphasis" "\\emph{emphasized}" - (Inline $ Emph [Str "emphasized"]) - ] +tests = [ testGroup "basic" + [ latexTest "simplest" "word" (Inline $ Str "word") + , latexTest "space" "some text" + (Inlines $ [Str "some", Space, Str "text"]) - , testGroup "headers" [ latexTest "1. level" "\\section{header}" - $ Block $ Header 1 [Str "header"] + , latexTest "emphasis" "\\emph{emphasized}" + (Inline $ Emph [Str "emphasized"]) + ] - , latexTest "2. level" "\\subsection{header}" - $ Block $ Header 2 [Str "header"] + , testGroup "headers" + [ latexTest "1. level" "\\section{header}" + $ Block $ Header 1 [Str "header"] - , latexTest "3. level" "\\subsubsection{header}" - $ Block $ Header 3 [Str "header"] + , latexTest "2. level" "\\subsection{header}" + $ Block $ Header 2 [Str "header"] - , latexTest "with emphasis" "\\section{text \\emph{emph}}" - $ Block $ Header 1 [Str "text", Space, Emph [Str "emph"]] + , latexTest "3. level" "\\subsubsection{header}" + $ Block $ Header 3 [Str "header"] - , latexTest "with link" "\\section{text \\href{/url}{link}}" - $ Block $ Header 1 [Str "text", Space, Link [Str "link"] ("/url", "")] - ] + , latexTest "with emphasis" "\\section{text \\emph{emph}}" + $ Block $ Header 1 [Str "text", Space, Emph [Str "emph"]] + + , latexTest "with link" "\\section{text \\href{/url}{link}}" + $ Block + $ Header 1 [Str "text", Space, Link [Str "link"] ("/url", "")] + ] ] From b3fb541d0138fb97ab06e0a2a41f2f37330be557 Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Thu, 13 Jan 2011 22:31:04 -0800 Subject: [PATCH 25/28] Added Tests/Arbitrary.hs, with Arbitrary instances. --- pandoc.cabal | 8 +- tests/Tests/Arbitrary.hs | 167 +++++++++++++++++++++++++++++++++++++++ 2 files changed, 173 insertions(+), 2 deletions(-) create mode 100644 tests/Tests/Arbitrary.hs diff --git a/pandoc.cabal b/pandoc.cabal index 30cbf190f..ad304ec91 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -303,5 +303,9 @@ Executable test-pandoc else Ghc-Options: -Wall Extensions: CPP - Build-Depends: base >= 4 && < 5, Diff, test-framework, test-framework-hunit, HUnit - Other-Modules: Text.Pandoc.Shared, Text.Pandoc.Highlighting, Text.Pandoc.Writers.Native + Build-Depends: base >= 4 && < 5, Diff, test-framework, + test-framework-hunit, HUnit, QuickCheck > 2 + Other-Modules: Tests.Old + Tests.Helpers + Tests.Arbitrary + Tests.Readers.LaTeX diff --git a/tests/Tests/Arbitrary.hs b/tests/Tests/Arbitrary.hs new file mode 100644 index 000000000..bd506a44f --- /dev/null +++ b/tests/Tests/Arbitrary.hs @@ -0,0 +1,167 @@ +{-# OPTIONS_GHC -fno-warn-orphans #-} +-- provides Arbitrary instance for Pandoc types +module Tests.Arbitrary () +where +import Test.QuickCheck.Gen +import Test.QuickCheck.Arbitrary +import Control.Monad (liftM, liftM2) +import Text.Pandoc +import Text.Pandoc.Shared + +realString :: Gen String +realString = elements wordlist + +wordlist :: [String] +wordlist = ["foo","Bar","baz","\\","/",":","\"","'","féé"] + +instance Arbitrary Inline where + arbitrary = resize 3 $ arbInline 3 + +-- restrict to 3 levels of nesting max; otherwise we get +-- bogged down in indefinitely large structures +arbInline :: Int -> Gen Inline +arbInline n = frequency $ [ (60, liftM Str realString) + , (60, return Space) + , (10, liftM Code realString) + , (5, return EmDash) + , (5, return EnDash) + , (5, return Apostrophe) + , (5, return Ellipses) + ] ++ [ x | x <- nesters, n > 1] + where nesters = [ (10, liftM Emph $ listOf $ arbInline (n-1)) + , (10, liftM Strong $ listOf $ arbInline (n-1)) + , (10, liftM Strikeout $ listOf $ arbInline (n-1)) + , (10, liftM Superscript $ listOf $ arbInline (n-1)) + , (10, liftM Subscript $ listOf $ arbInline (n-1)) + , (10, liftM SmallCaps $ listOf $ arbInline (n-1)) + , (10, do x1 <- arbitrary + x2 <- listOf $ arbInline (n-1) + return $ Quoted x1 x2) + , (10, do x1 <- arbitrary + x2 <- realString + return $ Math x1 x2) + , (10, do x1 <- listOf $ arbInline (n-1) + x3 <- realString + x2 <- realString + return $ Link x1 (x2,x3)) + , (10, do x1 <- listOf $ arbInline (n-1) + x3 <- realString + x2 <- realString + return $ Image x1 (x2,x3)) + , (2, liftM Note $ resize 3 $ listOf1 arbitrary) + ] + +instance Arbitrary Block where + arbitrary = resize 3 $ arbBlock 3 + +arbBlock :: Int -> Gen Block +arbBlock n = frequency $ [ (10, liftM Plain arbitrary) + , (15, liftM Para arbitrary) + , (5, liftM2 CodeBlock arbitrary realString) + , (2, liftM RawHtml realString) + , (5, do x1 <- choose (1 :: Int, 6) + x2 <- arbitrary + return (Header x1 x2)) + , (2, return HorizontalRule) + ] ++ [x | x <- nesters, n > 0] + where nesters = [ (5, liftM BlockQuote $ listOf $ arbBlock (n-1)) + , (5, liftM2 OrderedList arbitrary + $ (listOf $ listOf $ arbBlock (n-1))) + , (5, liftM BulletList $ (listOf $ listOf $ arbBlock (n-1))) + , (5, do x1 <- listOf $ listOf $ listOf $ arbBlock (n-1) + x2 <- arbitrary + return (DefinitionList $ zip x2 x1)) + , (2, do rs <- choose (1 :: Int, 4) + cs <- choose (1 :: Int, 4) + x1 <- arbitrary + x2 <- vector cs + x3 <- vectorOf cs $ elements [0, 0.25] + x4 <- vectorOf cs $ listOf $ arbBlock (n-1) + x5 <- vectorOf rs $ vectorOf cs + $ listOf $ arbBlock (n-1) + return (Table x1 x2 x3 x4 x5)) + ] + +instance Arbitrary Pandoc where + arbitrary + = do x1 <- arbitrary + x2 <- arbitrary + return $ normalize (Pandoc x1 x2) + +{- +instance Arbitrary CitationMode where + arbitrary + = do x <- choose (0 :: Int, 2) + case x of + 0 -> return AuthorInText + 1 -> return SuppressAuthor + 2 -> return NormalCitation + _ -> error "FATAL ERROR: Arbitrary instance, logic bug" + +instance Arbitrary Citation where + arbitrary + = do x1 <- liftM (filter (`notElem` ",;]@ \t\n")) arbitrary + x2 <- arbitrary + x3 <- arbitrary + x4 <- arbitrary + x5 <- arbitrary + x6 <- arbitrary + return (Citation x1 x2 x3 x4 x5 x6) +-} + +instance Arbitrary MathType where + arbitrary + = do x <- choose (0 :: Int, 1) + case x of + 0 -> return DisplayMath + 1 -> return InlineMath + _ -> error "FATAL ERROR: Arbitrary instance, logic bug" + +instance Arbitrary QuoteType where + arbitrary + = do x <- choose (0 :: Int, 1) + case x of + 0 -> return SingleQuote + 1 -> return DoubleQuote + _ -> error "FATAL ERROR: Arbitrary instance, logic bug" + +instance Arbitrary Meta where + arbitrary + = do x1 <- arbitrary + x2 <- liftM (filter (not . null)) arbitrary + x3 <- arbitrary + return (Meta x1 x2 x3) + +instance Arbitrary Alignment where + arbitrary + = do x <- choose (0 :: Int, 3) + case x of + 0 -> return AlignLeft + 1 -> return AlignRight + 2 -> return AlignCenter + 3 -> return AlignDefault + _ -> error "FATAL ERROR: Arbitrary instance, logic bug" + +instance Arbitrary ListNumberStyle where + arbitrary + = do x <- choose (0 :: Int, 6) + case x of + 0 -> return DefaultStyle + 1 -> return Example + 2 -> return Decimal + 3 -> return LowerRoman + 4 -> return UpperRoman + 5 -> return LowerAlpha + 6 -> return UpperAlpha + _ -> error "FATAL ERROR: Arbitrary instance, logic bug" + +instance Arbitrary ListNumberDelim where + arbitrary + = do x <- choose (0 :: Int, 3) + case x of + 0 -> return DefaultDelim + 1 -> return Period + 2 -> return OneParen + 3 -> return TwoParens + _ -> error "FATAL ERROR: Arbitrary instance, logic bug" + From d41c17a2d5b3de54334eb05c60be76b468f5811f Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Fri, 14 Jan 2011 00:30:36 -0800 Subject: [PATCH 26/28] Added quickcheck tests for normalize in Shared. --- pandoc.cabal | 7 +++++-- tests/Tests/Shared.hs | 13 +++++++++++++ tests/test-pandoc.hs | 7 +++++-- 3 files changed, 23 insertions(+), 4 deletions(-) create mode 100644 tests/Tests/Shared.hs diff --git a/pandoc.cabal b/pandoc.cabal index ad304ec91..20bb6ff3d 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -303,9 +303,12 @@ Executable test-pandoc else Ghc-Options: -Wall Extensions: CPP - Build-Depends: base >= 4 && < 5, Diff, test-framework, - test-framework-hunit, HUnit, QuickCheck > 2 + Build-Depends: base >= 4 && < 5, Diff, test-framework >= 0.3 && < 0.4, + test-framework-hunit >= 0.2 && < 0.3, + test-framework-quickcheck2 >= 0.2 && < 0.3, + HUnit >= 1.2 && < 1.3, QuickCheck >= 2.3 && < 2.5 Other-Modules: Tests.Old Tests.Helpers Tests.Arbitrary + Tests.Shared Tests.Readers.LaTeX diff --git a/tests/Tests/Shared.hs b/tests/Tests/Shared.hs new file mode 100644 index 000000000..c7222c035 --- /dev/null +++ b/tests/Tests/Shared.hs @@ -0,0 +1,13 @@ +module Tests.Shared (tests) where +import Test.Framework.Providers.QuickCheck2 +import Test.Framework +import Tests.Arbitrary +import Text.Pandoc.Shared +import Text.Pandoc + +normalize_rt :: Pandoc -> Bool +normalize_rt d = normalize (normalize d) == normalize d + +tests :: [Test] +tests = [ testProperty "normalize_rt" normalize_rt ] + diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs index b67998177..9f3d65300 100644 --- a/tests/test-pandoc.hs +++ b/tests/test-pandoc.hs @@ -6,11 +6,14 @@ import Test.Framework import qualified Tests.Old import qualified Tests.Readers.LaTeX +import qualified Tests.Shared tests :: [Test] tests = [ testGroup "Old" Tests.Old.tests - , testGroup "Readers" [ testGroup "LaTeX" Tests.Readers.LaTeX.tests - ] + , testGroup "Readers" + [ testGroup "LaTeX" Tests.Readers.LaTeX.tests + ] + , testGroup "Shared" Tests.Shared.tests ] main :: IO () From 0222f367b18ac4f77ab76751792c5757c2641d51 Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Fri, 14 Jan 2011 18:01:57 -0800 Subject: [PATCH 27/28] Keep Tests.Arbitrary but remove quickcheck tests for now. Remove Tests.Shared. Remove dependency on QuickCheck. --- pandoc.cabal | 4 +--- tests/Tests/Shared.hs | 13 ------------- tests/test-pandoc.hs | 2 -- 3 files changed, 1 insertion(+), 18 deletions(-) delete mode 100644 tests/Tests/Shared.hs diff --git a/pandoc.cabal b/pandoc.cabal index 20bb6ff3d..63a6f7fa9 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -305,10 +305,8 @@ Executable test-pandoc Extensions: CPP Build-Depends: base >= 4 && < 5, Diff, test-framework >= 0.3 && < 0.4, test-framework-hunit >= 0.2 && < 0.3, - test-framework-quickcheck2 >= 0.2 && < 0.3, - HUnit >= 1.2 && < 1.3, QuickCheck >= 2.3 && < 2.5 + HUnit >= 1.2 && < 1.3 Other-Modules: Tests.Old Tests.Helpers Tests.Arbitrary - Tests.Shared Tests.Readers.LaTeX diff --git a/tests/Tests/Shared.hs b/tests/Tests/Shared.hs deleted file mode 100644 index c7222c035..000000000 --- a/tests/Tests/Shared.hs +++ /dev/null @@ -1,13 +0,0 @@ -module Tests.Shared (tests) where -import Test.Framework.Providers.QuickCheck2 -import Test.Framework -import Tests.Arbitrary -import Text.Pandoc.Shared -import Text.Pandoc - -normalize_rt :: Pandoc -> Bool -normalize_rt d = normalize (normalize d) == normalize d - -tests :: [Test] -tests = [ testProperty "normalize_rt" normalize_rt ] - diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs index 9f3d65300..316060c83 100644 --- a/tests/test-pandoc.hs +++ b/tests/test-pandoc.hs @@ -6,14 +6,12 @@ import Test.Framework import qualified Tests.Old import qualified Tests.Readers.LaTeX -import qualified Tests.Shared tests :: [Test] tests = [ testGroup "Old" Tests.Old.tests , testGroup "Readers" [ testGroup "LaTeX" Tests.Readers.LaTeX.tests ] - , testGroup "Shared" Tests.Shared.tests ] main :: IO () From dc93073804acecaf883d099ef3e1d067a29c9951 Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Fri, 14 Jan 2011 18:09:16 -0800 Subject: [PATCH 28/28] Minor code cleanup. --- tests/Tests/Helpers.hs | 12 +++++++++--- 1 file changed, 9 insertions(+), 3 deletions(-) diff --git a/tests/Tests/Helpers.hs b/tests/Tests/Helpers.hs index e6d3640d9..539b26dcd 100644 --- a/tests/Tests/Helpers.hs +++ b/tests/Tests/Helpers.hs @@ -20,9 +20,15 @@ assertPandoc (Block e) (Pandoc _ [g] ) = e @=? g assertPandoc (Blocks e) (Pandoc _ g ) = e @=? g assertPandoc _ _ = assertFailure "Wrong structure of Pandoc document." -latexTest :: String-> String -> Expect -> Test +latexTest :: String -> String -> Expect -> Test latexTest = readerTestWithState defaultParserState readLaTeX -readerTestWithState :: ParserState -> (ParserState -> String -> Pandoc) -> String -> String -> Expect -> Test -readerTestWithState state reader name string exp = testCase name $ exp `assertPandoc` reader state string +readerTestWithState :: ParserState + -> (ParserState -> String -> Pandoc) + -> String + -> String + -> Expect + -> Test +readerTestWithState state reader name string e = + testCase name $ e `assertPandoc` reader state string