aboutsummaryrefslogtreecommitdiff
path: root/tests/Tests/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Tests/Writers')
-rw-r--r--tests/Tests/Writers/AsciiDoc.hs2
-rw-r--r--tests/Tests/Writers/ConTeXt.hs2
-rw-r--r--tests/Tests/Writers/Docbook.hs59
-rw-r--r--tests/Tests/Writers/HTML.hs2
-rw-r--r--tests/Tests/Writers/LaTeX.hs61
-rw-r--r--tests/Tests/Writers/Markdown.hs142
-rw-r--r--tests/Tests/Writers/Native.hs2
-rw-r--r--tests/Tests/Writers/Plain.hs2
-rw-r--r--tests/Tests/Writers/RST.hs2
-rw-r--r--tests/Tests/Writers/TEI.hs2
10 files changed, 259 insertions, 17 deletions
diff --git a/tests/Tests/Writers/AsciiDoc.hs b/tests/Tests/Writers/AsciiDoc.hs
index 0062667cf..8ab216753 100644
--- a/tests/Tests/Writers/AsciiDoc.hs
+++ b/tests/Tests/Writers/AsciiDoc.hs
@@ -4,7 +4,7 @@ import Test.Framework
import Text.Pandoc.Builder
import Text.Pandoc
import Tests.Helpers
-import Tests.Arbitrary()
+import Text.Pandoc.Arbitrary()
asciidoc :: (ToPandoc a) => a -> String
asciidoc = writeAsciiDoc def{ writerWrapText = WrapNone } . toPandoc
diff --git a/tests/Tests/Writers/ConTeXt.hs b/tests/Tests/Writers/ConTeXt.hs
index 5098a5fee..629e58b8f 100644
--- a/tests/Tests/Writers/ConTeXt.hs
+++ b/tests/Tests/Writers/ConTeXt.hs
@@ -5,7 +5,7 @@ import Test.Framework
import Text.Pandoc.Builder
import Text.Pandoc
import Tests.Helpers
-import Tests.Arbitrary()
+import Text.Pandoc.Arbitrary()
context :: (ToPandoc a) => a -> String
context = writeConTeXt def . toPandoc
diff --git a/tests/Tests/Writers/Docbook.hs b/tests/Tests/Writers/Docbook.hs
index 2c0ff6179..0e80bcc05 100644
--- a/tests/Tests/Writers/Docbook.hs
+++ b/tests/Tests/Writers/Docbook.hs
@@ -5,10 +5,13 @@ import Test.Framework
import Text.Pandoc.Builder
import Text.Pandoc
import Tests.Helpers
-import Tests.Arbitrary()
+import Text.Pandoc.Arbitrary()
docbook :: (ToPandoc a) => a -> String
-docbook = writeDocbook def{ writerWrapText = WrapNone } . toPandoc
+docbook = docbookWithOpts def{ writerWrapText = WrapNone }
+
+docbookWithOpts :: ToPandoc a => WriterOptions -> a -> String
+docbookWithOpts opts = writeDocbook opts . toPandoc
{-
"my test" =: X =?> Y
@@ -226,4 +229,56 @@ tests = [ testGroup "line blocks"
]
]
]
+ , testGroup "writer options" $
+ [ testGroup "top-level division" $
+ let
+ headers = header 1 (text "header1")
+ <> header 2 (text "header2")
+ <> header 3 (text "header3")
+
+ docbookTopLevelDiv :: (ToPandoc a) => Division -> a -> String
+ docbookTopLevelDiv division =
+ docbookWithOpts def{ writerTopLevelDivision = division }
+ in
+ [ test (docbookTopLevelDiv Section) "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 Chapter) "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 Part) "parts as top-level" $ headers =?>
+ unlines [ "<part>"
+ , " <title>header1</title>"
+ , " <chapter>"
+ , " <title>header2</title>"
+ , " <sect1>"
+ , " <title>header3</title>"
+ , " <para>"
+ , " </para>"
+ , " </sect1>"
+ , " </chapter>"
+ , "</part>"
+ ]
+ ]
+ ]
]
diff --git a/tests/Tests/Writers/HTML.hs b/tests/Tests/Writers/HTML.hs
index 9b612e446..5bea99f71 100644
--- a/tests/Tests/Writers/HTML.hs
+++ b/tests/Tests/Writers/HTML.hs
@@ -5,7 +5,7 @@ import Test.Framework
import Text.Pandoc.Builder
import Text.Pandoc
import Tests.Helpers
-import Tests.Arbitrary()
+import Text.Pandoc.Arbitrary()
html :: (ToPandoc a) => a -> String
html = writeHtmlString def{ writerWrapText = WrapNone } . toPandoc
diff --git a/tests/Tests/Writers/LaTeX.hs b/tests/Tests/Writers/LaTeX.hs
index 3dacaacd5..28d6618c1 100644
--- a/tests/Tests/Writers/LaTeX.hs
+++ b/tests/Tests/Writers/LaTeX.hs
@@ -2,16 +2,19 @@
module Tests.Writers.LaTeX (tests) where
import Test.Framework
-import Text.Pandoc.Builder
-import Text.Pandoc
import Tests.Helpers
-import Tests.Arbitrary()
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
latex :: (ToPandoc a) => a -> String
-latex = writeLaTeX def{ writerHighlight = True } . toPandoc
+latex = latexWithOpts def{ writerHighlight = True }
latexListing :: (ToPandoc a) => a -> String
-latexListing = writeLaTeX def{ writerListings = True } . toPandoc
+latexListing = latexWithOpts def{ writerListings = True }
+
+latexWithOpts :: (ToPandoc a) => WriterOptions -> a -> String
+latexWithOpts opts = writeLaTeX opts . toPandoc
{-
"my test" =: X =?> Y
@@ -78,4 +81,52 @@ tests = [ testGroup "code blocks"
, "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) => Division -> a -> String
+ latexTopLevelDiv division =
+ latexWithOpts def{ writerTopLevelDivision = division }
+
+ beamerTopLevelDiv :: (ToPandoc a) => Division -> a -> String
+ beamerTopLevelDiv division =
+ latexWithOpts def { writerTopLevelDivision = division
+ , writerBeamer = True }
+ in
+ [ test (latexTopLevelDiv Section) "sections as top-level" $ headers =?>
+ unlines [ "\\section{header1}\n"
+ , "\\subsection{header2}\n"
+ , "\\subsubsection{header3}"
+ ]
+ , test (latexTopLevelDiv Chapter) "chapters as top-level" $ headers =?>
+ unlines [ "\\chapter{header1}\n"
+ , "\\section{header2}\n"
+ , "\\subsection{header3}"
+ ]
+ , test (latexTopLevelDiv Part) "parts as top-level" $ headers =?>
+ unlines [ "\\part{header1}\n"
+ , "\\chapter{header2}\n"
+ , "\\section{header3}"
+ ]
+ , test (beamerTopLevelDiv Section) "sections as top-level in beamer" $ headers =?>
+ unlines [ "\\section{header1}\n"
+ , "\\subsection{header2}\n"
+ , "\\subsubsection{header3}"
+ ]
+ , test (beamerTopLevelDiv Chapter) "chapters are as part in beamer" $ headers =?>
+ unlines [ "\\part{header1}\n"
+ , "\\section{header2}\n"
+ , "\\subsection{header3}"
+ ]
+ , test (beamerTopLevelDiv Part) "parts as top-level in beamer" $ headers =?>
+ unlines [ "\\part{header1}\n"
+ , "\\section{header2}\n"
+ , "\\subsection{header3}"
+ ]
+ ]
+ ]
]
diff --git a/tests/Tests/Writers/Markdown.hs b/tests/Tests/Writers/Markdown.hs
index 1c27ebdf4..aab916b38 100644
--- a/tests/Tests/Writers/Markdown.hs
+++ b/tests/Tests/Writers/Markdown.hs
@@ -6,11 +6,14 @@ import Test.Framework
import Text.Pandoc.Builder
import Text.Pandoc
import Tests.Helpers
-import Tests.Arbitrary()
+import Text.Pandoc.Arbitrary()
markdown :: (ToPandoc a) => a -> String
markdown = writeMarkdown def . toPandoc
+markdownWithOpts :: (ToPandoc a) => WriterOptions -> a -> String
+markdownWithOpts opts x = writeMarkdown opts $ toPandoc x
+
{-
"my test" =: X =?> Y
@@ -36,13 +39,146 @@ tests = [ "indented code after list"
=: bulletList [ plain "foo" <> bulletList [ plain "bar" ],
plain "baz" ]
=?> "- foo\n - bar\n- baz\n"
- ] ++ [shortcutLinkRefsTests]
+ ] ++ [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 def)
+ "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 def{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 def{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 def{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
+
+ => String -> (a, String) -> Test
(=:) = test (writeMarkdown (def {writerReferenceLinks = True}) . toPandoc)
in testGroup "Shortcut reference links"
[ "Simple link (shortcutable)"
diff --git a/tests/Tests/Writers/Native.hs b/tests/Tests/Writers/Native.hs
index 9833bf5ae..a8659587f 100644
--- a/tests/Tests/Writers/Native.hs
+++ b/tests/Tests/Writers/Native.hs
@@ -4,7 +4,7 @@ import Test.Framework
import Text.Pandoc.Builder
import Text.Pandoc
import Tests.Helpers
-import Tests.Arbitrary()
+import Text.Pandoc.Arbitrary()
p_write_rt :: Pandoc -> Bool
p_write_rt d =
diff --git a/tests/Tests/Writers/Plain.hs b/tests/Tests/Writers/Plain.hs
index f8f1d3d90..42f77e3ec 100644
--- a/tests/Tests/Writers/Plain.hs
+++ b/tests/Tests/Writers/Plain.hs
@@ -5,7 +5,7 @@ import Test.Framework
import Text.Pandoc.Builder
import Text.Pandoc
import Tests.Helpers
-import Tests.Arbitrary()
+import Text.Pandoc.Arbitrary()
infix 4 =:
diff --git a/tests/Tests/Writers/RST.hs b/tests/Tests/Writers/RST.hs
index b9e359dae..e07d3ffee 100644
--- a/tests/Tests/Writers/RST.hs
+++ b/tests/Tests/Writers/RST.hs
@@ -5,7 +5,7 @@ import Test.Framework
import Text.Pandoc.Builder
import Text.Pandoc
import Tests.Helpers
-import Tests.Arbitrary()
+import Text.Pandoc.Arbitrary()
infix 4 =:
(=:) :: (ToString a, ToPandoc a)
diff --git a/tests/Tests/Writers/TEI.hs b/tests/Tests/Writers/TEI.hs
index 56764db9f..3eb8478b7 100644
--- a/tests/Tests/Writers/TEI.hs
+++ b/tests/Tests/Writers/TEI.hs
@@ -5,7 +5,7 @@ import Test.Framework
import Text.Pandoc.Builder
import Text.Pandoc
import Tests.Helpers
-import Tests.Arbitrary()
+import Text.Pandoc.Arbitrary()
{-
"my test" =: X =?> Y