Use tasty for tests rather than test-framework.

This commit is contained in:
John MacFarlane 2017-03-14 17:05:36 +01:00
parent 0b4ae3af66
commit 6ecc5b96a9
29 changed files with 137 additions and 142 deletions

View file

@ -4,14 +4,14 @@ sourcefiles=$(shell find pandoc.hs src test -name '*.hs')
BRANCH?=master
quick:
stack install --flag 'pandoc:embed_data_files' --fast --test --test-arguments='-j4'
stack install --flag 'pandoc:embed_data_files' --fast --test --test-arguments='-j4 --hide-successes'
full:
stack install --flag 'pandoc:embed_data_files' --test --test-arguments='-j4' --pedantic
stack haddock
test:
stack test --test-arguments='-j4'
stack test --flag 'pandoc:embed_data_files' --fast --test-arguments='-j4 --hide-successes'
bench:
stack bench

View file

@ -510,9 +510,9 @@ Test-Suite test-pandoc
process >= 1.2.3 && < 1.5,
skylighting >= 0.3.1 && < 0.4,
Diff >= 0.2 && < 0.4,
test-framework >= 0.3 && < 0.9,
test-framework-hunit >= 0.2 && < 0.4,
test-framework-quickcheck2 >= 0.2.9 && < 0.4,
tasty >= 0.11 && < 0.12,
tasty-hunit >= 0.9 && < 0.10,
tasty-quickcheck >= 0.8 && < 0.9,
QuickCheck >= 2.4 && < 2.10,
HUnit >= 1.2 && < 1.6,
containers >= 0.1 && < 0.6,

View file

