diff options
author | Clare Macrae <github@cfmacrae.fastmail.co.uk> | 2014-06-29 19:22:31 +0100 |
---|---|---|
committer | Clare Macrae <github@cfmacrae.fastmail.co.uk> | 2014-06-29 19:22:31 +0100 |
commit | 717e16660d1ee83f690b35d0aa9b60c8ac9d6b61 (patch) | |
tree | aa850d4ee99fa0b14da9ba0396ba6aa67e2037e3 /tests/Tests | |
parent | fccfc8429cf4d002df37977f03508c9aae457416 (diff) | |
parent | ce69021e42d7bf50deccba2a52ed4717f6ddac10 (diff) | |
download | pandoc-717e16660d1ee83f690b35d0aa9b60c8ac9d6b61.tar.gz |
Merge remote-tracking branch 'jgm/master' into dokuwiki
Diffstat (limited to 'tests/Tests')
-rw-r--r-- | tests/Tests/Arbitrary.hs | 19 | ||||
-rw-r--r-- | tests/Tests/Old.hs | 33 | ||||
-rw-r--r-- | tests/Tests/Readers/Docx.hs | 160 | ||||
-rw-r--r-- | tests/Tests/Readers/LaTeX.hs | 55 | ||||
-rw-r--r-- | tests/Tests/Readers/Markdown.hs | 23 | ||||
-rw-r--r-- | tests/Tests/Readers/Org.hs | 994 | ||||
-rw-r--r-- | tests/Tests/Walk.hs | 47 | ||||
-rw-r--r-- | tests/Tests/Writers/AsciiDoc.hs | 37 | ||||
-rw-r--r-- | tests/Tests/Writers/Docbook.hs | 229 | ||||
-rw-r--r-- | tests/Tests/Writers/HTML.hs | 5 | ||||
-rw-r--r-- | tests/Tests/Writers/LaTeX.hs | 32 | ||||
-rw-r--r-- | tests/Tests/Writers/Markdown.hs | 4 |
12 files changed, 1576 insertions, 62 deletions
diff --git a/tests/Tests/Arbitrary.hs b/tests/Tests/Arbitrary.hs index 5939d088d..3675d97bf 100644 --- a/tests/Tests/Arbitrary.hs +++ b/tests/Tests/Arbitrary.hs @@ -41,15 +41,15 @@ arbInline :: Int -> Gen Inline arbInline n = frequency $ [ (60, liftM Str realString) , (60, return Space) , (10, liftM2 Code arbAttr realString) - , (5, elements [ RawInline "html" "<a id=\"eek\">" - , RawInline "latex" "\\my{command}" ]) + , (5, elements [ RawInline (Format "html") "<a id=\"eek\">" + , RawInline (Format "latex") "\\my{command}" ]) ] ++ [ x | x <- nesters, n > 1] where nesters = [ (10, liftM Emph $ arbInlines (n-1)) , (10, liftM Strong $ arbInlines (n-1)) , (10, liftM Strikeout $ arbInlines (n-1)) , (10, liftM Superscript $ arbInlines (n-1)) , (10, liftM Subscript $ arbInlines (n-1)) --- , (10, liftM SmallCaps $ arbInlines (n-1)) + , (10, liftM SmallCaps $ arbInlines (n-1)) , (10, do x1 <- arbitrary x2 <- arbInlines (n-1) return $ Quoted x1 x2) @@ -64,6 +64,7 @@ arbInline n = frequency $ [ (60, liftM Str realString) x3 <- realString x2 <- liftM escapeURI realString return $ Image x1 (x2,x3)) + , (2, liftM2 Cite arbitrary (arbInlines 1)) , (2, liftM Note $ resize 3 $ listOf1 $ arbBlock (n-1)) ] @@ -74,9 +75,9 @@ arbBlock :: Int -> Gen Block arbBlock n = frequency $ [ (10, liftM Plain $ arbInlines (n-1)) , (15, liftM Para $ arbInlines (n-1)) , (5, liftM2 CodeBlock arbAttr realString) - , (2, elements [ RawBlock "html" + , (2, elements [ RawBlock (Format "html") "<div>\n*&*\n</div>" - , RawBlock "latex" + , RawBlock (Format "latex") "\\begin[opt]{env}\nhi\n{\\end{env}" ]) , (5, do x1 <- choose (1 :: Int, 6) @@ -111,7 +112,6 @@ instance Arbitrary Pandoc where arbitrary = resize 8 $ liftM normalize $ liftM2 Pandoc arbitrary arbitrary -{- instance Arbitrary CitationMode where arbitrary = do x <- choose (0 :: Int, 2) @@ -123,14 +123,13 @@ instance Arbitrary CitationMode where instance Arbitrary Citation where arbitrary - = do x1 <- liftM (filter (`notElem` ",;]@ \t\n")) arbitrary - x2 <- arbitrary - x3 <- arbitrary + = do x1 <- listOf $ elements $ ['a'..'z'] ++ ['0'..'9'] ++ ['_'] + x2 <- arbInlines 1 + x3 <- arbInlines 1 x4 <- arbitrary x5 <- arbitrary x6 <- arbitrary return (Citation x1 x2 x3 x4 x5 x6) --} instance Arbitrary MathType where arbitrary diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs index 573ec1afe..44ed9f53a 100644 --- a/tests/Tests/Old.hs +++ b/tests/Tests/Old.hs @@ -3,7 +3,7 @@ module Tests.Old (tests) where import Test.Framework (testGroup, Test ) import Test.Framework.Providers.HUnit import Test.HUnit ( assertBool ) - +import System.Environment ( getArgs ) import System.IO ( openTempFile, stderr ) import System.Process ( runProcess, waitForProcess ) import System.FilePath ( (</>), (<.>) ) @@ -22,9 +22,6 @@ import Text.Printf readFileUTF8 :: FilePath -> IO String readFileUTF8 f = B.readFile f >>= return . toStringLazy -pandocPath :: FilePath -pandocPath = ".." </> "dist" </> "build" </> "pandoc" </> "pandoc" - data TestResult = TestPassed | TestError ExitCode | TestFailed String FilePath [Diff String] @@ -63,7 +60,10 @@ tests = [ testGroup "markdown" "markdown-reader-more.txt" "markdown-reader-more.native" , lhsReaderTest "markdown+lhs" ] - , testGroup "citations" markdownCitationTests + , testGroup "citations" + [ test "citations" ["-r", "markdown", "-w", "native"] + "markdown-citations.txt" "markdown-citations.native" + ] ] , testGroup "rst" [ testGroup "writer" (writerTests "rst" ++ lhsWriterTests "rst") @@ -136,11 +136,12 @@ tests = [ testGroup "markdown" "opml-reader.opml" "opml-reader.native" ] , testGroup "haddock" - [ test "reader" ["-r", "haddock", "-w", "native", "-s"] + [ testGroup "writer" $ writerTests "haddock" + , test "reader" ["-r", "haddock", "-w", "native", "-s"] "haddock-reader.haddock" "haddock-reader.native" ] , testGroup "other writers" $ map (\f -> testGroup f $ writerTests f) - [ "opendocument" , "context" , "texinfo" + [ "opendocument" , "context" , "texinfo", "icml" , "man" , "plain" , "rtf", "org", "asciidoc" ] ] @@ -195,19 +196,6 @@ fb2WriterTest title opts inputfile normfile = ignoreBinary = unlines . filter (not . startsWith "<binary ") . lines startsWith tag str = all (uncurry (==)) $ zip tag str -markdownCitationTests :: [Test] -markdownCitationTests - = map styleToTest ["chicago-author-date","ieee","mhra"] - ++ [test "natbib" wopts "markdown-citations.txt" - "markdown-citations.txt"] - where - ropts = ["-r", "markdown", "-w", "markdown", "--bibliography", - "biblio.bib", "--no-wrap"] - wopts = ["-r", "markdown", "-w", "markdown", "--no-wrap", "--natbib"] - styleToTest style = test style (ropts ++ ["--csl", style ++ ".csl"]) - "markdown-citations.txt" - ("markdown-citations." ++ style ++ ".txt") - -- | Run a test without normalize function, return True if test passed. test :: String -- ^ Title of test -> [String] -- ^ Options to pass to pandoc @@ -224,6 +212,11 @@ testWithNormalize :: (String -> String) -- ^ Normalize function for output -> FilePath -- ^ Norm (for test results) filepath -> Test testWithNormalize normalizer testname opts inp norm = testCase testname $ do + args <- getArgs + let buildDir = case args of + (x:_) -> ".." </> x + _ -> error "test-pandoc: missing buildDir argument" + let pandocPath = buildDir </> "pandoc" </> "pandoc" (outputPath, hOut) <- openTempFile "" "pandoc-test" let inpPath = inp let normPath = norm diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs new file mode 100644 index 000000000..8c51217cf --- /dev/null +++ b/tests/Tests/Readers/Docx.hs @@ -0,0 +1,160 @@ +module Tests.Readers.Docx (tests) where + +import Text.Pandoc.Options +import Text.Pandoc.Readers.Native +import Text.Pandoc.Definition +import Tests.Helpers +import Test.Framework +import qualified Data.ByteString.Lazy as B +import Text.Pandoc.Readers.Docx +import Text.Pandoc.Writers.Native (writeNative) +import qualified Data.Map as M + +-- We define a wrapper around pandoc that doesn't normalize in the +-- tests. Since we do our own normalization, we want to make sure +-- we're doing it right. + +data NoNormPandoc = NoNormPandoc {unNoNorm :: Pandoc} + deriving Show + +noNorm :: Pandoc -> NoNormPandoc +noNorm = NoNormPandoc + +instance ToString NoNormPandoc where + toString d = writeNative def{ writerStandalone = s } $ toPandoc d + where s = case d of + NoNormPandoc (Pandoc (Meta m) _) + | M.null m -> False + | otherwise -> True + +instance ToPandoc NoNormPandoc where + toPandoc = unNoNorm + +compareOutput :: ReaderOptions + -> FilePath + -> FilePath + -> IO (NoNormPandoc, NoNormPandoc) +compareOutput opts docxFile nativeFile = do + df <- B.readFile docxFile + nf <- Prelude.readFile nativeFile + return $ (noNorm (readDocx opts df), noNorm (readNative nf)) + +testCompareWithOptsIO :: ReaderOptions -> String -> FilePath -> FilePath -> IO Test +testCompareWithOptsIO opts name docxFile nativeFile = do + (dp, np) <- compareOutput opts docxFile nativeFile + return $ test id name (dp, np) + +testCompareWithOpts :: ReaderOptions -> String -> FilePath -> FilePath -> Test +testCompareWithOpts opts name docxFile nativeFile = + buildTest $ testCompareWithOptsIO opts name docxFile nativeFile + +testCompare :: String -> FilePath -> FilePath -> Test +testCompare = testCompareWithOpts def + + +tests :: [Test] +tests = [ testGroup "inlines" + [ testCompare + "font formatting" + "docx.inline_formatting.docx" + "docx.inline_formatting.native" + , testCompare + "hyperlinks" + "docx.links.docx" + "docx.links.native" + , testCompare + "inline image with reference output" + "docx.image.docx" + "docx.image_no_embed.native" + , testCompare + "handling unicode input" + "docx.unicode.docx" + "docx.unicode.native" + , testCompare + "literal tabs" + "docx.tabs.docx" + "docx.tabs.native" + , testCompare + "normalizing inlines" + "docx.normalize.docx" + "docx.normalize.native" + , testCompare + "normalizing inlines deep inside blocks" + "docx.deep_normalize.docx" + "docx.deep_normalize.native" + , testCompare + "move trailing spaces outside of formatting" + "docx.trailing_spaces_in_formatting.docx" + "docx.trailing_spaces_in_formatting.native" + , testCompare + "inline code (with VerbatimChar style)" + "docx.inline_code.docx" + "docx.inline_code.native" + ] + , testGroup "blocks" + [ testCompare + "headers" + "docx.headers.docx" + "docx.headers.native" + , testCompare + "lists" + "docx.lists.docx" + "docx.lists.native" + , testCompare + "definition lists" + "docx.definition_list.docx" + "docx.definition_list.native" + , testCompare + "footnotes and endnotes" + "docx.notes.docx" + "docx.notes.native" + , testCompare + "blockquotes (parsing indent as blockquote)" + "docx.block_quotes.docx" + "docx.block_quotes_parse_indent.native" + , testCompare + "tables" + "docx.tables.docx" + "docx.tables.native" + , testCompare + "code block" + "docx.codeblock.docx" + "docx.codeblock.native" + + ] + , testGroup "track changes" + [ testCompare + "insertion (default)" + "docx.track_changes_insertion.docx" + "docx.track_changes_insertion_accept.native" + , testCompareWithOpts def{readerTrackChanges=AcceptChanges} + "insert insertion (accept)" + "docx.track_changes_insertion.docx" + "docx.track_changes_insertion_accept.native" + , testCompareWithOpts def{readerTrackChanges=RejectChanges} + "remove insertion (reject)" + "docx.track_changes_insertion.docx" + "docx.track_changes_insertion_reject.native" + , testCompare + "deletion (default)" + "docx.track_changes_deletion.docx" + "docx.track_changes_deletion_accept.native" + , testCompareWithOpts def{readerTrackChanges=AcceptChanges} + "remove deletion (accept)" + "docx.track_changes_deletion.docx" + "docx.track_changes_deletion_accept.native" + , testCompareWithOpts def{readerTrackChanges=RejectChanges} + "insert deletion (reject)" + "docx.track_changes_deletion.docx" + "docx.track_changes_deletion_reject.native" + , testCompareWithOpts def{readerTrackChanges=AllChanges} + "keep insertion (all)" + "docx.track_changes_deletion.docx" + "docx.track_changes_deletion_all.native" + , testCompareWithOpts def{readerTrackChanges=AllChanges} + "keep deletion (all)" + "docx.track_changes_deletion.docx" + "docx.track_changes_deletion_all.native" + ] + ] + diff --git a/tests/Tests/Readers/LaTeX.hs b/tests/Tests/Readers/LaTeX.hs index 271b32689..8ff23ebc1 100644 --- a/tests/Tests/Readers/LaTeX.hs +++ b/tests/Tests/Readers/LaTeX.hs @@ -21,24 +21,24 @@ tests = [ testGroup "basic" [ "simple" =: "word" =?> para "word" , "space" =: - "some text" =?> para ("some text") + "some text" =?> para "some text" , "emphasized" =: "\\emph{emphasized}" =?> para (emph "emphasized") ] , testGroup "headers" [ "level 1" =: - "\\section{header}" =?> header 1 "header" + "\\section{header}" =?> headerWith ("header",[],[]) 1 "header" , "level 2" =: - "\\subsection{header}" =?> header 2 "header" + "\\subsection{header}" =?> headerWith ("header",[],[]) 2 "header" , "level 3" =: - "\\subsubsection{header}" =?> header 3 "header" + "\\subsubsection{header}" =?> headerWith ("header",[],[]) 3 "header" , "emph" =: "\\section{text \\emph{emph}}" =?> - header 1 ("text" <> space <> emph "emph") + headerWith ("text-emph",[],[]) 1 ("text" <> space <> emph "emph") , "link" =: "\\section{text \\href{/url}{link}}" =?> - header 1 ("text" <> space <> link "/url" "" "link") + headerWith ("text-link",[],[]) 1 ("text" <> space <> link "/url" "" "link") ] , testGroup "math" @@ -55,6 +55,13 @@ tests = [ testGroup "basic" "hi % this is a comment\nthere\n" =?> para "hi there" ] + , testGroup "code blocks" + [ "identifier" =: + "\\begin{lstlisting}[label=test]\\end{lstlisting}" =?> codeBlockWith ("test", [], [("label","test")]) "" + , "no identifier" =: + "\\begin{lstlisting}\\end{lstlisting}" =?> codeBlock "" + ] + , testGroup "citations" [ natbibCitations , biblatexCitations @@ -79,14 +86,14 @@ natbibCitations = testGroup "natbib" =?> para (cite [baseCitation] (rt "\\citet{item1}")) , "suffix" =: "\\citet[p.~30]{item1}" =?> para - (cite [baseCitation{ citationSuffix = toList $ text ", p.\160\&30" }] (rt "\\citet[p.~30]{item1}")) + (cite [baseCitation{ citationSuffix = toList $ text "p.\160\&30" }] (rt "\\citet[p.~30]{item1}")) , "suffix long" =: "\\citet[p.~30, with suffix]{item1}" =?> para (cite [baseCitation{ citationSuffix = - toList $ text ", p.\160\&30, with suffix" }] (rt "\\citet[p.~30, with suffix]{item1}")) + toList $ text "p.\160\&30, with suffix" }] (rt "\\citet[p.~30, with suffix]{item1}")) , "multiple" =: "\\citeauthor{item1} \\citetext{\\citeyear{item1}; \\citeyear[p.~30]{item2}; \\citealp[see also][]{item3}}" =?> para (cite [baseCitation{ citationMode = AuthorInText } ,baseCitation{ citationMode = SuppressAuthor - , citationSuffix = [Str ",",Space,Str "p.\160\&30"] + , citationSuffix = [Str "p.\160\&30"] , citationId = "item2" } ,baseCitation{ citationId = "item3" , citationPrefix = [Str "see",Space,Str "also"] @@ -95,28 +102,28 @@ natbibCitations = testGroup "natbib" , "group" =: "\\citetext{\\citealp[see][p.~34--35]{item1}; \\citealp[also][chap. 3]{item3}}" =?> para (cite [baseCitation{ citationMode = NormalCitation , citationPrefix = [Str "see"] - , citationSuffix = [Str ",",Space,Str "p.\160\&34\8211\&35"] } + , citationSuffix = [Str "p.\160\&34\8211\&35"] } ,baseCitation{ citationMode = NormalCitation , citationId = "item3" , citationPrefix = [Str "also"] - , citationSuffix = [Str ",",Space,Str "chap.",Space,Str "3"] } + , citationSuffix = [Str "chap.",Space,Str "3"] } ] (rt "\\citetext{\\citealp[see][p.~34--35]{item1}; \\citealp[also][chap. 3]{item3}}")) , "suffix and locator" =: "\\citep[pp.~33, 35--37, and nowhere else]{item1}" =?> para (cite [baseCitation{ citationMode = NormalCitation - , citationSuffix = [Str ",",Space,Str "pp.\160\&33,",Space,Str "35\8211\&37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] (rt "\\citep[pp.~33, 35--37, and nowhere else]{item1}")) + , citationSuffix = [Str "pp.\160\&33,",Space,Str "35\8211\&37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] (rt "\\citep[pp.~33, 35--37, and nowhere else]{item1}")) , "suffix only" =: "\\citep[and nowhere else]{item1}" =?> para (cite [baseCitation{ citationMode = NormalCitation - , citationSuffix = toList $ text ", and nowhere else" }] (rt "\\citep[and nowhere else]{item1}")) + , citationSuffix = toList $ text "and nowhere else" }] (rt "\\citep[and nowhere else]{item1}")) , "no author" =: "\\citeyearpar{item1}, and now Doe with a locator \\citeyearpar[p.~44]{item2}" =?> para (cite [baseCitation{ citationMode = SuppressAuthor }] (rt "\\citeyearpar{item1}") <> text ", and now Doe with a locator " <> cite [baseCitation{ citationMode = SuppressAuthor - , citationSuffix = [Str ",",Space,Str "p.\160\&44"] + , citationSuffix = [Str "p.\160\&44"] , citationId = "item2" }] (rt "\\citeyearpar[p.~44]{item2}")) , "markup" =: "\\citep[\\emph{see}][p. \\textbf{32}]{item1}" =?> para (cite [baseCitation{ citationMode = NormalCitation , citationPrefix = [Emph [Str "see"]] - , citationSuffix = [Str ",",Space,Str "p.",Space, + , citationSuffix = [Str "p.",Space, Strong [Str "32"]] }] (rt "\\citep[\\emph{see}][p. \\textbf{32}]{item1}")) ] @@ -126,14 +133,14 @@ biblatexCitations = testGroup "biblatex" =?> para (cite [baseCitation] (rt "\\textcite{item1}")) , "suffix" =: "\\textcite[p.~30]{item1}" =?> para - (cite [baseCitation{ citationSuffix = toList $ text ", p.\160\&30" }] (rt "\\textcite[p.~30]{item1}")) + (cite [baseCitation{ citationSuffix = toList $ text "p.\160\&30" }] (rt "\\textcite[p.~30]{item1}")) , "suffix long" =: "\\textcite[p.~30, with suffix]{item1}" =?> para (cite [baseCitation{ citationSuffix = - toList $ text ", p.\160\&30, with suffix" }] (rt "\\textcite[p.~30, with suffix]{item1}")) + toList $ text "p.\160\&30, with suffix" }] (rt "\\textcite[p.~30, with suffix]{item1}")) , "multiple" =: "\\textcites{item1}[p.~30]{item2}[see also][]{item3}" =?> para (cite [baseCitation{ citationMode = AuthorInText } ,baseCitation{ citationMode = NormalCitation - , citationSuffix = [Str ",",Space,Str "p.\160\&30"] + , citationSuffix = [Str "p.\160\&30"] , citationId = "item2" } ,baseCitation{ citationId = "item3" , citationPrefix = [Str "see",Space,Str "also"] @@ -142,28 +149,28 @@ biblatexCitations = testGroup "biblatex" , "group" =: "\\autocites[see][p.~34--35]{item1}[also][chap. 3]{item3}" =?> para (cite [baseCitation{ citationMode = NormalCitation , citationPrefix = [Str "see"] - , citationSuffix = [Str ",",Space,Str "p.\160\&34\8211\&35"] } + , citationSuffix = [Str "p.\160\&34\8211\&35"] } ,baseCitation{ citationMode = NormalCitation , citationId = "item3" , citationPrefix = [Str "also"] - , citationSuffix = [Str ",",Space,Str "chap.",Space,Str "3"] } + , citationSuffix = [Str "chap.",Space,Str "3"] } ] (rt "\\autocites[see][p.~34--35]{item1}[also][chap. 3]{item3}")) , "suffix and locator" =: "\\autocite[pp.~33, 35--37, and nowhere else]{item1}" =?> para (cite [baseCitation{ citationMode = NormalCitation - , citationSuffix = [Str ",",Space,Str "pp.\160\&33,",Space,Str "35\8211\&37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] (rt "\\autocite[pp.~33, 35--37, and nowhere else]{item1}")) + , citationSuffix = [Str "pp.\160\&33,",Space,Str "35\8211\&37,",Space,Str "and",Space,Str "nowhere",Space, Str "else"] }] (rt "\\autocite[pp.~33, 35--37, and nowhere else]{item1}")) , "suffix only" =: "\\autocite[and nowhere else]{item1}" =?> para (cite [baseCitation{ citationMode = NormalCitation - , citationSuffix = toList $ text ", and nowhere else" }] (rt "\\autocite[and nowhere else]{item1}")) + , citationSuffix = toList $ text "and nowhere else" }] (rt "\\autocite[and nowhere else]{item1}")) , "no author" =: "\\autocite*{item1}, and now Doe with a locator \\autocite*[p.~44]{item2}" =?> para (cite [baseCitation{ citationMode = SuppressAuthor }] (rt "\\autocite*{item1}") <> text ", and now Doe with a locator " <> cite [baseCitation{ citationMode = SuppressAuthor - , citationSuffix = [Str ",",Space,Str "p.\160\&44"] + , citationSuffix = [Str "p.\160\&44"] , citationId = "item2" }] (rt "\\autocite*[p.~44]{item2}")) , "markup" =: "\\autocite[\\emph{see}][p. \\textbf{32}]{item1}" =?> para (cite [baseCitation{ citationMode = NormalCitation , citationPrefix = [Emph [Str "see"]] - , citationSuffix = [Str ",",Space,Str "p.",Space, + , citationSuffix = [Str "p.",Space, Strong [Str "32"]] }] (rt "\\autocite[\\emph{see}][p. \\textbf{32}]{item1}")) , "parencite" =: "\\parencite{item1}" =?> para (cite [baseCitation{ citationMode = NormalCitation }] (rt "\\parencite{item1}")) diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs index 8a9ed9667..5a51fe759 100644 --- a/tests/Tests/Readers/Markdown.hs +++ b/tests/Tests/Readers/Markdown.hs @@ -24,7 +24,7 @@ infix 4 =: testBareLink :: (String, Inlines) -> Test testBareLink (inp, ils) = test (readMarkdown def{ readerExtensions = - Set.fromList [Ext_autolink_bare_uris] }) + Set.fromList [Ext_autolink_bare_uris, Ext_raw_html] }) inp (inp, doc $ para ils) autolink :: String -> Inlines @@ -34,6 +34,9 @@ bareLinkTests :: [(String, Inlines)] bareLinkTests = [ ("http://google.com is a search engine.", autolink "http://google.com" <> " is a search engine.") + , ("<a href=\"http://foo.bar.baz\">http://foo.bar.baz</a>", + rawInline "html" "<a href=\"http://foo.bar.baz\">" <> + "http://foo.bar.baz" <> rawInline "html" "</a>") , ("Try this query: http://google.com?search=fish&time=hour.", "Try this query: " <> autolink "http://google.com?search=fish&time=hour" <> ".") , ("HTTPS://GOOGLE.COM,", @@ -133,6 +136,11 @@ tests = [ testGroup "inline code" "`*` {.haskell .special x=\"7\"}" =?> para (codeWith ("",["haskell","special"],[("x","7")]) "*") ] + , testGroup "emph and strong" + [ "two strongs in emph" =: + "***a**b **c**d*" =?> para (emph (strong (str "a") <> str "b" <> space + <> strong (str "c") <> str "d")) + ] , testGroup "raw LaTeX" [ "in URL" =: "\\begin\n" =?> para (text "\\begin") @@ -163,13 +171,13 @@ tests = [ testGroup "inline code" , testGroup "smart punctuation" [ test markdownSmart "quote before ellipses" ("'...hi'" - =?> para (singleQuoted ("…hi"))) + =?> para (singleQuoted "…hi")) , test markdownSmart "apostrophe before emph" ("D'oh! A l'*aide*!" =?> para ("D’oh! A l’" <> emph "aide" <> "!")) , 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»")) + =?> para "À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»") ] , testGroup "mixed emphasis and strong" [ "emph and strong emph alternating" =: @@ -208,4 +216,13 @@ tests = [ testGroup "inline code" -- , testGroup "round trip" -- [ property "p_markdown_round_trip" p_markdown_round_trip -- ] + , testGroup "lists" + [ "issue #1154" =: + " - <div>\n first div breaks\n </div>\n\n <button>if this button exists</button>\n\n <div>\n with this div too.\n </div>\n" + =?> bulletList [divWith nullAttr (plain $ text "first div breaks") <> + rawBlock "html" "<button>" <> + plain (text "if this button exists") <> + rawBlock "html" "</button>\n" <> + divWith nullAttr (plain $ text "with this div too.")] + ] ] diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs new file mode 100644 index 000000000..f8240ca3d --- /dev/null +++ b/tests/Tests/Readers/Org.hs @@ -0,0 +1,994 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Org (tests) where + +import Text.Pandoc.Definition +import Test.Framework +import Tests.Helpers +import Tests.Arbitrary() +import Text.Pandoc.Builder +import Text.Pandoc +import Data.List (intersperse) +import Data.Monoid (mempty, mappend, mconcat) + +org :: String -> Pandoc +org = readOrg def + +infix 4 =: +(=:) :: ToString c + => String -> (String, c) -> Test +(=:) = test org + +spcSep :: [Inlines] -> Inlines +spcSep = mconcat . intersperse space + +simpleTable' :: Int + -> [Blocks] + -> [[Blocks]] + -> Blocks +simpleTable' n = table "" (take n $ repeat (AlignDefault, 0.0)) + +tests :: [Test] +tests = + [ testGroup "Inlines" $ + [ "Plain String" =: + "Hello, World" =?> + para (spcSep [ "Hello,", "World" ]) + + , "Emphasis" =: + "/Planet Punk/" =?> + para (emph . spcSep $ ["Planet", "Punk"]) + + , "Strong" =: + "*Cider*" =?> + para (strong "Cider") + + , "Strong Emphasis" =: + "/*strength*/" =?> + para (emph . strong $ "strength") + + , "Strikeout" =: + "+Kill Bill+" =?> + para (strikeout . spcSep $ [ "Kill", "Bill" ]) + + , "Verbatim" =: + "=Robot.rock()=" =?> + para (code "Robot.rock()") + + , "Code" =: + "~word for word~" =?> + para (code "word for word") + + , "Math $..$" =: + "$E=mc^2$" =?> + para (math "E=mc^2") + + , "Math $$..$$" =: + "$$E=mc^2$$" =?> + para (displayMath "E=mc^2") + + , "Math \\[..\\]" =: + "\\[E=ℎν\\]" =?> + para (displayMath "E=ℎν") + + , "Math \\(..\\)" =: + "\\(σ_x σ_p ≥ \\frac{ℏ}{2}\\)" =?> + para (math "σ_x σ_p ≥ \\frac{ℏ}{2}") + + , "Symbol" =: + "A * symbol" =?> + para (str "A" <> space <> str "*" <> space <> "symbol") + + , "Superscript simple expression" =: + "2^-λ" =?> + para (str "2" <> superscript "-λ") + + , "Superscript multi char" =: + "2^{n-1}" =?> + para (str "2" <> superscript "n-1") + + , "Subscript simple expression" =: + "a_n" =?> + para (str "a" <> subscript "n") + + , "Subscript multi char" =: + "a_{n+1}" =?> + para (str "a" <> subscript "n+1") + + , "Linebreak" =: + "line \\\\ \nbreak" =?> + para ("line" <> linebreak <> "break") + + , "Inline note" =: + "[fn::Schreib mir eine E-Mail]" =?> + para (note $ para "Schreib mir eine E-Mail") + + , "Markup-chars not occuring on word break are symbols" =: + unlines [ "this+that+ +so+on" + , "seven*eight* nine*" + , "+not+funny+" + ] =?> + para (spcSep [ "this+that+", "+so+on" + , "seven*eight*", "nine*" + , strikeout "not+funny" + ]) + + , "No empty markup" =: + "// ** __ ++ == ~~ $$" =?> + para (spcSep [ "//", "**", "__", "++", "==", "~~", "$$" ]) + + , "Adherence to Org's rules for markup borders" =: + "/t/& a/ / ./r/ (*l*) /e/! /b/." =?> + para (spcSep [ emph $ "t/&" <> space <> "a" + , "/" + , "./r/" + , "(" <> (strong "l") <> ")" + , (emph "e") <> "!" + , (emph "b") <> "." + ]) + + , "Inline math must stay within three lines" =: + unlines [ "$a", "b", "c$", "$d", "e", "f", "g$" ] =?> + para ((math "a\nb\nc") <> space <> + spcSep [ "$d", "e", "f", "g$" ]) + + , "Single-character math" =: + "$a$ $b$! $c$?" =?> + para (spcSep [ math "a" + , "$b$!" + , (math "c") <> "?" + ]) + + , "Markup may not span more than two lines" =: + unlines [ "/this *is +totally", "nice+ not*", "emph/" ] =?> + para (spcSep [ "/this" + , (strong (spcSep + [ "is" + , (strikeout ("totally" <> space <> "nice")) + , "not" + ])) + , "emph/" ]) + + , "Sub- and superscript expressions" =: + unlines [ "a_(a(b)(c)d)" + , "e^(f(g)h)" + , "i_(jk)l)" + , "m^()n" + , "o_{p{q{}r}}" + , "s^{t{u}v}" + , "w_{xy}z}" + , "1^{}2" + , "3_{{}}" + , "4^(a(*b(c*)d))" + ] =?> + para (spcSep [ "a" <> subscript "(a(b)(c)d)" + , "e" <> superscript "(f(g)h)" + , "i" <> (subscript "(jk)") <> "l)" + , "m" <> (superscript "()") <> "n" + , "o" <> subscript "p{q{}r}" + , "s" <> superscript "t{u}v" + , "w" <> (subscript "xy") <> "z}" + , "1" <> (superscript "") <> "2" + , "3" <> subscript "{}" + , "4" <> superscript ("(a(" <> strong "b(c" <> ")d))") + ]) + + , "Image" =: + "[[./sunset.jpg]]" =?> + (para $ image "./sunset.jpg" "" "") + + , "Explicit link" =: + "[[http://zeitlens.com/][pseudo-random /nonsense/]]" =?> + (para $ link "http://zeitlens.com/" "" + ("pseudo-random" <> space <> emph "nonsense")) + + , "Self-link" =: + "[[http://zeitlens.com/]]" =?> + (para $ link "http://zeitlens.com/" "" "http://zeitlens.com/") + + , "Image link" =: + "[[sunset.png][dusk.svg]]" =?> + (para $ link "sunset.png" "" (image "dusk.svg" "" "")) + + , "Plain link" =: + "Posts on http://zeitlens.com/ can be funny at times." =?> + (para $ spcSep [ "Posts", "on" + , link "http://zeitlens.com/" "" "http://zeitlens.com/" + , "can", "be", "funny", "at", "times." + ]) + + , "Angle link" =: + "Look at <http://moltkeplatz.de> for fnords." =?> + (para $ spcSep [ "Look", "at" + , link "http://moltkeplatz.de" "" "http://moltkeplatz.de" + , "for", "fnords." + ]) + + , "Anchor" =: + "<<anchor>> Link here later." =?> + (para $ spanWith ("anchor", [], []) mempty <> + "Link" <> space <> "here" <> space <> "later.") + + , "Inline code block" =: + "src_emacs-lisp{(message \"Hello\")}" =?> + (para $ codeWith ( "" + , [ "commonlisp", "rundoc-block" ] + , [ ("rundoc-language", "emacs-lisp") ]) + "(message \"Hello\")") + + , "Inline code block with arguments" =: + "src_sh[:export both :results output]{echo 'Hello, World'}" =?> + (para $ codeWith ( "" + , [ "bash", "rundoc-block" ] + , [ ("rundoc-language", "sh") + , ("rundoc-export", "both") + , ("rundoc-results", "output") + ] + ) + "echo 'Hello, World'") + + , "Citation" =: + "[@nonexistent]" =?> + let citation = Citation + { citationId = "nonexistent" + , citationPrefix = [] + , citationSuffix = [] + , citationMode = NormalCitation + , citationNoteNum = 0 + , citationHash = 0} + in (para $ cite [citation] "[@nonexistent]") + + , "Citation containing text" =: + "[see @item1 p. 34-35]" =?> + let citation = Citation + { citationId = "item1" + , citationPrefix = [Str "see"] + , citationSuffix = [Space ,Str "p.",Space,Str "34-35"] + , citationMode = NormalCitation + , citationNoteNum = 0 + , citationHash = 0} + in (para $ cite [citation] "[see @item1 p. 34-35]") + + , "Inline LaTeX symbol" =: + "\\dots" =?> + para "…" + + , "Inline LaTeX command" =: + "\\textit{Emphasised}" =?> + para (emph "Emphasised") + + , "Inline LaTeX math symbol" =: + "\\tau" =?> + para (emph "τ") + + , "Unknown inline LaTeX command" =: + "\\notacommand{foo}" =?> + para (rawInline "latex" "\\notacommand{foo}") + + , "LaTeX citation" =: + "\\cite{Coffee}" =?> + let citation = Citation + { citationId = "Coffee" + , citationPrefix = [] + , citationSuffix = [] + , citationMode = AuthorInText + , citationNoteNum = 0 + , citationHash = 0} + in (para . cite [citation] $ rawInline "latex" "\\cite{Coffee}") + ] + + , testGroup "Meta Information" $ + [ "Comment" =: + "# Nothing to see here" =?> + (mempty::Blocks) + + , "Not a comment" =: + "#-tag" =?> + para "#-tag" + + , "Comment surrounded by Text" =: + unlines [ "Before" + , "# Comment" + , "After" + ] =?> + mconcat [ para "Before" + , para "After" + ] + + , "Title" =: + "#+TITLE: Hello, World" =?> + let titleInline = toList $ "Hello," <> space <> "World" + meta = setMeta "title" (MetaInlines titleInline) $ nullMeta + in Pandoc meta mempty + + , "Author" =: + "#+author: Albert /Emacs-Fanboy/ Krewinkel" =?> + let author = toList . spcSep $ [ "Albert", emph "Emacs-Fanboy", "Krewinkel" ] + meta = setMeta "author" (MetaInlines author) $ nullMeta + in Pandoc meta mempty + + , "Date" =: + "#+Date: Feb. *28*, 2014" =?> + let date = toList . spcSep $ [ "Feb.", (strong "28") <> ",", "2014" ] + meta = setMeta "date" (MetaInlines date) $ nullMeta + in Pandoc meta mempty + + , "Description" =: + "#+DESCRIPTION: Explanatory text" =?> + let description = toList . spcSep $ [ "Explanatory", "text" ] + meta = setMeta "description" (MetaInlines description) $ nullMeta + in Pandoc meta mempty + + , "Properties drawer" =: + unlines [ " :PROPERTIES:" + , " :setting: foo" + , " :END:" + ] =?> + (mempty::Blocks) + + , "Logbook drawer" =: + unlines [ " :LogBook:" + , " - State \"DONE\" from \"TODO\" [2014-03-03 Mon 11:00]" + , " :END:" + ] =?> + (mempty::Blocks) + + , "Drawer surrounded by text" =: + unlines [ "Before" + , ":PROPERTIES:" + , ":END:" + , "After" + ] =?> + para "Before" <> para "After" + + , "Drawer start is the only text in first line of a drawer" =: + unlines [ " :LOGBOOK: foo" + , " :END:" + ] =?> + para (spcSep [ ":LOGBOOK:", "foo", ":END:" ]) + + , "Drawers with unknown names are just text" =: + unlines [ ":FOO:" + , ":END:" + ] =?> + para (":FOO:" <> space <> ":END:") + + , "Anchor reference" =: + unlines [ "<<link-here>> Target." + , "" + , "[[link-here][See here!]]" + ] =?> + (para (spanWith ("link-here", [], []) mempty <> "Target.") <> + para (link "#link-here" "" ("See" <> space <> "here!"))) + + , "Search links are read as emph" =: + "[[Wally][Where's Wally?]]" =?> + (para (emph $ "Where's" <> space <> "Wally?")) + + , "Link to nonexistent anchor" =: + unlines [ "<<link-here>> Target." + , "" + , "[[link$here][See here!]]" + ] =?> + (para (spanWith ("link-here", [], []) mempty <> "Target.") <> + para (emph ("See" <> space <> "here!"))) + + , "Link abbreviation" =: + unlines [ "#+LINK: wp https://en.wikipedia.org/wiki/%s" + , "[[wp:Org_mode][Wikipedia on Org-mode]]" + ] =?> + (para (link "https://en.wikipedia.org/wiki/Org_mode" "" + ("Wikipedia" <> space <> "on" <> space <> "Org-mode"))) + + , "Link abbreviation, defined after first use" =: + unlines [ "[[zl:non-sense][Non-sense articles]]" + , "#+LINK: zl http://zeitlens.com/tags/%s.html" + ] =?> + (para (link "http://zeitlens.com/tags/non-sense.html" "" + ("Non-sense" <> space <> "articles"))) + + , "Link abbreviation, URL encoded arguments" =: + unlines [ "#+link: expl http://example.com/%h/foo" + , "[[expl:Hello, World!][Moin!]]" + ] =?> + (para (link "http://example.com/Hello%2C%20World%21/foo" "" "Moin!")) + + , "Link abbreviation, append arguments" =: + unlines [ "#+link: expl http://example.com/" + , "[[expl:foo][bar]]" + ] =?> + (para (link "http://example.com/foo" "" "bar")) + ] + + , testGroup "Basic Blocks" $ + [ "Paragraph" =: + "Paragraph\n" =?> + para "Paragraph" + + , "First Level Header" =: + "* Headline\n" =?> + header 1 "Headline" + + , "Third Level Header" =: + "*** Third Level Headline\n" =?> + header 3 ("Third" <> space <> + "Level" <> space <> + "Headline") + + , "Compact Headers with Paragraph" =: + unlines [ "* First Level" + , "** Second Level" + , " Text" + ] =?> + mconcat [ header 1 ("First" <> space <> "Level") + , header 2 ("Second" <> space <> "Level") + , para "Text" + ] + + , "Separated Headers with Paragraph" =: + unlines [ "* First Level" + , "" + , "** Second Level" + , "" + , " Text" + ] =?> + mconcat [ header 1 ("First" <> space <> "Level") + , header 2 ("Second" <> space <> "Level") + , para "Text" + ] + + , "Headers not preceded by a blank line" =: + unlines [ "** eat dinner" + , "Spaghetti and meatballs tonight." + , "** walk dog" + ] =?> + mconcat [ header 2 ("eat" <> space <> "dinner") + , para $ spcSep [ "Spaghetti", "and", "meatballs", "tonight." ] + , header 2 ("walk" <> space <> "dog") + ] + + , "Paragraph starting with an asterisk" =: + "*five" =?> + para "*five" + + , "Paragraph containing asterisk at beginning of line" =: + unlines [ "lucky" + , "*star" + ] =?> + para ("lucky" <> space <> "*star") + + , "Example block" =: + unlines [ ": echo hello" + , ": echo dear tester" + ] =?> + codeBlockWith ("", ["example"], []) "echo hello\necho dear tester\n" + + , "Example block surrounded by text" =: + unlines [ "Greetings" + , ": echo hello" + , ": echo dear tester" + , "Bye" + ] =?> + mconcat [ para "Greetings" + , codeBlockWith ("", ["example"], []) + "echo hello\necho dear tester\n" + , para "Bye" + ] + + , "Horizontal Rule" =: + unlines [ "before" + , "-----" + , "after" + ] =?> + mconcat [ para "before" + , horizontalRule + , para "after" + ] + + , "Not a Horizontal Rule" =: + "----- five dashes" =?> + (para $ spcSep [ "-----", "five", "dashes" ]) + + , "Comment Block" =: + unlines [ "#+BEGIN_COMMENT" + , "stuff" + , "bla" + , "#+END_COMMENT"] =?> + (mempty::Blocks) + + , "Figure" =: + unlines [ "#+caption: A very courageous man." + , "#+name: goodguy" + , "[[edward.jpg]]" + ] =?> + para (image "edward.jpg" "fig:goodguy" "A very courageous man.") + + , "Unnamed figure" =: + unlines [ "#+caption: A great whistleblower." + , "[[snowden.png]]" + ] =?> + para (image "snowden.png" "" "A great whistleblower.") + + , "Figure with `fig:` prefix in name" =: + unlines [ "#+caption: Used as a metapher in evolutionary biology." + , "#+name: fig:redqueen" + , "[[the-red-queen.jpg]]" + ] =?> + para (image "the-red-queen.jpg" "fig:redqueen" + "Used as a metapher in evolutionary biology.") + + , "Footnote" =: + unlines [ "A footnote[1]" + , "" + , "[1] First paragraph" + , "" + , "second paragraph" + ] =?> + para (mconcat + [ "A", space, "footnote" + , note $ mconcat [ para ("First" <> space <> "paragraph") + , para ("second" <> space <> "paragraph") + ] + ]) + + , "Two footnotes" =: + unlines [ "Footnotes[fn:1][fn:2]" + , "" + , "[fn:1] First note." + , "" + , "[fn:2] Second note." + ] =?> + para (mconcat + [ "Footnotes" + , note $ para ("First" <> space <> "note.") + , note $ para ("Second" <> space <> "note.") + ]) + + , "Footnote followed by header" =: + unlines [ "Another note[fn:yay]" + , "" + , "[fn:yay] This is great!" + , "" + , "** Headline" + ] =?> + mconcat + [ para (mconcat + [ "Another", space, "note" + , note $ para ("This" <> space <> "is" <> space <> "great!") + ]) + , header 2 "Headline" + ] + ] + + , testGroup "Lists" $ + [ "Simple Bullet Lists" =: + ("- Item1\n" ++ + "- Item2\n") =?> + bulletList [ plain "Item1" + , plain "Item2" + ] + + , "Indented Bullet Lists" =: + (" - Item1\n" ++ + " - Item2\n") =?> + bulletList [ plain "Item1" + , plain "Item2" + ] + + , "Multi-line Bullet Lists" =: + ("- *Fat\n" ++ + " Tony*\n" ++ + "- /Sideshow\n" ++ + " Bob/") =?> + bulletList [ plain $ strong ("Fat" <> space <> "Tony") + , plain $ emph ("Sideshow" <> space <> "Bob") + ] + + , "Nested Bullet Lists" =: + ("- Discovery\n" ++ + " + One More Time\n" ++ + " + Harder, Better, Faster, Stronger\n" ++ + "- Homework\n" ++ + " + Around the World\n"++ + "- Human After All\n" ++ + " + Technologic\n" ++ + " + Robot Rock\n") =?> + bulletList [ mconcat + [ para "Discovery" + , bulletList [ plain ("One" <> space <> + "More" <> space <> + "Time") + , plain ("Harder," <> space <> + "Better," <> space <> + "Faster," <> space <> + "Stronger") + ] + ] + , mconcat + [ para "Homework" + , bulletList [ plain ("Around" <> space <> + "the" <> space <> + "World") + ] + ] + , mconcat + [ para ("Human" <> space <> "After" <> space <> "All") + , bulletList [ plain "Technologic" + , plain ("Robot" <> space <> "Rock") + ] + ] + ] + + , "Simple Ordered List" =: + ("1. Item1\n" ++ + "2. Item2\n") =?> + let listStyle = (1, DefaultStyle, DefaultDelim) + listStructure = [ plain "Item1" + , plain "Item2" + ] + in orderedListWith listStyle listStructure + + , "Simple Ordered List with Parens" =: + ("1) Item1\n" ++ + "2) Item2\n") =?> + let listStyle = (1, DefaultStyle, DefaultDelim) + listStructure = [ plain "Item1" + , plain "Item2" + ] + in orderedListWith listStyle listStructure + + , "Indented Ordered List" =: + (" 1. Item1\n" ++ + " 2. Item2\n") =?> + let listStyle = (1, DefaultStyle, DefaultDelim) + listStructure = [ plain "Item1" + , plain "Item2" + ] + in orderedListWith listStyle listStructure + + , "Nested Ordered Lists" =: + ("1. One\n" ++ + " 1. One-One\n" ++ + " 2. One-Two\n" ++ + "2. Two\n" ++ + " 1. Two-One\n"++ + " 2. Two-Two\n") =?> + let listStyle = (1, DefaultStyle, DefaultDelim) + listStructure = [ mconcat + [ para "One" + , orderedList [ plain "One-One" + , plain "One-Two" + ] + ] + , mconcat + [ para "Two" + , orderedList [ plain "Two-One" + , plain "Two-Two" + ] + ] + ] + in orderedListWith listStyle listStructure + + , "Ordered List in Bullet List" =: + ("- Emacs\n" ++ + " 1. Org\n") =?> + bulletList [ (para "Emacs") <> + (orderedList [ plain "Org"]) + ] + + , "Bullet List in Ordered List" =: + ("1. GNU\n" ++ + " - Freedom\n") =?> + orderedList [ (para "GNU") <> bulletList [ (plain "Freedom") ] ] + + , "Definition List" =: + unlines [ "- PLL :: phase-locked loop" + , "- TTL ::" + , " transistor-transistor logic" + , "- PSK::phase-shift keying" + , "" + , " a digital modulation scheme" + ] =?> + definitionList [ ("PLL", [ plain $ "phase-locked" <> space <> "loop" ]) + , ("TTL", [ plain $ "transistor-transistor" <> space <> + "logic" ]) + , ("PSK", [ mconcat + [ para $ "phase-shift" <> space <> "keying" + , para $ spcSep [ "a", "digital" + , "modulation", "scheme" ] + ] + ]) + ] + + , "Compact definition list" =: + unlines [ "- ATP :: adenosine 5' triphosphate" + , "- DNA :: deoxyribonucleic acid" + , "- PCR :: polymerase chain reaction" + , "" + ] =?> + definitionList + [ ("ATP", [ plain $ spcSep [ "adenosine", "5'", "triphosphate" ] ]) + , ("DNA", [ plain $ spcSep [ "deoxyribonucleic", "acid" ] ]) + , ("PCR", [ plain $ spcSep [ "polymerase", "chain", "reaction" ] ]) + ] + + , "Loose bullet list" =: + unlines [ "- apple" + , "" + , "- orange" + , "" + , "- peach" + ] =?> + bulletList [ para "apple" + , para "orange" + , para "peach" + ] + ] + + , testGroup "Tables" + [ "Single cell table" =: + "|Test|" =?> + simpleTable' 1 mempty [[plain "Test"]] + + , "Multi cell table" =: + "| One | Two |" =?> + simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ] + + , "Multi line table" =: + unlines [ "| One |" + , "| Two |" + , "| Three |" + ] =?> + simpleTable' 1 mempty + [ [ plain "One" ] + , [ plain "Two" ] + , [ plain "Three" ] + ] + + , "Empty table" =: + "||" =?> + simpleTable' 1 mempty mempty + + , "Glider Table" =: + unlines [ "| 1 | 0 | 0 |" + , "| 0 | 1 | 1 |" + , "| 1 | 1 | 0 |" + ] =?> + simpleTable' 3 mempty + [ [ plain "1", plain "0", plain "0" ] + , [ plain "0", plain "1", plain "1" ] + , [ plain "1", plain "1", plain "0" ] + ] + + , "Table between Paragraphs" =: + unlines [ "Before" + , "| One | Two |" + , "After" + ] =?> + mconcat [ para "Before" + , simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ] + , para "After" + ] + + , "Table with Header" =: + unlines [ "| Species | Status |" + , "|--------------+--------------|" + , "| cervisiae | domesticated |" + , "| paradoxus | wild |" + ] =?> + simpleTable [ plain "Species", plain "Status" ] + [ [ plain "cervisiae", plain "domesticated" ] + , [ plain "paradoxus", plain "wild" ] + ] + + , "Table with final hline" =: + unlines [ "| cervisiae | domesticated |" + , "| paradoxus | wild |" + , "|--------------+--------------|" + ] =?> + simpleTable' 2 mempty + [ [ plain "cervisiae", plain "domesticated" ] + , [ plain "paradoxus", plain "wild" ] + ] + + , "Table in a box" =: + unlines [ "|---------|---------|" + , "| static | Haskell |" + , "| dynamic | Lisp |" + , "|---------+---------|" + ] =?> + simpleTable' 2 mempty + [ [ plain "static", plain "Haskell" ] + , [ plain "dynamic", plain "Lisp" ] + ] + + , "Table with alignment row" =: + unlines [ "| Numbers | Text | More |" + , "| <c> | <r> | |" + , "| 1 | One | foo |" + , "| 2 | Two | bar |" + ] =?> + table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0]) + [] + [ [ plain "Numbers", plain "Text", plain "More" ] + , [ plain "1" , plain "One" , plain "foo" ] + , [ plain "2" , plain "Two" , plain "bar" ] + ] + + , "Pipe within text doesn't start a table" =: + "Ceci n'est pas une | pipe " =?> + para (spcSep [ "Ceci", "n'est", "pas", "une", "|", "pipe" ]) + + , "Missing pipe at end of row" =: + "|incomplete-but-valid" =?> + simpleTable' 1 mempty [ [ plain "incomplete-but-valid" ] ] + + , "Table with differing row lengths" =: + unlines [ "| Numbers | Text " + , "|-" + , "| <c> | <r> |" + , "| 1 | One | foo |" + , "| 2" + ] =?> + table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0]) + [ plain "Numbers", plain "Text" , plain mempty ] + [ [ plain "1" , plain "One" , plain "foo" ] + , [ plain "2" , plain mempty , plain mempty ] + ] + + , "Table with caption" =: + unlines [ "#+CAPTION: Hitchhiker's Multiplication Table" + , "| x | 6 |" + , "| 9 | 42 |" + ] =?> + table "Hitchhiker's Multiplication Table" + [(AlignDefault, 0), (AlignDefault, 0)] + [] + [ [ plain "x", plain "6" ] + , [ plain "9", plain "42" ] + ] + ] + + , testGroup "Blocks and fragments" + [ "Source block" =: + unlines [ " #+BEGIN_SRC haskell" + , " main = putStrLn greeting" + , " where greeting = \"moin\"" + , " #+END_SRC" ] =?> + let attr' = ("", ["haskell"], []) + code' = "main = putStrLn greeting\n" ++ + " where greeting = \"moin\"\n" + in codeBlockWith attr' code' + + , "Source block between paragraphs" =: + unlines [ "Low German greeting" + , " #+BEGIN_SRC haskell" + , " main = putStrLn greeting" + , " where greeting = \"Moin!\"" + , " #+END_SRC" ] =?> + let attr' = ("", ["haskell"], []) + code' = "main = putStrLn greeting\n" ++ + " where greeting = \"Moin!\"\n" + in mconcat [ para $ spcSep [ "Low", "German", "greeting" ] + , codeBlockWith attr' code' + ] + , "Source block with rundoc/babel arguments" =: + unlines [ "#+BEGIN_SRC emacs-lisp :exports both" + , "(progn (message \"Hello, World!\")" + , " (+ 23 42))" + , "#+END_SRC" ] =?> + let classes = [ "commonlisp" -- as kate doesn't know emacs-lisp syntax + , "rundoc-block" + ] + params = [ ("rundoc-language", "emacs-lisp") + , ("rundoc-exports", "both") + ] + code' = unlines [ "(progn (message \"Hello, World!\")" + , " (+ 23 42))" ] + in codeBlockWith ("", classes, params) code' + + , "Example block" =: + unlines [ "#+begin_example" + , "A chosen representation of" + , "a rule." + , "#+eND_exAMPle" + ] =?> + codeBlockWith ("", ["example"], []) + "A chosen representation of\na rule.\n" + + , "HTML block" =: + unlines [ "#+BEGIN_HTML" + , "<aside>HTML5 is pretty nice.</aside>" + , "#+END_HTML" + ] =?> + rawBlock "html" "<aside>HTML5 is pretty nice.</aside>\n" + + , "Quote block" =: + unlines [ "#+BEGIN_QUOTE" + , "/Niemand/ hat die Absicht, eine Mauer zu errichten!" + , "#+END_QUOTE" + ] =?> + blockQuote (para (spcSep [ emph "Niemand", "hat", "die", "Absicht," + , "eine", "Mauer", "zu", "errichten!" + ])) + + , "Verse block" =: + unlines [ "The first lines of Goethe's /Faust/:" + , "#+begin_verse" + , "Habe nun, ach! Philosophie," + , "Juristerei und Medizin," + , "Und leider auch Theologie!" + , "Durchaus studiert, mit heißem Bemühn." + , "#+end_verse" + ] =?> + mconcat + [ para $ spcSep [ "The", "first", "lines", "of" + , "Goethe's", emph "Faust" <> ":"] + , para $ mconcat + [ spcSep [ "Habe", "nun,", "ach!", "Philosophie," ] + , linebreak + , spcSep [ "Juristerei", "und", "Medizin," ] + , linebreak + , spcSep [ "Und", "leider", "auch", "Theologie!" ] + , linebreak + , spcSep [ "Durchaus", "studiert,", "mit", "heißem", "Bemühn." ] + ] + ] + + , "LaTeX fragment" =: + unlines [ "\\begin{equation}" + , "X_i = \\begin{cases}" + , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) = \\alpha(i)\\\\" + , " C_{\\alpha(i)} & \\text{otherwise}" + , " \\end{cases}" + , "\\end{equation}" + ] =?> + rawBlock "latex" + (unlines [ "\\begin{equation}" + , "X_i = \\begin{cases}" + , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) =" ++ + " \\alpha(i)\\\\" + , " C_{\\alpha(i)} & \\text{otherwise}" + , " \\end{cases}" + , "\\end{equation}" + ]) + + , "Code block with caption" =: + unlines [ "#+CAPTION: Functor laws in Haskell" + , "#+NAME: functor-laws" + , "#+BEGIN_SRC haskell" + , "fmap id = id" + , "fmap (p . q) = (fmap p) . (fmap q)" + , "#+END_SRC" + ] =?> + divWith + nullAttr + (mappend + (plain $ spanWith ("", ["label"], []) + (spcSep [ "Functor", "laws", "in", "Haskell" ])) + (codeBlockWith ("functor-laws", ["haskell"], []) + (unlines [ "fmap id = id" + , "fmap (p . q) = (fmap p) . (fmap q)" + ]))) + + , "Convert blank lines in blocks to single newlines" =: + unlines [ "#+begin_html" + , "" + , "<span>boring</span>" + , "" + , "#+end_html" + ] =?> + rawBlock "html" "\n<span>boring</span>\n\n" + + , "Non-letter chars in source block parameters" =: + unlines [ "#+BEGIN_SRC C :tangle xxxx.c :city Zürich" + , "code body" + , "#+END_SRC" + ] =?> + let classes = [ "c", "rundoc-block" ] + params = [ ("rundoc-language", "C") + , ("rundoc-tangle", "xxxx.c") + , ("rundoc-city", "Zürich") + ] + in codeBlockWith ( "", classes, params) "code body\n" + ] + ] diff --git a/tests/Tests/Walk.hs b/tests/Tests/Walk.hs new file mode 100644 index 000000000..34350e28a --- /dev/null +++ b/tests/Tests/Walk.hs @@ -0,0 +1,47 @@ +{-# LANGUAGE ScopedTypeVariables, FlexibleContexts #-} +module Tests.Walk (tests) where + +import Text.Pandoc.Definition +import Text.Pandoc.Walk +import Test.Framework +import Tests.Helpers +import Data.Char (toUpper) +import Tests.Arbitrary() +import Data.Generics +import Data.Monoid + +tests :: [Test] +tests = [ testGroup "Walk" + [ property "p_walk inlineTrans" (p_walk inlineTrans) + , property "p_walk blockTrans" (p_walk blockTrans) + , property "p_query inlineQuery" (p_query inlineQuery) + , property "p_query blockQuery" (p_query blockQuery) + ] + ] + +p_walk :: (Typeable a, Walkable a Pandoc) + => (a -> a) -> Pandoc -> Bool +p_walk f d = everywhere (mkT f) d == walk f d + +p_query :: (Eq a, Typeable a1, Monoid a, Walkable a1 Pandoc) + => (a1 -> a) -> Pandoc -> Bool +p_query f d = everything mappend (mempty `mkQ` f) d == query f d + +inlineTrans :: Inline -> Inline +inlineTrans (Str xs) = Str $ map toUpper xs +inlineTrans (Emph xs) = Strong xs +inlineTrans x = x + +blockTrans :: Block -> Block +blockTrans (Plain xs) = Para xs +blockTrans (BlockQuote xs) = Div ("",["special"],[]) xs +blockTrans x = x + +inlineQuery :: Inline -> String +inlineQuery (Str xs) = xs +inlineQuery _ = "" + +blockQuery :: Block -> [Int] +blockQuery (Header lev _ _) = [lev] +blockQuery _ = [] + diff --git a/tests/Tests/Writers/AsciiDoc.hs b/tests/Tests/Writers/AsciiDoc.hs new file mode 100644 index 000000000..118e648d3 --- /dev/null +++ b/tests/Tests/Writers/AsciiDoc.hs @@ -0,0 +1,37 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.AsciiDoc (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Tests.Arbitrary() +import Data.Monoid + +asciidoc :: (ToString a, ToPandoc a) => a -> String +asciidoc = writeAsciiDoc def{ writerWrapText = False } . toPandoc + +tests :: [Test] +tests = [ testGroup "tables" + [ test asciidoc "empty cells" $ + simpleTable [] [[mempty],[mempty]] =?> unlines + [ "[cols=\"\",]" + , "|====" + , "|" + , "|" + , "|====" + ] + , test asciidoc "multiblock cells" $ + simpleTable [] [[para "Para 1" <> para "Para 2"]] + =?> unlines + [ "[cols=\"\",]" + , "|=====" + , "a|" + , "Para 1" + , "" + , "Para 2" + , "" + , "|=====" + ] + ] + ] diff --git a/tests/Tests/Writers/Docbook.hs b/tests/Tests/Writers/Docbook.hs new file mode 100644 index 000000000..97126b473 --- /dev/null +++ b/tests/Tests/Writers/Docbook.hs @@ -0,0 +1,229 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.Docbook (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Tests.Arbitrary() + +docbook :: (ToString a, ToPandoc a) => a -> String +docbook = writeDocbook def{ writerWrapText = False } . toPandoc + +{- + "my test" =: X =?> Y + +is shorthand for + + test docbook "my test" $ X =?> Y + +which is in turn shorthand for + + test docbook "my test" (X,Y) +-} + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> Test +(=:) = test docbook + +lineblock :: Blocks +lineblock = para ("some text" <> linebreak <> + "and more lines" <> linebreak <> + "and again") +lineblock_out :: [String] +lineblock_out = [ "<literallayout>some text" + , "and more lines" + , "and again</literallayout>" + ] + +tests :: [Test] +tests = [ testGroup "line blocks" + [ "none" =: para "This is a test" + =?> unlines + [ "<para>" + , " This is a test" + , "</para>" + ] + , "basic" =: lineblock + =?> unlines lineblock_out + , "blockquote" =: blockQuote lineblock + =?> unlines + ( [ "<blockquote>" ] ++ + lineblock_out ++ + [ "</blockquote>" ] + ) + , "footnote" =: para ("This is a test" <> + note lineblock <> + " of footnotes") + =?> unlines + ( [ "<para>" + , " This is a test<footnote>" ] ++ + lineblock_out ++ + [ " </footnote> of footnotes" + , "</para>" ] + ) + ] + , testGroup "compact lists" + [ testGroup "bullet" + [ "compact" =: bulletList [plain "a", plain "b", plain "c"] + =?> unlines + [ "<itemizedlist spacing=\"compact\">" + , " <listitem>" + , " <para>" + , " a" + , " </para>" + , " </listitem>" + , " <listitem>" + , " <para>" + , " b" + , " </para>" + , " </listitem>" + , " <listitem>" + , " <para>" + , " c" + , " </para>" + , " </listitem>" + , "</itemizedlist>" + ] + , "loose" =: bulletList [para "a", para "b", para "c"] + =?> unlines + [ "<itemizedlist>" + , " <listitem>" + , " <para>" + , " a" + , " </para>" + , " </listitem>" + , " <listitem>" + , " <para>" + , " b" + , " </para>" + , " </listitem>" + , " <listitem>" + , " <para>" + , " c" + , " </para>" + , " </listitem>" + , "</itemizedlist>" + ] + ] + , testGroup "ordered" + [ "compact" =: orderedList [plain "a", plain "b", plain "c"] + =?> unlines + [ "<orderedlist spacing=\"compact\">" + , " <listitem>" + , " <para>" + , " a" + , " </para>" + , " </listitem>" + , " <listitem>" + , " <para>" + , " b" + , " </para>" + , " </listitem>" + , " <listitem>" + , " <para>" + , " c" + , " </para>" + , " </listitem>" + , "</orderedlist>" + ] + , "loose" =: orderedList [para "a", para "b", para "c"] + =?> unlines + [ "<orderedlist>" + , " <listitem>" + , " <para>" + , " a" + , " </para>" + , " </listitem>" + , " <listitem>" + , " <para>" + , " b" + , " </para>" + , " </listitem>" + , " <listitem>" + , " <para>" + , " c" + , " </para>" + , " </listitem>" + , "</orderedlist>" + ] + ] + , testGroup "definition" + [ "compact" =: definitionList [ ("an", [plain "apple" ]) + , ("a", [plain "banana"]) + , ("an", [plain "orange"])] + =?> unlines + [ "<variablelist spacing=\"compact\">" + , " <varlistentry>" + , " <term>" + , " an" + , " </term>" + , " <listitem>" + , " <para>" + , " apple" + , " </para>" + , " </listitem>" + , " </varlistentry>" + , " <varlistentry>" + , " <term>" + , " a" + , " </term>" + , " <listitem>" + , " <para>" + , " banana" + , " </para>" + , " </listitem>" + , " </varlistentry>" + , " <varlistentry>" + , " <term>" + , " an" + , " </term>" + , " <listitem>" + , " <para>" + , " orange" + , " </para>" + , " </listitem>" + , " </varlistentry>" + , "</variablelist>" + ] + , "loose" =: definitionList [ ("an", [para "apple" ]) + , ("a", [para "banana"]) + , ("an", [para "orange"])] + =?> unlines + [ "<variablelist>" + , " <varlistentry>" + , " <term>" + , " an" + , " </term>" + , " <listitem>" + , " <para>" + , " apple" + , " </para>" + , " </listitem>" + , " </varlistentry>" + , " <varlistentry>" + , " <term>" + , " a" + , " </term>" + , " <listitem>" + , " <para>" + , " banana" + , " </para>" + , " </listitem>" + , " </varlistentry>" + , " <varlistentry>" + , " <term>" + , " an" + , " </term>" + , " <listitem>" + , " <para>" + , " orange" + , " </para>" + , " </listitem>" + , " </varlistentry>" + , "</variablelist>" + ] + ] + ] + ] diff --git a/tests/Tests/Writers/HTML.hs b/tests/Tests/Writers/HTML.hs index 1693f2fc1..84f4db191 100644 --- a/tests/Tests/Writers/HTML.hs +++ b/tests/Tests/Writers/HTML.hs @@ -6,7 +6,6 @@ import Text.Pandoc.Builder import Text.Pandoc import Tests.Helpers import Tests.Arbitrary() -import Text.Highlighting.Kate (languages) -- null if no hl support html :: (ToString a, ToPandoc a) => a -> String html = writeHtmlString def{ writerWrapText = False } . toPandoc @@ -32,9 +31,7 @@ tests :: [Test] tests = [ testGroup "inline code" [ "basic" =: code "@&" =?> "<code>@&</code>" , "haskell" =: codeWith ("",["haskell"],[]) ">>=" - =?> if null languages - then "<code class=\"haskell\">>>=</code>" - else "<code class=\"sourceCode haskell\"><span class=\"fu\">>>=</span></code>" + =?> "<code class=\"haskell\">>>=</code>" , "nolanguage" =: codeWith ("",["nolanguage"],[]) ">>=" =?> "<code class=\"nolanguage\">>>=</code>" ] diff --git a/tests/Tests/Writers/LaTeX.hs b/tests/Tests/Writers/LaTeX.hs index b1427d91f..c32ded36d 100644 --- a/tests/Tests/Writers/LaTeX.hs +++ b/tests/Tests/Writers/LaTeX.hs @@ -8,7 +8,10 @@ import Tests.Helpers import Tests.Arbitrary() latex :: (ToString a, ToPandoc a) => a -> String -latex = writeLaTeX def . toPandoc +latex = writeLaTeX def{ writerHighlight = True } . toPandoc + +latexListing :: (ToString a, ToPandoc a) => a -> String +latexListing = writeLaTeX def{ writerListings = True } . toPandoc {- "my test" =: X =?> Y @@ -31,9 +34,36 @@ tests :: [Test] tests = [ testGroup "code blocks" [ "in footnotes" =: note (para "hi" <> codeBlock "hi") =?> "\\footnote{hi\n\n\\begin{Verbatim}\nhi\n\\end{Verbatim}\n}" + , test latexListing "identifier" $ codeBlockWith ("id",[],[]) "hi" =?> + ("\\begin{lstlisting}[label=id]\nhi\n\\end{lstlisting}" :: String) + , test latexListing "no identifier" $ codeBlock "hi" =?> + ("\\begin{lstlisting}\nhi\n\\end{lstlisting}" :: String) + ] + , testGroup "definition lists" + [ "with internal link" =: definitionList [(link "#go" "" (str "testing"), + [plain (text "hi there")])] =?> + "\\begin{description}\n\\itemsep1pt\\parskip0pt\\parsep0pt\n\\item[{\\hyperref[go]{testing}}]\nhi there\n\\end{description}" ] , testGroup "math" [ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?> "$\\sigma|_{\\{x\\}}$" ] + , testGroup "headers" + [ "unnumbered header" =: + headerWith ("foo",["unnumbered"],[]) 1 + (text "Header 1" <> note (plain $ text "note")) =?> + "\\section*{Header 1\\footnote{note}}\\label{foo}\n\\addcontentsline{toc}{section}{Header 1}\n" + ] + , testGroup "inline code" + [ "struck out and highlighted" =: + strikeout (codeWith ("",["haskell"],[]) "foo" <> space + <> str "bar") =?> + "\\sout{\\mbox{\\VERB|\\NormalTok{foo}|} bar}" + , "struck out and not highlighted" =: + strikeout (code "foo" <> space + <> str "bar") =?> + "\\sout{\\texttt{foo} bar}" + , "single quotes" =: + code "dog's" =?> "\\texttt{dog\\textquotesingle{}s}" + ] ] diff --git a/tests/Tests/Writers/Markdown.hs b/tests/Tests/Writers/Markdown.hs index 99b85dfb7..c2a8f5903 100644 --- a/tests/Tests/Writers/Markdown.hs +++ b/tests/Tests/Writers/Markdown.hs @@ -31,4 +31,8 @@ tests :: [Test] tests = [ "indented code after list" =: (orderedList [ para "one" <> para "two" ] <> codeBlock "test") =?> "1. one\n\n two\n\n<!-- -->\n\n test" + , "list with tight sublist" + =: bulletList [ plain "foo" <> bulletList [ plain "bar" ], + plain "baz" ] + =?> "- foo\n - bar\n- baz\n" ] |