diff options
author | John MacFarlane <jgm@berkeley.edu> | 2017-02-04 12:56:30 +0100 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2017-02-04 12:56:30 +0100 |
commit | 18ab8642692caca2716fd9b5a0e6dbfd3d9cf9cc (patch) | |
tree | 05f4e9024093e233c131b3494e71265062ffd94a /test/Tests/Writers | |
parent | 8418c1a7d7e5312dfddbc011adb257552b2a864b (diff) | |
download | pandoc-18ab8642692caca2716fd9b5a0e6dbfd3d9cf9cc.tar.gz |
Moved tests/ -> test/.
Diffstat (limited to 'test/Tests/Writers')
-rw-r--r-- | test/Tests/Writers/AsciiDoc.hs | 55 | ||||
-rw-r--r-- | test/Tests/Writers/ConTeXt.hs | 70 | ||||
-rw-r--r-- | test/Tests/Writers/Docbook.hs | 302 | ||||
-rw-r--r-- | test/Tests/Writers/Docx.hs | 151 | ||||
-rw-r--r-- | test/Tests/Writers/HTML.hs | 43 | ||||
-rw-r--r-- | test/Tests/Writers/LaTeX.hs | 175 | ||||
-rw-r--r-- | test/Tests/Writers/Markdown.hs | 266 | ||||
-rw-r--r-- | test/Tests/Writers/Native.hs | 21 | ||||
-rw-r--r-- | test/Tests/Writers/Plain.hs | 21 | ||||
-rw-r--r-- | test/Tests/Writers/RST.hs | 107 | ||||
-rw-r--r-- | test/Tests/Writers/TEI.hs | 43 |
11 files changed, 1254 insertions, 0 deletions
diff --git a/test/Tests/Writers/AsciiDoc.hs b/test/Tests/Writers/AsciiDoc.hs new file mode 100644 index 000000000..7103b838b --- /dev/null +++ b/test/Tests/Writers/AsciiDoc.hs @@ -0,0 +1,55 @@ +module Tests.Writers.AsciiDoc (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Text.Pandoc.Arbitrary() + +asciidoc :: (ToPandoc a) => a -> String +asciidoc = purely (writeAsciiDoc def{ writerWrapText = WrapNone }) . toPandoc + +tests :: [Test] +tests = [ testGroup "emphasis" + [ test asciidoc "emph word before" $ + para (text "foo" <> emph (text "bar")) =?> + "foo__bar__" + , test asciidoc "emph word after" $ + para (emph (text "foo") <> text "bar") =?> + "__foo__bar" + , test asciidoc "emph quoted" $ + para (doubleQuoted (emph (text "foo"))) =?> + "``__foo__''" + , test asciidoc "strong word before" $ + para (text "foo" <> strong (text "bar")) =?> + "foo**bar**" + , test asciidoc "strong word after" $ + para (strong (text "foo") <> text "bar") =?> + "**foo**bar" + , test asciidoc "strong quoted" $ + para (singleQuoted (strong (text "foo"))) =?> + "`**foo**'" + ] + , testGroup "tables" + [ test asciidoc "empty cells" $ + simpleTable [] [[mempty],[mempty]] =?> unlines + [ "[cols=\"\",]" + , "|====" + , "|" + , "|" + , "|====" + ] + , test asciidoc "multiblock cells" $ + simpleTable [] [[para (text "Para 1") <> para (text "Para 2")]] + =?> unlines + [ "[cols=\"\",]" + , "|=====" + , "a|" + , "Para 1" + , "" + , "Para 2" + , "" + , "|=====" + ] + ] + ] diff --git a/test/Tests/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs new file mode 100644 index 000000000..b3e12a571 --- /dev/null +++ b/test/Tests/Writers/ConTeXt.hs @@ -0,0 +1,70 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.ConTeXt (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Text.Pandoc.Arbitrary() + +context :: (ToPandoc a) => a -> String +context = purely (writeConTeXt def) . toPandoc + +context' :: (ToPandoc a) => a -> String +context' = purely (writeConTeXt def{ writerWrapText = WrapNone }) . toPandoc + +{- + "my test" =: X =?> Y + +is shorthand for + + test context "my test" $ X =?> Y + +which is in turn shorthand for + + test context "my test" (X,Y) +-} + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> Test +(=:) = test context + +tests :: [Test] +tests = [ testGroup "inline code" + [ "with '}'" =: code "}" =?> "\\mono{\\}}" + , "without '}'" =: code "]" =?> "\\type{]}" + , property "code property" $ \s -> null s || + if '{' `elem` s || '}' `elem` s + then (context' $ code s) == "\\mono{" ++ + (context' $ str s) ++ "}" + else (context' $ code s) == "\\type{" ++ s ++ "}" + ] + , testGroup "headers" + [ "level 1" =: + headerWith ("my-header",[],[]) 1 "My header" =?> "\\section[my-header]{My header}" + ] + , testGroup "bullet lists" + [ "nested" =: + bulletList [ + plain (text "top") + <> bulletList [ + plain (text "next") + <> bulletList [plain (text "bot")] + ] + ] =?> unlines + [ "\\startitemize[packed]" + , "\\item" + , " top" + , " \\startitemize[packed]" + , " \\item" + , " next" + , " \\startitemize[packed]" + , " \\item" + , " bot" + , " \\stopitemize" + , " \\stopitemize" + , "\\stopitemize" ] + ] + ] + diff --git a/test/Tests/Writers/Docbook.hs b/test/Tests/Writers/Docbook.hs new file mode 100644 index 000000000..f34f2495c --- /dev/null +++ b/test/Tests/Writers/Docbook.hs @@ -0,0 +1,302 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.Docbook (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Text.Pandoc.Arbitrary() + +docbook :: (ToPandoc a) => a -> String +docbook = docbookWithOpts def{ writerWrapText = WrapNone } + +docbookWithOpts :: ToPandoc a => WriterOptions -> a -> String +docbookWithOpts opts = purely (writeDocbook4 opts) . 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>" + ] + ] + ] + , testGroup "writer options" $ + [ testGroup "top-level division" $ + let + headers = header 1 (text "header1") + <> header 2 (text "header2") + <> header 3 (text "header3") + + docbookTopLevelDiv :: (ToPandoc a) + => TopLevelDivision -> a -> String + docbookTopLevelDiv division = + docbookWithOpts def{ writerTopLevelDivision = division } + in + [ test (docbookTopLevelDiv TopLevelSection) "sections as top-level" $ + headers =?> + unlines [ "<sect1>" + , " <title>header1</title>" + , " <sect2>" + , " <title>header2</title>" + , " <sect3>" + , " <title>header3</title>" + , " <para>" + , " </para>" + , " </sect3>" + , " </sect2>" + , "</sect1>" + ] + , test (docbookTopLevelDiv TopLevelChapter) "chapters as top-level" $ + headers =?> + unlines [ "<chapter>" + , " <title>header1</title>" + , " <sect1>" + , " <title>header2</title>" + , " <sect2>" + , " <title>header3</title>" + , " <para>" + , " </para>" + , " </sect2>" + , " </sect1>" + , "</chapter>" + ] + , test (docbookTopLevelDiv TopLevelPart) "parts as top-level" $ + headers =?> + unlines [ "<part>" + , " <title>header1</title>" + , " <chapter>" + , " <title>header2</title>" + , " <sect1>" + , " <title>header3</title>" + , " <para>" + , " </para>" + , " </sect1>" + , " </chapter>" + , "</part>" + ] + , test (docbookTopLevelDiv TopLevelDefault) "default top-level" $ + headers =?> + unlines [ "<sect1>" + , " <title>header1</title>" + , " <sect2>" + , " <title>header2</title>" + , " <sect3>" + , " <title>header3</title>" + , " <para>" + , " </para>" + , " </sect3>" + , " </sect2>" + , "</sect1>" + ] + ] + ] + ] diff --git a/test/Tests/Writers/Docx.hs b/test/Tests/Writers/Docx.hs new file mode 100644 index 000000000..fd320d224 --- /dev/null +++ b/test/Tests/Writers/Docx.hs @@ -0,0 +1,151 @@ +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 System.FilePath ((</>)) +import Text.Pandoc.Class (runIOorExplode) + +type Options = (WriterOptions, ReaderOptions) + +compareOutput :: Options + -> FilePath + -> FilePath + -> IO (Pandoc, Pandoc) +compareOutput opts nativeFileIn nativeFileOut = do + nf <- Prelude.readFile nativeFileIn + nf' <- Prelude.readFile nativeFileOut + let wopts = fst opts + df <- runIOorExplode $ do + d <- readNative def nf + writeDocx wopts{writerUserDataDir = Just (".." </> "data")} d + df' <- runIOorExplode (readNative def nf') + p <- runIOorExplode $ readDocx (snd opts) df + return (p, df') + +testCompareWithOptsIO :: Options -> String -> FilePath -> FilePath -> IO Test +testCompareWithOptsIO opts name nativeFileIn nativeFileOut = do + (dp, np) <- compareOutput opts nativeFileIn nativeFileOut + return $ test id name (dp, np) + +testCompareWithOpts :: Options -> String -> FilePath -> FilePath -> Test +testCompareWithOpts opts name nativeFileIn nativeFileOut = + buildTest $ testCompareWithOptsIO opts name nativeFileIn nativeFileOut + +roundTripCompareWithOpts :: Options -> String -> FilePath -> Test +roundTripCompareWithOpts opts name nativeFile = + testCompareWithOpts opts name nativeFile nativeFile + +-- testCompare :: String -> FilePath -> FilePath -> Test +-- testCompare = testCompareWithOpts def + +roundTripCompare :: String -> FilePath -> Test +roundTripCompare = roundTripCompareWithOpts def + +tests :: [Test] +tests = [ testGroup "inlines" + [ roundTripCompare + "font formatting" + "docx/inline_formatting_writer.native" + , roundTripCompare + "font formatting with character styles" + "docx/char_styles.native" + , roundTripCompare + "hyperlinks" + "docx/links_writer.native" + , roundTripCompare + "inline image" + "docx/image_no_embed_writer.native" + , roundTripCompare + "inline image in links" + "docx/inline_images_writer.native" + , roundTripCompare + "handling unicode input" + "docx/unicode.native" + , roundTripCompare + "literal tabs" + "docx/tabs.native" + , roundTripCompare + "normalizing inlines" + "docx/normalize.native" + , roundTripCompare + "normalizing inlines deep inside blocks" + "docx/deep_normalize.native" + , roundTripCompare + "move trailing spaces outside of formatting" + "docx/trailing_spaces_in_formatting.native" + , roundTripCompare + "inline code (with VerbatimChar style)" + "docx/inline_code.native" + , roundTripCompare + "inline code in subscript and superscript" + "docx/verbatim_subsuper.native" + ] + , testGroup "blocks" + [ roundTripCompare + "headers" + "docx/headers.native" + , roundTripCompare + "headers already having auto identifiers" + "docx/already_auto_ident.native" + , roundTripCompare + "numbered headers automatically made into list" + "docx/numbered_header.native" + , roundTripCompare + "i18n blocks (headers and blockquotes)" + "docx/i18n_blocks.native" + -- Continuation does not survive round-trip + , roundTripCompare + "lists" + "docx/lists_writer.native" + , roundTripCompare + "definition lists" + "docx/definition_list.native" + , roundTripCompare + "custom defined lists in styles" + "docx/german_styled_lists.native" + , roundTripCompare + "footnotes and endnotes" + "docx/notes.native" + , roundTripCompare + "blockquotes (parsing indent as blockquote)" + "docx/block_quotes_parse_indent.native" + , roundTripCompare + "hanging indents" + "docx/hanging_indent.native" + -- tables headers do not survive round-trip, should look into that + , roundTripCompare + "tables" + "docx/tables.native" + , roundTripCompare + "tables with lists in cells" + "docx/table_with_list_cell.native" + , roundTripCompare + "code block" + "docx/codeblock.native" + , roundTripCompare + "dropcap paragraphs" + "docx/drop_cap.native" + ] + , testGroup "metadata" + [ roundTripCompareWithOpts (def,def{readerStandalone=True}) + "metadata fields" + "docx/metadata.native" + , roundTripCompareWithOpts (def,def{readerStandalone=True}) + "stop recording metadata with normal text" + "docx/metadata_after_normal.native" + ] + , testGroup "customized styles" + [ testCompareWithOpts + ( def{writerReferenceDoc=Just "docx/custom-style-reference.docx"} + , def) + "simple customized blocks and inlines" + "docx/custom-style-roundtrip-start.native" + "docx/custom-style-roundtrip-end.native" + ] + + ] diff --git a/test/Tests/Writers/HTML.hs b/test/Tests/Writers/HTML.hs new file mode 100644 index 000000000..45de2b042 --- /dev/null +++ b/test/Tests/Writers/HTML.hs @@ -0,0 +1,43 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.HTML (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Text.Pandoc.Arbitrary() + +html :: (ToPandoc a) => a -> String +html = purely (writeHtml4String def{ writerWrapText = WrapNone }) . toPandoc + +{- + "my test" =: X =?> Y + +is shorthand for + + test html "my test" $ X =?> Y + +which is in turn shorthand for + + test html "my test" (X,Y) +-} + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> Test +(=:) = test html + +tests :: [Test] +tests = [ testGroup "inline code" + [ "basic" =: code "@&" =?> "<code>@&</code>" + , "haskell" =: codeWith ("",["haskell"],[]) ">>=" + =?> "<code class=\"sourceCode haskell\"><span class=\"fu\">>>=</span></code>" + , "nolanguage" =: codeWith ("",["nolanguage"],[]) ">>=" + =?> "<code class=\"nolanguage\">>>=</code>" + ] + , testGroup "images" + [ "alt with formatting" =: + image "/url" "title" ("my " <> emph "image") + =?> "<img src=\"/url\" title=\"title\" alt=\"my image\" />" + ] + ] diff --git a/test/Tests/Writers/LaTeX.hs b/test/Tests/Writers/LaTeX.hs new file mode 100644 index 000000000..f54aef4dc --- /dev/null +++ b/test/Tests/Writers/LaTeX.hs @@ -0,0 +1,175 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.LaTeX (tests) where + +import Test.Framework +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +latex :: (ToPandoc a) => a -> String +latex = latexWithOpts def + +latexListing :: (ToPandoc a) => a -> String +latexListing = latexWithOpts def{ writerListings = True } + +latexWithOpts :: (ToPandoc a) => WriterOptions -> a -> String +latexWithOpts opts = purely (writeLaTeX opts) . toPandoc + +beamerWithOpts :: (ToPandoc a) => WriterOptions -> a -> String +beamerWithOpts opts = purely (writeBeamer opts) . toPandoc + +{- + "my test" =: X =?> Y + +is shorthand for + + test latex "my test" $ X =?> Y + +which is in turn shorthand for + + test latex "my test" (X,Y) +-} + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> Test +(=:) = test latex + +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\\tightlist\n\\item[{\\protect\\hyperlink{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*{\\texorpdfstring{Header 1\\footnote{note}}{Header 1}}\\label{foo}\n\\addcontentsline{toc}{section}{Header 1}\n" + , "in list item" =: + bulletList [header 2 (text "foo")] =?> + "\\begin{itemize}\n\\item ~\n \\subsection{foo}\n\\end{itemize}" + , "in definition list item" =: + definitionList [(text "foo", [header 2 (text "bar"), + para $ text "baz"])] =?> + "\\begin{description}\n\\item[foo] ~ \n\\subsection{bar}\n\nbaz\n\\end{description}" + , "containing image" =: + header 1 (image "imgs/foo.jpg" "" (text "Alt text")) =?> + "\\section{\\texorpdfstring{\\protect\\includegraphics{imgs/foo.jpg}}{Alt text}}" + ] + , 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}" + , "backtick" =: + code "`nu?`" =?> "\\texttt{\\textasciigrave{}nu?\\textasciigrave{}}" + ] + , testGroup "writer options" + [ testGroup "top-level division" $ + let + headers = header 1 (text "header1") + <> header 2 (text "header2") + <> header 3 (text "header3") + + latexTopLevelDiv :: (ToPandoc a) => TopLevelDivision -> a -> String + latexTopLevelDiv division = + latexWithOpts def{ writerTopLevelDivision = division } + + beamerTopLevelDiv :: (ToPandoc a) + => TopLevelDivision -> a -> String + beamerTopLevelDiv division = + beamerWithOpts def { writerTopLevelDivision = division } + in + [ test (latexTopLevelDiv TopLevelSection) + "sections as top-level" $ headers =?> + unlines [ "\\section{header1}\n" + , "\\subsection{header2}\n" + , "\\subsubsection{header3}" + ] + , test (latexTopLevelDiv TopLevelChapter) + "chapters as top-level" $ headers =?> + unlines [ "\\chapter{header1}\n" + , "\\section{header2}\n" + , "\\subsection{header3}" + ] + , test (latexTopLevelDiv TopLevelPart) + "parts as top-level" $ headers =?> + unlines [ "\\part{header1}\n" + , "\\chapter{header2}\n" + , "\\section{header3}" + ] + , test (latexTopLevelDiv TopLevelDefault) + "default top-level" $ headers =?> + unlines [ "\\section{header1}\n" + , "\\subsection{header2}\n" + , "\\subsubsection{header3}" + ] + , test (beamerTopLevelDiv TopLevelSection) + "sections as top-level in beamer" $ headers =?> + unlines [ "\\section{header1}\n" + , "\\subsection{header2}\n" + , "\\subsubsection{header3}" + ] + , test (beamerTopLevelDiv TopLevelChapter) + "chapters are as part in beamer" $ headers =?> + unlines [ "\\part{header1}\n" + , "\\section{header2}\n" + , "\\subsection{header3}" + ] + , test (beamerTopLevelDiv TopLevelPart) + "parts as top-level in beamer" $ headers =?> + unlines [ "\\part{header1}\n" + , "\\section{header2}\n" + , "\\subsection{header3}" + ] + , test (beamerTopLevelDiv TopLevelDefault) + "default top-level in beamer" $ headers =?> + unlines [ "\\section{header1}\n" + , "\\subsection{header2}\n" + , "\\subsubsection{header3}" + ] + , test (latexTopLevelDiv TopLevelPart) + "part top-level, section not in toc" $ + ( headerWith ("", ["unnumbered"], []) 1 (text "header1") + <> headerWith ("", ["unnumbered"], []) 2 (text "header2") + <> headerWith ("", ["unnumbered"], []) 3 (text "header3") + <> headerWith ("", ["unnumbered"], []) 4 (text "header4") + <> headerWith ("", ["unnumbered"], []) 5 (text "header5") + <> headerWith ("", ["unnumbered"], []) 6 (text "header6")) + =?> + unlines [ "\\part*{header1}" + , "\\addcontentsline{toc}{part}{header1}\n" + , "\\chapter*{header2}" + , "\\addcontentsline{toc}{chapter}{header2}\n" + , "\\section*{header3}" + , "\\addcontentsline{toc}{section}{header3}\n" + , "\\subsection*{header4}" + , "\\addcontentsline{toc}{subsection}{header4}\n" + , "\\subsubsection*{header5}" + , "\\addcontentsline{toc}{subsubsection}{header5}\n" + , "\\paragraph{header6}" + , "\\addcontentsline{toc}{paragraph}{header6}" + ] + ] + ] + ] diff --git a/test/Tests/Writers/Markdown.hs b/test/Tests/Writers/Markdown.hs new file mode 100644 index 000000000..abefe27d5 --- /dev/null +++ b/test/Tests/Writers/Markdown.hs @@ -0,0 +1,266 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# OPTIONS_GHC -fno-warn-name-shadowing #-} +module Tests.Writers.Markdown (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Text.Pandoc.Arbitrary() + +defopts :: WriterOptions +defopts = def{ writerExtensions = pandocExtensions } + +markdown :: (ToPandoc a) => a -> String +markdown = purely (writeMarkdown defopts) . toPandoc + +markdownWithOpts :: (ToPandoc a) => WriterOptions -> a -> String +markdownWithOpts opts x = purely (writeMarkdown opts) $ toPandoc x + +{- + "my test" =: X =?> Y + +is shorthand for + + test markdown "my test" $ X =?> Y + +which is in turn shorthand for + + test markdown "my test" (X,Y) +-} + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> Test +(=:) = test markdown + +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" + ] ++ [noteTests] ++ [shortcutLinkRefsTests] + +{- + +Testing with the following text: + +First Header +============ + +This is a footnote.[^1] And this is a [link](https://www.google.com). + +> A note inside a block quote.[^2] +> +> A second paragraph. + +Second Header +============= + +Some more text. + + +[^1]: Down here. + +[^2]: The second note. + +-} + +noteTestDoc :: Blocks +noteTestDoc = + header 1 "First Header" <> + para ("This is a footnote." <> + note (para "Down here.") <> + " And this is a " <> + link "https://www.google.com" "" "link" <> + ".") <> + blockQuote (para ("A note inside a block quote." <> + note (para "The second note.")) <> + para ("A second paragraph.")) <> + header 1 "Second Header" <> + para "Some more text." + + + +noteTests :: Test +noteTests = testGroup "note and reference location" + [ test (markdownWithOpts defopts) + "footnotes at the end of a document" $ + noteTestDoc =?> + (unlines $ [ "First Header" + , "============" + , "" + , "This is a footnote.[^1] And this is a [link](https://www.google.com)." + , "" + , "> A note inside a block quote.[^2]" + , ">" + , "> A second paragraph." + , "" + , "Second Header" + , "=============" + , "" + , "Some more text." + , "" + , "[^1]: Down here." + , "" + , "[^2]: The second note." + ]) + , test (markdownWithOpts defopts{writerReferenceLocation=EndOfBlock}) + "footnotes at the end of blocks" $ + noteTestDoc =?> + (unlines $ [ "First Header" + , "============" + , "" + , "This is a footnote.[^1] And this is a [link](https://www.google.com)." + , "" + , "[^1]: Down here." + , "" + , "> A note inside a block quote.[^2]" + , ">" + , "> A second paragraph." + , "" + , "[^2]: The second note." + , "" + , "Second Header" + , "=============" + , "" + , "Some more text." + ]) + , test (markdownWithOpts defopts{writerReferenceLocation=EndOfBlock, writerReferenceLinks=True}) + "footnotes and reference links at the end of blocks" $ + noteTestDoc =?> + (unlines $ [ "First Header" + , "============" + , "" + , "This is a footnote.[^1] And this is a [link]." + , "" + , "[^1]: Down here." + , "" + , " [link]: https://www.google.com" + , "" + , "> A note inside a block quote.[^2]" + , ">" + , "> A second paragraph." + , "" + , "[^2]: The second note." + , "" + , "Second Header" + , "=============" + , "" + , "Some more text." + ]) + , test (markdownWithOpts defopts{writerReferenceLocation=EndOfSection}) + "footnotes at the end of section" $ + noteTestDoc =?> + (unlines $ [ "First Header" + , "============" + , "" + , "This is a footnote.[^1] And this is a [link](https://www.google.com)." + , "" + , "> A note inside a block quote.[^2]" + , ">" + , "> A second paragraph." + , "" + , "[^1]: Down here." + , "" + , "[^2]: The second note." + , "" + , "Second Header" + , "=============" + , "" + , "Some more text." + ]) + + ] + +shortcutLinkRefsTests :: Test +shortcutLinkRefsTests = + let infix 4 =: + (=:) :: (ToString a, ToPandoc a) + + => String -> (a, String) -> Test + (=:) = test (purely (writeMarkdown defopts{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/test/Tests/Writers/Native.hs b/test/Tests/Writers/Native.hs new file mode 100644 index 000000000..88bad7944 --- /dev/null +++ b/test/Tests/Writers/Native.hs @@ -0,0 +1,21 @@ +module Tests.Writers.Native (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Text.Pandoc.Arbitrary() + +p_write_rt :: Pandoc -> Bool +p_write_rt d = + read (purely (writeNative def{ writerTemplate = Just "" }) d) == d + +p_write_blocks_rt :: [Block] -> Bool +p_write_blocks_rt bs = length bs > 20 || + read (purely (writeNative def) (Pandoc nullMeta bs)) == + bs + +tests :: [Test] +tests = [ property "p_write_rt" p_write_rt + , property "p_write_blocks_rt" p_write_blocks_rt + ] diff --git a/test/Tests/Writers/Plain.hs b/test/Tests/Writers/Plain.hs new file mode 100644 index 000000000..bead6857c --- /dev/null +++ b/test/Tests/Writers/Plain.hs @@ -0,0 +1,21 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.Plain (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Text.Pandoc.Arbitrary() + + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> Test +(=:) = test (purely (writePlain def) . toPandoc) + + +tests :: [Test] +tests = [ "strongly emphasized text to uppercase" + =: strong "Straße" + =?> "STRASSE" + ] diff --git a/test/Tests/Writers/RST.hs b/test/Tests/Writers/RST.hs new file mode 100644 index 000000000..dd55580c9 --- /dev/null +++ b/test/Tests/Writers/RST.hs @@ -0,0 +1,107 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.RST (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Text.Pandoc.Arbitrary() + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> Test +(=:) = test (purely (writeRST def . 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" + , "==="] + -- note: heading normalization is only done in standalone mode + , test (purely (writeRST def{ writerTemplate = Just "$body$\n" }) . toPandoc) + "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" + , "--------"] + , test (purely (writeRST def{ writerTemplate = Just "$body$\n" }) . toPandoc) + "minimal heading levels" $ + header 2 (text "Header 1") <> + header 3 (text "Header 2") <> + header 2 (text "Header 1") <> + header 4 (text "Header 2") <> + header 5 (text "Header 3") <> + header 3 (text "Header 2") =?> + unlines + [ "Header 1" + , "========" + , "" + , "Header 2" + , "--------" + , "" + , "Header 1" + , "========" + , "" + , "Header 2" + , "--------" + , "" + , "Header 3" + , "~~~~~~~~" + , "" + , "Header 2" + , "--------"] + ] + ] diff --git a/test/Tests/Writers/TEI.hs b/test/Tests/Writers/TEI.hs new file mode 100644 index 000000000..703f565bb --- /dev/null +++ b/test/Tests/Writers/TEI.hs @@ -0,0 +1,43 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.TEI (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Text.Pandoc.Arbitrary() + +{- + "my test" =: X =?> Y + +is shorthand for + + test html "my test" $ X =?> Y + +which is in turn shorthand for + + test html "my test" (X,Y) +-} + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> Test +(=:) = test (purely (writeTEI def) . toPandoc) + +tests :: [Test] +tests = [ testGroup "block elements" + ["para" =: para "Lorem ipsum cetera." + =?> "<p>Lorem ipsum cetera.</p>" + ] + , testGroup "inlines" + [ + "Emphasis" =: emph ("emphasized") + =?> "<p><hi rendition=\"simple:italic\">emphasized</hi></p>" + ,"SingleQuoted" =: singleQuoted (text "quoted material") + =?> "<p><quote>quoted material</quote></p>" + ,"DoubleQuoted" =: doubleQuoted (text "quoted material") + =?> "<p><quote>quoted material</quote></p>" + ,"NestedQuoted" =: doubleQuoted (singleQuoted (text "quoted material")) + =?> "<p><quote><quote>quoted material</quote></quote></p>" + ] + ] |