@ -8,20 +8,20 @@ import System.Directory
import System.Exit
import System.FilePath (joinPath, splitDirectories, takeDirectory, (</>))
import System.Process
import Test.Framework
import Test.Framework.Providers.HUnit
import Test.HUnit (assertBool)
import Test.Tasty
import Test.Tasty.HUnit
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Shared (trimr)
import qualified Text.Pandoc.UTF8 as UTF8
import System.IO.Unsafe (unsafePerformIO) -- TODO temporary
-- | Run a test with normalize function, return True if test passed.
runTest :: String -- ^ Title of test
-> String -- ^ Shell command
-> String -- ^ Input text
-> String -- ^ Expected output
-> Test
-> TestTree
runTest testname cmd inp norm = testCase testname $ do
let cmd' = cmd ++ " --quiet --data-dir ../data"
let findDynlibDir [] = Nothing
@ -48,8 +48,8 @@ runTest testname cmd inp norm = testCase testname $ do
else return $ TestError ec
assertBool (show result) (result == TestPassed)
tests :: Test
tests = buildTest $ do
tests :: TestTree
tests = unsafePerformIO $ do
files <- filter (".md" `isSuffixOf`) <$>
getDirectoryContents "command"
let cmds = map extractCommandTest files
@ -67,7 +67,7 @@ dropPercent :: String -> String
dropPercent ('%':xs) = dropWhile (== ' ') xs
dropPercent xs = xs
runCommandTest :: FilePath -> (Int, String) -> IO Test
runCommandTest :: FilePath -> (Int, String) -> IO TestTree
runCommandTest pandocpath (num, code) = do
let codelines = lines code
let (continuations, r1) = span ("\\" `isSuffixOf`) codelines
@ -80,8 +80,8 @@ runCommandTest pandocpath (num, code) = do
let shcmd = trimr $ takeDirectory pandocpath </> cmd
return $ runTest ("#" ++ show num) shcmd input norm
extractCommandTest :: FilePath -> Test
extractCommandTest fp = buildTest $ do
extractCommandTest :: FilePath -> TestTree
extractCommandTest fp = unsafePerformIO $ do
pandocpath <- findPandoc
contents <- UTF8.readFile ("command" </> fp)
Pandoc _ blocks <- runIOorExplode (readMarkdown

View file

@ -8,7 +8,6 @@ module Tests.Helpers ( test
, findPandoc
, (=?>)
, purely
, property
, ToString(..)
, ToPandoc(..)
)
@ -20,11 +19,8 @@ import System.Directory
import System.Environment.Executable (getExecutablePath)
import System.Exit
import System.FilePath
import Test.Framework
import Test.Framework.Providers.HUnit
import Test.Framework.Providers.QuickCheck2
import Test.HUnit (assertBool)
import qualified Test.QuickCheck.Property as QP
import Test.Tasty
import Test.Tasty.HUnit
import Text.Pandoc.Builder (Blocks, Inlines, doc, plain)
import Text.Pandoc.Class
import Text.Pandoc.Definition
@ -37,14 +33,17 @@ test :: (ToString a, ToString b, ToString c)
=> (a -> b) -- ^ function to test
-> String -- ^ name of test case
-> (a, c) -- ^ (input, expected value)
-> Test
-> TestTree
test fn name (input, expected) =
testCase name $ assertBool msg (actual' == expected')
testCase name' $ assertBool msg (actual' == expected')
where msg = nl ++ dashes "input" ++ nl ++ input' ++ nl ++
dashes "result" ++ nl ++
unlines (map vividize diff) ++
dashes ""
nl = "\n"
name' = if length name > 54
then take 52 name ++ "..." -- avoid wide output
else name
input' = toString input
actual' = lines $ toString $ fn input
expected' = lines $ toString expected
@ -95,9 +94,6 @@ vividize (Both s _) = " " ++ s
vividize (First s) = "- " ++ s
vividize (Second s) = "+ " ++ s
property :: QP.Testable a => TestName -> a -> Test
property = testProperty
purely :: (b -> PandocPure a) -> b -> a
purely f = either (error . show) id . runPure . f

View file

@ -7,13 +7,12 @@ import System.Exit
import System.FilePath (joinPath, splitDirectories, (<.>), (</>))
import System.IO (openTempFile, stderr)
import System.Process (runProcess, waitForProcess)
import Test.Framework (Test, testGroup)
import Test.Framework.Providers.HUnit
import Test.HUnit (assertBool)
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.HUnit
import Tests.Helpers hiding (test)
import qualified Text.Pandoc.UTF8 as UTF8
tests :: [Test]
tests :: [TestTree]
tests = [ testGroup "markdown"
[ testGroup "writer"
$ writerTests "markdown" ++ lhsWriterTests "markdown"
@ -152,7 +151,7 @@ readFile' :: FilePath -> IO String
readFile' f = do s <- UTF8.readFile f
return $! (length s `seq` s)
lhsWriterTests :: String -> [Test]
lhsWriterTests :: String -> [TestTree]
lhsWriterTests format
= [ t "lhs to normal" format
, t "lhs to lhs" (format ++ "+lhs")
@ -161,7 +160,7 @@ lhsWriterTests format
t n f = test n ["--wrap=preserve", "-r", "native", "-s", "-w", f]
"lhs-test.native" ("lhs-test" <.> f)
lhsReaderTest :: String -> Test
lhsReaderTest :: String -> TestTree
lhsReaderTest format =
test "lhs" ["-r", format, "-w", "native"]
("lhs-test" <.> format) norm
@ -169,7 +168,7 @@ lhsReaderTest format =
then "lhs-test-markdown.native"
else "lhs-test.native"
writerTests :: String -> [Test]
writerTests :: String -> [TestTree]
writerTests format
= [ test "basic" (opts ++ ["-s"]) "testsuite.native" ("writer" <.> format)
, test "tables" opts "tables.native" ("tables" <.> format)
@ -178,13 +177,13 @@ writerTests format
opts = ["-r", "native", "-w", format, "--columns=78",
"--variable", "pandoc-version="]
s5WriterTest :: String -> [String] -> String -> Test
s5WriterTest :: String -> [String] -> String -> TestTree
s5WriterTest modifier opts format
= test (format ++ " writer (" ++ modifier ++ ")")
(["-r", "native", "-w", format] ++ opts)
"s5.native" ("s5-" ++ modifier <.> "html")
fb2WriterTest :: String -> [String] -> String -> String -> Test
fb2WriterTest :: String -> [String] -> String -> String -> TestTree
fb2WriterTest title opts inputfile normfile =
testWithNormalize (ignoreBinary . formatXML)
title (["-t", "fb2"]++opts) inputfile normfile
@ -202,7 +201,7 @@ test :: String -- ^ Title of test
-> [String] -- ^ Options to pass to pandoc
-> String -- ^ Input filepath
-> FilePath -- ^ Norm (for test results) filepath
-> Test
-> TestTree
test = testWithNormalize id
-- | Run a test with normalize function, return True if test passed.
@ -211,7 +210,7 @@ testWithNormalize :: (String -> String) -- ^ Normalize function for output
-> [String] -- ^ Options to pass to pandoc
-> String -- ^ Input filepath
-> FilePath -- ^ Norm (for test results) filepath
-> Test
-> TestTree
testWithNormalize normalizer testname opts inp norm = testCase testname $ do
-- find pandoc executable relative to test-pandoc
-- First, try in same directory (e.g. if both in ~/.cabal/bin)

View file

@ -3,13 +3,13 @@ module Tests.Readers.Docx (tests) where
import Codec.Archive.Zip
import qualified Data.ByteString.Lazy as B
import qualified Data.Map as M
import Test.Framework
import Test.Framework.Providers.HUnit
import Test.HUnit (assertBool)
import Test.Tasty
import Test.Tasty.HUnit
import Tests.Helpers
import Text.Pandoc
import qualified Text.Pandoc.Class as P
import Text.Pandoc.MediaBag (MediaBag, lookupMedia, mediaDirectory)
import System.IO.Unsafe -- TODO temporary
-- We define a wrapper around pandoc that doesn't normalize in the
-- tests. Since we do our own normalization, we want to make sure
@ -45,30 +45,30 @@ compareOutput opts docxFile nativeFile = do
df' <- runIOorExplode $ readNative def nf
return $ (noNorm p, noNorm df')
testCompareWithOptsIO :: ReaderOptions -> String -> FilePath -> FilePath -> IO Test
testCompareWithOptsIO :: ReaderOptions -> String -> FilePath -> FilePath -> IO TestTree
testCompareWithOptsIO opts name docxFile nativeFile = do
(dp, np) <- compareOutput opts docxFile nativeFile
return $ test id name (dp, np)
testCompareWithOpts :: ReaderOptions -> String -> FilePath -> FilePath -> Test
testCompareWithOpts :: ReaderOptions -> String -> FilePath -> FilePath -> TestTree
testCompareWithOpts opts name docxFile nativeFile =
buildTest $ testCompareWithOptsIO opts name docxFile nativeFile
unsafePerformIO $ testCompareWithOptsIO opts name docxFile nativeFile
testCompare :: String -> FilePath -> FilePath -> Test
testCompare :: String -> FilePath -> FilePath -> TestTree
testCompare = testCompareWithOpts defopts
testForWarningsWithOptsIO :: ReaderOptions -> String -> FilePath -> [String] -> IO Test
testForWarningsWithOptsIO :: ReaderOptions -> String -> FilePath -> [String] -> IO TestTree
testForWarningsWithOptsIO opts name docxFile expected = do
df <- B.readFile docxFile
logs <- runIOorExplode (readDocx opts df >> P.getLog)
let warns = [m | DocxParserWarning m <- logs]
return $ test id name (unlines warns, unlines expected)
testForWarningsWithOpts :: ReaderOptions -> String -> FilePath -> [String] -> Test
testForWarningsWithOpts :: ReaderOptions -> String -> FilePath -> [String] -> TestTree
testForWarningsWithOpts opts name docxFile expected =
buildTest $ testForWarningsWithOptsIO opts name docxFile expected
unsafePerformIO $ testForWarningsWithOptsIO opts name docxFile expected
-- testForWarnings :: String -> FilePath -> [String] -> Test
-- testForWarnings :: String -> FilePath -> [String] -> TestTree
-- testForWarnings = testForWarningsWithOpts defopts
getMedia :: FilePath -> FilePath -> IO (Maybe B.ByteString)
@ -100,17 +100,17 @@ compareMediaBagIO docxFile = do
(mediaDirectory mb)
return $ and bools
testMediaBagIO :: String -> FilePath -> IO Test
testMediaBagIO :: String -> FilePath -> IO TestTree
testMediaBagIO name docxFile = do
outcome <- compareMediaBagIO docxFile
return $ testCase name (assertBool
("Media didn't match media bag in file " ++ docxFile)
outcome)
testMediaBag :: String -> FilePath -> Test
testMediaBag name docxFile = buildTest $ testMediaBagIO name docxFile
testMediaBag :: String -> FilePath -> TestTree
testMediaBag name docxFile = unsafePerformIO $ testMediaBagIO name docxFile
tests :: [Test]
tests :: [TestTree]
tests = [ testGroup "inlines"
[ testCompare
"font formatting"

View file

@ -1,9 +1,8 @@
module Tests.Readers.EPUB (tests) where
import qualified Data.ByteString.Lazy as BL
import Test.Framework
import Test.Framework.Providers.HUnit
import Test.HUnit (assertBool)
import Test.Tasty
import Test.Tasty.HUnit
import qualified Text.Pandoc.Class as P
import Text.Pandoc.MediaBag (MediaBag, mediaDirectory)
import Text.Pandoc.Options
@ -30,7 +29,7 @@ featuresBag = [("img/check.gif","image/gif",1340)
,("img/multiscripts_and_greek_alphabet.png","image/png",10060)
]
tests :: [Test]
tests :: [TestTree]
tests =
[ testGroup "EPUB Mediabag"
[ testCase "features bag"

View file

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Readers.HTML (tests) where
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@ -10,7 +10,7 @@ import Text.Pandoc.Builder
html :: String -> Pandoc
html = purely $ readHtml def
tests :: [Test]
tests :: [TestTree]
tests = [ testGroup "base tag"
[ test html "simple" $
"<head><base href=\"http://www.w3schools.com/images/foo\" ></head><body><img src=\"stickman.gif\" alt=\"Stickman\"></head>" =?>

View file

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Readers.LaTeX (tests) where
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@ -13,14 +13,14 @@ latex = purely $ readLaTeX def{
infix 4 =:
(=:) :: ToString c
=> String -> (String, c) -> Test
=> String -> (String, c) -> TestTree
(=:) = test latex
simpleTable' :: [Alignment] -> [[Blocks]] -> Blocks
simpleTable' aligns = table "" (zip aligns (repeat 0.0))
(map (const mempty) aligns)
tests :: [Test]
tests :: [TestTree]
tests = [ testGroup "basic"
[ "simple" =:
"word" =?> para "word"
@ -128,7 +128,7 @@ baseCitation = Citation{ citationId = "item1"
rt :: String -> Inlines
rt = rawInline "latex"
natbibCitations :: Test
natbibCitations :: TestTree
natbibCitations = testGroup "natbib"
[ "citet" =: "\\citet{item1}"
=?> para (cite [baseCitation] (rt "\\citet{item1}"))
@ -175,7 +175,7 @@ natbibCitations = testGroup "natbib"
Strong [Str "32"]] }] (rt "\\citep[\\emph{see}][p. \\textbf{32}]{item1}"))
]
biblatexCitations :: Test
biblatexCitations :: TestTree
biblatexCitations = testGroup "biblatex"
[ "textcite" =: "\\textcite{item1}"
=?> para (cite [baseCitation] (rt "\\textcite{item1}"))

View file

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Readers.Markdown (tests) where
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@ -25,10 +25,10 @@ markdownGH = purely $ readMarkdown def {
infix 4 =:
(=:) :: ToString c
=> String -> (String, c) -> Test
=> String -> (String, c) -> TestTree
(=:) = test markdown
testBareLink :: (String, Inlines) -> Test
testBareLink :: (String, Inlines) -> TestTree
testBareLink (inp, ils) =
test (purely $ readMarkdown def{ readerExtensions =
extensionsFromList [Ext_autolink_bare_uris, Ext_raw_html] })
@ -142,7 +142,7 @@ p_markdown_round_trip b = matches d' d''
matches x y = x == y
-}
tests :: [Test]
tests :: [TestTree]
tests = [ testGroup "inline code"
[ "with attribute" =:
"`document.write(\"Hello\");`{.javascript}"

View file

@ -3,17 +3,18 @@ module Tests.Readers.Odt (tests) where
import Control.Monad (liftM)
import qualified Data.ByteString.Lazy as B
import qualified Data.Map as M
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import System.IO.Unsafe (unsafePerformIO) -- TODO temporary
defopts :: ReaderOptions
defopts = def{ readerExtensions = getDefaultExtensions "odt" }
tests :: [Test]
tests :: [TestTree]
tests = testsComparingToMarkdown ++ testsComparingToNative
testsComparingToMarkdown :: [Test]
testsComparingToMarkdown :: [TestTree]
testsComparingToMarkdown = map nameToTest namesOfTestsComparingToMarkdown
where nameToTest name = createTest
compareOdtToMarkdown
@ -23,7 +24,7 @@ testsComparingToMarkdown = map nameToTest namesOfTestsComparingToMarkdown
toOdtPath name = "odt/odt/" ++ name ++ ".odt"
toMarkdownPath name = "odt/markdown/" ++ name ++ ".md"
testsComparingToNative :: [Test]
testsComparingToNative :: [TestTree]
testsComparingToNative = map nameToTest namesOfTestsComparingToNative
where nameToTest name = createTest
compareOdtToNative
@ -77,9 +78,9 @@ compareOdtToMarkdown opts odtPath markdownPath = do
createTest :: TestCreator
-> TestName
-> FilePath -> FilePath
-> Test
-> TestTree
createTest creator name path1 path2 =
buildTest $ liftM (test id name) (creator defopts path1 path2)
unsafePerformIO $ liftM (test id name) (creator defopts path1 path2)
{-
--
@ -113,14 +114,14 @@ compareMediaBagIO odtFile = do
(mediaDirectory mb)
return $ and bools
testMediaBagIO :: String -> FilePath -> IO Test
testMediaBagIO :: String -> FilePath -> IO TestTree
testMediaBagIO name odtFile = do
outcome <- compareMediaBagIO odtFile
return $ testCase name (assertBool
("Media didn't match media bag in file " ++ odtFile)
outcome)
testMediaBag :: String -> FilePath -> Test
testMediaBag :: String -> FilePath -> TestTree
testMediaBag name odtFile = buildTest $ testMediaBagIO name odtFile
-}
--

View file

@ -2,7 +2,7 @@
module Tests.Readers.Org (tests) where
import Data.List (intersperse)
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Builder
@ -16,7 +16,7 @@ orgSmart = purely $ readOrg def { readerExtensions =
infix 4 =:
(=:) :: ToString c
=> String -> (String, c) -> Test
=> String -> (String, c) -> TestTree
(=:) = test org
spcSep :: [Inlines] -> Inlines
@ -28,7 +28,7 @@ simpleTable' :: Int
-> Blocks
simpleTable' n = table "" (take n $ repeat (AlignDefault, 0.0))
tests :: [Test]
tests :: [TestTree]
tests =
[ testGroup "Inlines" $
[ "Plain String" =:

View file

@ -2,7 +2,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
module Tests.Readers.RST (tests) where
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@ -13,10 +13,10 @@ rst = purely $ readRST def{ readerStandalone = True }
infix 4 =:
(=:) :: ToString c
=> String -> (String, c) -> Test
=> String -> (String, c) -> TestTree
(=:) = test rst
tests :: [Test]
tests :: [TestTree]
tests = [ "line block with blank line" =:
"| a\n|\n| b" =?> lineBlock [ "a", mempty, "\160b" ]
, testGroup "field list"

View file

@ -2,7 +2,7 @@
module Tests.Readers.Txt2Tags (tests) where
import Data.List (intersperse)
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@ -20,7 +20,7 @@ t2t = purely $ \s -> do
infix 4 =:
(=:) :: ToString c
=> String -> (String, c) -> Test
=> String -> (String, c) -> TestTree
(=:) = test t2t
spcSep :: [Inlines] -> Inlines
@ -32,7 +32,7 @@ simpleTable' :: Int
-> Blocks
simpleTable' n = table "" (take n $ repeat (AlignCenter, 0.0))
tests :: [Test]
tests :: [TestTree]
tests =
[ testGroup "Inlines" $
[ "Plain String" =:

View file

@ -1,14 +1,13 @@
module Tests.Shared (tests) where
import System.FilePath.Posix (joinPath)
import Test.Framework
import Test.Framework.Providers.HUnit
import Test.HUnit (assertBool, (@?=))
import Test.Tasty
import Test.Tasty.HUnit (assertBool, (@?=), testCase)
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
import Text.Pandoc.Shared
tests :: [Test]
tests :: [TestTree]
tests = [ testGroup "compactifyDL"
[ testCase "compactifyDL with empty def" $
assertBool "compactifyDL"
@ -18,7 +17,7 @@ tests = [ testGroup "compactifyDL"
, testGroup "collapseFilePath" testCollapse
]
testCollapse :: [Test]
testCollapse :: [TestTree]
testCollapse = map (testCase "collapse")
[ (collapseFilePath (joinPath [ ""]) @?= (joinPath [ ""]))
, (collapseFilePath (joinPath [ ".","foo"]) @?= (joinPath [ "foo"]))

View file

@ -1,6 +1,6 @@
module Tests.Writers.AsciiDoc (tests) where
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@ -9,7 +9,7 @@ import Text.Pandoc.Builder
asciidoc :: (ToPandoc a) => a -> String
asciidoc = purely (writeAsciiDoc def{ writerWrapText = WrapNone }) . toPandoc
tests :: [Test]
tests :: [TestTree]
tests = [ testGroup "emphasis"
[ test asciidoc "emph word before" $
para (text "foo" <> emph (text "bar")) =?>

View file

@ -1,7 +1,8 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.ConTeXt (tests) where
import Test.Framework
import Test.Tasty
import Test.Tasty.QuickCheck
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@ -27,14 +28,14 @@ which is in turn shorthand for
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
=> String -> (a, String) -> TestTree
(=:) = test context
tests :: [Test]
tests :: [TestTree]
tests = [ testGroup "inline code"
[ "with '}'" =: code "}" =?> "\\mono{\\}}"
, "without '}'" =: code "]" =?> "\\type{]}"
, property "code property" $ \s -> null s ||
, testProperty "code property" $ \s -> null s ||
if '{' `elem` s || '}' `elem` s
then (context' $ code s) == "\\mono{" ++
(context' $ str s) ++ "}"

View file

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Docbook (tests) where
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@ -27,7 +27,7 @@ which is in turn shorthand for
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
=> String -> (a, String) -> TestTree
(=:) = test docbook
lineblock :: Blocks
@ -40,7 +40,7 @@ lineblock_out = [ "<literallayout>some text"
, "and again</literallayout>"
]
tests :: [Test]
tests :: [TestTree]
tests = [ testGroup "line blocks"
[ "none" =: para "This is a test"
=?> unlines

View file

@ -1,7 +1,7 @@
module Tests.Writers.Docx (tests) where
import System.FilePath ((</>))
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc.Class (runIOorExplode)
import Text.Pandoc.Definition
@ -9,6 +9,7 @@ import Text.Pandoc.Options
import Text.Pandoc.Readers.Docx
import Text.Pandoc.Readers.Native
import Text.Pandoc.Writers.Docx
import System.IO.Unsafe (unsafePerformIO) -- TODO temporary
type Options = (WriterOptions, ReaderOptions)
@ -27,26 +28,26 @@ compareOutput opts nativeFileIn nativeFileOut = do
p <- runIOorExplode $ readDocx (snd opts) df
return (p, df')
testCompareWithOptsIO :: Options -> String -> FilePath -> FilePath -> IO Test
testCompareWithOptsIO :: Options -> String -> FilePath -> FilePath -> IO TestTree
testCompareWithOptsIO opts name nativeFileIn nativeFileOut = do
(dp, np) <- compareOutput opts nativeFileIn nativeFileOut
return $ test id name (dp, np)
testCompareWithOpts :: Options -> String -> FilePath -> FilePath -> Test
testCompareWithOpts :: Options -> String -> FilePath -> FilePath -> TestTree
testCompareWithOpts opts name nativeFileIn nativeFileOut =
buildTest $ testCompareWithOptsIO opts name nativeFileIn nativeFileOut
unsafePerformIO $ testCompareWithOptsIO opts name nativeFileIn nativeFileOut
roundTripCompareWithOpts :: Options -> String -> FilePath -> Test
roundTripCompareWithOpts :: Options -> String -> FilePath -> TestTree
roundTripCompareWithOpts opts name nativeFile =
testCompareWithOpts opts name nativeFile nativeFile
-- testCompare :: String -> FilePath -> FilePath -> Test
-- testCompare :: String -> FilePath -> FilePath -> TestTree
-- testCompare = testCompareWithOpts def
roundTripCompare :: String -> FilePath -> Test
roundTripCompare :: String -> FilePath -> TestTree
roundTripCompare = roundTripCompareWithOpts def
tests :: [Test]
tests :: [TestTree]
tests = [ testGroup "inlines"
[ roundTripCompare
"font formatting"

View file

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.HTML (tests) where
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@ -24,10 +24,10 @@ which is in turn shorthand for
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
=> String -> (a, String) -> TestTree
(=:) = test html
tests :: [Test]
tests :: [TestTree]
tests = [ testGroup "inline code"
[ "basic" =: code "@&" =?> "<code>@&amp;</code>"
, "haskell" =: codeWith ("",["haskell"],[]) ">>="

View file

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.LaTeX (tests) where
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@ -33,10 +33,10 @@ which is in turn shorthand for
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
=> String -> (a, String) -> TestTree
(=:) = test latex
tests :: [Test]
tests :: [TestTree]
tests = [ testGroup "code blocks"
[ "in footnotes" =: note (para "hi" <> codeBlock "hi") =?>
"\\footnote{hi\n\n\\begin{Verbatim}\nhi\n\\end{Verbatim}\n}"

View file

@ -2,7 +2,7 @@
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module Tests.Writers.Markdown (tests) where
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@ -31,10 +31,10 @@ which is in turn shorthand for
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
=> String -> (a, String) -> TestTree
(=:) = test markdown
tests :: [Test]
tests :: [TestTree]
tests = [ "indented code after list"
=: (orderedList [ para "one" <> para "two" ] <> codeBlock "test")
=?> "1. one\n\n two\n\n<!-- -->\n\n test"
@ -85,7 +85,7 @@ noteTestDoc =
noteTests :: Test
noteTests :: TestTree
noteTests = testGroup "note and reference location"
[ test (markdownWithOpts defopts)
"footnotes at the end of a document" $
@ -176,12 +176,12 @@ noteTests = testGroup "note and reference location"
]
shortcutLinkRefsTests :: Test
shortcutLinkRefsTests :: TestTree
shortcutLinkRefsTests =
let infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
=> String -> (a, String) -> TestTree
(=:) = test (purely (writeMarkdown defopts{writerReferenceLinks = True}) . toPandoc)
in testGroup "Shortcut reference links"
[ "Simple link (shortcutable)"

View file

@ -1,6 +1,6 @@
module Tests.Writers.Muse (tests) where
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary()
@ -14,10 +14,10 @@ museWithOpts opts = purely (writeMuse opts) . toPandoc
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
=> String -> (a, String) -> TestTree
(=:) = test muse
tests :: [Test]
tests :: [TestTree]
tests = [ testGroup "block elements"
[ "plain" =: plain (text "Foo bar.") =?> "Foo bar."
, testGroup "paragraphs"

View file

@ -1,6 +1,7 @@
module Tests.Writers.Native (tests) where
import Test.Framework
import Test.Tasty
import Test.Tasty.QuickCheck
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@ -15,8 +16,8 @@ p_write_blocks_rt bs =
read (purely (writeNative def) (Pandoc nullMeta bs)) ==
bs
tests :: [Test]
tests = [ property "p_write_rt" p_write_rt
, property "p_write_blocks_rt" $ mapSize
tests :: [TestTree]
tests = [ testProperty "p_write_rt" p_write_rt
, testProperty "p_write_blocks_rt" $ mapSize
(\x -> if x > 3 then 3 else x) $ p_write_blocks_rt
]

View file

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Org (tests) where
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@ -9,10 +9,10 @@ import Text.Pandoc.Builder
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
=> String -> (a, String) -> TestTree
(=:) = test (purely (writeOrg def . toPandoc))
tests :: [Test]
tests :: [TestTree]
tests = [ testGroup "links"
-- See http://orgmode.org/manual/Internal-links.html#Internal-links
[ "simple link"

View file

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Plain (tests) where
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@ -10,11 +10,11 @@ import Text.Pandoc.Builder
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
=> String -> (a, String) -> TestTree
(=:) = test (purely (writePlain def) . toPandoc)
tests :: [Test]
tests :: [TestTree]
tests = [ "strongly emphasized text to uppercase"
=: strong "Straße"
=?> "STRASSE"

View file

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.RST (tests) where
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@ -9,10 +9,10 @@ import Text.Pandoc.Builder
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
=> String -> (a, String) -> TestTree
(=:) = test (purely (writeRST def . toPandoc))
tests :: [Test]
tests :: [TestTree]
tests = [ testGroup "rubrics"
[ "in list item" =:
bulletList [header 2 (text "foo")] =?>

View file

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.TEI (tests) where
import Test.Framework
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@ -21,10 +21,10 @@ which is in turn shorthand for
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
=> String -> (a, String) -> TestTree
(=:) = test (purely (writeTEI def) . toPandoc)
tests :: [Test]
tests :: [TestTree]
tests = [ testGroup "block elements"
["para" =: para "Lorem ipsum cetera."
=?> "<p>Lorem ipsum cetera.</p>"

View file

@ -3,8 +3,7 @@
module Main where
import GHC.IO.Encoding
import System.Environment (getArgs)
import Test.Framework
import Test.Tasty
import qualified Tests.Command
import qualified Tests.Old
import qualified Tests.Readers.Docx
@ -32,8 +31,8 @@ import qualified Tests.Writers.TEI
import qualified Tests.Writers.Muse
import Text.Pandoc.Shared (inDirectory)
tests :: [Test]
tests = [ Tests.Command.tests
tests :: TestTree
tests = testGroup "pandoc tests" [ Tests.Command.tests
, testGroup "Old" Tests.Old.tests
, testGroup "Shared" Tests.Shared.tests
, testGroup "Writers"
@ -67,5 +66,4 @@ tests = [ Tests.Command.tests
main :: IO ()
main = do
setLocaleEncoding utf8
args <- getArgs
inDirectory "test" $ defaultMainWithArgs tests args
inDirectory "test" $ defaultMain tests