aboutsummaryrefslogtreecommitdiff
path: root/test/Tests
diff options
context:
space:
mode:
Diffstat (limited to 'test/Tests')
-rw-r--r--test/Tests/Command.hs73
-rw-r--r--test/Tests/Helpers.hs61
-rw-r--r--test/Tests/Lua.hs4
-rw-r--r--test/Tests/Lua/Module.hs4
-rw-r--r--test/Tests/Old.hs40
-rw-r--r--test/Tests/Readers/Creole.hs4
-rw-r--r--test/Tests/Readers/Docx.hs32
-rw-r--r--test/Tests/Readers/DokuWiki.hs2
-rw-r--r--test/Tests/Readers/EPUB.hs6
-rw-r--r--test/Tests/Readers/FB2.hs2
-rw-r--r--test/Tests/Readers/HTML.hs35
-rw-r--r--test/Tests/Readers/JATS.hs3
-rw-r--r--test/Tests/Readers/Jira.hs24
-rw-r--r--test/Tests/Readers/LaTeX.hs23
-rw-r--r--test/Tests/Readers/Man.hs3
-rw-r--r--test/Tests/Readers/Markdown.hs10
-rw-r--r--test/Tests/Readers/Muse.hs2
-rw-r--r--test/Tests/Readers/Odt.hs5
-rw-r--r--test/Tests/Readers/Org.hs2
-rw-r--r--test/Tests/Readers/Org/Block.hs4
-rw-r--r--test/Tests/Readers/Org/Block/CodeBlock.hs10
-rw-r--r--test/Tests/Readers/Org/Block/Figure.hs4
-rw-r--r--test/Tests/Readers/Org/Block/Header.hs4
-rw-r--r--test/Tests/Readers/Org/Block/List.hs17
-rw-r--r--test/Tests/Readers/Org/Block/Table.hs4
-rw-r--r--test/Tests/Readers/Org/Directive.hs4
-rw-r--r--test/Tests/Readers/Org/Inline.hs8
-rw-r--r--test/Tests/Readers/Org/Inline/Citation.hs44
-rw-r--r--test/Tests/Readers/Org/Inline/Note.hs4
-rw-r--r--test/Tests/Readers/Org/Inline/Smart.hs4
-rw-r--r--test/Tests/Readers/Org/Meta.hs20
-rw-r--r--test/Tests/Readers/Org/Shared.hs4
-rw-r--r--test/Tests/Readers/RST.hs4
-rw-r--r--test/Tests/Readers/Txt2Tags.hs4
-rw-r--r--test/Tests/Shared.hs4
-rw-r--r--test/Tests/Writers/AnnotatedTable.hs1
-rw-r--r--test/Tests/Writers/AsciiDoc.hs2
-rw-r--r--test/Tests/Writers/ConTeXt.hs237
-rw-r--r--test/Tests/Writers/Docbook.hs105
-rw-r--r--test/Tests/Writers/Docx.hs17
-rw-r--r--test/Tests/Writers/FB2.hs2
-rw-r--r--test/Tests/Writers/HTML.hs111
-rw-r--r--test/Tests/Writers/JATS.hs228
-rw-r--r--test/Tests/Writers/Jira.hs61
-rw-r--r--test/Tests/Writers/LaTeX.hs2
-rw-r--r--test/Tests/Writers/Markdown.hs2
-rw-r--r--test/Tests/Writers/Ms.hs2
-rw-r--r--test/Tests/Writers/Muse.hs1
-rw-r--r--test/Tests/Writers/Native.hs2
-rw-r--r--test/Tests/Writers/OOXML.hs9
-rw-r--r--test/Tests/Writers/Org.hs59
-rw-r--r--test/Tests/Writers/Plain.hs2
-rw-r--r--test/Tests/Writers/Powerpoint.hs2
-rw-r--r--test/Tests/Writers/RST.hs2
-rw-r--r--test/Tests/Writers/TEI.hs2
55 files changed, 795 insertions, 532 deletions
diff --git a/test/Tests/Command.hs b/test/Tests/Command.hs
index 522c4b3a1..539be1a1a 100644
--- a/test/Tests/Command.hs
+++ b/test/Tests/Command.hs
@@ -1,7 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{- |
Module : Tests.Command
- Copyright : © 2006-2020 John MacFarlane
+ Copyright : © 2006-2021 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley@edu>
@@ -10,19 +9,17 @@
Run commands, and test results, defined in markdown files.
-}
-module Tests.Command (findPandoc, runTest, tests)
+module Tests.Command (runTest, tests)
where
-import Prelude
import Data.Algorithm.Diff
+import System.Environment (getExecutablePath)
import qualified Data.ByteString as BS
import qualified Data.Text as T
-import Data.List (isSuffixOf, intercalate)
-import Data.Maybe (catMaybes)
+import Data.List (isSuffixOf)
import System.Directory
-import qualified System.Environment as Env
import System.Exit
-import System.FilePath (joinPath, splitDirectories, takeDirectory, (</>))
+import System.FilePath ((</>))
import System.IO (hPutStr, stderr)
import System.IO.Unsafe (unsafePerformIO)
import System.Process
@@ -34,27 +31,13 @@ import Text.Pandoc
import qualified Text.Pandoc.UTF8 as UTF8
-- | Run a test with and return output.
-execTest :: FilePath -- ^ Path to pandoc
+execTest :: String -- ^ Path to test executable
-> String -- ^ Shell command
-> String -- ^ Input text
-> IO (ExitCode, String) -- ^ Exit code and actual output
-execTest pandocpath cmd inp = do
- mldpath <- Env.lookupEnv "LD_LIBRARY_PATH"
- mdyldpath <- Env.lookupEnv "DYLD_LIBRARY_PATH"
- let findDynlibDir [] = Nothing
- findDynlibDir ("build":xs) = Just $ joinPath (reverse xs) </> "build"
- findDynlibDir (_:xs) = findDynlibDir xs
- let mbDynlibDir = findDynlibDir (reverse $ splitDirectories $
- takeDirectory $ takeWhile (/=' ') cmd)
- let dynlibEnv = [("DYLD_LIBRARY_PATH",
- intercalate ":" $ catMaybes [mbDynlibDir, mdyldpath])
- ,("LD_LIBRARY_PATH",
- intercalate ":" $ catMaybes [mbDynlibDir, mldpath])]
- let env' = dynlibEnv ++ [("PATH",takeDirectory pandocpath),("TMP","."),
- ("LANG","en_US.UTF-8"),
- ("HOME", "./"),
- ("pandoc_datadir", "..")]
- let pr = (shell cmd){ env = Just env' }
+execTest testExePath cmd inp = do
+ env' <- setupEnvironment testExePath
+ let pr = (shell (pandocToEmulate True cmd)){ env = Just env' }
(ec, out', err') <- readCreateProcessWithExitCode pr inp
-- filter \r so the tests will work on Windows machines
let out = filter (/= '\r') $ err' ++ out'
@@ -63,15 +46,23 @@ execTest pandocpath cmd inp = do
ExitSuccess -> return ()
return (ec, out)
+pandocToEmulate :: Bool -> String -> String
+pandocToEmulate True ('p':'a':'n':'d':'o':'c':cs) =
+ "test-pandoc --emulate" ++ pandocToEmulate False cs
+pandocToEmulate False ('|':' ':'p':'a':'n':'d':'o':'c':cs) =
+ "| " ++ "test-pandoc --emulate" ++ pandocToEmulate False cs
+pandocToEmulate _ (c:cs) = c : pandocToEmulate False cs
+pandocToEmulate _ [] = []
+
-- | Run a test, return True if test passed.
-runTest :: String -- ^ Title of test
- -> FilePath -- ^ Path to pandoc
+runTest :: String -- ^ Path to test executable
+ -> String -- ^ Title of test
-> String -- ^ Shell command
-> String -- ^ Input text
-> String -- ^ Expected output
-> TestTree
-runTest testname pandocpath cmd inp norm = testCase testname $ do
- (ec, out) <- execTest pandocpath cmd inp
+runTest testExePath testname cmd inp norm = testCase testname $ do
+ (ec, out) <- execTest testExePath cmd inp
result <- if ec == ExitSuccess
then
if out == norm
@@ -82,12 +73,13 @@ runTest testname pandocpath cmd inp norm = testCase testname $ do
else return $ TestError ec
assertBool (show result) (result == TestPassed)
-tests :: FilePath -> TestTree
+tests :: TestTree
{-# NOINLINE tests #-}
-tests pandocPath = unsafePerformIO $ do
+tests = unsafePerformIO $ do
files <- filter (".md" `isSuffixOf`) <$>
getDirectoryContents "command"
- let cmds = map (extractCommandTest pandocPath) files
+ testExePath <- getExecutablePath
+ let cmds = map (extractCommandTest testExePath) files
return $ testGroup "Command:" cmds
isCodeBlock :: Block -> Bool
@@ -103,7 +95,7 @@ dropPercent ('%':xs) = dropWhile (== ' ') xs
dropPercent xs = xs
runCommandTest :: FilePath -> FilePath -> Int -> String -> TestTree
-runCommandTest pandocpath fp num code =
+runCommandTest testExePath fp num code =
goldenTest testname getExpected getActual compareValues updateGolden
where
testname = "#" <> show num
@@ -116,7 +108,7 @@ runCommandTest pandocpath fp num code =
input = unlines inplines
norm = unlines normlines
getExpected = return norm
- getActual = snd <$> execTest pandocpath cmd input
+ getActual = snd <$> execTest testExePath cmd input
compareValues expected actual
| actual == expected = return Nothing
| otherwise = return $ Just $ "--- test/command/" ++ fp ++ "\n+++ " ++
@@ -128,14 +120,17 @@ runCommandTest pandocpath fp num code =
let cmdline = "% " <> cmd
let x = cmdline <> "\n" <> input <> "^D\n" <> norm
let y = cmdline <> "\n" <> input <> "^D\n" <> newnorm
- let updated = T.unpack $ T.replace (T.pack x) (T.pack y) (T.pack raw)
+ let updated = T.replace (T.pack x) (T.pack y) raw
UTF8.writeFile fp' updated
extractCommandTest :: FilePath -> FilePath -> TestTree
-extractCommandTest pandocpath fp = unsafePerformIO $ do
+extractCommandTest testExePath fp = unsafePerformIO $ do
contents <- UTF8.toText <$> BS.readFile ("command" </> fp)
Pandoc _ blocks <- runIOorExplode (readMarkdown
def{ readerExtensions = pandocExtensions } contents)
let codeblocks = map extractCode $ filter isCodeBlock blocks
- let cases = zipWith (runCommandTest pandocpath fp) [1..] codeblocks
- return $ testGroup fp cases
+ let cases = zipWith (runCommandTest testExePath fp) [1..] codeblocks
+ return $ testGroup fp
+ $ if null cases
+ then [testCase "!!" $ assertFailure "No command tests defined"]
+ else cases
diff --git a/test/Tests/Helpers.hs b/test/Tests/Helpers.hs
index c9ee6d206..a48a5894e 100644
--- a/test/Tests/Helpers.hs
+++ b/test/Tests/Helpers.hs
@@ -1,9 +1,9 @@
{-# LANGUAGE CPP #-}
-{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE TupleSections #-}
{-# LANGUAGE FlexibleInstances #-}
{- |
Module : Tests.Helpers
- Copyright : © 2006-2020 John MacFarlane
+ Copyright : © 2006-2021 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley@edu>
@@ -14,8 +14,8 @@ Utility functions for the test suite.
-}
module Tests.Helpers ( test
, TestResult(..)
+ , setupEnvironment
, showDiff
- , findPandoc
, (=?>)
, purely
, ToString(..)
@@ -23,14 +23,12 @@ module Tests.Helpers ( test
)
where
-import Prelude
import Data.Algorithm.Diff
import qualified Data.Map as M
import Data.Text (Text, unpack)
-import System.Directory
-import System.Environment.Executable (getExecutablePath)
import System.Exit
-import System.FilePath
+import System.FilePath (takeDirectory)
+import qualified System.Environment as Env
import Test.Tasty
import Test.Tasty.HUnit
import Text.Pandoc.Builder (Blocks, Inlines, doc, plain)
@@ -41,7 +39,7 @@ import Text.Pandoc.Shared (trimr)
import Text.Pandoc.Writers.Native (writeNative)
import Text.Printf
-test :: (ToString a, ToString b, ToString c)
+test :: (ToString a, ToString b, ToString c, HasCallStack)
=> (a -> b) -- ^ function to test
-> String -- ^ name of test case
-> (a, c) -- ^ (input, expected value)
@@ -63,6 +61,25 @@ test fn name (input, expected) =
dashes "" = replicate 72 '-'
dashes x = replicate (72 - length x - 5) '-' ++ " " ++ x ++ " ---"
+-- | Set up environment for pandoc command tests.
+setupEnvironment :: FilePath -> IO [(String, String)]
+setupEnvironment testExePath = do
+ mldpath <- Env.lookupEnv "LD_LIBRARY_PATH"
+ mdyldpath <- Env.lookupEnv "DYLD_LIBRARY_PATH"
+ mpdd <- Env.lookupEnv "pandoc_datadir"
+ -- Note that Cabal sets the pandoc_datadir environment variable
+ -- to point to the source directory, since otherwise getDataFilename
+ -- will look in the data directory into which pandoc will be installed
+ -- (but has not yet been). So when we spawn a new process with
+ -- pandoc, we need to make sure this environment variable is set.
+ return $ ("PATH",takeDirectory testExePath) :
+ ("TMP",".") :
+ ("LANG","en_US.UTF-8") :
+ ("HOME", "./") :
+ maybe [] ((:[]) . ("pandoc_datadir",)) mpdd ++
+ maybe [] ((:[]) . ("LD_LIBRARY_PATH",)) mldpath ++
+ maybe [] ((:[]) . ("DYLD_LIBRARY_PATH",)) mdyldpath
+
data TestResult = TestPassed
| TestError ExitCode
| TestFailed String FilePath [Diff String]
@@ -86,34 +103,6 @@ showDiff (l,r) (Second ln : ds) =
showDiff (l,r) (Both _ _ : ds) =
showDiff (l+1,r+1) ds
--- | Find pandoc executable relative to test-pandoc
-findPandoc :: IO FilePath
-findPandoc = do
- testExePath <- getExecutablePath
- let pandocDir =
- case reverse (splitDirectories (takeDirectory testExePath)) of
- -- cabalv2 with --disable-optimization
- "test-pandoc" : "build" : "noopt" : "test-pandoc" : "t" : ps
- -> joinPath (reverse ps) </>
- "x" </> "pandoc" </> "noopt" </> "build" </> "pandoc"
- -- cabalv2 without --disable-optimization
- "test-pandoc" : "build" : "test-pandoc" : "t" : ps
- -> joinPath (reverse ps) </>
- "x" </> "pandoc" </> "build" </> "pandoc"
- -- cabalv1
- "test-pandoc" : "build" : ps
- -> joinPath (reverse ps) </> "build" </> "pandoc"
- _ -> error "findPandoc: could not find pandoc executable"
- let pandocPath = pandocDir </> "pandoc"
-#ifdef _WINDOWS
- <.> "exe"
-#endif
- found <- doesFileExist pandocPath
- if found
- then return pandocPath
- else error $ "findPandoc: could not find pandoc executable at "
- ++ pandocPath
-
vividize :: Diff String -> String
vividize (Both s _) = " " ++ s
vividize (First s) = "- " ++ s
diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs
index 853375327..31c011900 100644
--- a/test/Tests/Lua.hs
+++ b/test/Tests/Lua.hs
@@ -1,9 +1,8 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{- |
Module : Tests.Lua
- Copyright : © 2017-2020 Albert Krewinkel
+ Copyright : © 2017-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
@@ -14,7 +13,6 @@ Unit and integration tests for pandoc's Lua subsystem.
-}
module Tests.Lua ( runLuaTest, tests ) where
-import Prelude
import Control.Monad (when)
import System.FilePath ((</>))
import Test.Tasty (TestTree, localOption)
diff --git a/test/Tests/Lua/Module.hs b/test/Tests/Lua/Module.hs
index e2570e87f..8be445f65 100644
--- a/test/Tests/Lua/Module.hs
+++ b/test/Tests/Lua/Module.hs
@@ -1,6 +1,6 @@
{- |
Module : Tests.Lua.Module
-Copyright : © 2019-2020 Albert Krewinkel
+Copyright : © 2019-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
@@ -25,6 +25,8 @@ tests =
("lua" </> "module" </> "pandoc-list.lua")
, testPandocLua "pandoc.mediabag"
("lua" </> "module" </> "pandoc-mediabag.lua")
+ , testPandocLua "pandoc.path"
+ ("lua" </> "module" </> "pandoc-path.lua")
, testPandocLua "pandoc.types"
("lua" </> "module" </> "pandoc-types.lua")
, testPandocLua "pandoc.util"
diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs
index aca2d05d0..ad9f249c4 100644
--- a/test/Tests/Old.hs
+++ b/test/Tests/Old.hs
@@ -1,7 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{- |
Module : Tests.Old
- Copyright : © 2006-2020 John MacFarlane
+ Copyright : © 2006-2021 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley@edu>
@@ -12,18 +11,16 @@
-}
module Tests.Old (tests) where
-import Prelude
import Data.Algorithm.Diff
-import Data.List (intercalate)
-import Data.Maybe (catMaybes)
import System.Exit
-import System.FilePath (joinPath, splitDirectories, (<.>), (</>))
-import qualified System.Environment as Env
+import System.FilePath ((<.>), (</>))
+import System.Environment (getExecutablePath)
import Text.Pandoc.Process (pipeProcess)
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.Golden.Advanced (goldenTest)
import Tests.Helpers hiding (test)
import qualified Text.Pandoc.UTF8 as UTF8
+import qualified Data.Text as T
tests :: FilePath -> [TestTree]
tests pandocPath =
@@ -58,7 +55,7 @@ tests pandocPath =
]
, testGroup "latex"
[ testGroup "writer"
- (writerTests' "latex" ++ lhsWriterTests' "latex")
+ (extWriterTests' "latex" ++ lhsWriterTests' "latex")
, testGroup "reader"
[ test' "basic" ["-r", "latex+raw_tex", "-w", "native", "-s"]
"latex-reader.latex" "latex-reader.native"
@@ -233,7 +230,7 @@ tests pandocPath =
-- makes sure file is fully closed after reading
readFile' :: FilePath -> IO String
readFile' f = do s <- UTF8.readFile f
- return $! (length s `seq` s)
+ return $! (T.length s `seq` T.unpack s)
lhsWriterTests :: FilePath -> String -> [TestTree]
lhsWriterTests pandocPath format
@@ -320,27 +317,21 @@ testWithNormalize normalizer pandocPath testname opts inp norm =
(compareValues norm options) updateGolden
where getExpected = normalizer <$> readFile' norm
getActual = do
- mldpath <- Env.lookupEnv "LD_LIBRARY_PATH"
- mdyldpath <- Env.lookupEnv "DYLD_LIBRARY_PATH"
- let mbDynlibDir = findDynlibDir (reverse $
- splitDirectories pandocPath)
- let dynlibEnv = [("DYLD_LIBRARY_PATH", intercalate ":" $ catMaybes [mbDynlibDir, mdyldpath])
- ,("LD_LIBRARY_PATH", intercalate ":" $ catMaybes [mbDynlibDir, mldpath])]
- let env = dynlibEnv ++
- [("TMP","."),("LANG","en_US.UTF-8"),("HOME", "./")]
- (ec, out) <- pipeProcess (Just env) pandocPath options mempty
+ env <- setupEnvironment pandocPath
+ (ec, out) <- pipeProcess (Just env) pandocPath
+ ("--emulate":options) mempty
if ec == ExitSuccess
then return $ filter (/='\r') . normalizer
$ UTF8.toStringLazy out
-- filter \r so the tests will work on Windows machines
else fail $ "Pandoc failed with error code " ++ show ec
- updateGolden = UTF8.writeFile norm
- options = ["--data-dir=../data","--quiet"] ++ [inp] ++ opts
+ updateGolden = UTF8.writeFile norm . T.pack
+ options = ["--quiet"] ++ [inp] ++ opts
compareValues :: FilePath -> [String] -> String -> String -> IO (Maybe String)
compareValues norm options expected actual = do
- pandocPath <- findPandoc
- let cmd = pandocPath ++ " " ++ unwords options
+ testExePath <- getExecutablePath
+ let cmd = testExePath ++ " --emulate " ++ unwords options
let dash = replicate 72 '-'
let diff = getDiff (lines actual) (lines expected)
if expected == actual
@@ -350,8 +341,3 @@ compareValues norm options expected actual = do
"\n--- " ++ norm ++
"\n+++ " ++ cmd ++ "\n" ++
showDiff (1,1) diff ++ dash
-
-findDynlibDir :: [FilePath] -> Maybe FilePath
-findDynlibDir [] = Nothing
-findDynlibDir ("build":xs) = Just $ joinPath (reverse xs) </> "build"
-findDynlibDir (_:xs) = findDynlibDir xs
diff --git a/test/Tests/Readers/Creole.hs b/test/Tests/Readers/Creole.hs
index 15b826460..3320b78e8 100644
--- a/test/Tests/Readers/Creole.hs
+++ b/test/Tests/Readers/Creole.hs
@@ -1,9 +1,8 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Creole
Copyright : © 2017 Sascha Wilde
- 2017-2020 John MacFarlane
+ 2017-2021 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : Sascha Wilde <wilde@sha-bang.de>
@@ -14,7 +13,6 @@ Tests for the creole reader.
-}
module Tests.Readers.Creole (tests) where
-import Prelude
import Data.Text (Text)
import qualified Data.Text as T
import Test.Tasty
diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs
index 12007f502..220c7d9c5 100644
--- a/test/Tests/Readers/Docx.hs
+++ b/test/Tests/Readers/Docx.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Docx
@@ -13,7 +12,6 @@ Tests for the word docx reader.
-}
module Tests.Readers.Docx (tests) where
-import Prelude
import Codec.Archive.Zip
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as B
@@ -26,7 +24,7 @@ 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 qualified Text.Pandoc.MediaBag as MB
import Text.Pandoc.UTF8 as UTF8
-- We define a wrapper around pandoc that doesn't normalize in the
@@ -93,11 +91,11 @@ getMedia :: FilePath -> FilePath -> IO (Maybe B.ByteString)
getMedia archivePath mediaPath = fmap fromEntry . findEntryByPath
("word/" ++ mediaPath) . toArchive <$> B.readFile archivePath
-compareMediaPathIO :: FilePath -> MediaBag -> FilePath -> IO Bool
+compareMediaPathIO :: FilePath -> MB.MediaBag -> FilePath -> IO Bool
compareMediaPathIO mediaPath mediaBag docxPath = do
docxMedia <- getMedia docxPath mediaPath
- let mbBS = case lookupMedia mediaPath mediaBag of
- Just (_, bs) -> bs
+ let mbBS = case MB.lookupMedia mediaPath mediaBag of
+ Just item -> MB.mediaContents item
Nothing -> error ("couldn't find " ++
mediaPath ++
" in media bag")
@@ -112,7 +110,7 @@ compareMediaBagIO docxFile = do
mb <- runIOorExplode $ readDocx defopts df >> P.getMediaBag
bools <- mapM
(\(fp, _, _) -> compareMediaPathIO fp mb docxFile)
- (mediaDirectory mb)
+ (MB.mediaDirectory mb)
return $ and bools
testMediaBagIO :: String -> FilePath -> IO TestTree
@@ -158,6 +156,10 @@ tests = [ testGroup "document"
"docx/image_vml.docx"
"docx/image_vml.native"
, testCompare
+ "VML image as object"
+ "docx/image_vml_as_object.docx"
+ "docx/image_vml_as_object.native"
+ , testCompare
"inline image in links"
"docx/inline_images.docx"
"docx/inline_images.native"
@@ -316,14 +318,30 @@ tests = [ testGroup "document"
"docx/table_with_list_cell.docx"
"docx/table_with_list_cell.native"
, testCompare
+ "a table with a header which contains rowspans greater than 1"
+ "docx/table_header_rowspan.docx"
+ "docx/table_header_rowspan.native"
+ , testCompare
"tables with one row"
"docx/table_one_row.docx"
"docx/table_one_row.native"
, testCompare
+ "tables with just one row, which is a header"
+ "docx/table_one_header_row.docx"
+ "docx/table_one_header_row.native"
+ , testCompare
"tables with variable width"
"docx/table_variable_width.docx"
"docx/table_variable_width.native"
, testCompare
+ "tables with captions which contain a Table field"
+ "docx/table_captions_with_field.docx"
+ "docx/table_captions_with_field.native"
+ , testCompare
+ "tables with captions which don't contain a Table field"
+ "docx/table_captions_no_field.docx"
+ "docx/table_captions_no_field.native"
+ , testCompare
"code block"
"docx/codeblock.docx"
"docx/codeblock.native"
diff --git a/test/Tests/Readers/DokuWiki.hs b/test/Tests/Readers/DokuWiki.hs
index d5f0c45a9..84ba86d46 100644
--- a/test/Tests/Readers/DokuWiki.hs
+++ b/test/Tests/Readers/DokuWiki.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{- |
@@ -14,7 +13,6 @@ Tests for DokuWiki reader.
-}
module Tests.Readers.DokuWiki (tests) where
-import Prelude
import Data.Text (Text)
import qualified Data.Text as T
import Test.Tasty
diff --git a/test/Tests/Readers/EPUB.hs b/test/Tests/Readers/EPUB.hs
index 700d6723d..040fc96e7 100644
--- a/test/Tests/Readers/EPUB.hs
+++ b/test/Tests/Readers/EPUB.hs
@@ -1,7 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{- |
Module : Tests.Readers.EPUB
- Copyright : © 2006-2020 John MacFarlane
+ Copyright : © 2006-2021 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.eu>
@@ -12,7 +11,6 @@ Tests for the EPUB mediabag.
-}
module Tests.Readers.EPUB (tests) where
-import Prelude
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as T
import Test.Tasty
@@ -49,7 +47,7 @@ featuresBag = [("img/check.gif","image/gif",1340)
-- with additional meta tag for cover in EPUB2 format
epub3CoverBag :: [(String, String, Int)]
-epub3CoverBag = [("wasteland-cover.jpg","image/jpeg",103477)]
+epub3CoverBag = [("wasteland-cover.jpg","image/jpeg", 16586)]
epub3NoCoverBag :: [(String, String, Int)]
epub3NoCoverBag = [("img/check.gif","image/gif",1340)
diff --git a/test/Tests/Readers/FB2.hs b/test/Tests/Readers/FB2.hs
index fbb2e2150..42054a235 100644
--- a/test/Tests/Readers/FB2.hs
+++ b/test/Tests/Readers/FB2.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{- |
Module : Tests.Readers.FB2
Copyright : © 2018-2020 Alexander Krotov
@@ -12,7 +11,6 @@ Tests for the EPUB mediabag.
-}
module Tests.Readers.FB2 (tests) where
-import Prelude
import Test.Tasty
import Tests.Helpers
import Test.Tasty.Golden (goldenVsString)
diff --git a/test/Tests/Readers/HTML.hs b/test/Tests/Readers/HTML.hs
index e4c681421..4ed1e44af 100644
--- a/test/Tests/Readers/HTML.hs
+++ b/test/Tests/Readers/HTML.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.HTML
- Copyright : © 2006-2020 John MacFarlane
+ Copyright : © 2006-2021 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
@@ -13,7 +12,6 @@ Tests for the HTML reader.
-}
module Tests.Readers.HTML (tests) where
-import Prelude
import Data.Text (Text)
import qualified Data.Text as T
import Test.Tasty
@@ -76,6 +74,12 @@ tests = [ testGroup "base tag"
[ test html "anchor without href" $ "<a name=\"anchor\"/>" =?>
plain (spanWith ("anchor",[],[]) mempty)
]
+ , testGroup "img"
+ [ test html "data-external attribute" $ "<img data-external=\"1\" src=\"http://example.com/stickman.gif\">" =?>
+ plain (imageWith ("", [], [("external", "1")]) "http://example.com/stickman.gif" "" "")
+ , test html "title" $ "<img title=\"The title\" src=\"http://example.com/stickman.gif\">" =?>
+ plain (imageWith ("", [], []) "http://example.com/stickman.gif" "The title" "")
+ ]
, testGroup "lang"
[ test html "lang on <html>" $ "<html lang=\"es\">hola" =?>
setMeta "lang" (text "es") (doc (plain (text "hola")))
@@ -101,11 +105,26 @@ tests = [ testGroup "base tag"
plain (codeWith ("",["sample"],[]) "Answer is 42")
]
, testGroup "var"
- [
- test html "inline var block" $
- "<var>result</var>" =?>
- plain (codeWith ("",["variable"],[]) "result")
- ]
+ [ test html "inline var block" $
+ "<var>result</var>" =?>
+ plain (codeWith ("",["variable"],[]) "result")
+ ]
+ , testGroup "header"
+ [ test htmlNativeDivs "<header> is parsed as a div" $
+ "<header id=\"title\">Title</header>" =?>
+ divWith ("title", mempty, mempty) (plain "Title")
+ ]
+ , testGroup "code block"
+ [ test html "attributes in pre > code element" $
+ "<pre><code id=\"a\" class=\"python\">\nprint('hi')\n</code></pre>"
+ =?>
+ codeBlockWith ("a", ["python"], []) "print('hi')"
+
+ , test html "attributes in pre take precendence" $
+ "<pre id=\"c\"><code id=\"d\">\nprint('hi mom!')\n</code></pre>"
+ =?>
+ codeBlockWith ("c", [], []) "print('hi mom!')"
+ ]
, askOption $ \(QuickCheckTests numtests) ->
testProperty "Round trip" $
withMaxSuccess (if QuickCheckTests numtests == defaultValue
diff --git a/test/Tests/Readers/JATS.hs b/test/Tests/Readers/JATS.hs
index 3c61f602f..a9c9a0586 100644
--- a/test/Tests/Readers/JATS.hs
+++ b/test/Tests/Readers/JATS.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.JATS
@@ -13,7 +12,6 @@ Tests for the JATS reader.
-}
module Tests.Readers.JATS (tests) where
-import Prelude
import Data.Text (Text)
import Test.Tasty
import Tests.Helpers
@@ -90,6 +88,7 @@ tests = [ testGroup "inline code"
"<p>\n\
\ <inline-formula><alternatives>\n\
\ <tex-math><![CDATA[\\sigma|_{\\{x\\}}]]></tex-math>\n\
+ \ </alternatives></inline-formula>\n\
\</p>"
=?> para (math "\\sigma|_{\\{x\\}}")
, test jats "math ml only" $
diff --git a/test/Tests/Readers/Jira.hs b/test/Tests/Readers/Jira.hs
index 32b8ecb7c..b7194a3b9 100644
--- a/test/Tests/Readers/Jira.hs
+++ b/test/Tests/Readers/Jira.hs
@@ -1,9 +1,8 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{- |
Module : Tests.Readers.Jira
- Copyright : © 2019-2020 Albert Krewinel
+ Copyright : © 2019-2021 Albert Krewinel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <tarleb@zeitkraut.de>
@@ -35,6 +34,9 @@ tests =
[ testGroup "para"
[ "Simple sentence" =:
"Hello, World!" =?> para "Hello, World!"
+
+ , "leading blank lines" =:
+ "\n\ntext" =?> para "text"
]
, testGroup "header"
@@ -94,6 +96,12 @@ tests =
simpleTable [para "Name"] [[para "Test"]]
]
+ , testGroup "panel"
+ [ "simple panel" =:
+ "{panel}\nInterviewer: Jane Doe{panel}\n" =?>
+ divWith ("", ["panel"], []) (para "Interviewer: Jane Doe")
+ ]
+
, testGroup "inlines"
[ "emphasis" =:
"*quid pro quo*" =?>
@@ -132,6 +140,10 @@ tests =
"[Example|https://example.org]" =?>
para (link "https://example.org" "" "Example")
+ , "URL in alias" =:
+ "[See https://example.com|https://example.com]" =?>
+ para (link "https://example.com" "" "See https://example.com")
+
, "email" =:
"[mailto:me@example.org]" =?>
para (link "mailto:me@example.org" "" "me@example.org")
@@ -155,6 +167,14 @@ tests =
, "user with description" =:
"[John Doe|~johndoe]" =?>
para (linkWith ("", ["user-account"], []) "~johndoe" "" "John Doe")
+
+ , "'smart' link" =:
+ "[x|http://example.com|smart-link]" =?>
+ para (linkWith ("", ["smart-link"], []) "http://example.com" "" "x")
+
+ , "'smart' card" =:
+ "[x|http://example.com|smart-card]" =?>
+ para (linkWith ("", ["smart-card"], []) "http://example.com" "" "x")
]
, "image" =:
diff --git a/test/Tests/Readers/LaTeX.hs b/test/Tests/Readers/LaTeX.hs
index c50c91ca1..4bda15140 100644
--- a/test/Tests/Readers/LaTeX.hs
+++ b/test/Tests/Readers/LaTeX.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.LaTeX
- Copyright : © 2006-2020 John MacFarlane
+ Copyright : © 2006-2021 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
@@ -13,14 +12,9 @@ Tests for the LaTeX reader.
-}
module Tests.Readers.LaTeX (tests) where
-import Prelude
import Data.Text (Text)
import qualified Data.Text as T
-import qualified Text.Pandoc.UTF8 as UTF8
-import Text.Pandoc.Readers.LaTeX (tokenize, untokenize)
import Test.Tasty
-import Test.Tasty.HUnit
-import Test.Tasty.QuickCheck
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@@ -49,21 +43,8 @@ simpleTable' aligns rows
where
toRow = Row nullAttr . map simpleCell
-tokUntokRt :: String -> Bool
-tokUntokRt s = untokenize (tokenize "random" t) == t
- where t = T.pack s
-
tests :: [TestTree]
-tests = [ testGroup "tokenization"
- [ testCase "tokenizer round trip on test case" $ do
- orig <- T.pack <$> UTF8.readFile "../test/latex-reader.latex"
- let new = untokenize $ tokenize "../test/latex-reader.latex"
- orig
- assertEqual "untokenize . tokenize is identity" orig new
- , testProperty "untokenize . tokenize is identity" tokUntokRt
- ]
-
- , testGroup "basic"
+tests = [ testGroup "basic"
[ "simple" =:
"word" =?> para "word"
, "space" =:
diff --git a/test/Tests/Readers/Man.hs b/test/Tests/Readers/Man.hs
index f591aa00d..d36151d58 100644
--- a/test/Tests/Readers/Man.hs
+++ b/test/Tests/Readers/Man.hs
@@ -2,7 +2,7 @@
{- |
Module : Tests.Readers.Man
Copyright : © 2018-2019 Yan Pas <yanp.bugz@gmail.com>,
- 2018-2020 John MacFarlane
+ 2018-2021 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
@@ -13,7 +13,6 @@ Tests for the Man reader.
-}
module Tests.Readers.Man (tests) where
-import Prelude
import Data.Text (Text)
import Test.Tasty
import Tests.Helpers
diff --git a/test/Tests/Readers/Markdown.hs b/test/Tests/Readers/Markdown.hs
index 3af5e2a94..f055ab197 100644
--- a/test/Tests/Readers/Markdown.hs
+++ b/test/Tests/Readers/Markdown.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Markdown
- Copyright : © 2006-2020 John MacFarlane
+ Copyright : © 2006-2021 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
@@ -13,7 +12,6 @@ Tests for the Markdown reader.
-}
module Tests.Readers.Markdown (tests) where
-import Prelude
import Data.Text (Text, unpack)
import qualified Data.Text as T
import Test.Tasty
@@ -360,7 +358,7 @@ tests = [ testGroup "inline code"
para (text "The value of the " <> math "x" <> text "\8217s and the systems\8217 condition.")
, test markdownSmart "unclosed double quote"
("**this should \"be bold**"
- =?> para (strong "this should \"be bold"))
+ =?> para (strong "this should \8220be bold"))
]
, testGroup "footnotes"
[ "indent followed by newline and flush-left text" =:
@@ -376,8 +374,8 @@ tests = [ testGroup "inline code"
, testGroup "lhs"
[ test (purely $ readMarkdown def{ readerExtensions = enableExtension
Ext_literate_haskell pandocExtensions })
- "inverse bird tracks and html" $
- "> a\n\n< b\n\n<div>\n"
+ "inverse bird tracks and html"
+ $ ("> a\n\n< b\n\n<div>\n" :: Text)
=?> codeBlockWith ("",["haskell","literate"],[]) "a"
<>
codeBlockWith ("",["haskell"],[]) "b"
diff --git a/test/Tests/Readers/Muse.hs b/test/Tests/Readers/Muse.hs
index 4ec1631e0..68bdc87b4 100644
--- a/test/Tests/Readers/Muse.hs
+++ b/test/Tests/Readers/Muse.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Muse
@@ -13,7 +12,6 @@ Tests for the Muse reader.
-}
module Tests.Readers.Muse (tests) where
-import Prelude
import Data.List (intersperse)
import Data.Monoid (Any (..))
import Data.Text (Text)
diff --git a/test/Tests/Readers/Odt.hs b/test/Tests/Readers/Odt.hs
index 14062c884..edff4fe2c 100644
--- a/test/Tests/Readers/Odt.hs
+++ b/test/Tests/Readers/Odt.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Odt
- Copyright : © 2015-2020 John MacFarlane
+ Copyright : © 2015-2021 John MacFarlane
2015 Martin Linnemann
License : GNU GPL, version 2 or above
@@ -14,7 +13,6 @@ Tests for the ODT reader.
-}
module Tests.Readers.Odt (tests) where
-import Prelude
import Control.Monad (liftM)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as B
@@ -178,6 +176,7 @@ namesOfTestsComparingToNative = [ "blockquote"
, "referenceToText"
, "simpleTable"
, "simpleTableWithCaption"
+ , "tab"
-- , "table"
, "textMixedStyles"
, "tableWithContents"
diff --git a/test/Tests/Readers/Org.hs b/test/Tests/Readers/Org.hs
index d4f7bb6dc..290bb603e 100644
--- a/test/Tests/Readers/Org.hs
+++ b/test/Tests/Readers/Org.hs
@@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Shared
- Copyright : © 2014-2020 Albert Krewinkel
+ Copyright : © 2014-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
diff --git a/test/Tests/Readers/Org/Block.hs b/test/Tests/Readers/Org/Block.hs
index 995bd0316..779563794 100644
--- a/test/Tests/Readers/Org/Block.hs
+++ b/test/Tests/Readers/Org/Block.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Org.Block
- Copyright : © 2014-2020 Albert Krewinkel
+ Copyright : © 2014-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
@@ -13,7 +12,6 @@ Tests parsing of org blocks.
-}
module Tests.Readers.Org.Block (tests) where
-import Prelude
import Test.Tasty (TestTree, testGroup)
import Tests.Helpers ((=?>))
import Tests.Readers.Org.Shared ((=:), spcSep)
diff --git a/test/Tests/Readers/Org/Block/CodeBlock.hs b/test/Tests/Readers/Org/Block/CodeBlock.hs
index adf6661ca..6b83ec6a9 100644
--- a/test/Tests/Readers/Org/Block/CodeBlock.hs
+++ b/test/Tests/Readers/Org/Block/CodeBlock.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Org.Block.CodeBlock
- Copyright : © 2014-2020 Albert Krewinkel
+ Copyright : © 2014-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
@@ -13,7 +12,6 @@ Test parsing of org code blocks.
-}
module Tests.Readers.Org.Block.CodeBlock (tests) where
-import Prelude
import Test.Tasty (TestTree)
import Tests.Helpers ((=?>))
import Tests.Readers.Org.Shared ((=:), spcSep)
@@ -185,10 +183,10 @@ tests =
, "#+end_src"
] =?>
divWith
- nullAttr
+ ("", ["captioned-content"], [] )
(mappend
- (plain $ spanWith ("", ["label"], [])
- (spcSep [ "Functor", "laws", "in", "Haskell" ]))
+ (divWith ("", ["caption"], []) $
+ plain (spcSep [ "Functor", "laws", "in", "Haskell" ]))
(codeBlockWith ("functor-laws", ["haskell"], [])
(T.unlines [ "fmap id = id"
, "fmap (p . q) = (fmap p) . (fmap q)"
diff --git a/test/Tests/Readers/Org/Block/Figure.hs b/test/Tests/Readers/Org/Block/Figure.hs
index 56ddde9d8..eb5be1c2b 100644
--- a/test/Tests/Readers/Org/Block/Figure.hs
+++ b/test/Tests/Readers/Org/Block/Figure.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Org.Block.Figure
- Copyright : © 2014-2020 Albert Krewinkel
+ Copyright : © 2014-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
@@ -13,7 +12,6 @@ Test parsing of org figures.
-}
module Tests.Readers.Org.Block.Figure (tests) where
-import Prelude
import Test.Tasty (TestTree)
import Tests.Helpers ((=?>))
import Tests.Readers.Org.Shared ((=:))
diff --git a/test/Tests/Readers/Org/Block/Header.hs b/test/Tests/Readers/Org/Block/Header.hs
index d38d26efb..1344ad79b 100644
--- a/test/Tests/Readers/Org/Block/Header.hs
+++ b/test/Tests/Readers/Org/Block/Header.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Org.Block.Header
- Copyright : © 2014-2020 Albert Krewinkel
+ Copyright : © 2014-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
@@ -13,7 +12,6 @@ Test parsing of org header blocks.
-}
module Tests.Readers.Org.Block.Header (tests) where
-import Prelude
import Test.Tasty (TestTree, testGroup)
import Tests.Helpers ((=?>))
import Tests.Readers.Org.Shared ((=:), spcSep, tagSpan)
diff --git a/test/Tests/Readers/Org/Block/List.hs b/test/Tests/Readers/Org/Block/List.hs
index 15373b3b3..2ee37081e 100644
--- a/test/Tests/Readers/Org/Block/List.hs
+++ b/test/Tests/Readers/Org/Block/List.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Org.Block.Header
- Copyright : © 2014-2020 Albert Krewinkel
+ Copyright : © 2014-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
@@ -13,7 +12,6 @@ Test parsing of org lists.
-}
module Tests.Readers.Org.Block.List (tests) where
-import Prelude
import Test.Tasty (TestTree)
import Tests.Helpers ((=?>))
import Tests.Readers.Org.Shared ((=:), spcSep)
@@ -120,6 +118,19 @@ tests =
] =?>
bulletList [ plain "", plain "" ]
+ , "Task list" =:
+ T.unlines [ "- [ ] nope"
+ , "- [X] yup"
+ , "- [-] started"
+ , " 1. [X] sure"
+ , " 2. [ ] nuh-uh"
+ ] =?>
+ bulletList [ plain "☐ nope", plain "☒ yup"
+ , mconcat [ plain "☐ started"
+ , orderedList [plain "☒ sure", plain "☐ nuh-uh"]
+ ]
+ ]
+
, "Simple Ordered List" =:
("1. Item1\n" <>
"2. Item2\n") =?>
diff --git a/test/Tests/Readers/Org/Block/Table.hs b/test/Tests/Readers/Org/Block/Table.hs
index 31c994d3f..ce18e6a5b 100644
--- a/test/Tests/Readers/Org/Block/Table.hs
+++ b/test/Tests/Readers/Org/Block/Table.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Org.Block.Table
- Copyright : © 2014-2020 Albert Krewinkel
+ Copyright : © 2014-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
@@ -13,7 +12,6 @@ Test parsing of org tables.
-}
module Tests.Readers.Org.Block.Table (tests) where
-import Prelude
import Test.Tasty (TestTree)
import Tests.Helpers ((=?>))
import Tests.Readers.Org.Shared ((=:), spcSep)
diff --git a/test/Tests/Readers/Org/Directive.hs b/test/Tests/Readers/Org/Directive.hs
index 727a29658..85d1bc088 100644
--- a/test/Tests/Readers/Org/Directive.hs
+++ b/test/Tests/Readers/Org/Directive.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Org.Directive
- Copyright : © 2014-2020 Albert Krewinkel
+ Copyright : © 2014-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
@@ -13,7 +12,6 @@ Tests parsing of org directives (like @#+OPTIONS@).
-}
module Tests.Readers.Org.Directive (tests) where
-import Prelude
import Data.Time (UTCTime (UTCTime), secondsToDiffTime)
import Data.Time.Calendar (Day (ModifiedJulianDay))
import Test.Tasty (TestTree, testGroup)
diff --git a/test/Tests/Readers/Org/Inline.hs b/test/Tests/Readers/Org/Inline.hs
index 9edd328c3..111d74879 100644
--- a/test/Tests/Readers/Org/Inline.hs
+++ b/test/Tests/Readers/Org/Inline.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Org.Inline
- Copyright : © 2014-2020 Albert Krewinkel
+ Copyright : © 2014-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
@@ -13,7 +12,6 @@ Tests parsing of org inlines.
-}
module Tests.Readers.Org.Inline (tests) where
-import Prelude
import Data.List (intersperse)
import Test.Tasty (TestTree, testGroup)
import Tests.Helpers ((=?>))
@@ -56,7 +54,7 @@ tests =
, "Verbatim" =:
"=Robot.rock()=" =?>
- para (code "Robot.rock()")
+ para (codeWith ("", ["verbatim"], []) "Robot.rock()")
, "Code" =:
"~word for word~" =?>
@@ -190,7 +188,7 @@ tests =
])
, "Verbatim text can contain equal signes (=)" =:
"=is_subst = True=" =?>
- para (code "is_subst = True")
+ para (codeWith ("", ["verbatim"], []) "is_subst = True")
, testGroup "Images"
[ "Image" =:
diff --git a/test/Tests/Readers/Org/Inline/Citation.hs b/test/Tests/Readers/Org/Inline/Citation.hs
index 792e4559c..a11804983 100644
--- a/test/Tests/Readers/Org/Inline/Citation.hs
+++ b/test/Tests/Readers/Org/Inline/Citation.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Org.Inline.Citation
- Copyright : © 2014-2020 Albert Krewinkel
+ Copyright : © 2014-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
@@ -13,7 +12,6 @@ Test parsing of citations in org input.
-}
module Tests.Readers.Org.Inline.Citation (tests) where
-import Prelude
import Test.Tasty (TestTree, testGroup)
import Tests.Helpers ((=?>))
import Tests.Readers.Org.Shared ((=:))
@@ -118,6 +116,46 @@ tests =
}
in (para $ cite [citation] "citep:pandoc")
+ , "multiple simple citations" =:
+ "citep:picard,riker" =?>
+ let picard = Citation
+ { citationId = "picard"
+ , citationPrefix = mempty
+ , citationSuffix = mempty
+ , citationMode = NormalCitation
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ riker = Citation
+ { citationId = "riker"
+ , citationPrefix = mempty
+ , citationSuffix = mempty
+ , citationMode = NormalCitation
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ in (para $ cite [picard,riker] "citep:picard,riker")
+
+ , "multiple simple citations succeeded by comma" =:
+ "citep:picard,riker," =?>
+ let picard = Citation
+ { citationId = "picard"
+ , citationPrefix = mempty
+ , citationSuffix = mempty
+ , citationMode = NormalCitation
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ riker = Citation
+ { citationId = "riker"
+ , citationPrefix = mempty
+ , citationSuffix = mempty
+ , citationMode = NormalCitation
+ , citationNoteNum = 0
+ , citationHash = 0
+ }
+ in (para $ cite [picard,riker] "citep:picard,riker" <> str ",")
+
, "extended citation" =:
"[[citep:Dominik201408][See page 20::, for example]]" =?>
let citation = Citation
diff --git a/test/Tests/Readers/Org/Inline/Note.hs b/test/Tests/Readers/Org/Inline/Note.hs
index 5924e69cc..c37133d54 100644
--- a/test/Tests/Readers/Org/Inline/Note.hs
+++ b/test/Tests/Readers/Org/Inline/Note.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Org.Inline.Note
- Copyright : © 2014-2020 Albert Krewinkel
+ Copyright : © 2014-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
@@ -13,7 +12,6 @@ Test parsing of footnotes in org input.
-}
module Tests.Readers.Org.Inline.Note (tests) where
-import Prelude
import Test.Tasty (TestTree)
import Tests.Helpers ((=?>))
import Tests.Readers.Org.Shared ((=:))
diff --git a/test/Tests/Readers/Org/Inline/Smart.hs b/test/Tests/Readers/Org/Inline/Smart.hs
index e9309108e..db96eb2ca 100644
--- a/test/Tests/Readers/Org/Inline/Smart.hs
+++ b/test/Tests/Readers/Org/Inline/Smart.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Org.Inline.Smart
- Copyright : © 2014-2020 Albert Krewinkel
+ Copyright : © 2014-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
@@ -13,7 +12,6 @@ Test smart parsing of quotes, apostrophe, etc.
-}
module Tests.Readers.Org.Inline.Smart (tests) where
-import Prelude
import Data.Text (Text)
import Test.Tasty (TestTree)
import Tests.Helpers ((=?>), purely, test)
diff --git a/test/Tests/Readers/Org/Meta.hs b/test/Tests/Readers/Org/Meta.hs
index 041016f64..6363d84b0 100644
--- a/test/Tests/Readers/Org/Meta.hs
+++ b/test/Tests/Readers/Org/Meta.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Org.Meta
- Copyright : © 2014-2020 Albert Krewinkel
+ Copyright : © 2014-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
@@ -13,7 +12,6 @@ Tests parsing of org meta data (mostly lines starting with @#+@).
-}
module Tests.Readers.Org.Meta (tests) where
-import Prelude
import Test.Tasty (TestTree, testGroup)
import Tests.Helpers ((=?>))
import Tests.Readers.Org.Shared ((=:), spcSep)
@@ -116,6 +114,16 @@ tests =
"#+LANGUAGE: de-DE" =?>
Pandoc (setMeta "lang" (MetaString "de-DE") nullMeta) mempty
+ , testGroup "Todo sequences"
+ [ "not included in document" =:
+ "#+todo: WAITING | FINISHED" =?>
+ Pandoc mempty mempty
+
+ , "can contain multiple pipe characters" =:
+ "#+todo: UNFINISHED | RESEARCH | NOTES | CHART\n" =?>
+ Pandoc mempty mempty
+ ]
+
, testGroup "LaTeX"
[ "LATEX_HEADER" =:
"#+latex_header: \\usepackage{tikz}" =?>
@@ -270,7 +278,8 @@ tests =
, "Search links are read as emph" =:
"[[Wally][Where's Wally?]]" =?>
- para (emph $ "Where's" <> space <> "Wally?")
+ para (spanWith ("", ["spurious-link"], [("target", "Wally")])
+ (emph $ "Where's" <> space <> "Wally?"))
, "Link to nonexistent anchor" =:
T.unlines [ "<<link-here>> Target."
@@ -278,5 +287,6 @@ tests =
, "[[link$here][See here!]]"
] =?>
(para (spanWith ("link-here", [], []) mempty <> "Target.") <>
- para (emph ("See" <> space <> "here!")))
+ para (spanWith ("", ["spurious-link"], [("target", "link$here")])
+ (emph ("See" <> space <> "here!"))))
]
diff --git a/test/Tests/Readers/Org/Shared.hs b/test/Tests/Readers/Org/Shared.hs
index 184adee44..c584eff19 100644
--- a/test/Tests/Readers/Org/Shared.hs
+++ b/test/Tests/Readers/Org/Shared.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Org.Shared
- Copyright : © 2014-2020 Albert Krewinkel
+ Copyright : © 2014-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <albert@zeitkraut.de>
@@ -18,7 +17,6 @@ module Tests.Readers.Org.Shared
, tagSpan
) where
-import Prelude
import Data.List (intersperse)
import Data.Text (Text)
import Tests.Helpers (ToString, purely, test)
diff --git a/test/Tests/Readers/RST.hs b/test/Tests/Readers/RST.hs
index bd9897ebc..a12b59fc2 100644
--- a/test/Tests/Readers/RST.hs
+++ b/test/Tests/Readers/RST.hs
@@ -1,9 +1,8 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{- |
Module : Tests.Readers.RST
- Copyright : © 2006-2020 John MacFarlane
+ Copyright : © 2006-2021 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
@@ -14,7 +13,6 @@ Tests for the RST reader.
-}
module Tests.Readers.RST (tests) where
-import Prelude
import Data.Text (Text)
import qualified Data.Text as T
import Test.Tasty
diff --git a/test/Tests/Readers/Txt2Tags.hs b/test/Tests/Readers/Txt2Tags.hs
index 989b7f673..013f29d68 100644
--- a/test/Tests/Readers/Txt2Tags.hs
+++ b/test/Tests/Readers/Txt2Tags.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Readers.Txt2Tags
- Copyright : © 2014-2020 John MacFarlane,
+ Copyright : © 2014-2021 John MacFarlane,
© 2014 Matthew Pickering
License : GNU GPL, version 2 or above
@@ -14,7 +13,6 @@ Tests for the Txt2Tags reader.
-}
module Tests.Readers.Txt2Tags (tests) where
-import Prelude
import Data.List (intersperse)
import Data.Text (Text)
import qualified Data.Text as T
diff --git a/test/Tests/Shared.hs b/test/Tests/Shared.hs
index a23edf452..e415ea153 100644
--- a/test/Tests/Shared.hs
+++ b/test/Tests/Shared.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Shared
- Copyright : © 2006-2020 John MacFarlane
+ Copyright : © 2006-2021 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley@edu>
@@ -13,7 +12,6 @@ Tests for functions used in many parts of the library.
-}
module Tests.Shared (tests) where
-import Prelude
import System.FilePath.Posix (joinPath)
import Test.Tasty
import Test.Tasty.HUnit (assertBool, testCase, (@?=))
diff --git a/test/Tests/Writers/AnnotatedTable.hs b/test/Tests/Writers/AnnotatedTable.hs
index 7e16cf8e0..53cca80a6 100644
--- a/test/Tests/Writers/AnnotatedTable.hs
+++ b/test/Tests/Writers/AnnotatedTable.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Tests.Writers.AnnotatedTable
diff --git a/test/Tests/Writers/AsciiDoc.hs b/test/Tests/Writers/AsciiDoc.hs
index 75f6e5e97..04655635f 100644
--- a/test/Tests/Writers/AsciiDoc.hs
+++ b/test/Tests/Writers/AsciiDoc.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.AsciiDoc (tests) where
-import Prelude
import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
diff --git a/test/Tests/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs
index c747e5d2f..fbbf9b948 100644
--- a/test/Tests/Writers/ConTeXt.hs
+++ b/test/Tests/Writers/ConTeXt.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.ConTeXt (tests) where
-import Prelude
import Data.Text (unpack, pack)
import Test.Tasty
import Test.Tasty.QuickCheck
@@ -41,116 +39,125 @@ infix 4 =:
(=:) = test context
tests :: [TestTree]
-tests = [ testGroup "inline code"
- [ "with '}'" =: code "}" =?> "\\mono{\\}}"
- , "without '}'" =: code "]" =?> "\\type{]}"
- , testProperty "code property" $ \s -> null s || '\n' `elem` s ||
- if '{' `elem` s || '}' `elem` s
- then context' (code $ pack s) == "\\mono{" ++
- context' (str $ pack s) ++ "}"
- else context' (code $ pack s) == "\\type{" ++ s ++ "}"
- ]
- , testGroup "headers"
- [ "level 1" =:
- headerWith ("my-header",[],[]) 1 "My header" =?> "\\section[title={My header},reference={my-header}]"
- , test contextDiv "section-divs" $
- ( headerWith ("header1", [], []) 1 (text "Header1")
- <> headerWith ("header2", [], []) 2 (text "Header2")
- <> headerWith ("header3", [], []) 3 (text "Header3")
- <> headerWith ("header4", [], []) 4 (text "Header4")
- <> headerWith ("header5", [], []) 5 (text "Header5")
- <> headerWith ("header6", [], []) 6 (text "Header6"))
- =?>
- unlines [ "\\startsection[title={Header1},reference={header1}]\n"
- , "\\startsubsection[title={Header2},reference={header2}]\n"
- , "\\startsubsubsection[title={Header3},reference={header3}]\n"
- , "\\startsubsubsubsection[title={Header4},reference={header4}]\n"
- , "\\startsubsubsubsubsection[title={Header5},reference={header5}]\n"
- , "\\startsubsubsubsubsubsection[title={Header6},reference={header6}]\n"
- , "\\stopsubsubsubsubsubsection\n"
- , "\\stopsubsubsubsubsection\n"
- , "\\stopsubsubsubsection\n"
- , "\\stopsubsubsection\n"
- , "\\stopsubsection\n"
- , "\\stopsection" ]
- ]
- , testGroup "bullet lists"
- [ "nested" =:
- bulletList [
- plain (text "top")
- <> bulletList [
- plain (text "next")
- <> bulletList [plain (text "bot")]
- ]
- ] =?> unlines
- [ "\\startitemize[packed]"
- , "\\item"
- , " top"
- , " \\startitemize[packed]"
- , " \\item"
- , " next"
- , " \\startitemize[packed]"
- , " \\item"
- , " bot"
- , " \\stopitemize"
- , " \\stopitemize"
- , "\\stopitemize" ]
- ]
- , testGroup "natural tables"
- [ test contextNtb "table with header and caption" $
- let capt = text "Table 1"
- aligns = [(AlignRight, ColWidthDefault), (AlignLeft, ColWidthDefault), (AlignCenter, ColWidthDefault), (AlignDefault, ColWidthDefault)]
- headers = [plain $ text "Right",
- plain $ text "Left",
- plain $ text "Center",
- plain $ text "Default"]
- rows = [[plain $ text "1.1",
- plain $ text "1.2",
- plain $ text "1.3",
- plain $ text "1.4"]
- ,[plain $ text "2.1",
- plain $ text "2.2",
- plain $ text "2.3",
- plain $ text "2.4"]
- ,[plain $ text "3.1",
- plain $ text "3.2",
- plain $ text "3.3",
- plain $ text "3.4"]]
- toRow = Row nullAttr . map simpleCell
- in table (simpleCaption $ plain capt)
- aligns
- (TableHead nullAttr [toRow headers])
- [TableBody nullAttr 0 [] $ map toRow rows]
- (TableFoot nullAttr [])
- =?> unlines [ "\\startplacetable[title={Table 1}]"
- , "\\startTABLE"
- , "\\startTABLEhead"
- , "\\NC[align=left] Right"
- , "\\NC[align=right] Left"
- , "\\NC[align=middle] Center"
- , "\\NC Default"
- , "\\NC\\NR"
- , "\\stopTABLEhead"
- , "\\startTABLEbody"
- , "\\NC[align=left] 1.1"
- , "\\NC[align=right] 1.2"
- , "\\NC[align=middle] 1.3"
- , "\\NC 1.4"
- , "\\NC\\NR"
- , "\\NC[align=left] 2.1"
- , "\\NC[align=right] 2.2"
- , "\\NC[align=middle] 2.3"
- , "\\NC 2.4"
- , "\\NC\\NR"
- , "\\stopTABLEbody"
- , "\\startTABLEfoot"
- , "\\NC[align=left] 3.1"
- , "\\NC[align=right] 3.2"
- , "\\NC[align=middle] 3.3"
- , "\\NC 3.4"
- , "\\NC\\NR"
- , "\\stopTABLEfoot"
- , "\\stopTABLE"
- , "\\stopplacetable" ]
- ]
- ]
+tests =
+ [ testGroup "inline code"
+ [ "with '}'" =: code "}" =?> "\\mono{\\}}"
+ , "without '}'" =: code "]" =?> "\\type{]}"
+ , "span with ID" =:
+ spanWith ("city", [], []) "Berlin" =?>
+ "\\reference[city]{}Berlin"
+ , testProperty "code property" $ \s -> null s || '\n' `elem` s ||
+ if '{' `elem` s || '}' `elem` s
+ then context' (code $ pack s) == "\\mono{" ++
+ context' (str $ pack s) ++ "}"
+ else context' (code $ pack s) == "\\type{" ++ s ++ "}"
+ ]
+ , testGroup "headers"
+ [ "level 1" =:
+ headerWith ("my-header",[],[]) 1 "My header" =?>
+ "\\section[title={My header},reference={my-header}]"
+ , test contextDiv "section-divs" $
+ ( headerWith ("header1", [], []) 1 (text "Header1")
+ <> headerWith ("header2", [], []) 2 (text "Header2")
+ <> headerWith ("header3", [], []) 3 (text "Header3")
+ <> headerWith ("header4", [], []) 4 (text "Header4")
+ <> headerWith ("header5", [], []) 5 (text "Header5")
+ <> headerWith ("header6", [], []) 6 (text "Header6"))
+ =?>
+ unlines
+ [ "\\startsection[title={Header1},reference={header1}]\n"
+ , "\\startsubsection[title={Header2},reference={header2}]\n"
+ , "\\startsubsubsection[title={Header3},reference={header3}]\n"
+ , "\\startsubsubsubsection[title={Header4},reference={header4}]\n"
+ , "\\startsubsubsubsubsection[title={Header5},reference={header5}]\n"
+ , "\\startsubsubsubsubsubsection[title={Header6},reference={header6}]\n"
+ , "\\stopsubsubsubsubsubsection\n"
+ , "\\stopsubsubsubsubsection\n"
+ , "\\stopsubsubsubsection\n"
+ , "\\stopsubsubsection\n"
+ , "\\stopsubsection\n"
+ , "\\stopsection" ]
+ ]
+ , testGroup "bullet lists"
+ [ "nested" =:
+ bulletList [
+ plain (text "top")
+ <> bulletList [
+ plain (text "next")
+ <> bulletList [plain (text "bot")]
+ ]
+ ] =?> unlines
+ [ "\\startitemize[packed]"
+ , "\\item"
+ , " top"
+ , " \\startitemize[packed]"
+ , " \\item"
+ , " next"
+ , " \\startitemize[packed]"
+ , " \\item"
+ , " bot"
+ , " \\stopitemize"
+ , " \\stopitemize"
+ , "\\stopitemize" ]
+ ]
+ , testGroup "natural tables"
+ [ test contextNtb "table with header and caption" $
+ let capt = text "Table 1"
+ aligns = [ (AlignRight, ColWidthDefault)
+ , (AlignLeft, ColWidthDefault)
+ , (AlignCenter, ColWidthDefault)
+ , (AlignDefault, ColWidthDefault) ]
+ headers = [plain $ text "Right",
+ plain $ text "Left",
+ plain $ text "Center",
+ plain $ text "Default"]
+ rows = [[plain $ text "1.1",
+ plain $ text "1.2",
+ plain $ text "1.3",
+ plain $ text "1.4"]
+ ,[plain $ text "2.1",
+ plain $ text "2.2",
+ plain $ text "2.3",
+ plain $ text "2.4"]
+ ,[plain $ text "3.1",
+ plain $ text "3.2",
+ plain $ text "3.3",
+ plain $ text "3.4"]]
+ toRow = Row nullAttr . map simpleCell
+ in table (simpleCaption $ plain capt)
+ aligns
+ (TableHead nullAttr [toRow headers])
+ [TableBody nullAttr 0 [] $ map toRow rows]
+ (TableFoot nullAttr [])
+ =?> unlines [ "\\startplacetable[title={Table 1}]"
+ , "\\startTABLE"
+ , "\\startTABLEhead"
+ , "\\NC[align=left] Right"
+ , "\\NC[align=right] Left"
+ , "\\NC[align=middle] Center"
+ , "\\NC Default"
+ , "\\NC\\NR"
+ , "\\stopTABLEhead"
+ , "\\startTABLEbody"
+ , "\\NC[align=left] 1.1"
+ , "\\NC[align=right] 1.2"
+ , "\\NC[align=middle] 1.3"
+ , "\\NC 1.4"
+ , "\\NC\\NR"
+ , "\\NC[align=left] 2.1"
+ , "\\NC[align=right] 2.2"
+ , "\\NC[align=middle] 2.3"
+ , "\\NC 2.4"
+ , "\\NC\\NR"
+ , "\\stopTABLEbody"
+ , "\\startTABLEfoot"
+ , "\\NC[align=left] 3.1"
+ , "\\NC[align=right] 3.2"
+ , "\\NC[align=middle] 3.3"
+ , "\\NC 3.4"
+ , "\\NC\\NR"
+ , "\\stopTABLEfoot"
+ , "\\stopTABLE"
+ , "\\stopplacetable" ]
+ ]
+ ]
diff --git a/test/Tests/Writers/Docbook.hs b/test/Tests/Writers/Docbook.hs
index f6a047b0b..f517f803a 100644
--- a/test/Tests/Writers/Docbook.hs
+++ b/test/Tests/Writers/Docbook.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Docbook (tests) where
-import Prelude
import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
@@ -13,9 +11,14 @@ import Text.Pandoc.Builder
docbook :: (ToPandoc a) => a -> String
docbook = docbookWithOpts def{ writerWrapText = WrapNone }
+docbook5 :: (ToPandoc a) => a -> String
+docbook5 = docbook5WithOpts def{ writerWrapText = WrapNone }
+
docbookWithOpts :: ToPandoc a => WriterOptions -> a -> String
docbookWithOpts opts = unpack . purely (writeDocbook4 opts) . toPandoc
+docbook5WithOpts :: ToPandoc a => WriterOptions -> a -> String
+docbook5WithOpts opts = unpack . purely (writeDocbook5 opts) . toPandoc
{-
"my test" =: X =?> Y
@@ -70,6 +73,72 @@ tests = [ testGroup "line blocks"
, "</para>" ]
)
]
+ , testGroup "divs"
+ [ "admonition" =: divWith ("foo", ["warning"], []) (para "This is a test")
+ =?> unlines
+ [ "<warning id=\"foo\">"
+ , " <para>"
+ , " This is a test"
+ , " </para>"
+ , "</warning>"
+ ]
+ , "admonition-with-title" =:
+ divWith ("foo", ["note"], []) (
+ divWith ("foo", ["title"], [])
+ (plain (text "This is title")) <>
+ para "This is a test"
+ )
+ =?> unlines
+ [ "<note id=\"foo\">"
+ , " <title>This is title</title>"
+ , " <para>"
+ , " This is a test"
+ , " </para>"
+ , "</note>"
+ ]
+ , "admonition-with-title-in-para" =:
+ divWith ("foo", ["note"], []) (
+ divWith ("foo", ["title"], [])
+ (para "This is title") <>
+ para "This is a test"
+ )
+ =?> unlines
+ [ "<note id=\"foo\">"
+ , " <title>This is title</title>"
+ , " <para>"
+ , " This is a test"
+ , " </para>"
+ , "</note>"
+ ]
+ , "single-child" =:
+ divWith ("foo", [], []) (para "This is a test")
+ =?> unlines
+ [ "<para id=\"foo\">"
+ , " This is a test"
+ , "</para>"
+ ]
+ , "single-literal-child" =:
+ divWith ("foo", [], []) lineblock
+ =?> unlines
+ [ "<literallayout id=\"foo\">some text"
+ , "and more lines"
+ , "and again</literallayout>"
+ ]
+ , "multiple-children" =:
+ divWith ("foo", [], []) (
+ para "This is a test" <>
+ para "This is an another test"
+ )
+ =?> unlines
+ [ "<anchor id=\"foo\" />"
+ , "<para>"
+ , " This is a test"
+ , "</para>"
+ , "<para>"
+ , " This is an another test"
+ , "</para>"
+ ]
+ ]
, testGroup "compact lists"
[ testGroup "bullet"
[ "compact" =: bulletList [plain "a", plain "b", plain "c"]
@@ -302,4 +371,36 @@ tests = [ testGroup "line blocks"
]
]
]
+ , testGroup "section attributes" $
+ let
+ headers = headerWith ("myid1",[],[("role","internal"),("xml:id","anotherid"),("dir","rtl")]) 1 "header1"
+ <> headerWith ("myid2",[],[("invalidname","value"),("arch","linux"),("dir","invaliddir")]) 1 "header2"
+ in
+ [ test docbook5 "sections with attributes (db5)" $
+ headers =?>
+ unlines [ "<section xmlns=\"http://docbook.org/ns/docbook\" xmlns:xlink=\"http://www.w3.org/1999/xlink\" xml:id=\"myid1\" role=\"internal\" dir=\"rtl\">"
+ , " <title>header1</title>"
+ , " <para>"
+ , " </para>"
+ , "</section>"
+ , "<section xmlns=\"http://docbook.org/ns/docbook\" xmlns:xlink=\"http://www.w3.org/1999/xlink\" xml:id=\"myid2\">"
+ , " <title>header2</title>"
+ , " <para>"
+ , " </para>"
+ , "</section>"
+ ]
+ , test docbook "sections with attributes (db4)" $
+ headers =?>
+ unlines [ "<sect1 id=\"myid1\" role=\"internal\">"
+ , " <title>header1</title>"
+ , " <para>"
+ , " </para>"
+ , "</sect1>"
+ , "<sect1 id=\"myid2\" arch=\"linux\">"
+ , " <title>header2</title>"
+ , " <para>"
+ , " </para>"
+ , "</sect1>"
+ ]
+ ]
]
diff --git a/test/Tests/Writers/Docx.hs b/test/Tests/Writers/Docx.hs
index 8f051b4b7..da25b95e0 100644
--- a/test/Tests/Writers/Docx.hs
+++ b/test/Tests/Writers/Docx.hs
@@ -1,7 +1,5 @@
-{-# LANGUAGE NoImplicitPrelude #-}
module Tests.Writers.Docx (tests) where
-import Prelude
import Text.Pandoc
import Test.Tasty
import Tests.Writers.OOXML
@@ -114,6 +112,11 @@ tests = [ testGroup "inlines"
"docx/tables.native"
"docx/golden/tables.docx"
, docxTest
+ "tables without explicit column widths"
+ def
+ "docx/tables-default-widths.native"
+ "docx/golden/tables-default-widths.docx"
+ , docxTest
"tables with lists in cells"
def
"docx/table_with_list_cell.native"
@@ -128,6 +131,16 @@ tests = [ testGroup "inlines"
def
"docx/codeblock.native"
"docx/golden/codeblock.docx"
+ , docxTest
+ "raw OOXML blocks"
+ def
+ "docx/raw-blocks.native"
+ "docx/golden/raw-blocks.docx"
+ , docxTest
+ "raw bookmark markers"
+ def
+ "docx/raw-bookmarks.native"
+ "docx/golden/raw-bookmarks.docx"
]
, testGroup "track changes"
[ docxTest
diff --git a/test/Tests/Writers/FB2.hs b/test/Tests/Writers/FB2.hs
index 7699c58e9..2e10636fa 100644
--- a/test/Tests/Writers/FB2.hs
+++ b/test/Tests/Writers/FB2.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.FB2 (tests) where
-import Prelude
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
diff --git a/test/Tests/Writers/HTML.hs b/test/Tests/Writers/HTML.hs
index 6ff0a6e1d..404f6da98 100644
--- a/test/Tests/Writers/HTML.hs
+++ b/test/Tests/Writers/HTML.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.HTML (tests) where
-import Prelude
import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
@@ -36,55 +34,60 @@ infix 4 =:
(=:) = test html
tests :: [TestTree]
-tests = [ testGroup "inline code"
- [ "basic" =: code "@&" =?> "<code>@&amp;</code>"
- , "haskell" =: codeWith ("",["haskell"],[]) ">>="
- =?> "<code class=\"sourceCode haskell\"><span class=\"op\">&gt;&gt;=</span></code>"
- , "nolanguage" =: codeWith ("",["nolanguage"],[]) ">>="
- =?> "<code class=\"nolanguage\">&gt;&gt;=</code>"
- ]
- , testGroup "images"
- [ "alt with formatting" =:
- image "/url" "title" ("my " <> emph "image")
- =?> "<img src=\"/url\" title=\"title\" alt=\"my image\" />"
- ]
- , testGroup "blocks"
- [ "definition list with empty <dt>" =:
- definitionList [(mempty, [para $ text "foo bar"])]
- =?> "<dl><dt></dt><dd><p>foo bar</p></dd></dl>"
- ]
- , testGroup "quotes"
- [ "quote with cite attribute (without q-tags)" =:
- doubleQuoted (spanWith ("", [], [("cite", "http://example.org")]) (str "examples"))
- =?> "“<span cite=\"http://example.org\">examples</span>”"
- , tQ "quote with cite attribute (with q-tags)" $
- doubleQuoted (spanWith ("", [], [("cite", "http://example.org")]) (str "examples"))
- =?> "<q cite=\"http://example.org\">examples</q>"
- ]
- , testGroup "sample"
- [ "sample should be rendered correctly" =:
- plain (codeWith ("",["sample"],[]) "Answer is 42") =?>
- "<samp>Answer is 42</samp>"
- ]
- , testGroup "variable"
- [ "variable should be rendered correctly" =:
- plain (codeWith ("",["variable"],[]) "result") =?>
- "<var>result</var>"
- ]
- , testGroup "sample with style"
- [ "samp should wrap highlighted code" =:
- codeWith ("",["sample","haskell"],[]) ">>="
- =?> ("<samp><code class=\"sourceCode haskell\">" ++
- "<span class=\"op\">&gt;&gt;=</span></code></samp>")
- ]
- , testGroup "variable with style"
- [ "var should wrap highlighted code" =:
- codeWith ("",["haskell","variable"],[]) ">>="
- =?> ("<var><code class=\"sourceCode haskell\">" ++
- "<span class=\"op\">&gt;&gt;=</span></code></var>")
- ]
- ]
- where
- tQ :: (ToString a, ToPandoc a)
- => String -> (a, String) -> TestTree
- tQ = test htmlQTags
+tests =
+ [ testGroup "inline code"
+ [ "basic" =: code "@&" =?> "<code>@&amp;</code>"
+ , "haskell" =: codeWith ("",["haskell"],[]) ">>="
+ =?> "<code class=\"sourceCode haskell\"><span class=\"op\">&gt;&gt;=</span></code>"
+ , "nolanguage" =: codeWith ("",["nolanguage"],[]) ">>="
+ =?> "<code class=\"nolanguage\">&gt;&gt;=</code>"
+ ]
+ , testGroup "images"
+ [ "alt with formatting" =:
+ image "/url" "title" ("my " <> emph "image")
+ =?> "<img src=\"/url\" title=\"title\" alt=\"my image\" />"
+ ]
+ , testGroup "blocks"
+ [ "definition list with empty <dt>" =:
+ definitionList [(mempty, [para $ text "foo bar"])]
+ =?> "<dl><dt></dt><dd><p>foo bar</p></dd></dl>"
+ , "heading with disallowed attributes" =:
+ headerWith ("", [], [("invalid","1"), ("lang", "en")]) 1 "test"
+ =?>
+ "<h1 lang=\"en\">test</h1>"
+ ]
+ , testGroup "quotes"
+ [ "quote with cite attribute (without q-tags)" =:
+ doubleQuoted (spanWith ("", [], [("cite", "http://example.org")]) (str "examples"))
+ =?> "“<span cite=\"http://example.org\">examples</span>”"
+ , tQ "quote with cite attribute (with q-tags)" $
+ doubleQuoted (spanWith ("", [], [("cite", "http://example.org")]) (str "examples"))
+ =?> "<q cite=\"http://example.org\">examples</q>"
+ ]
+ , testGroup "sample"
+ [ "sample should be rendered correctly" =:
+ plain (codeWith ("",["sample"],[]) "Answer is 42") =?>
+ "<samp>Answer is 42</samp>"
+ ]
+ , testGroup "variable"
+ [ "variable should be rendered correctly" =:
+ plain (codeWith ("",["variable"],[]) "result") =?>
+ "<var>result</var>"
+ ]
+ , testGroup "sample with style"
+ [ "samp should wrap highlighted code" =:
+ codeWith ("",["sample","haskell"],[]) ">>="
+ =?> ("<samp><code class=\"sourceCode haskell\">" ++
+ "<span class=\"op\">&gt;&gt;=</span></code></samp>")
+ ]
+ , testGroup "variable with style"
+ [ "var should wrap highlighted code" =:
+ codeWith ("",["haskell","variable"],[]) ">>="
+ =?> ("<var><code class=\"sourceCode haskell\">" ++
+ "<span class=\"op\">&gt;&gt;=</span></code></var>")
+ ]
+ ]
+ where
+ tQ :: (ToString a, ToPandoc a)
+ => String -> (a, String) -> TestTree
+ tQ = test htmlQTags
diff --git a/test/Tests/Writers/JATS.hs b/test/Tests/Writers/JATS.hs
index 7d98f979b..5b96ed2ed 100644
--- a/test/Tests/Writers/JATS.hs
+++ b/test/Tests/Writers/JATS.hs
@@ -1,23 +1,21 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.JATS (tests) where
-import Prelude
-import Data.Text (unpack)
+import Data.Text (Text)
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
+import qualified Data.Text as T
-jats :: (ToPandoc a) => a -> String
-jats = unpack
- . purely (writeJATS def{ writerWrapText = WrapNone })
- . toPandoc
+jats :: (ToPandoc a) => a -> Text
+jats = purely (writeJATS def{ writerWrapText = WrapNone })
+ . toPandoc
-jatsArticleAuthoring :: (ToPandoc a) => a -> String
-jatsArticleAuthoring = unpack
- . purely (writeJatsArticleAuthoring def{ writerWrapText = WrapNone })
+jatsArticleAuthoring :: (ToPandoc a) => a -> Text
+jatsArticleAuthoring =
+ purely (writeJatsArticleAuthoring def{ writerWrapText = WrapNone })
. toPandoc
{-
@@ -34,89 +32,133 @@ which is in turn shorthand for
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
- => String -> (a, String) -> TestTree
+ => String -> (a, Text) -> TestTree
(=:) = test jats
tests :: [TestTree]
-tests = [ testGroup "inline code"
- [ "basic" =: code "@&" =?> "<p><monospace>@&amp;</monospace></p>"
- , "lang" =: codeWith ("", ["c"], []) "@&" =?> "<p><code language=\"c\">@&amp;</code></p>"
- ]
- , testGroup "block code"
- [ "basic" =: codeBlock "@&" =?> "<preformat>@&amp;</preformat>"
- , "lang" =: codeBlockWith ("", ["c"], []) "@&" =?> "<code language=\"c\">@&amp;</code>"
- ]
- , testGroup "images"
- [ "basic" =:
- image "/url" "title" mempty
- =?> "<graphic mimetype=\"image\" mime-subtype=\"\" xlink:href=\"/url\" xlink:title=\"title\" />"
- ]
- , testGroup "inlines"
- [ "Emphasis" =: emph "emphasized"
- =?> "<p><italic>emphasized</italic></p>"
-
- , test jatsArticleAuthoring "footnote in articleauthoring tag set"
- ("test" <> note (para "footnote") =?>
- unlines [ "<p>test<fn>"
- , " <p>footnote</p>"
- , "</fn></p>"
- ])
- ]
- , "bullet list" =: bulletList [ plain $ text "first"
- , plain $ text "second"
- , plain $ text "third"
- ]
- =?> "<list list-type=\"bullet\">\n\
- \ <list-item>\n\
- \ <p>first</p>\n\
- \ </list-item>\n\
- \ <list-item>\n\
- \ <p>second</p>\n\
- \ </list-item>\n\
- \ <list-item>\n\
- \ <p>third</p>\n\
- \ </list-item>\n\
- \</list>"
- , testGroup "definition lists"
- [ "with internal link" =: definitionList [(link "#go" "" (str "testing"),
- [plain (text "hi there")])] =?>
- "<def-list>\n\
- \ <def-item>\n\
- \ <term><xref alt=\"testing\" rid=\"go\">testing</xref></term>\n\
- \ <def>\n\
- \ <p>hi there</p>\n\
- \ </def>\n\
- \ </def-item>\n\
- \</def-list>"
- ]
- , testGroup "math"
- [ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?>
- "<p><inline-formula><alternatives>\n\
- \<tex-math><![CDATA[\\sigma|_{\\{x\\}}]]></tex-math>\n\
- \<mml:math display=\"inline\" xmlns:mml=\"http://www.w3.org/1998/Math/MathML\"><mml:mrow><mml:mi>σ</mml:mi><mml:msub><mml:mo stretchy=\"false\" form=\"prefix\">|</mml:mo><mml:mrow><mml:mo stretchy=\"false\" form=\"prefix\">{</mml:mo><mml:mi>x</mml:mi><mml:mo stretchy=\"false\" form=\"postfix\">}</mml:mo></mml:mrow></mml:msub></mml:mrow></mml:math></alternatives></inline-formula></p>"
- ]
- , testGroup "headers"
- [ "unnumbered header" =:
- headerWith ("foo",["unnumbered"],[]) 1
- (text "Header 1" <> note (plain $ text "note")) =?>
- "<sec id=\"foo\">\n\
- \ <title>Header 1<xref ref-type=\"fn\" rid=\"fn1\">1</xref></title>\n\
- \</sec>"
- , "unnumbered sub header" =:
- headerWith ("foo",["unnumbered"],[]) 1
- (text "Header")
- <> headerWith ("foo",["unnumbered"],[]) 2
- (text "Sub-Header") =?>
- "<sec id=\"foo\">\n\
- \ <title>Header</title>\n\
- \ <sec id=\"foo\">\n\
- \ <title>Sub-Header</title>\n\
- \ </sec>\n\
- \</sec>"
- , "containing image" =:
- header 1 (image "imgs/foo.jpg" "" (text "Alt text")) =?>
- "<sec>\n\
- \ <title><inline-graphic mimetype=\"image\" mime-subtype=\"jpeg\" xlink:href=\"imgs/foo.jpg\" /></title>\n\
- \</sec>"
- ]
- ]
+tests =
+ [ testGroup "inline code"
+ [ "basic" =: code "@&" =?> "<p><monospace>@&amp;</monospace></p>"
+ , "lang" =: codeWith ("", ["c"], []) "@&" =?> "<p><code language=\"c\">@&amp;</code></p>"
+ ]
+ , testGroup "block code"
+ [ "basic" =: codeBlock "@&" =?> "<preformat>@&amp;</preformat>"
+ , "lang" =: codeBlockWith ("", ["c"], []) "@&" =?> "<code language=\"c\">@&amp;</code>"
+ ]
+ , testGroup "images"
+ [ "basic" =:
+ image "/url" "title" mempty
+ =?> "<graphic mimetype=\"image\" mime-subtype=\"\" xlink:href=\"/url\" xlink:title=\"title\" />"
+ ]
+ , testGroup "inlines"
+ [ "Emphasis" =: emph "emphasized"
+ =?> "<p><italic>emphasized</italic></p>"
+
+ , test jatsArticleAuthoring "footnote in articleauthoring tag set"
+ ("test" <> note (para "footnote") =?>
+ unlines [ "<p>test<fn>"
+ , " <p>footnote</p>"
+ , "</fn></p>"
+ ])
+ ]
+ , "bullet list" =: bulletList [ plain $ text "first"
+ , plain $ text "second"
+ , plain $ text "third"
+ ]
+ =?> "<list list-type=\"bullet\">\n\
+ \ <list-item>\n\
+ \ <p>first</p>\n\
+ \ </list-item>\n\
+ \ <list-item>\n\
+ \ <p>second</p>\n\
+ \ </list-item>\n\
+ \ <list-item>\n\
+ \ <p>third</p>\n\
+ \ </list-item>\n\
+ \</list>"
+ , testGroup "definition lists"
+ [ "with internal link" =: definitionList [(link "#go" "" (str "testing"),
+ [plain (text "hi there")])] =?>
+ "<def-list>\n\
+ \ <def-item>\n\
+ \ <term><xref alt=\"testing\" rid=\"go\">testing</xref></term>\n\
+ \ <def>\n\
+ \ <p>hi there</p>\n\
+ \ </def>\n\
+ \ </def-item>\n\
+ \</def-list>"
+ ]
+ , testGroup "math"
+ [ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?>
+ "<p><inline-formula><alternatives>\n\
+ \<tex-math><![CDATA[\\sigma|_{\\{x\\}}]]></tex-math>\n\
+ \<mml:math display=\"inline\" xmlns:mml=\"http://www.w3.org/1998/Math/MathML\"><mml:mrow><mml:mi>σ</mml:mi><mml:msub><mml:mo stretchy=\"false\" form=\"prefix\">|</mml:mo><mml:mrow><mml:mo stretchy=\"false\" form=\"prefix\">{</mml:mo><mml:mi>x</mml:mi><mml:mo stretchy=\"false\" form=\"postfix\">}</mml:mo></mml:mrow></mml:msub></mml:mrow></mml:math></alternatives></inline-formula></p>"
+ ]
+ , testGroup "headers"
+ [ "unnumbered header" =:
+ headerWith ("foo",["unnumbered"],[]) 1
+ (text "Header 1" <> note (plain $ text "note")) =?>
+ "<sec id=\"foo\">\n\
+ \ <title>Header 1<xref ref-type=\"fn\" rid=\"fn1\">1</xref></title>\n\
+ \</sec>"
+ , "unnumbered sub header" =:
+ headerWith ("foo",["unnumbered"],[]) 1
+ (text "Header")
+ <> headerWith ("foo",["unnumbered"],[]) 2
+ (text "Sub-Header") =?>
+ "<sec id=\"foo\">\n\
+ \ <title>Header</title>\n\
+ \ <sec id=\"foo\">\n\
+ \ <title>Sub-Header</title>\n\
+ \ </sec>\n\
+ \</sec>"
+ , "containing image" =:
+ header 1 (image "imgs/foo.jpg" "" (text "Alt text")) =?>
+ "<sec>\n\
+ \ <title><inline-graphic mimetype=\"image\" mime-subtype=\"jpeg\" xlink:href=\"imgs/foo.jpg\" /></title>\n\
+ \</sec>"
+ ]
+
+ , testGroup "ids"
+ [ "non-ASCII in header ID" =:
+ headerWith ("smørbrød",[],[]) 1 (text "smørbrød") =?>
+ T.unlines [ "<sec id=\"smørbrød\">"
+ , " <title>smørbrød</title>"
+ , "</sec>"
+ ]
+
+ , "disallowed symbol in header id" =:
+ headerWith ("i/o",[],[]) 1 (text "I/O") =?>
+ T.unlines [ "<sec id=\"iU002Fo\">"
+ , " <title>I/O</title>"
+ , "</sec>"
+ ]
+
+ , "disallowed symbols in internal link target" =:
+ link "#foo:bar" "" "baz" =?>
+ "<p><xref alt=\"baz\" rid=\"fooU003Abar\">baz</xref></p>"
+
+ , "code id starting with a number" =:
+ codeWith ("7y",[],[]) "print 5" =?>
+ "<p><monospace id=\"U0037y\">print 5</monospace></p>"
+ ]
+
+ , testGroup "spans"
+ [ "unwrapped if no attributes given" =:
+ spanWith nullAttr "text in span" =?>
+ "<p>text in span</p>"
+
+ , "converted to named-content element if class given" =:
+ spanWith ("a", ["genus-species"], [("alt", "aa")]) "C. elegans" =?>
+ ("<p><named-content id=\"a\" alt=\"aa\" content-type=\"genus-species\">"
+ <> "C. elegans</named-content></p>")
+
+ , "unwrapped if styled-content element would have no attributes" =:
+ spanWith ("", [], [("hidden", "true")]) "text in span" =?>
+ "<p>text in span</p>"
+
+ , "use content-type attribute if present" =:
+ spanWith ("", [], [("content-type", "species")]) "E. coli" =?>
+ "<p><named-content content-type=\"species\">E. coli</named-content></p>"
+ ]
+ ]
diff --git a/test/Tests/Writers/Jira.hs b/test/Tests/Writers/Jira.hs
index 93d830c94..00a7ae931 100644
--- a/test/Tests/Writers/Jira.hs
+++ b/test/Tests/Writers/Jira.hs
@@ -3,6 +3,7 @@ module Tests.Writers.Jira (tests) where
import Data.Text (unpack)
import Test.Tasty
+import Test.Tasty.HUnit (HasCallStack)
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
@@ -12,7 +13,7 @@ jira :: (ToPandoc a) => a -> String
jira = unpack . purely (writeJira def) . toPandoc
infix 4 =:
-(=:) :: (ToString a, ToPandoc a)
+(=:) :: (ToString a, ToPandoc a, HasCallStack)
=> String -> (a, String) -> TestTree
(=:) = test jira
@@ -60,6 +61,64 @@ tests =
, "user link with user as description" =:
linkWith ("", ["user-account"], []) "~johndoe" "" "~johndoe" =?>
"[~johndoe]"
+
+ , "'smart' link" =:
+ para (linkWith ("", ["smart-link"], []) "http://example.com" "" "x") =?>
+ "[x|http://example.com|smart-link]"
+
+ , "'smart' card" =:
+ para (linkWith ("", ["smart-card"], []) "http://example.org" "" "x") =?>
+ "[x|http://example.org|smart-card]"
+ ]
+
+ , testGroup "spans"
+ [ "id is used as anchor" =:
+ spanWith ("unicorn", [], []) (str "Unicorn") =?>
+ "{anchor:unicorn}Unicorn"
+
+ , "use `color` attribute" =:
+ spanWith ("",[],[("color","red")]) "ruby" =?>
+ "{color:red}ruby{color}"
+ ]
+
+ , testGroup "code"
+ [ "code block with known language" =:
+ codeBlockWith ("", ["java"], []) "Book book = new Book(\"Algebra\")" =?>
+ "{code:java}\nBook book = new Book(\"Algebra\")\n{code}"
+
+ , "code block without language" =:
+ codeBlockWith ("", [], []) "preformatted\n text.\n" =?>
+ "{noformat}\npreformatted\n text.\n{noformat}"
+ ]
+ ]
+
+ , testGroup "blocks"
+ [ testGroup "div"
+ [ "empty attributes" =:
+ divWith nullAttr (para "interesting text") =?>
+ "interesting text"
+
+ , "just identifier" =:
+ divWith ("a", [], []) (para "interesting text") =?>
+ "{anchor:a}interesting text"
+
+ , "with class 'panel'" =:
+ divWith ("", ["panel"], []) (para "Contents!") =?>
+ "{panel}\nContents\\!\n{panel}\n"
+
+ , "panel with id" =:
+ divWith ("b", ["panel"], []) (para "text") =?>
+ "{panel}\n{anchor:b}text\n{panel}\n"
+
+ , "title attribute" =:
+ divWith ("", [], [("title", "Gimme!")]) (para "Contents!") =?>
+ "{panel:title=Gimme!}\nContents\\!\n{panel}\n"
+
+ , "nested panels" =:
+ let panelAttr = ("", ["panel"], [])
+ in divWith panelAttr (para "hi" <>
+ divWith panelAttr (para "wassup?")) =?>
+ "{panel}\nhi\n\nwassup?\n{panel}\n"
]
]
]
diff --git a/test/Tests/Writers/LaTeX.hs b/test/Tests/Writers/LaTeX.hs
index 44e23d48e..ae5879099 100644
--- a/test/Tests/Writers/LaTeX.hs
+++ b/test/Tests/Writers/LaTeX.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.LaTeX (tests) where
-import Prelude
import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
diff --git a/test/Tests/Writers/Markdown.hs b/test/Tests/Writers/Markdown.hs
index 4b819de24..d4f927ebe 100644
--- a/test/Tests/Writers/Markdown.hs
+++ b/test/Tests/Writers/Markdown.hs
@@ -1,9 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module Tests.Writers.Markdown (tests) where
-import Prelude
import Data.Text (unpack)
import Test.Tasty
import Tests.Helpers
diff --git a/test/Tests/Writers/Ms.hs b/test/Tests/Writers/Ms.hs
index d73603314..ad6849633 100644
--- a/test/Tests/Writers/Ms.hs
+++ b/test/Tests/Writers/Ms.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Ms (tests) where
-import Prelude
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
diff --git a/test/Tests/Writers/Muse.hs b/test/Tests/Writers/Muse.hs
index d0df0799f..5bddca3af 100644
--- a/test/Tests/Writers/Muse.hs
+++ b/test/Tests/Writers/Muse.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Muse (tests) where
diff --git a/test/Tests/Writers/Native.hs b/test/Tests/Writers/Native.hs
index 905e83b1e..d7771ca19 100644
--- a/test/Tests/Writers/Native.hs
+++ b/test/Tests/Writers/Native.hs
@@ -1,7 +1,5 @@
-{-# LANGUAGE NoImplicitPrelude #-}
module Tests.Writers.Native (tests) where
-import Prelude
import Data.Text (unpack)
import Test.Tasty
import Test.Tasty.QuickCheck
diff --git a/test/Tests/Writers/OOXML.hs b/test/Tests/Writers/OOXML.hs
index 628ea9409..83f05cfec 100644
--- a/test/Tests/Writers/OOXML.hs
+++ b/test/Tests/Writers/OOXML.hs
@@ -1,10 +1,8 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.OOXML (ooxmlTest) where
-import Prelude
import Text.Pandoc
import Test.Tasty
import Test.Tasty.Golden.Advanced
@@ -45,7 +43,8 @@ compareXMLBool _ _ = False
displayDiff :: Content -> Content -> String
displayDiff elemA elemB =
- showDiff (1,1) $ getDiff (lines $ ppContent elemA) (lines $ ppContent elemB)
+ showDiff (1,1)
+ (getDiff (lines $ showContent elemA) (lines $ showContent elemB))
goldenArchive :: FilePath -> IO Archive
goldenArchive fp = toArchive . BL.fromStrict <$> BS.readFile fp
@@ -56,7 +55,9 @@ testArchive :: (WriterOptions -> Pandoc -> PandocIO BL.ByteString)
-> IO Archive
testArchive writerFn opts fp = do
txt <- T.readFile fp
- bs <- runIOorExplode $ readNative def txt >>= writerFn opts
+ bs <- runIOorExplode $ do
+ setTranslations "en-US"
+ readNative def txt >>= writerFn opts
return $ toArchive bs
compareFileList :: FilePath -> Archive -> Archive -> Maybe String
diff --git a/test/Tests/Writers/Org.hs b/test/Tests/Writers/Org.hs
index c99f7344d..bd6c9b7ab 100644
--- a/test/Tests/Writers/Org.hs
+++ b/test/Tests/Writers/Org.hs
@@ -1,8 +1,7 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Org (tests) where
-import Prelude
+import Data.Text as T
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
@@ -11,17 +10,51 @@ import Text.Pandoc.Builder
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
- => String -> (a, String) -> TestTree
-(=:) = test (purely (writeOrg def . toPandoc))
+ => String -> (a, Text) -> TestTree
+(=:) = test org
+
+defopts :: WriterOptions
+defopts = def
+ { writerExtensions = getDefaultExtensions "org"
+ }
+
+org :: (ToPandoc a) => a -> Text
+org = orgWithOpts defopts
+
+orgWithOpts :: (ToPandoc a) => WriterOptions -> a -> Text
+orgWithOpts opts x = purely (writeOrg opts) $ toPandoc x
+
tests :: [TestTree]
-tests = [ testGroup "links"
- -- See http://orgmode.org/manual/Internal-links.html#Internal-links
- [ "simple link"
- =: link "/url" "" "foo"
- =?> "[[/url][foo]]"
- , "internal link to anchor"
- =: link "#my-custom-id" "" "#my-custom-id"
- =?> "[[#my-custom-id]]"
+tests =
+ [ testGroup "links"
+ -- See http://orgmode.org/manual/Internal-links.html#Internal-links
+ [ "simple link"
+ =: link "/url" "" "foo"
+ =?> "[[/url][foo]]"
+ , "internal link to anchor"
+ =: link "#my-custom-id" "" "#my-custom-id"
+ =?> "[[#my-custom-id]]"
+ ]
+
+ , testGroup "lists"
+ [ "bullet task list"
+ =: bulletList [plain "☐ a", plain "☒ b"]
+ =?> T.unlines
+ [ "- [ ] a"
+ , "- [X] b"
+ ]
+ , "ordered task list"
+ =: orderedList [plain ("☐" <> space <> "a"), plain "☒ b"]
+ =?> T.unlines
+ [ "1. [ ] a"
+ , "2. [X] b"
+ ]
+ , test (orgWithOpts def) "bullet without task_lists" $
+ bulletList [plain "☐ a", plain "☒ b"]
+ =?> T.unlines
+ [ "- ☐ a"
+ , "- ☒ b"
]
- ]
+ ]
+ ]
diff --git a/test/Tests/Writers/Plain.hs b/test/Tests/Writers/Plain.hs
index b8d1f6693..17edc9dbd 100644
--- a/test/Tests/Writers/Plain.hs
+++ b/test/Tests/Writers/Plain.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.Plain (tests) where
-import Prelude
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs
index be98fe0e7..87ebe990c 100644
--- a/test/Tests/Writers/Powerpoint.hs
+++ b/test/Tests/Writers/Powerpoint.hs
@@ -1,7 +1,5 @@
-{-# LANGUAGE NoImplicitPrelude #-}
module Tests.Writers.Powerpoint (tests) where
-import Prelude
import Tests.Writers.OOXML (ooxmlTest)
import Text.Pandoc
import Test.Tasty
diff --git a/test/Tests/Writers/RST.hs b/test/Tests/Writers/RST.hs
index a52423fad..94745e9a2 100644
--- a/test/Tests/Writers/RST.hs
+++ b/test/Tests/Writers/RST.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.RST (tests) where
-import Prelude
import Control.Monad.Identity
import Test.Tasty
import Test.Tasty.HUnit
diff --git a/test/Tests/Writers/TEI.hs b/test/Tests/Writers/TEI.hs
index 31e970495..fa372909f 100644
--- a/test/Tests/Writers/TEI.hs
+++ b/test/Tests/Writers/TEI.hs
@@ -1,8 +1,6 @@
-{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Tests.Writers.TEI (tests) where
-import Prelude
import Test.Tasty
import Tests.Helpers
import Text.Pandoc