diff options
Diffstat (limited to 'tests/Tests')
-rw-r--r-- | tests/Tests/Old.hs | 3 | ||||
-rw-r--r-- | tests/Tests/Readers/Docx.hs | 15 | ||||
-rw-r--r-- | tests/Tests/Readers/EPUB.hs | 3 | ||||
-rw-r--r-- | tests/Tests/Readers/LaTeX.hs | 52 | ||||
-rw-r--r-- | tests/Tests/Readers/Markdown.hs | 16 | ||||
-rw-r--r-- | tests/Tests/Readers/Org.hs | 31 | ||||
-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 | 129 | ||||
-rw-r--r-- | tests/Tests/Writers/Markdown.hs | 91 | ||||
-rw-r--r-- | tests/Tests/Writers/RST.hs | 79 |
11 files changed, 409 insertions, 16 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 d7278b7c2..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) @@ -145,6 +146,10 @@ tests = [ testGroup "inlines" "inline code (with VerbatimChar style)" "docx/inline_code.docx" "docx/inline_code.native" + , testCompare + "inline code in subscript and superscript" + "docx/verbatim_subsuper.docx" + "docx/verbatim_subsuper.native" ] , testGroup "blocks" [ testCompare @@ -172,6 +177,10 @@ tests = [ testGroup "inlines" "docx/definition_list.docx" "docx/definition_list.native" , testCompare + "custom defined lists in styles" + "docx/german_styled_lists.docx" + "docx/german_styled_lists.native" + , testCompare "footnotes and endnotes" "docx/notes.docx" "docx/notes.native" 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..b72d707e7 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,10 +68,54 @@ 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 ] + + , let hex = ['0'..'9']++['a'..'f'] in + testGroup "Character Escapes" + [ "Two-character escapes" =: + concat ["^^"++[i,j] | i <- hex, j <- hex] =?> + para (str ['\0'..'\255']) + , "One-character escapes" =: + concat ["^^"++[i] | i <- hex] =?> + para (str $ ['p'..'y']++['!'..'&']) + ] ] baseCitation :: Citation diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs index b8d118d78..1cc00fd5e 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) @@ -207,6 +208,9 @@ tests = [ testGroup "inline code" , test markdownSmart "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 markdownSmart "apostrophe after math" $ -- issue #1909 + "The value of the $x$'s and the systems' condition." =?> + para (text "The value of the " <> math "x" <> text "\8217s and the systems\8217 condition.") ] , testGroup "footnotes" [ "indent followed by newline and flush-left text" =: @@ -220,7 +224,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 39c40cd45..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 @@ -212,6 +216,10 @@ tests = "[[sunset.png][dusk.svg]]" =?> (para $ link "sunset.png" "" (image "dusk.svg" "" "")) + , "Image link with non-image target" =: + "[[http://example.com][logo.png]]" =?> + (para $ link "http://example.com" "" (image "logo.png" "" "")) + , "Plain link" =: "Posts on http://zeitlens.com/ can be funny at times." =?> (para $ spcSep [ "Posts", "on" @@ -1152,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 diff --git a/tests/Tests/Writers/Docx.hs b/tests/Tests/Writers/Docx.hs new file mode 100644 index 000000000..068c5a935 --- /dev/null +++ b/tests/Tests/Writers/Docx.hs @@ -0,0 +1,129 @@ +module Tests.Writers.Docx (tests) where + +import Text.Pandoc.Options +import Text.Pandoc.Readers.Native +import Text.Pandoc.Definition +import Tests.Helpers +import Test.Framework +import Text.Pandoc.Readers.Docx +import Text.Pandoc.Writers.Docx +import Text.Pandoc.Error + +type Options = (WriterOptions, ReaderOptions) + +compareOutput :: Options + -> FilePath + -> IO (Pandoc, Pandoc) +compareOutput opts nativeFile = do + nf <- Prelude.readFile nativeFile + 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 + (dp, np) <- compareOutput opts nativeFile + return $ test id name (dp, np) + +testCompareWithOpts :: Options -> String -> FilePath -> Test +testCompareWithOpts opts name nativeFile = + buildTest $ testCompareWithOptsIO opts name nativeFile + +testCompare :: String -> FilePath -> Test +testCompare = testCompareWithOpts def + +tests :: [Test] +tests = [ testGroup "inlines" + [ testCompare + "font formatting" + "docx/inline_formatting_writer.native" + , testCompare + "font formatting with character styles" + "docx/char_styles.native" + , testCompare + "hyperlinks" + "docx/links_writer.native" + , testCompare + "inline image" + "docx/image_no_embed_writer.native" + , testCompare + "inline image in links" + "docx/inline_images_writer.native" + , testCompare + "handling unicode input" + "docx/unicode.native" + , testCompare + "literal tabs" + "docx/tabs.native" + , testCompare + "normalizing inlines" + "docx/normalize.native" + , testCompare + "normalizing inlines deep inside blocks" + "docx/deep_normalize.native" + , testCompare + "move trailing spaces outside of formatting" + "docx/trailing_spaces_in_formatting.native" + , testCompare + "inline code (with VerbatimChar style)" + "docx/inline_code.native" + , testCompare + "inline code in subscript and superscript" + "docx/verbatim_subsuper.native" + ] + , testGroup "blocks" + [ testCompare + "headers" + "docx/headers.native" + , testCompare + "headers already having auto identifiers" + "docx/already_auto_ident.native" + , testCompare + "numbered headers automatically made into list" + "docx/numbered_header.native" + , testCompare + "i18n blocks (headers and blockquotes)" + "docx/i18n_blocks.native" + -- Continuation does not survive round-trip + , testCompare + "lists" + "docx/lists_writer.native" + , testCompare + "definition lists" + "docx/definition_list.native" + , testCompare + "custom defined lists in styles" + "docx/german_styled_lists.native" + , testCompare + "footnotes and endnotes" + "docx/notes.native" + , testCompare + "blockquotes (parsing indent as blockquote)" + "docx/block_quotes_parse_indent.native" + , testCompare + "hanging indents" + "docx/hanging_indent.native" + -- tables headers do not survive round-trip, should look into that + , testCompare + "tables" + "docx/tables.native" + , testCompare + "tables with lists in cells" + "docx/table_with_list_cell.native" + , testCompare + "code block" + "docx/codeblock.native" + , testCompare + "dropcap paragraphs" + "docx/drop_cap.native" + ] + , testGroup "metadata" + [ testCompareWithOpts (def,def{readerStandalone=True}) + "metadata fields" + "docx/metadata.native" + , testCompareWithOpts (def,def{readerStandalone=True}) + "stop recording metadata with normal text" + "docx/metadata_after_normal.native" + ] + + ] diff --git a/tests/Tests/Writers/Markdown.hs b/tests/Tests/Writers/Markdown.hs index c2a8f5903..dce40ddcb 100644 --- a/tests/Tests/Writers/Markdown.hs +++ b/tests/Tests/Writers/Markdown.hs @@ -1,4 +1,5 @@ {-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -fno-warn-name-shadowing #-} module Tests.Writers.Markdown (tests) where import Test.Framework @@ -35,4 +36,92 @@ tests = [ "indented code after list" =: bulletList [ plain "foo" <> bulletList [ plain "bar" ], plain "baz" ] =?> "- foo\n - bar\n- baz\n" - ] + ] ++ [shortcutLinkRefsTests] + +shortcutLinkRefsTests :: Test +shortcutLinkRefsTests = + let infix 4 =: + (=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> Test + (=:) = test (writeMarkdown (def {writerReferenceLinks = True}) . toPandoc) + in testGroup "Shortcut reference links" + [ "Simple link (shortcutable)" + =: (para (link "/url" "title" "foo")) + =?> "[foo]\n\n [foo]: /url \"title\"" + , "Followed by another link (unshortcutable)" + =: (para ((link "/url1" "title1" "first") + <> (link "/url2" "title2" "second"))) + =?> unlines [ "[first][][second]" + , "" + , " [first]: /url1 \"title1\"" + , " [second]: /url2 \"title2\"" + ] + , "Followed by space and another link (unshortcutable)" + =: (para ((link "/url1" "title1" "first") <> " " + <> (link "/url2" "title2" "second"))) + =?> unlines [ "[first][] [second]" + , "" + , " [first]: /url1 \"title1\"" + , " [second]: /url2 \"title2\"" + ] + , "Reference link is used multiple times (unshortcutable)" + =: (para ((link "/url1" "" "foo") <> (link "/url2" "" "foo") + <> (link "/url3" "" "foo"))) + =?> unlines [ "[foo][][foo][1][foo][2]" + , "" + , " [foo]: /url1" + , " [1]: /url2" + , " [2]: /url3" + ] + , "Reference link is used multiple times (unshortcutable)" + =: (para ((link "/url1" "" "foo") <> " " <> (link "/url2" "" "foo") + <> " " <> (link "/url3" "" "foo"))) + =?> unlines [ "[foo][] [foo][1] [foo][2]" + , "" + , " [foo]: /url1" + , " [1]: /url2" + , " [2]: /url3" + ] + , "Reference link is followed by text in brackets" + =: (para ((link "/url" "" "link") <> "[text in brackets]")) + =?> unlines [ "[link][][text in brackets]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by space and text in brackets" + =: (para ((link "/url" "" "link") <> " [text in brackets]")) + =?> unlines [ "[link][] [text in brackets]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by RawInline" + =: (para ((link "/url" "" "link") <> rawInline "markdown" "[rawText]")) + =?> unlines [ "[link][][rawText]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by space and RawInline" + =: (para ((link "/url" "" "link") <> space <> rawInline "markdown" "[rawText]")) + =?> unlines [ "[link][] [rawText]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by RawInline with space" + =: (para ((link "/url" "" "link") <> rawInline "markdown" " [rawText]")) + =?> unlines [ "[link][] [rawText]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by citation" + =: (para ((link "/url" "" "link") <> cite [Citation "author" [] [] NormalCitation 0 0] (str "[@author]"))) + =?> unlines [ "[link][][@author]" + , "" + , " [link]: /url" + ] + , "Reference link is followed by space and citation" + =: (para ((link "/url" "" "link") <> space <> cite [Citation "author" [] [] NormalCitation 0 0] (str "[@author]"))) + =?> unlines [ "[link][] [@author]" + , "" + , " [link]: /url" + ] + ] diff --git a/tests/Tests/Writers/RST.hs b/tests/Tests/Writers/RST.hs new file mode 100644 index 000000000..2a511782f --- /dev/null +++ b/tests/Tests/Writers/RST.hs @@ -0,0 +1,79 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.RST (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Tests.Arbitrary() + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> Test +(=:) = test (writeRST def{ writerHighlight = True } . toPandoc) + +tests :: [Test] +tests = [ testGroup "rubrics" + [ "in list item" =: + bulletList [header 2 (text "foo")] =?> + "- .. rubric:: foo" + , "in definition list item" =: + definitionList [(text "foo", [header 2 (text "bar"), + para $ text "baz"])] =?> + unlines + [ "foo" + , " .. rubric:: bar" + , "" + , " baz"] + , "in block quote" =: + blockQuote (header 1 (text "bar")) =?> + " .. rubric:: bar" + , "with id" =: + blockQuote (headerWith ("foo",[],[]) 1 (text "bar")) =?> + unlines + [ " .. rubric:: bar" + , " :name: foo"] + , "with id class" =: + blockQuote (headerWith ("foo",["baz"],[]) 1 (text "bar")) =?> + unlines + [ " .. rubric:: bar" + , " :name: foo" + , " :class: baz"] + ] + , testGroup "headings" + [ "normal heading" =: + header 1 (text "foo") =?> + unlines + [ "foo" + , "==="] + , "heading levels" =: + header 1 (text "Header 1") <> + header 3 (text "Header 2") <> + header 2 (text "Header 2") <> + header 1 (text "Header 1") <> + header 4 (text "Header 2") <> + header 5 (text "Header 3") <> + header 3 (text "Header 2") =?> + unlines + [ "Header 1" + , "========" + , "" + , "Header 2" + , "--------" + , "" + , "Header 2" + , "--------" + , "" + , "Header 1" + , "========" + , "" + , "Header 2" + , "--------" + , "" + , "Header 3" + , "~~~~~~~~" + , "" + , "Header 2" + , "--------"] + ] + ] |