summaryrefslogtreecommitdiff
path: root/tests/Tests
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Tests')
-rw-r--r--tests/Tests/Helpers.hs19
-rw-r--r--tests/Tests/Old.hs29
-rw-r--r--tests/Tests/Readers/Docx.hs27
-rw-r--r--tests/Tests/Readers/EPUB.hs6
-rw-r--r--tests/Tests/Readers/HTML.hs2
-rw-r--r--tests/Tests/Readers/LaTeX.hs3
-rw-r--r--tests/Tests/Readers/Markdown.hs22
-rw-r--r--tests/Tests/Readers/Odt.hs25
-rw-r--r--tests/Tests/Readers/Org.hs9
-rw-r--r--tests/Tests/Readers/RST.hs2
-rw-r--r--tests/Tests/Readers/Txt2Tags.hs15
-rw-r--r--tests/Tests/Shared.hs28
-rw-r--r--tests/Tests/Walk.hs46
-rw-r--r--tests/Tests/Writers/AsciiDoc.hs2
-rw-r--r--tests/Tests/Writers/ConTeXt.hs4
-rw-r--r--tests/Tests/Writers/Docbook.hs2
-rw-r--r--tests/Tests/Writers/Docx.hs14
-rw-r--r--tests/Tests/Writers/HTML.hs4
-rw-r--r--tests/Tests/Writers/LaTeX.hs10
-rw-r--r--tests/Tests/Writers/Markdown.hs17
-rw-r--r--tests/Tests/Writers/Native.hs4
-rw-r--r--tests/Tests/Writers/Plain.hs2
-rw-r--r--tests/Tests/Writers/RST.hs6
-rw-r--r--tests/Tests/Writers/TEI.hs2
24 files changed, 129 insertions, 171 deletions
diff --git a/tests/Tests/Helpers.hs b/tests/Tests/Helpers.hs
index 69f40fe48..84c2394bc 100644
--- a/tests/Tests/Helpers.hs
+++ b/tests/Tests/Helpers.hs
@@ -3,6 +3,7 @@
module Tests.Helpers ( test
, (=?>)
+ , purely
, property
, ToString(..)
, ToPandoc(..)
@@ -11,11 +12,12 @@ module Tests.Helpers ( test
import Text.Pandoc.Definition
import Text.Pandoc.Builder (Inlines, Blocks, doc, plain)
+import Text.Pandoc.Class
import Test.Framework
import Test.Framework.Providers.HUnit
import Test.Framework.Providers.QuickCheck2
import Test.HUnit (assertBool)
-import Text.Pandoc.Shared (normalize, trimr)
+import Text.Pandoc.Shared (trimr)
import Text.Pandoc.Options
import Text.Pandoc.Writers.Native (writeNative)
import qualified Test.QuickCheck.Property as QP
@@ -49,6 +51,9 @@ 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
+
infix 5 =?>
(=?>) :: a -> b -> (a,b)
x =?> y = (x, y)
@@ -57,17 +62,17 @@ class ToString a where
toString :: a -> String
instance ToString Pandoc where
- toString d = writeNative def{ writerTemplate = s } $ toPandoc d
+ toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d
where s = case d of
(Pandoc (Meta m) _)
| M.null m -> Nothing
| otherwise -> Just "" -- need this to get meta output
instance ToString Blocks where
- toString = writeNative def . toPandoc
+ toString = purely (writeNative def) . toPandoc
instance ToString Inlines where
- toString = trimr . writeNative def . toPandoc
+ toString = trimr . purely (writeNative def) . toPandoc
instance ToString String where
toString = id
@@ -76,10 +81,10 @@ class ToPandoc a where
toPandoc :: a -> Pandoc
instance ToPandoc Pandoc where
- toPandoc = normalize
+ toPandoc = id
instance ToPandoc Blocks where
- toPandoc = normalize . doc
+ toPandoc = doc
instance ToPandoc Inlines where
- toPandoc = normalize . doc . plain
+ toPandoc = doc . plain
diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs
index ef21990ba..f22636747 100644
--- a/tests/Tests/Old.hs
+++ b/tests/Tests/Old.hs
@@ -11,15 +11,10 @@ import System.FilePath ( (</>), (<.>), takeDirectory, splitDirectories,
import System.Directory
import System.Exit
import Data.Algorithm.Diff
-import Text.Pandoc.Shared ( normalize )
-import Text.Pandoc.Options
-import Text.Pandoc.Writers.Native ( writeNative )
-import Text.Pandoc.Readers.Native ( readNative )
import Prelude hiding ( readFile )
import qualified Data.ByteString.Lazy as B
import Text.Pandoc.UTF8 (toStringLazy)
import Text.Printf
-import Text.Pandoc.Error
readFileUTF8 :: FilePath -> IO String
readFileUTF8 f = B.readFile f >>= return . toStringLazy
@@ -52,13 +47,13 @@ tests = [ testGroup "markdown"
[ testGroup "writer"
$ writerTests "markdown" ++ lhsWriterTests "markdown"
, testGroup "reader"
- [ test "basic" ["-r", "markdown", "-w", "native", "-s", "-S"]
+ [ test "basic" ["-r", "markdown", "-w", "native", "-s"]
"testsuite.txt" "testsuite.native"
, test "tables" ["-r", "markdown", "-w", "native", "--columns=80"]
"tables.txt" "tables.native"
, test "pipe tables" ["-r", "markdown", "-w", "native", "--columns=80"]
"pipe-tables.txt" "pipe-tables.native"
- , test "more" ["-r", "markdown", "-w", "native", "-s", "-S"]
+ , test "more" ["-r", "markdown", "-w", "native", "-s"]
"markdown-reader-more.txt" "markdown-reader-more.native"
, lhsReaderTest "markdown+lhs"
]
@@ -70,8 +65,8 @@ tests = [ testGroup "markdown"
, testGroup "rst"
[ testGroup "writer" (writerTests "rst" ++ lhsWriterTests "rst")
, testGroup "reader"
- [ test "basic" ["-r", "rst", "-w", "native",
- "-s", "-S", "--columns=80"] "rst-reader.rst" "rst-reader.native"
+ [ test "basic" ["-r", "rst+smart", "-w", "native",
+ "-s", "--columns=80"] "rst-reader.rst" "rst-reader.native"
, test "tables" ["-r", "rst", "-w", "native", "--columns=80"]
"tables.rst" "tables-rstsubset.native"
, lhsReaderTest "rst+lhs"
@@ -86,16 +81,17 @@ tests = [ testGroup "markdown"
]
]
, testGroup "html"
- [ testGroup "writer" (writerTests "html" ++ lhsWriterTests "html")
+ [ testGroup "writer" (writerTests "html4" ++ writerTests "html5" ++
+ lhsWriterTests "html")
, test "reader" ["-r", "html", "-w", "native", "-s"]
"html-reader.html" "html-reader.native"
]
, testGroup "s5"
[ s5WriterTest "basic" ["-s"] "s5"
, s5WriterTest "fancy" ["-s","-m","-i"] "s5"
- , s5WriterTest "fragment" [] "html"
+ , s5WriterTest "fragment" [] "html4"
, s5WriterTest "inserts" ["-s", "-H", "insert",
- "-B", "insert", "-A", "insert", "-c", "main.css"] "html"
+ "-B", "insert", "-A", "insert", "-c", "main.css"] "html4"
]
, testGroup "textile"
[ testGroup "writer" $ writerTests "textile"
@@ -103,7 +99,7 @@ tests = [ testGroup "markdown"
"textile-reader.textile" "textile-reader.native"
]
, testGroup "docbook"
- [ testGroup "writer" $ writerTests "docbook"
+ [ testGroup "writer" $ writerTests "docbook4"
, test "reader" ["-r", "docbook", "-w", "native", "-s"]
"docbook-reader.docbook" "docbook-reader.native"
, test "reader" ["-r", "docbook", "-w", "native", "-s"]
@@ -193,10 +189,9 @@ lhsWriterTests format
lhsReaderTest :: String -> Test
lhsReaderTest format =
- testWithNormalize normalizer "lhs" ["-r", format, "-w", "native"]
+ test "lhs" ["-r", format, "-w", "native"]
("lhs-test" <.> format) norm
- where normalizer = writeNative def . normalize . handleError . readNative
- norm = if format == "markdown+lhs"
+ where norm = if format == "markdown+lhs"
then "lhs-test-markdown.native"
else "lhs-test.native"
@@ -259,7 +254,7 @@ testWithNormalize normalizer testname opts inp norm = testCase testname $ do
(outputPath, hOut) <- openTempFile "" "pandoc-test"
let inpPath = inp
let normPath = norm
- let options = ["--data-dir", ".." </> "data"] ++ [inpPath] ++ opts
+ let options = ["--quiet", "--data-dir", ".." </> "data"] ++ [inpPath] ++ opts
let cmd = pandocPath ++ " " ++ unwords options
let findDynlibDir [] = Nothing
findDynlibDir ("build":xs) = Just $ joinPath (reverse xs) </> "build"
diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs
index 0d31eb629..8ced43907 100644
--- a/tests/Tests/Readers/Docx.hs
+++ b/tests/Tests/Readers/Docx.hs
@@ -1,19 +1,17 @@
module Tests.Readers.Docx (tests) where
-import Text.Pandoc.Options
-import Text.Pandoc.Readers.Native
-import Text.Pandoc.Definition
+import Text.Pandoc
import Tests.Helpers
import Test.Framework
import Test.HUnit (assertBool)
import Test.Framework.Providers.HUnit
import qualified Data.ByteString.Lazy as B
-import Text.Pandoc.Readers.Docx
import Text.Pandoc.Writers.Native (writeNative)
import qualified Data.Map as M
import Text.Pandoc.MediaBag (MediaBag, lookupMedia, mediaDirectory)
import Codec.Archive.Zip
-import Text.Pandoc.Error
+import Text.Pandoc.Class (runIOorExplode)
+import qualified Text.Pandoc.Class as P
-- We define a wrapper around pandoc that doesn't normalize in the
-- tests. Since we do our own normalization, we want to make sure
@@ -25,8 +23,11 @@ data NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc}
noNorm :: Pandoc -> NoNormPandoc
noNorm = NoNormPandoc
+defopts :: ReaderOptions
+defopts = def{ readerExtensions = getDefaultExtensions "docx" }
+
instance ToString NoNormPandoc where
- toString d = writeNative def{ writerTemplate = s } $ toPandoc d
+ toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d
where s = case d of
NoNormPandoc (Pandoc (Meta m) _)
| M.null m -> Nothing
@@ -42,8 +43,9 @@ compareOutput :: ReaderOptions
compareOutput opts docxFile nativeFile = do
df <- B.readFile docxFile
nf <- Prelude.readFile nativeFile
- let (p, _) = handleError $ readDocx opts df
- return $ (noNorm p, noNorm (handleError $ readNative nf))
+ p <- runIOorExplode $ readDocx opts df
+ df' <- runIOorExplode $ readNative def nf
+ return $ (noNorm p, noNorm df')
testCompareWithOptsIO :: ReaderOptions -> String -> FilePath -> FilePath -> IO Test
testCompareWithOptsIO opts name docxFile nativeFile = do
@@ -55,12 +57,13 @@ testCompareWithOpts opts name docxFile nativeFile =
buildTest $ testCompareWithOptsIO opts name docxFile nativeFile
testCompare :: String -> FilePath -> FilePath -> Test
-testCompare = testCompareWithOpts def
+testCompare = testCompareWithOpts defopts
testForWarningsWithOptsIO :: ReaderOptions -> String -> FilePath -> [String] -> IO Test
testForWarningsWithOptsIO opts name docxFile expected = do
df <- B.readFile docxFile
- let (_, _, warns) = handleError $ readDocxWithWarnings opts df
+ logs <- runIOorExplode (readDocx opts df >> P.getLog)
+ let warns = [s | (WARNING, s) <- logs]
return $ test id name (unlines warns, unlines expected)
testForWarningsWithOpts :: ReaderOptions -> String -> FilePath -> [String] -> Test
@@ -68,7 +71,7 @@ testForWarningsWithOpts opts name docxFile expected =
buildTest $ testForWarningsWithOptsIO opts name docxFile expected
-- testForWarnings :: String -> FilePath -> [String] -> Test
--- testForWarnings = testForWarningsWithOpts def
+-- testForWarnings = testForWarningsWithOpts defopts
getMedia :: FilePath -> FilePath -> IO (Maybe B.ByteString)
getMedia archivePath mediaPath = do
@@ -93,7 +96,7 @@ compareMediaPathIO mediaPath mediaBag docxPath = do
compareMediaBagIO :: FilePath -> IO Bool
compareMediaBagIO docxFile = do
df <- B.readFile docxFile
- let (_, mb) = handleError $ readDocx def df
+ mb <- runIOorExplode (readDocx defopts df >> P.getMediaBag)
bools <- mapM
(\(fp, _, _) -> compareMediaPathIO fp mb docxFile)
(mediaDirectory mb)
diff --git a/tests/Tests/Readers/EPUB.hs b/tests/Tests/Readers/EPUB.hs
index 2ad36eba6..9190671c3 100644
--- a/tests/Tests/Readers/EPUB.hs
+++ b/tests/Tests/Readers/EPUB.hs
@@ -7,10 +7,12 @@ import Test.Framework.Providers.HUnit
import qualified Data.ByteString.Lazy as BL
import Text.Pandoc.Readers.EPUB
import Text.Pandoc.MediaBag (MediaBag, mediaDirectory)
-import Text.Pandoc.Error
+import qualified Text.Pandoc.Class as P
getMediaBag :: FilePath -> IO MediaBag
-getMediaBag fp = snd . handleError . readEPUB def <$> BL.readFile fp
+getMediaBag fp = do
+ bs <- BL.readFile fp
+ snd <$> (P.runIOorExplode $ P.withMediaBag $ readEPUB def bs)
testMediaBag :: FilePath -> [(String, String, Int)] -> IO ()
testMediaBag fp bag = do
diff --git a/tests/Tests/Readers/HTML.hs b/tests/Tests/Readers/HTML.hs
index 1426a8bea..a1533e42a 100644
--- a/tests/Tests/Readers/HTML.hs
+++ b/tests/Tests/Readers/HTML.hs
@@ -9,7 +9,7 @@ import Text.Pandoc.Builder
import Text.Pandoc
html :: String -> Pandoc
-html = handleError . readHtml def
+html = purely $ readHtml def
tests :: [Test]
tests = [ testGroup "base tag"
diff --git a/tests/Tests/Readers/LaTeX.hs b/tests/Tests/Readers/LaTeX.hs
index 27e775724..d8572b15b 100644
--- a/tests/Tests/Readers/LaTeX.hs
+++ b/tests/Tests/Readers/LaTeX.hs
@@ -9,7 +9,8 @@ import Text.Pandoc.Builder
import Text.Pandoc
latex :: String -> Pandoc
-latex = handleError . readLaTeX def
+latex = purely $ readLaTeX def{
+ readerExtensions = getDefaultExtensions "latex" }
infix 4 =:
(=:) :: ToString c
diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs
index 439307dc9..65edf7c38 100644
--- a/tests/Tests/Readers/Markdown.hs
+++ b/tests/Tests/Readers/Markdown.hs
@@ -6,21 +6,23 @@ import Test.Framework
import Tests.Helpers
import Text.Pandoc.Arbitrary()
import Text.Pandoc.Builder
-import qualified Data.Set as Set
import Text.Pandoc
markdown :: String -> Pandoc
-markdown = handleError . readMarkdown def
+markdown = purely $ readMarkdown def { readerExtensions =
+ disableExtension Ext_smart pandocExtensions }
markdownSmart :: String -> Pandoc
-markdownSmart = handleError . readMarkdown def { readerSmart = True }
+markdownSmart = purely $ readMarkdown def { readerExtensions =
+ enableExtension Ext_smart pandocExtensions }
markdownCDL :: String -> Pandoc
-markdownCDL = handleError . readMarkdown def { readerExtensions = Set.insert
- Ext_compact_definition_lists $ readerExtensions def }
+markdownCDL = purely $ readMarkdown def { readerExtensions = enableExtension
+ Ext_compact_definition_lists pandocExtensions }
markdownGH :: String -> Pandoc
-markdownGH = handleError . readMarkdown def { readerExtensions = githubMarkdownExtensions }
+markdownGH = purely $ readMarkdown def {
+ readerExtensions = githubMarkdownExtensions }
infix 4 =:
(=:) :: ToString c
@@ -29,8 +31,8 @@ infix 4 =:
testBareLink :: (String, Inlines) -> Test
testBareLink (inp, ils) =
- test (handleError . readMarkdown def{ readerExtensions =
- Set.fromList [Ext_autolink_bare_uris, Ext_raw_html] })
+ test (purely $ readMarkdown def{ readerExtensions =
+ extensionsFromList [Ext_autolink_bare_uris, Ext_raw_html] })
inp (inp, doc $ para ils)
autolink :: String -> Inlines
@@ -303,8 +305,8 @@ tests = [ testGroup "inline code"
=?> para (note (para "See [^1]"))
]
, testGroup "lhs"
- [ test (handleError . readMarkdown def{ readerExtensions = Set.insert
- Ext_literate_haskell $ readerExtensions def })
+ [ test (purely $ readMarkdown def{ readerExtensions = enableExtension
+ Ext_literate_haskell pandocExtensions })
"inverse bird tracks and html" $
"> a\n\n< b\n\n<div>\n"
=?> codeBlockWith ("",["sourceCode","literate","haskell"],[]) "a"
diff --git a/tests/Tests/Readers/Odt.hs b/tests/Tests/Readers/Odt.hs
index 56711c76b..63283497b 100644
--- a/tests/Tests/Readers/Odt.hs
+++ b/tests/Tests/Readers/Odt.hs
@@ -1,17 +1,16 @@
module Tests.Readers.Odt (tests) where
import Control.Monad ( liftM )
-import Text.Pandoc.Options
-import Text.Pandoc.Readers.Native
-import Text.Pandoc.Readers.Markdown
-import Text.Pandoc.Definition
+import Text.Pandoc
+import Text.Pandoc.Class (runIO)
import Tests.Helpers
import Test.Framework
import qualified Data.ByteString.Lazy as B
-import Text.Pandoc.Readers.Odt
import Text.Pandoc.Writers.Native (writeNative)
import qualified Data.Map as M
-import Text.Pandoc.Error
+
+defopts :: ReaderOptions
+defopts = def{ readerExtensions = getDefaultExtensions "odt" }
tests :: [Test]
tests = testsComparingToMarkdown ++ testsComparingToNative
@@ -41,7 +40,7 @@ newtype NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc}
deriving ( Show )
instance ToString NoNormPandoc where
- toString d = writeNative def{ writerTemplate = s } $ toPandoc d
+ toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d
where s = case d of
NoNormPandoc (Pandoc (Meta m) _)
| M.null m -> Nothing
@@ -62,16 +61,18 @@ compareOdtToNative :: TestCreator
compareOdtToNative opts odtPath nativePath = do
nativeFile <- Prelude.readFile nativePath
odtFile <- B.readFile odtPath
- let native = getNoNormVia id "native" $ readNative nativeFile
- let odt = getNoNormVia fst "odt" $ readOdt opts odtFile
+ native <- getNoNormVia id "native" <$> runIO (readNative def nativeFile)
+ odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile)
return (odt,native)
compareOdtToMarkdown :: TestCreator
compareOdtToMarkdown opts odtPath markdownPath = do
markdownFile <- Prelude.readFile markdownPath
odtFile <- B.readFile odtPath
- let markdown = getNoNormVia id "markdown" $ readMarkdown opts markdownFile
- let odt = getNoNormVia fst "odt" $ readOdt opts odtFile
+ markdown <- getNoNormVia id "markdown" <$>
+ runIO (readMarkdown def{ readerExtensions = pandocExtensions }
+ markdownFile)
+ odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile)
return (odt,markdown)
@@ -80,7 +81,7 @@ createTest :: TestCreator
-> FilePath -> FilePath
-> Test
createTest creator name path1 path2 =
- buildTest $ liftM (test id name) (creator def path1 path2)
+ buildTest $ liftM (test id name) (creator defopts path1 path2)
{-
--
diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs
index 72b7e2601..ef0530b37 100644
--- a/tests/Tests/Readers/Org.hs
+++ b/tests/Tests/Readers/Org.hs
@@ -9,10 +9,11 @@ import Text.Pandoc
import Data.List (intersperse)
org :: String -> Pandoc
-org = handleError . readOrg def
-
+org = purely $ readOrg def{ readerExtensions = getDefaultExtensions "org" }
+
orgSmart :: String -> Pandoc
-orgSmart = handleError . readOrg def { readerSmart = True }
+orgSmart = purely $ readOrg def { readerExtensions =
+ enableExtension Ext_smart $ getDefaultExtensions "org" }
infix 4 =:
(=:) :: ToString c
@@ -1525,7 +1526,7 @@ tests =
, ""
, "#+RESULTS:"
, ": 65" ] =?>
- rawBlock "html" ""
+ (mempty :: Blocks)
, "Source block with toggling header arguments" =:
unlines [ "#+BEGIN_SRC sh :noeval"
diff --git a/tests/Tests/Readers/RST.hs b/tests/Tests/Readers/RST.hs
index 9ecbb7af7..464720496 100644
--- a/tests/Tests/Readers/RST.hs
+++ b/tests/Tests/Readers/RST.hs
@@ -9,7 +9,7 @@ import Text.Pandoc.Builder
import Text.Pandoc
rst :: String -> Pandoc
-rst = handleError . readRST def{ readerStandalone = True }
+rst = purely $ readRST def{ readerStandalone = True }
infix 4 =:
(=:) :: ToString c
diff --git a/tests/Tests/Readers/Txt2Tags.hs b/tests/Tests/Readers/Txt2Tags.hs
index 1bda32a49..46831d86f 100644
--- a/tests/Tests/Readers/Txt2Tags.hs
+++ b/tests/Tests/Readers/Txt2Tags.hs
@@ -8,10 +8,17 @@ import Text.Pandoc.Arbitrary()
import Text.Pandoc.Builder
import Text.Pandoc
import Data.List (intersperse)
-import Text.Pandoc.Readers.Txt2Tags
+import Text.Pandoc.Class
+
t2t :: String -> Pandoc
-t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def
+-- t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def
+t2t = purely $ \s -> do
+ putCommonState
+ def { stInputFiles = Just ["in"]
+ , stOutputFile = Just "out"
+ }
+ readTxt2Tags def s
infix 4 =:
(=:) :: ToString c
@@ -78,10 +85,10 @@ tests =
, "Macros: Date" =:
"%%date" =?>
- para "date"
+ para "1970-01-01"
, "Macros: Mod Time" =:
"%%mtime" =?>
- para "mtime"
+ para (str "")
, "Macros: Infile" =:
"%%infile" =?>
para "in"
diff --git a/tests/Tests/Shared.hs b/tests/Tests/Shared.hs
index 55f520433..9b9aeb6a3 100644
--- a/tests/Tests/Shared.hs
+++ b/tests/Tests/Shared.hs
@@ -1,9 +1,7 @@
module Tests.Shared (tests) where
-import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Test.Framework
-import Tests.Helpers
import Text.Pandoc.Arbitrary()
import Test.Framework.Providers.HUnit
import Test.HUnit ( assertBool, (@?=) )
@@ -11,33 +9,15 @@ import Text.Pandoc.Builder
import System.FilePath.Posix (joinPath)
tests :: [Test]
-tests = [ testGroup "normalize"
- [ property "p_normalize_blocks_rt" p_normalize_blocks_rt
- , property "p_normalize_inlines_rt" p_normalize_inlines_rt
- , property "p_normalize_no_trailing_spaces"
- p_normalize_no_trailing_spaces
- ]
- , testGroup "compactify'DL"
- [ testCase "compactify'DL with empty def" $
- assertBool "compactify'DL"
+tests = [ testGroup "compactifyDL"
+ [ testCase "compactifyDL with empty def" $
+ assertBool "compactifyDL"
(let x = [(str "word", [para (str "def"), mempty])]
- in compactify'DL x == x)
+ in compactifyDL x == x)
]
, testGroup "collapseFilePath" testCollapse
]
-p_normalize_blocks_rt :: [Block] -> Bool
-p_normalize_blocks_rt bs =
- normalizeBlocks bs == normalizeBlocks (normalizeBlocks bs)
-
-p_normalize_inlines_rt :: [Inline] -> Bool
-p_normalize_inlines_rt ils =
- normalizeInlines ils == normalizeInlines (normalizeInlines ils)
-
-p_normalize_no_trailing_spaces :: [Inline] -> Bool
-p_normalize_no_trailing_spaces ils = null ils' || last ils' /= Space
- where ils' = normalizeInlines $ ils ++ [Space]
-
testCollapse :: [Test]
testCollapse = map (testCase "collapse")
[ (collapseFilePath (joinPath [ ""]) @?= (joinPath [ ""]))
diff --git a/tests/Tests/Walk.hs b/tests/Tests/Walk.hs
deleted file mode 100644
index 876d75e30..000000000
--- a/tests/Tests/Walk.hs
+++ /dev/null
@@ -1,46 +0,0 @@
-{-# LANGUAGE ScopedTypeVariables, FlexibleContexts #-}
-module Tests.Walk (tests) where
-
-import Text.Pandoc.Definition
-import Text.Pandoc.Walk
-import Test.Framework
-import Tests.Helpers
-import Data.Char (toUpper)
-import Text.Pandoc.Arbitrary()
-import Data.Generics
-
-tests :: [Test]
-tests = [ testGroup "Walk"
- [ property "p_walk inlineTrans" (p_walk inlineTrans)
- , property "p_walk blockTrans" (p_walk blockTrans)
- , property "p_query inlineQuery" (p_query inlineQuery)
- , property "p_query blockQuery" (p_query blockQuery)
- ]
- ]
-
-p_walk :: (Typeable a, Walkable a Pandoc)
- => (a -> a) -> Pandoc -> Bool
-p_walk f d = everywhere (mkT f) d == walk f d
-
-p_query :: (Eq a, Typeable a1, Monoid a, Walkable a1 Pandoc)
- => (a1 -> a) -> Pandoc -> Bool
-p_query f d = everything mappend (mempty `mkQ` f) d == query f d
-
-inlineTrans :: Inline -> Inline
-inlineTrans (Str xs) = Str $ map toUpper xs
-inlineTrans (Emph xs) = Strong xs
-inlineTrans x = x
-
-blockTrans :: Block -> Block
-blockTrans (Plain xs) = Para xs
-blockTrans (BlockQuote xs) = Div ("",["special"],[]) xs
-blockTrans x = x
-
-inlineQuery :: Inline -> String
-inlineQuery (Str xs) = xs
-inlineQuery _ = ""
-
-blockQuery :: Block -> [Int]
-blockQuery (Header lev _ _) = [lev]
-blockQuery _ = []
-
diff --git a/tests/Tests/Writers/AsciiDoc.hs b/tests/Tests/Writers/AsciiDoc.hs
index 8ab216753..7103b838b 100644
--- a/tests/Tests/Writers/AsciiDoc.hs
+++ b/tests/Tests/Writers/AsciiDoc.hs
@@ -7,7 +7,7 @@ import Tests.Helpers
import Text.Pandoc.Arbitrary()
asciidoc :: (ToPandoc a) => a -> String
-asciidoc = writeAsciiDoc def{ writerWrapText = WrapNone } . toPandoc
+asciidoc = purely (writeAsciiDoc def{ writerWrapText = WrapNone }) . toPandoc
tests :: [Test]
tests = [ testGroup "emphasis"
diff --git a/tests/Tests/Writers/ConTeXt.hs b/tests/Tests/Writers/ConTeXt.hs
index 629e58b8f..b3e12a571 100644
--- a/tests/Tests/Writers/ConTeXt.hs
+++ b/tests/Tests/Writers/ConTeXt.hs
@@ -8,10 +8,10 @@ import Tests.Helpers
import Text.Pandoc.Arbitrary()
context :: (ToPandoc a) => a -> String
-context = writeConTeXt def . toPandoc
+context = purely (writeConTeXt def) . toPandoc
context' :: (ToPandoc a) => a -> String
-context' = writeConTeXt def{ writerWrapText = WrapNone } . toPandoc
+context' = purely (writeConTeXt def{ writerWrapText = WrapNone }) . toPandoc
{-
"my test" =: X =?> Y
diff --git a/tests/Tests/Writers/Docbook.hs b/tests/Tests/Writers/Docbook.hs
index a288242dc..f34f2495c 100644
--- a/tests/Tests/Writers/Docbook.hs
+++ b/tests/Tests/Writers/Docbook.hs
@@ -11,7 +11,7 @@ docbook :: (ToPandoc a) => a -> String
docbook = docbookWithOpts def{ writerWrapText = WrapNone }
docbookWithOpts :: ToPandoc a => WriterOptions -> a -> String
-docbookWithOpts opts = writeDocbook opts . toPandoc
+docbookWithOpts opts = purely (writeDocbook4 opts) . toPandoc
{-
"my test" =: X =?> Y
diff --git a/tests/Tests/Writers/Docx.hs b/tests/Tests/Writers/Docx.hs
index 31fc3a47b..fd320d224 100644
--- a/tests/Tests/Writers/Docx.hs
+++ b/tests/Tests/Writers/Docx.hs
@@ -7,8 +7,8 @@ import Tests.Helpers
import Test.Framework
import Text.Pandoc.Readers.Docx
import Text.Pandoc.Writers.Docx
-import Text.Pandoc.Error
import System.FilePath ((</>))
+import Text.Pandoc.Class (runIOorExplode)
type Options = (WriterOptions, ReaderOptions)
@@ -20,10 +20,12 @@ compareOutput opts nativeFileIn nativeFileOut = do
nf <- Prelude.readFile nativeFileIn
nf' <- Prelude.readFile nativeFileOut
let wopts = fst opts
- df <- writeDocx wopts{writerUserDataDir = Just (".." </> "data")}
- (handleError $ readNative nf)
- let (p, _) = handleError $ readDocx (snd opts) df
- return (p, handleError $ readNative nf')
+ df <- runIOorExplode $ do
+ d <- readNative def nf
+ writeDocx wopts{writerUserDataDir = Just (".." </> "data")} d
+ df' <- runIOorExplode (readNative def nf')
+ p <- runIOorExplode $ readDocx (snd opts) df
+ return (p, df')
testCompareWithOptsIO :: Options -> String -> FilePath -> FilePath -> IO Test
testCompareWithOptsIO opts name nativeFileIn nativeFileOut = do
@@ -139,7 +141,7 @@ tests = [ testGroup "inlines"
]
, testGroup "customized styles"
[ testCompareWithOpts
- ( def{writerReferenceDocx=Just "docx/custom-style-reference.docx"}
+ ( def{writerReferenceDoc=Just "docx/custom-style-reference.docx"}
, def)
"simple customized blocks and inlines"
"docx/custom-style-roundtrip-start.native"
diff --git a/tests/Tests/Writers/HTML.hs b/tests/Tests/Writers/HTML.hs
index 5bea99f71..45de2b042 100644
--- a/tests/Tests/Writers/HTML.hs
+++ b/tests/Tests/Writers/HTML.hs
@@ -8,7 +8,7 @@ import Tests.Helpers
import Text.Pandoc.Arbitrary()
html :: (ToPandoc a) => a -> String
-html = writeHtmlString def{ writerWrapText = WrapNone } . toPandoc
+html = purely (writeHtml4String def{ writerWrapText = WrapNone }) . toPandoc
{-
"my test" =: X =?> Y
@@ -31,7 +31,7 @@ tests :: [Test]
tests = [ testGroup "inline code"
[ "basic" =: code "@&" =?> "<code>@&amp;</code>"
, "haskell" =: codeWith ("",["haskell"],[]) ">>="
- =?> "<code class=\"haskell\">&gt;&gt;=</code>"
+ =?> "<code class=\"sourceCode haskell\"><span class=\"fu\">&gt;&gt;=</span></code>"
, "nolanguage" =: codeWith ("",["nolanguage"],[]) ">>="
=?> "<code class=\"nolanguage\">&gt;&gt;=</code>"
]
diff --git a/tests/Tests/Writers/LaTeX.hs b/tests/Tests/Writers/LaTeX.hs
index f140cc2dd..f54aef4dc 100644
--- a/tests/Tests/Writers/LaTeX.hs
+++ b/tests/Tests/Writers/LaTeX.hs
@@ -8,13 +8,16 @@ import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
latex :: (ToPandoc a) => a -> String
-latex = latexWithOpts def{ writerHighlight = True }
+latex = latexWithOpts def
latexListing :: (ToPandoc a) => a -> String
latexListing = latexWithOpts def{ writerListings = True }
latexWithOpts :: (ToPandoc a) => WriterOptions -> a -> String
-latexWithOpts opts = writeLaTeX opts . toPandoc
+latexWithOpts opts = purely (writeLaTeX opts) . toPandoc
+
+beamerWithOpts :: (ToPandoc a) => WriterOptions -> a -> String
+beamerWithOpts opts = purely (writeBeamer opts) . toPandoc
{-
"my test" =: X =?> Y
@@ -95,8 +98,7 @@ tests = [ testGroup "code blocks"
beamerTopLevelDiv :: (ToPandoc a)
=> TopLevelDivision -> a -> String
beamerTopLevelDiv division =
- latexWithOpts def { writerTopLevelDivision = division
- , writerBeamer = True }
+ beamerWithOpts def { writerTopLevelDivision = division }
in
[ test (latexTopLevelDiv TopLevelSection)
"sections as top-level" $ headers =?>
diff --git a/tests/Tests/Writers/Markdown.hs b/tests/Tests/Writers/Markdown.hs
index aab916b38..abefe27d5 100644
--- a/tests/Tests/Writers/Markdown.hs
+++ b/tests/Tests/Writers/Markdown.hs
@@ -8,11 +8,14 @@ import Text.Pandoc
import Tests.Helpers
import Text.Pandoc.Arbitrary()
+defopts :: WriterOptions
+defopts = def{ writerExtensions = pandocExtensions }
+
markdown :: (ToPandoc a) => a -> String
-markdown = writeMarkdown def . toPandoc
+markdown = purely (writeMarkdown defopts) . toPandoc
markdownWithOpts :: (ToPandoc a) => WriterOptions -> a -> String
-markdownWithOpts opts x = writeMarkdown opts $ toPandoc x
+markdownWithOpts opts x = purely (writeMarkdown opts) $ toPandoc x
{-
"my test" =: X =?> Y
@@ -84,7 +87,7 @@ noteTestDoc =
noteTests :: Test
noteTests = testGroup "note and reference location"
- [ test (markdownWithOpts def)
+ [ test (markdownWithOpts defopts)
"footnotes at the end of a document" $
noteTestDoc =?>
(unlines $ [ "First Header"
@@ -105,7 +108,7 @@ noteTests = testGroup "note and reference location"
, ""
, "[^2]: The second note."
])
- , test (markdownWithOpts def{writerReferenceLocation=EndOfBlock})
+ , test (markdownWithOpts defopts{writerReferenceLocation=EndOfBlock})
"footnotes at the end of blocks" $
noteTestDoc =?>
(unlines $ [ "First Header"
@@ -126,7 +129,7 @@ noteTests = testGroup "note and reference location"
, ""
, "Some more text."
])
- , test (markdownWithOpts def{writerReferenceLocation=EndOfBlock, writerReferenceLinks=True})
+ , test (markdownWithOpts defopts{writerReferenceLocation=EndOfBlock, writerReferenceLinks=True})
"footnotes and reference links at the end of blocks" $
noteTestDoc =?>
(unlines $ [ "First Header"
@@ -149,7 +152,7 @@ noteTests = testGroup "note and reference location"
, ""
, "Some more text."
])
- , test (markdownWithOpts def{writerReferenceLocation=EndOfSection})
+ , test (markdownWithOpts defopts{writerReferenceLocation=EndOfSection})
"footnotes at the end of section" $
noteTestDoc =?>
(unlines $ [ "First Header"
@@ -179,7 +182,7 @@ shortcutLinkRefsTests =
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
- (=:) = test (writeMarkdown (def {writerReferenceLinks = True}) . toPandoc)
+ (=:) = test (purely (writeMarkdown defopts{writerReferenceLinks = True}) . toPandoc)
in testGroup "Shortcut reference links"
[ "Simple link (shortcutable)"
=: (para (link "/url" "title" "foo"))
diff --git a/tests/Tests/Writers/Native.hs b/tests/Tests/Writers/Native.hs
index 7ec43b339..88bad7944 100644
--- a/tests/Tests/Writers/Native.hs
+++ b/tests/Tests/Writers/Native.hs
@@ -8,11 +8,11 @@ import Text.Pandoc.Arbitrary()
p_write_rt :: Pandoc -> Bool
p_write_rt d =
- read (writeNative def{ writerTemplate = Just "" } d) == d
+ read (purely (writeNative def{ writerTemplate = Just "" }) d) == d
p_write_blocks_rt :: [Block] -> Bool
p_write_blocks_rt bs = length bs > 20 ||
- read (writeNative def (Pandoc nullMeta bs)) ==
+ read (purely (writeNative def) (Pandoc nullMeta bs)) ==
bs
tests :: [Test]
diff --git a/tests/Tests/Writers/Plain.hs b/tests/Tests/Writers/Plain.hs
index 42f77e3ec..bead6857c 100644
--- a/tests/Tests/Writers/Plain.hs
+++ b/tests/Tests/Writers/Plain.hs
@@ -11,7 +11,7 @@ import Text.Pandoc.Arbitrary()
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
-(=:) = test (writePlain def . toPandoc)
+(=:) = test (purely (writePlain def) . toPandoc)
tests :: [Test]
diff --git a/tests/Tests/Writers/RST.hs b/tests/Tests/Writers/RST.hs
index 77dafeb4c..dd55580c9 100644
--- a/tests/Tests/Writers/RST.hs
+++ b/tests/Tests/Writers/RST.hs
@@ -10,7 +10,7 @@ import Text.Pandoc.Arbitrary()
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
-(=:) = test (writeRST def{ writerHighlight = True } . toPandoc)
+(=:) = test (purely (writeRST def . toPandoc))
tests :: [Test]
tests = [ testGroup "rubrics"
@@ -47,7 +47,7 @@ tests = [ testGroup "rubrics"
[ "foo"
, "==="]
-- note: heading normalization is only done in standalone mode
- , test (writeRST def{ writerTemplate = Just "$body$\n" } . toPandoc)
+ , test (purely (writeRST def{ writerTemplate = Just "$body$\n" }) . toPandoc)
"heading levels" $
header 1 (text "Header 1") <>
header 3 (text "Header 2") <>
@@ -77,7 +77,7 @@ tests = [ testGroup "rubrics"
, ""
, "Header 2"
, "--------"]
- , test (writeRST def{ writerTemplate = Just "$body$\n" } . toPandoc)
+ , test (purely (writeRST def{ writerTemplate = Just "$body$\n" }) . toPandoc)
"minimal heading levels" $
header 2 (text "Header 1") <>
header 3 (text "Header 2") <>
diff --git a/tests/Tests/Writers/TEI.hs b/tests/Tests/Writers/TEI.hs
index 3eb8478b7..703f565bb 100644
--- a/tests/Tests/Writers/TEI.hs
+++ b/tests/Tests/Writers/TEI.hs
@@ -22,7 +22,7 @@ which is in turn shorthand for
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
=> String -> (a, String) -> Test
-(=:) = test (writeTEI def . toPandoc)
+(=:) = test (purely (writeTEI def) . toPandoc)
tests :: [Test]
tests = [ testGroup "block elements"