diff options
Diffstat (limited to 'tests')
28 files changed, 369 insertions, 29 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 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 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/docx/image_no_embed_writer.native b/tests/docx/image_no_embed_writer.native new file mode 100644 index 000000000..21802ebd1 --- /dev/null +++ b/tests/docx/image_no_embed_writer.native @@ -0,0 +1,2 @@ +[Para [Str "An",Space,Str "image:"] +,Para [Image [] ("media/rId25.jpg","")]] diff --git a/tests/docx/inline_formatting_writer.native b/tests/docx/inline_formatting_writer.native new file mode 100644 index 000000000..be346204e --- /dev/null +++ b/tests/docx/inline_formatting_writer.native @@ -0,0 +1,5 @@ +[Para [Str "Regular",Space,Str "text",Space,Emph [Str "italics"],Space,Strong [Str "bold",Space,Emph [Str "bold",Space,Str "italics"]],Str "."] +,Para [Str "This",Space,Str "is",Space,SmallCaps [Str "Small",Space,Str "Caps"],Str ",",Space,Str "and",Space,Str "this",Space,Str "is",Space,Strikeout [Str "strikethrough"],Str "."] +,Para [Str "Some",Space,Str "people",Space,Str "use",Space,Emph [Str "single",Space,Str "underlines",Space,Str "for",Space,Str "emphasis"],Str "."] +,Para [Str "Above",Space,Str "the",Space,Str "line",Space,Str "is",Space,Superscript [Str "superscript"],Space,Str "and",Space,Str "below",Space,Str "the",Space,Str "line",Space,Str "is",Space,Subscript [Str "subscript"],Str "."] +,Para [Str "A",Space,Str "line",LineBreak,Str "break."]] diff --git a/tests/docx/inline_images_writer.native b/tests/docx/inline_images_writer.native new file mode 100644 index 000000000..da2a2709b --- /dev/null +++ b/tests/docx/inline_images_writer.native @@ -0,0 +1,2 @@ +[Para [Str "This",Space,Str "picture",Space,Image [] ("media/rId26.jpg",""),Space,Str "is",Space,Str "an",Space,Str "identicon."] +,Para [Str "Here",Space,Str "is",Space,Link [Str "one",Space,Image [] ("media/rId27.jpg",""),Space,Str "that"] ("http://www.google.com",""),Space,Str "links."]] diff --git a/tests/docx/links_writer.native b/tests/docx/links_writer.native new file mode 100644 index 000000000..cc00e4326 --- /dev/null +++ b/tests/docx/links_writer.native @@ -0,0 +1,6 @@ +[Header 2 ("an-internal-link-and-an-external-link",[],[]) [Str "An",Space,Str "internal",Space,Str "link",Space,Str "and",Space,Str "an",Space,Str "external",Space,Str "link"] +,Para [Str "An",Space,Link [Str "external",Space,Str "link"] ("http://google.com",""),Space,Str "to",Space,Str "a",Space,Str "popular",Space,Str "website."] +,Para [Str "An",Space,Link [Str "external",Space,Str "link"] ("http://johnmacfarlane.net/pandoc/README.html#synopsis",""),Space,Str "to",Space,Str "a",Space,Str "website",Space,Str "with",Space,Str "an",Space,Str "anchor."] +,Para [Str "An",Space,Link [Str "internal",Space,Str "link"] ("#a-section-for-testing-link-targets",""),Space,Str "to",Space,Str "a",Space,Str "section",Space,Str "header."] +,Para [Str "An",Space,Link [Str "internal",Space,Str "link"] ("#my_bookmark",""),Space,Str "to",Space,Str "a",Space,Str "bookmark."] +,Header 2 ("a-section-for-testing-link-targets",[],[]) [Str "A",Space,Str "section",Space,Str "for",Space,Str "testing",Space,Str "link",Space,Str "targets"]] diff --git a/tests/docx/lists_writer.native b/tests/docx/lists_writer.native new file mode 100644 index 000000000..4c44ea603 --- /dev/null +++ b/tests/docx/lists_writer.native @@ -0,0 +1,17 @@ +[Header 2 ("some-nested-lists",[],[]) [Str "Some",Space,Str "nested",Space,Str "lists"] +,OrderedList (1,Decimal,Period) + [[Para [Str "one"]] + ,[Para [Str "two"] + ,OrderedList (1,LowerAlpha,DefaultDelim) + [[Para [Str "a"]] + ,[Para [Str "b"]]]]] +,BulletList + [[Para [Str "one"]] + ,[Para [Str "two"] + ,BulletList + [[Para [Str "three"] + ,BulletList + [[Para [Str "four"]]]]]] + ,[Para [Str "Same",Space,Str "list"]]] +,BulletList + [[Para [Str "Different",Space,Str "list",Space,Str "adjacent",Space,Str "to",Space,Str "the",Space,Str "one",Space,Str "above."]]]] diff --git a/tests/lhs-test.html b/tests/lhs-test.html index bde505a1e..362c93c04 100644 --- a/tests/lhs-test.html +++ b/tests/lhs-test.html @@ -7,6 +7,7 @@ <title></title> <style type="text/css">code{white-space: pre;}</style> <style type="text/css"> +div.sourceCode { overflow-x: auto; } table.sourceCode, tr.sourceCode, td.lineNumbers, td.sourceCode { margin: 0; padding: 0; vertical-align: baseline; border: none; } table.sourceCode { width: 100%; line-height: 100%; } @@ -29,9 +30,9 @@ code > span.er { color: #ff0000; font-weight: bold; } <body> <h1 id="lhs-test">lhs test</h1> <p><code>unsplit</code> is an arrow that takes a pair of values and combines them to return a single value:</p> -<pre class="sourceCode literate haskell"><code class="sourceCode haskell"><span class="ot">unsplit ::</span> (<span class="dt">Arrow</span> a) <span class="ot">=></span> (b <span class="ot">-></span> c <span class="ot">-></span> d) <span class="ot">-></span> a (b, c) d +<div class="sourceCode"><pre class="sourceCode literate haskell"><code class="sourceCode haskell"><span class="ot">unsplit ::</span> (<span class="dt">Arrow</span> a) <span class="ot">=></span> (b <span class="ot">-></span> c <span class="ot">-></span> d) <span class="ot">-></span> a (b, c) d unsplit <span class="fu">=</span> arr <span class="fu">.</span> uncurry - <span class="co">-- arr (\op (x,y) -> x `op` y)</span></code></pre> + <span class="co">-- arr (\op (x,y) -> x `op` y)</span></code></pre></div> <p><code>(***)</code> combines two arrows into a new arrow by running the two arrows on a pair of values (one arrow on the first item of the pair and one arrow on the second item of the pair).</p> <pre><code>f *** g = first f >>> second g</code></pre> <p>Block quote:</p> diff --git a/tests/lhs-test.html+lhs b/tests/lhs-test.html+lhs index fcdcad303..492d9c718 100644 --- a/tests/lhs-test.html+lhs +++ b/tests/lhs-test.html+lhs @@ -7,6 +7,7 @@ <title></title> <style type="text/css">code{white-space: pre;}</style> <style type="text/css"> +div.sourceCode { overflow-x: auto; } table.sourceCode, tr.sourceCode, td.lineNumbers, td.sourceCode { margin: 0; padding: 0; vertical-align: baseline; border: none; } table.sourceCode { width: 100%; line-height: 100%; } @@ -29,9 +30,9 @@ code > span.er { color: #ff0000; font-weight: bold; } <body> <h1 id="lhs-test">lhs test</h1> <p><code>unsplit</code> is an arrow that takes a pair of values and combines them to return a single value:</p> -<pre class="sourceCode literate literatehaskell"><code class="sourceCode literatehaskell"><span class="ot">> unsplit ::</span> (<span class="dt">Arrow</span> a) <span class="ot">=></span> (b <span class="ot">-></span> c <span class="ot">-></span> d) <span class="ot">-></span> a (b, c) d +<div class="sourceCode"><pre class="sourceCode literate literatehaskell"><code class="sourceCode literatehaskell"><span class="ot">> unsplit ::</span> (<span class="dt">Arrow</span> a) <span class="ot">=></span> (b <span class="ot">-></span> c <span class="ot">-></span> d) <span class="ot">-></span> a (b, c) d <span class="ot">></span> unsplit <span class="fu">=</span> arr <span class="fu">.</span> uncurry -<span class="ot">></span> <span class="co">-- arr (\op (x,y) -> x `op` y)</span></code></pre> +<span class="ot">></span> <span class="co">-- arr (\op (x,y) -> x `op` y)</span></code></pre></div> <p><code>(***)</code> combines two arrows into a new arrow by running the two arrows on a pair of values (one arrow on the first item of the pair and one arrow on the second item of the pair).</p> <pre><code>f *** g = first f >>> second g</code></pre> <p>Block quote:</p> diff --git a/tests/markdown-reader-more.native b/tests/markdown-reader-more.native index 3f4bb5740..96204898e 100644 --- a/tests/markdown-reader-more.native +++ b/tests/markdown-reader-more.native @@ -156,4 +156,7 @@ ,Para [Str "MapReduce",Space,Str "is",Space,Str "a",Space,Str "paradigm",Space,Str "popularized",Space,Str "by",Space,Link [Str "Google"] ("http://google.com",""),Space,Cite [Citation {citationId = "mapreduce", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@mapreduce]"],Space,Str "as",Space,Str "its",Space,Str "most",Space,Str "vocal",Space,Str "proponent."] ,Header 2 ("empty-reference-links",[],[]) [Str "Empty",Space,Str "reference",Space,Str "links"] ,Para [Str "bar"] -,Para [Link [Str "foo2"] ("","")]] +,Para [Link [Str "foo2"] ("","")] +,Header 2 ("wrapping-shouldnt-introduce-new-list-items",[],[]) [Str "Wrapping",Space,Str "shouldn\8217t",Space,Str "introduce",Space,Str "new",Space,Str "list",Space,Str "items"] +,BulletList + [[Plain [Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "2015."]]]] diff --git a/tests/markdown-reader-more.txt b/tests/markdown-reader-more.txt index d7439f6cb..99e9ec7e8 100644 --- a/tests/markdown-reader-more.txt +++ b/tests/markdown-reader-more.txt @@ -276,3 +276,8 @@ most vocal proponent. bar [foo2] + +## Wrapping shouldn't introduce new list items + +- blah blah blah blah blah blah blah blah blah blah blah blah blah blah 2015. + diff --git a/tests/media/rId25.jpg b/tests/media/rId25.jpg new file mode 100644 index 000000000..e69de29bb --- /dev/null +++ b/tests/media/rId25.jpg diff --git a/tests/media/rId26.jpg b/tests/media/rId26.jpg new file mode 100644 index 000000000..e69de29bb --- /dev/null +++ b/tests/media/rId26.jpg diff --git a/tests/media/rId27.jpg b/tests/media/rId27.jpg new file mode 100644 index 000000000..e69de29bb --- /dev/null +++ b/tests/media/rId27.jpg diff --git a/tests/pipe-tables.txt b/tests/pipe-tables.txt index ee8d54d9f..83debd595 100644 --- a/tests/pipe-tables.txt +++ b/tests/pipe-tables.txt @@ -1,7 +1,7 @@ Simplest table without caption: | Default1 | Default2 | Default3 | -|----------|----------|----------| + |----------|----------|----------| |12|12|12| |123|123|123| |1|1|1| @@ -27,6 +27,7 @@ Simple table without caption: Headerless table without caption: +| | | | |------:|:-----|:------:| |12|12|12| |123|123|123| @@ -48,5 +49,6 @@ One-column: Header-less one-column: +| | |:-:| |hi| diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs index b7b1c30b1..dd92a271a 100644 --- a/tests/test-pandoc.hs +++ b/tests/test-pandoc.hs @@ -20,6 +20,7 @@ import qualified Tests.Writers.Native import qualified Tests.Writers.Markdown import qualified Tests.Writers.Plain import qualified Tests.Writers.AsciiDoc +import qualified Tests.Writers.Docx import qualified Tests.Shared import qualified Tests.Walk import Text.Pandoc.Shared (inDirectory) @@ -38,6 +39,7 @@ tests = [ testGroup "Old" Tests.Old.tests , testGroup "Markdown" Tests.Writers.Markdown.tests , testGroup "Plain" Tests.Writers.Plain.tests , testGroup "AsciiDoc" Tests.Writers.AsciiDoc.tests + , testGroup "Docx" Tests.Writers.Docx.tests ] , testGroup "Readers" [ testGroup "LaTeX" Tests.Readers.LaTeX.tests diff --git a/tests/writer.asciidoc b/tests/writer.asciidoc index 4b063fe68..aebc529f0 100644 --- a/tests/writer.asciidoc +++ b/tests/writer.asciidoc @@ -375,15 +375,19 @@ HTML Blocks Simple block on one line: foo + And nested without indentation: foo bar + Interpreted markdown in a table: This is _emphasized_ + And this is *strong* + Here’s a simple block: foo @@ -405,6 +409,7 @@ As should this: Now, nested: foo + This should just be an HTML comment: Multiline: @@ -485,7 +490,7 @@ Ellipses…and…and…. LaTeX ----- -* +* * latexmath:[$2+2=4$] * latexmath:[$x \in y$] * latexmath:[$\alpha \wedge \omega$] diff --git a/tests/writer.markdown b/tests/writer.markdown index ad97b15ef..7276b31c7 100644 --- a/tests/writer.markdown +++ b/tests/writer.markdown @@ -549,8 +549,8 @@ LaTeX These shouldn’t be math: - To get the famous equation, write `$e = mc^2$`. -- \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot” is - emphasized.) +- \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot” + is emphasized.) - Shoes (\$20) and socks (\$5). - Escaped `$`: \$73 *this should be emphasized* 23\$. diff --git a/tests/writer.opml b/tests/writer.opml index 840c3c6e1..8f79e842c 100644 --- a/tests/writer.opml +++ b/tests/writer.opml @@ -33,7 +33,7 @@ <outline text="Lists"> <outline text="Unordered" _note="Asterisks tight: - asterisk 1 - asterisk 2 - asterisk 3 Asterisks loose: - asterisk 1 - asterisk 2 - asterisk 3 Pluses tight: - Plus 1 - Plus 2 - Plus 3 Pluses loose: - Plus 1 - Plus 2 - Plus 3 Minuses tight: - Minus 1 - Minus 2 - Minus 3 Minuses loose: - Minus 1 - Minus 2 - Minus 3 "> </outline> - <outline text="Ordered" _note="Tight: 1. First 2. Second 3. Third and: 1. One 2. Two 3. Three Loose using tabs: 1. First 2. Second 3. Third and using spaces: 1. One 2. Two 3. Three Multiple paragraphs: 1. Item 1, graf one. Item 1. graf two. The quick brown fox jumped over the lazy dog’s back. 2. Item 2. 3. Item 3. "> + <outline text="Ordered" _note="Tight: 1. First 2. Second 3. Third and: 1. One 2. Two 3. Three Loose using tabs: 1. First 2. Second 3. Third and using spaces: 1. One 2. Two 3. Three Multiple paragraphs: 1. Item 1, graf one. Item 1. graf two. The quick brown fox jumped over the lazy dog’s back. 2. Item 2. 3. Item 3. "> </outline> <outline text="Nested" _note="- Tab - Tab - Tab Here’s another: 1. First 2. Second: - Fee - Fie - Foe 3. Third Same thing but with paragraphs: 1. First 2. Second: - Fee - Fie - Foe 3. Third "> </outline> @@ -50,7 +50,7 @@ </outline> <outline text="Smart quotes, ellipses, dashes" _note="“Hello,” said the spider. “‘Shelob’ is my name.” ‘A’, ‘B’, and ‘C’ are letters. ‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’ ‘He said, “I want to go.”’ Were you alive in the 70’s? Here is some quoted ‘`code`’ and a “[quoted link](http://example.com/?foo=1&bar=2)”. Some dashes: one—two — three—four — five. Dashes between numbers: 5–7, 255–66, 1987–1999. Ellipses…and…and…. ------------------------------------------------------------------------"> </outline> -<outline text="LaTeX" _note="- \cite[22-23]{smith.1899} - $2+2=4$ - $x \in y$ - $\alpha \wedge \omega$ - $223$ - $p$-Tree - Here’s some display math: $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$ - Here’s one that has a line break in it: $\alpha + \omega \times x^2$. These shouldn’t be math: - To get the famous equation, write `$e = mc^2$`. - \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot” is emphasized.) - Shoes (\$20) and socks (\$5). - Escaped `$`: \$73 *this should be emphasized* 23\$. Here’s a LaTeX table: \begin{tabular}{|l|l|}\hline Animal & Number \\ \hline Dog & 2 \\ Cat & 1 \\ \hline \end{tabular} ------------------------------------------------------------------------"> +<outline text="LaTeX" _note="- \cite[22-23]{smith.1899} - $2+2=4$ - $x \in y$ - $\alpha \wedge \omega$ - $223$ - $p$-Tree - Here’s some display math: $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$ - Here’s one that has a line break in it: $\alpha + \omega \times x^2$. These shouldn’t be math: - To get the famous equation, write `$e = mc^2$`. - \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot” is emphasized.) - Shoes (\$20) and socks (\$5). - Escaped `$`: \$73 *this should be emphasized* 23\$. Here’s a LaTeX table: \begin{tabular}{|l|l|}\hline Animal & Number \\ \hline Dog & 2 \\ Cat & 1 \\ \hline \end{tabular} ------------------------------------------------------------------------"> </outline> <outline text="Special Characters" _note="Here is some unicode: - I hat: Î - o umlaut: ö - section: § - set membership: ∈ - copyright: © AT&T has an ampersand in their name. AT&T is another way to write it. This & that. 4 \< 5. 6 \> 5. Backslash: \\ Backtick: \` Asterisk: \* Underscore: \_ Left brace: { Right brace: } Left bracket: [ Right bracket: ] Left paren: ( Right paren: ) Greater-than: \> Hash: \# Period: . Bang: ! Plus: + Minus: - ------------------------------------------------------------------------"> </outline> diff --git a/tests/writer.plain b/tests/writer.plain index fab0489ac..0332a747b 100644 --- a/tests/writer.plain +++ b/tests/writer.plain @@ -499,8 +499,8 @@ LATEX These shouldn’t be math: - To get the famous equation, write $e = mc^2$. -- $22,000 is a _lot_ of money. So is $34,000. (It worked if “lot” is - emphasized.) +- $22,000 is a _lot_ of money. So is $34,000. (It worked if “lot” + is emphasized.) - Shoes ($20) and socks ($5). - Escaped $: $73 _this should be emphasized_ 23$. |