aboutsummaryrefslogtreecommitdiff
path: root/tests/Tests/Readers
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Tests/Readers')
-rw-r--r--tests/Tests/Readers/Docx.hs7
-rw-r--r--tests/Tests/Readers/EPUB.hs3
-rw-r--r--tests/Tests/Readers/LaTeX.hs42
-rw-r--r--tests/Tests/Readers/Markdown.hs13
-rw-r--r--tests/Tests/Readers/Org.hs27
-rw-r--r--tests/Tests/Readers/RST.hs3
-rw-r--r--tests/Tests/Readers/Txt2Tags.hs3
7 files changed, 84 insertions, 14 deletions
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 8ff23ebc1..38363af59 100644
--- a/tests/Tests/Readers/LaTeX.hs
+++ b/tests/Tests/Readers/LaTeX.hs
@@ -7,15 +7,21 @@ import Tests.Helpers
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
=> String -> (String, c) -> Test
(=:) = test latex
+simpleTable' :: [Alignment] -> [[Blocks]] -> Blocks
+simpleTable' aligns = table "" (zip aligns (repeat 0.0))
+ (map (const mempty) aligns)
+
tests :: [Test]
tests = [ testGroup "basic"
[ "simple" =:
@@ -62,6 +68,40 @@ tests = [ testGroup "basic"
"\\begin{lstlisting}\\end{lstlisting}" =?> codeBlock ""
]
+ , testGroup "tables"
+ [ "Single cell table" =:
+ "\\begin{tabular}{|l|}Test\\\\\\end{tabular}" =?>
+ simpleTable' [AlignLeft] [[plain "Test"]]
+ , "Multi cell table" =:
+ "\\begin{tabular}{|rl|}One & Two\\\\ \\end{tabular}" =?>
+ simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]]
+ , "Multi line table" =:
+ unlines [ "\\begin{tabular}{|c|}"
+ , "One\\\\"
+ , "Two\\\\"
+ , "Three\\\\"
+ , "\\end{tabular}" ] =?>
+ simpleTable' [AlignCenter]
+ [[plain "One"], [plain "Two"], [plain "Three"]]
+ , "Empty table" =:
+ "\\begin{tabular}{}\\end{tabular}" =?>
+ simpleTable' [] []
+ , "Table with fixed column width" =:
+ "\\begin{tabular}{|p{5cm}r|}One & Two\\\\ \\end{tabular}" =?>
+ simpleTable' [AlignLeft,AlignRight] [[plain "One", plain "Two"]]
+ , "Table with empty column separators" =:
+ "\\begin{tabular}{@{}r@{}l}One & Two\\\\ \\end{tabular}" =?>
+ simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]]
+ , "Table with custom column separators" =:
+ unlines [ "\\begin{tabular}{@{($\\to$)}r@{\\hspace{2cm}}l}"
+ , "One&Two\\\\"
+ , "\\end{tabular}" ] =?>
+ simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]]
+ , "Table with vertical alignment argument" =:
+ "\\begin{tabular}[t]{r|r}One & Two\\\\ \\end{tabular}" =?>
+ simpleTable' [AlignRight,AlignRight] [[plain "One", plain "Two"]]
+ ]
+
, testGroup "citations"
[ natbibCitations
, biblatexCitations
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 3a26861f0..4cec54a68 100644
--- a/tests/Tests/Readers/Org.hs
+++ b/tests/Tests/Readers/Org.hs
@@ -8,9 +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 = handleError . readOrg def { readerSmart = True }
infix 4 =:
(=:) :: ToString c
@@ -1156,4 +1160,25 @@ tests =
]
in codeBlockWith ( "", classes, params) "code body\n"
]
+ , testGroup "Smart punctuation"
+ [ test orgSmart "quote before ellipses"
+ ("'...hi'"
+ =?> para (singleQuoted "…hi"))
+
+ , test orgSmart "apostrophe before emph"
+ ("D'oh! A l'/aide/!"
+ =?> para ("D’oh! A l’" <> emph "aide" <> "!"))
+
+ , test orgSmart "apostrophe in French"
+ ("À l'arrivée de la guerre, le thème de l'«impossibilité du socialisme»"
+ =?> para "À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»")
+
+ , test orgSmart "Quotes cannot occur at the end of emphasized text"
+ ("/say \"yes\"/" =?>
+ para ("/say" <> space <> doubleQuoted "yes" <> "/"))
+
+ , test orgSmart "Dashes are allowed at the borders of emphasis'"
+ ("/foo---/" =?>
+ para (emph "foo—"))
+ ]
]
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