diff options
Diffstat (limited to 'tests')
-rw-r--r-- | tests/Tests/Old.hs | 3 | ||||
-rw-r--r-- | tests/Tests/Readers/Docx.hs | 7 | ||||
-rw-r--r-- | tests/Tests/Readers/EPUB.hs | 3 | ||||
-rw-r--r-- | tests/Tests/Readers/LaTeX.hs | 3 | ||||
-rw-r--r-- | tests/Tests/Readers/Markdown.hs | 13 | ||||
-rw-r--r-- | tests/Tests/Readers/Org.hs | 5 | ||||
-rw-r--r-- | tests/Tests/Readers/RST.hs | 3 | ||||
-rw-r--r-- | tests/Tests/Readers/Txt2Tags.hs | 3 | ||||
-rw-r--r-- | tests/Tests/Writers/Docx.hs | 7 |
9 files changed, 28 insertions, 19 deletions
diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs index 5bdf325b1..047ad0481 100644 --- a/tests/Tests/Old.hs +++ b/tests/Tests/Old.hs @@ -18,6 +18,7 @@ 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 @@ -182,7 +183,7 @@ lhsReaderTest :: String -> Test lhsReaderTest format = testWithNormalize normalizer "lhs" ["-r", format, "-w", "native"] ("lhs-test" <.> format) norm - where normalizer = writeNative def . normalize . readNative + where normalizer = writeNative def . normalize . handleError . readNative norm = if format == "markdown+lhs" then "lhs-test-markdown.native" else "lhs-test.native" diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs index 06e8a3a9c..47292bc99 100644 --- a/tests/Tests/Readers/Docx.hs +++ b/tests/Tests/Readers/Docx.hs @@ -13,6 +13,7 @@ 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 -- We define a wrapper around pandoc that doesn't normalize in the -- tests. Since we do our own normalization, we want to make sure @@ -41,8 +42,8 @@ compareOutput :: ReaderOptions compareOutput opts docxFile nativeFile = do df <- B.readFile docxFile nf <- Prelude.readFile nativeFile - let (p, _) = readDocx opts df - return $ (noNorm p, noNorm (readNative nf)) + let (p, _) = handleError $ readDocx opts df + return $ (noNorm p, noNorm (handleError $ readNative nf)) testCompareWithOptsIO :: ReaderOptions -> String -> FilePath -> FilePath -> IO Test testCompareWithOptsIO opts name docxFile nativeFile = do @@ -79,7 +80,7 @@ compareMediaPathIO mediaPath mediaBag docxPath = do compareMediaBagIO :: FilePath -> IO Bool compareMediaBagIO docxFile = do df <- B.readFile docxFile - let (_, mb) = readDocx def df + let (_, mb) = handleError $ readDocx def df bools <- mapM (\(fp, _, _) -> compareMediaPathIO fp mb docxFile) (mediaDirectory mb) diff --git a/tests/Tests/Readers/EPUB.hs b/tests/Tests/Readers/EPUB.hs index 0d19a8400..bfdaa45b7 100644 --- a/tests/Tests/Readers/EPUB.hs +++ b/tests/Tests/Readers/EPUB.hs @@ -9,9 +9,10 @@ import Text.Pandoc.Readers.EPUB import Text.Pandoc.MediaBag (MediaBag, mediaDirectory) import Control.Applicative import System.FilePath (joinPath) +import Text.Pandoc.Error getMediaBag :: FilePath -> IO MediaBag -getMediaBag fp = snd . readEPUB def <$> BL.readFile fp +getMediaBag fp = snd . handleError . readEPUB def <$> BL.readFile fp testMediaBag :: FilePath -> [(String, String, Int)] -> IO () testMediaBag fp bag = do diff --git a/tests/Tests/Readers/LaTeX.hs b/tests/Tests/Readers/LaTeX.hs index 47916b0c0..38363af59 100644 --- a/tests/Tests/Readers/LaTeX.hs +++ b/tests/Tests/Readers/LaTeX.hs @@ -8,9 +8,10 @@ import Tests.Arbitrary() import Text.Pandoc.Builder import Text.Pandoc import Data.Monoid (mempty) +import Text.Pandoc.Error latex :: String -> Pandoc -latex = readLaTeX def +latex = handleError . readLaTeX def infix 4 =: (=:) :: ToString c diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs index fdb1a7417..03884a8e5 100644 --- a/tests/Tests/Readers/Markdown.hs +++ b/tests/Tests/Readers/Markdown.hs @@ -9,19 +9,20 @@ import Text.Pandoc.Builder import qualified Data.Set as Set -- import Text.Pandoc.Shared ( normalize ) import Text.Pandoc +import Text.Pandoc.Error markdown :: String -> Pandoc -markdown = readMarkdown def +markdown = handleError . readMarkdown def markdownSmart :: String -> Pandoc -markdownSmart = readMarkdown def { readerSmart = True } +markdownSmart = handleError . readMarkdown def { readerSmart = True } markdownCDL :: String -> Pandoc -markdownCDL = readMarkdown def { readerExtensions = Set.insert +markdownCDL = handleError . readMarkdown def { readerExtensions = Set.insert Ext_compact_definition_lists $ readerExtensions def } markdownGH :: String -> Pandoc -markdownGH = readMarkdown def { readerExtensions = githubMarkdownExtensions } +markdownGH = handleError . readMarkdown def { readerExtensions = githubMarkdownExtensions } infix 4 =: (=:) :: ToString c @@ -30,7 +31,7 @@ infix 4 =: testBareLink :: (String, Inlines) -> Test testBareLink (inp, ils) = - test (readMarkdown def{ readerExtensions = + test (handleError . readMarkdown def{ readerExtensions = Set.fromList [Ext_autolink_bare_uris, Ext_raw_html] }) inp (inp, doc $ para ils) @@ -220,7 +221,7 @@ tests = [ testGroup "inline code" =?> para (note (para "See [^1]")) ] , testGroup "lhs" - [ test (readMarkdown def{ readerExtensions = Set.insert + [ test (handleError . readMarkdown def{ readerExtensions = Set.insert Ext_literate_haskell $ readerExtensions def }) "inverse bird tracks and html" $ "> a\n\n< b\n\n<div>\n" diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs index c373d52cc..f555447c7 100644 --- a/tests/Tests/Readers/Org.hs +++ b/tests/Tests/Readers/Org.hs @@ -8,12 +8,13 @@ import Text.Pandoc.Builder import Text.Pandoc import Data.List (intersperse) import Data.Monoid (mempty, mappend, mconcat) +import Text.Pandoc.Error org :: String -> Pandoc -org = readOrg def +org = handleError . readOrg def orgSmart :: String -> Pandoc -orgSmart = readOrg def { readerSmart = True } +orgSmart = handleError . readOrg def { readerSmart = True } infix 4 =: (=:) :: ToString c diff --git a/tests/Tests/Readers/RST.hs b/tests/Tests/Readers/RST.hs index 1aaf4897f..5eabec89a 100644 --- a/tests/Tests/Readers/RST.hs +++ b/tests/Tests/Readers/RST.hs @@ -7,10 +7,11 @@ import Tests.Helpers import Tests.Arbitrary() import Text.Pandoc.Builder import Text.Pandoc +import Text.Pandoc.Error import Data.Monoid (mempty) rst :: String -> Pandoc -rst = readRST def{ readerStandalone = True } +rst = handleError . readRST def{ readerStandalone = True } infix 4 =: (=:) :: ToString c diff --git a/tests/Tests/Readers/Txt2Tags.hs b/tests/Tests/Readers/Txt2Tags.hs index fd7c767e0..938a2b455 100644 --- a/tests/Tests/Readers/Txt2Tags.hs +++ b/tests/Tests/Readers/Txt2Tags.hs @@ -7,12 +7,13 @@ import Tests.Helpers import Tests.Arbitrary() import Text.Pandoc.Builder import Text.Pandoc +import Text.Pandoc.Error import Data.List (intersperse) import Data.Monoid (mempty, mconcat) import Text.Pandoc.Readers.Txt2Tags t2t :: String -> Pandoc -t2t s = readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def s +t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def infix 4 =: (=:) :: ToString c diff --git a/tests/Tests/Writers/Docx.hs b/tests/Tests/Writers/Docx.hs index 80ce0014d..068c5a935 100644 --- a/tests/Tests/Writers/Docx.hs +++ b/tests/Tests/Writers/Docx.hs @@ -7,6 +7,7 @@ import Tests.Helpers import Test.Framework import Text.Pandoc.Readers.Docx import Text.Pandoc.Writers.Docx +import Text.Pandoc.Error type Options = (WriterOptions, ReaderOptions) @@ -15,9 +16,9 @@ compareOutput :: Options -> IO (Pandoc, Pandoc) compareOutput opts nativeFile = do nf <- Prelude.readFile nativeFile - df <- writeDocx (fst opts) (readNative nf) - let (p, _) = readDocx (snd opts) df - return (p, readNative nf) + df <- writeDocx (fst opts) (handleError $ readNative nf) + let (p, _) = handleError $ readDocx (snd opts) df + return (p, handleError $ readNative nf) testCompareWithOptsIO :: Options -> String -> FilePath -> IO Test testCompareWithOptsIO opts name nativeFile = do |