aboutsummaryrefslogtreecommitdiff
path: root/tests/Tests
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Tests')
-rw-r--r--tests/Tests/Old.hs4
-rw-r--r--tests/Tests/Readers/Docx.hs12
-rw-r--r--tests/Tests/Readers/LaTeX.hs3
-rw-r--r--tests/Tests/Readers/Markdown.hs12
-rw-r--r--tests/Tests/Readers/Odt.hs16
-rw-r--r--tests/Tests/Readers/Org.hs6
-rw-r--r--tests/Tests/Writers/Markdown.hs15
7 files changed, 38 insertions, 30 deletions
diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs
index f9a8a71d5..21e00b033 100644
--- a/tests/Tests/Old.hs
+++ b/tests/Tests/Old.hs
@@ -47,13 +47,13 @@ tests = [ testGroup "markdown"
[ testGroup "writer"
$ writerTests "markdown" ++ lhsWriterTests "markdown"
, testGroup "reader"
- [ test "basic" ["-r", "markdown+smart", "-w", "native", "-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+smart", "-w", "native", "-s"]
+ , test "more" ["-r", "markdown", "-w", "native", "-s"]
"markdown-reader-more.txt" "markdown-reader-more.native"
, lhsReaderTest "markdown+lhs"
]
diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs
index ef060b8ae..1fdb29f2e 100644
--- a/tests/Tests/Readers/Docx.hs
+++ b/tests/Tests/Readers/Docx.hs
@@ -1,7 +1,6 @@
module Tests.Readers.Docx (tests) where
-import Text.Pandoc.Options
-import Text.Pandoc.Readers.Native
+import Text.Pandoc
import Text.Pandoc.Definition
import Tests.Helpers
import Test.Framework
@@ -26,6 +25,9 @@ data NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc}
noNorm :: Pandoc -> NoNormPandoc
noNorm = NoNormPandoc
+defopts :: ReaderOptions
+defopts = def{ readerExtensions = getDefaultExtensions "docx" }
+
instance ToString NoNormPandoc where
toString d = purely (writeNative def{ writerTemplate = s }) $ toPandoc d
where s = case d of
@@ -57,7 +59,7 @@ 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
@@ -70,7 +72,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
@@ -95,7 +97,7 @@ compareMediaPathIO mediaPath mediaBag docxPath = do
compareMediaBagIO :: FilePath -> IO Bool
compareMediaBagIO docxFile = do
df <- B.readFile docxFile
- mb <- runIOorExplode (readDocx def df >> P.getMediaBag)
+ mb <- runIOorExplode (readDocx defopts df >> P.getMediaBag)
bools <- mapM
(\(fp, _, _) -> compareMediaPathIO fp mb docxFile)
(mediaDirectory mb)
diff --git a/tests/Tests/Readers/LaTeX.hs b/tests/Tests/Readers/LaTeX.hs
index 45e88d90e..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 = purely $ 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 ff68b4d3f..65edf7c38 100644
--- a/tests/Tests/Readers/Markdown.hs
+++ b/tests/Tests/Readers/Markdown.hs
@@ -9,18 +9,20 @@ import Text.Pandoc.Builder
import Text.Pandoc
markdown :: String -> Pandoc
-markdown = purely $ readMarkdown def
+markdown = purely $ readMarkdown def { readerExtensions =
+ disableExtension Ext_smart pandocExtensions }
markdownSmart :: String -> Pandoc
markdownSmart = purely $ readMarkdown def { readerExtensions =
- enableExtension Ext_smart $ readerExtensions def }
+ enableExtension Ext_smart pandocExtensions }
markdownCDL :: String -> Pandoc
markdownCDL = purely $ readMarkdown def { readerExtensions = enableExtension
- Ext_compact_definition_lists $ readerExtensions def }
+ Ext_compact_definition_lists pandocExtensions }
markdownGH :: String -> Pandoc
-markdownGH = purely $ readMarkdown def { readerExtensions = githubMarkdownExtensions }
+markdownGH = purely $ readMarkdown def {
+ readerExtensions = githubMarkdownExtensions }
infix 4 =:
(=:) :: ToString c
@@ -304,7 +306,7 @@ tests = [ testGroup "inline code"
]
, testGroup "lhs"
[ test (purely $ readMarkdown def{ readerExtensions = enableExtension
- Ext_literate_haskell $ readerExtensions def })
+ 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 b0e916336..63283497b 100644
--- a/tests/Tests/Readers/Odt.hs
+++ b/tests/Tests/Readers/Odt.hs
@@ -1,18 +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
@@ -71,7 +69,9 @@ compareOdtToMarkdown :: TestCreator
compareOdtToMarkdown opts odtPath markdownPath = do
markdownFile <- Prelude.readFile markdownPath
odtFile <- B.readFile odtPath
- markdown <- getNoNormVia id "markdown" <$> runIO (readMarkdown opts markdownFile)
+ markdown <- getNoNormVia id "markdown" <$>
+ runIO (readMarkdown def{ readerExtensions = pandocExtensions }
+ markdownFile)
odt <- getNoNormVia id "odt" <$> runIO (readOdt opts odtFile)
return (odt,markdown)
@@ -81,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 ed29f1377..ef0530b37 100644
--- a/tests/Tests/Readers/Org.hs
+++ b/tests/Tests/Readers/Org.hs
@@ -9,11 +9,11 @@ import Text.Pandoc
import Data.List (intersperse)
org :: String -> Pandoc
-org = purely $ readOrg def
-
+org = purely $ readOrg def{ readerExtensions = getDefaultExtensions "org" }
+
orgSmart :: String -> Pandoc
orgSmart = purely $ readOrg def { readerExtensions =
- enableExtension Ext_smart $ readerExtensions def }
+ enableExtension Ext_smart $ getDefaultExtensions "org" }
infix 4 =:
(=:) :: ToString c
diff --git a/tests/Tests/Writers/Markdown.hs b/tests/Tests/Writers/Markdown.hs
index aa8a732f1..abefe27d5 100644
--- a/tests/Tests/Writers/Markdown.hs
+++ b/tests/Tests/Writers/Markdown.hs
@@ -8,8 +8,11 @@ import Text.Pandoc
import Tests.Helpers
import Text.Pandoc.Arbitrary()
+defopts :: WriterOptions
+defopts = def{ writerExtensions = pandocExtensions }
+
markdown :: (ToPandoc a) => a -> String
-markdown = purely (writeMarkdown def) . toPandoc
+markdown = purely (writeMarkdown defopts) . toPandoc
markdownWithOpts :: (ToPandoc a) => WriterOptions -> a -> String
markdownWithOpts opts x = purely (writeMarkdown opts) $ toPandoc x
@@ -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 (purely (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"))