aboutsummaryrefslogtreecommitdiff
path: root/tests/Tests/Readers
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Tests/Readers')
-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
9 files changed, 64 insertions, 47 deletions
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"