aboutsummaryrefslogtreecommitdiff
path: root/tests/Tests
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Tests')
-rw-r--r--tests/Tests/Arbitrary.hs194
-rw-r--r--tests/Tests/Readers/HTML.hs2
-rw-r--r--tests/Tests/Readers/LaTeX.hs2
-rw-r--r--tests/Tests/Readers/Markdown.hs2
-rw-r--r--tests/Tests/Readers/Odt.hs6
-rw-r--r--tests/Tests/Readers/Org.hs23
-rw-r--r--tests/Tests/Readers/RST.hs16
-rw-r--r--tests/Tests/Readers/Txt2Tags.hs2
-rw-r--r--tests/Tests/Shared.hs2
-rw-r--r--tests/Tests/Walk.hs2
-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
20 files changed, 294 insertions, 233 deletions
diff --git a/tests/Tests/Arbitrary.hs b/tests/Tests/Arbitrary.hs
deleted file mode 100644
index d792e1375..000000000
--- a/tests/Tests/Arbitrary.hs
+++ /dev/null
@@ -1,194 +0,0 @@
-{-# OPTIONS_GHC -fno-warn-orphans #-}
-{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, ScopedTypeVariables #-}
--- provides Arbitrary instance for Pandoc types
-module Tests.Arbitrary ()
-where
-import Test.QuickCheck.Gen
-import Test.QuickCheck.Arbitrary
-import Control.Monad (liftM, liftM2)
-import Text.Pandoc.Definition
-import Text.Pandoc.Shared (normalize, escapeURI)
-import Text.Pandoc.Builder
-
-realString :: Gen String
-realString = resize 8 $ listOf $ frequency [ (9, elements [' '..'\127'])
- , (1, elements ['\128'..'\9999']) ]
-
-arbAttr :: Gen Attr
-arbAttr = do
- id' <- elements ["","loc"]
- classes <- elements [[],["haskell"],["c","numberLines"]]
- keyvals <- elements [[],[("start","22")],[("a","11"),("b_2","a b c")]]
- return (id',classes,keyvals)
-
-instance Arbitrary Inlines where
- arbitrary = liftM (fromList :: [Inline] -> Inlines) arbitrary
-
-instance Arbitrary Blocks where
- arbitrary = liftM (fromList :: [Block] -> Blocks) arbitrary
-
-instance Arbitrary Inline where
- arbitrary = resize 3 $ arbInline 2
-
-arbInlines :: Int -> Gen [Inline]
-arbInlines n = listOf1 (arbInline n) `suchThat` (not . startsWithSpace)
- where startsWithSpace (Space:_) = True
- startsWithSpace _ = False
-
--- restrict to 3 levels of nesting max; otherwise we get
--- bogged down in indefinitely large structures
-arbInline :: Int -> Gen Inline
-arbInline n = frequency $ [ (60, liftM Str realString)
- , (60, return Space)
- , (10, liftM2 Code arbAttr realString)
- , (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, do x1 <- arbitrary
- x2 <- arbInlines (n-1)
- return $ Quoted x1 x2)
- , (10, do x1 <- arbitrary
- x2 <- realString
- return $ Math x1 x2)
- , (10, do x0 <- arbAttr
- x1 <- arbInlines (n-1)
- x3 <- realString
- x2 <- liftM escapeURI realString
- return $ Link x0 x1 (x2,x3))
- , (10, do x0 <- arbAttr
- x1 <- arbInlines (n-1)
- x3 <- realString
- x2 <- liftM escapeURI realString
- return $ Image x0 x1 (x2,x3))
- , (2, liftM2 Cite arbitrary (arbInlines 1))
- , (2, liftM Note $ resize 3 $ listOf1 $ arbBlock (n-1))
- ]
-
-instance Arbitrary Block where
- arbitrary = resize 3 $ arbBlock 2
-
-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 (Format "html")
- "<div>\n*&amp;*\n</div>"
- , RawBlock (Format "latex")
- "\\begin[opt]{env}\nhi\n{\\end{env}"
- ])
- , (5, do x1 <- choose (1 :: Int, 6)
- x2 <- arbInlines (n-1)
- return (Header x1 nullAttr x2))
- , (2, return HorizontalRule)
- ] ++ [x | x <- nesters, n > 0]
- where nesters = [ (5, liftM BlockQuote $ listOf1 $ arbBlock (n-1))
- , (5, do x2 <- arbitrary
- x3 <- arbitrary
- x1 <- arbitrary `suchThat` (> 0)
- x4 <- listOf1 $ listOf1 $ arbBlock (n-1)
- return $ OrderedList (x1,x2,x3) x4 )
- , (5, liftM BulletList $ (listOf1 $ listOf1 $ arbBlock (n-1)))
- , (5, do items <- listOf1 $ do
- x1 <- listOf1 $ listOf1 $ arbBlock (n-1)
- x2 <- arbInlines (n-1)
- return (x2,x1)
- return $ DefinitionList items)
- , (2, do rs <- choose (1 :: Int, 4)
- cs <- choose (1 :: Int, 4)
- x1 <- arbInlines (n-1)
- x2 <- vector cs
- x3 <- vectorOf cs $ elements [0, 0.25]
- x4 <- vectorOf cs $ listOf $ arbBlock (n-1)
- x5 <- vectorOf rs $ vectorOf cs
- $ listOf $ arbBlock (n-1)
- return (Table x1 x2 x3 x4 x5))
- ]
-
-instance Arbitrary Pandoc where
- arbitrary = resize 8 $ liftM normalize
- $ liftM2 Pandoc arbitrary arbitrary
-
-instance Arbitrary CitationMode where
- arbitrary
- = do x <- choose (0 :: Int, 2)
- case x of
- 0 -> return AuthorInText
- 1 -> return SuppressAuthor
- 2 -> return NormalCitation
- _ -> error "FATAL ERROR: Arbitrary instance, logic bug"
-
-instance Arbitrary Citation where
- 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
- = do x <- choose (0 :: Int, 1)
- case x of
- 0 -> return DisplayMath
- 1 -> return InlineMath
- _ -> error "FATAL ERROR: Arbitrary instance, logic bug"
-
-instance Arbitrary QuoteType where
- arbitrary
- = do x <- choose (0 :: Int, 1)
- case x of
- 0 -> return SingleQuote
- 1 -> return DoubleQuote
- _ -> error "FATAL ERROR: Arbitrary instance, logic bug"
-
-instance Arbitrary Meta where
- arbitrary
- = do (x1 :: Inlines) <- arbitrary
- (x2 :: [Inlines]) <- liftM (filter (not . isNull)) arbitrary
- (x3 :: Inlines) <- arbitrary
- return $ setMeta "title" x1
- $ setMeta "author" x2
- $ setMeta "date" x3
- $ nullMeta
-
-instance Arbitrary Alignment where
- arbitrary
- = do x <- choose (0 :: Int, 3)
- case x of
- 0 -> return AlignLeft
- 1 -> return AlignRight
- 2 -> return AlignCenter
- 3 -> return AlignDefault
- _ -> error "FATAL ERROR: Arbitrary instance, logic bug"
-
-instance Arbitrary ListNumberStyle where
- arbitrary
- = do x <- choose (0 :: Int, 6)
- case x of
- 0 -> return DefaultStyle
- 1 -> return Example
- 2 -> return Decimal
- 3 -> return LowerRoman
- 4 -> return UpperRoman
- 5 -> return LowerAlpha
- 6 -> return UpperAlpha
- _ -> error "FATAL ERROR: Arbitrary instance, logic bug"
-
-instance Arbitrary ListNumberDelim where
- arbitrary
- = do x <- choose (0 :: Int, 3)
- case x of
- 0 -> return DefaultDelim
- 1 -> return Period
- 2 -> return OneParen
- 3 -> return TwoParens
- _ -> error "FATAL ERROR: Arbitrary instance, logic bug"
-
diff --git a/tests/Tests/Readers/HTML.hs b/tests/Tests/Readers/HTML.hs
index ff27b8aed..1a6983b2b 100644
--- a/tests/Tests/Readers/HTML.hs
+++ b/tests/Tests/Readers/HTML.hs
@@ -4,7 +4,7 @@ module Tests.Readers.HTML (tests) where
import Text.Pandoc.Definition
import Test.Framework
import Tests.Helpers
-import Tests.Arbitrary()
+import Text.Pandoc.Arbitrary()
import Text.Pandoc.Builder
import Text.Pandoc
import Text.Pandoc.Error
diff --git a/tests/Tests/Readers/LaTeX.hs b/tests/Tests/Readers/LaTeX.hs
index e21f75aa9..c70ce8052 100644
--- a/tests/Tests/Readers/LaTeX.hs
+++ b/tests/Tests/Readers/LaTeX.hs
@@ -4,7 +4,7 @@ module Tests.Readers.LaTeX (tests) where
import Text.Pandoc.Definition
import Test.Framework
import Tests.Helpers
-import Tests.Arbitrary()
+import Text.Pandoc.Arbitrary()
import Text.Pandoc.Builder
import Text.Pandoc
import Text.Pandoc.Error
diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs
index 20602afe1..099d75b62 100644
--- a/tests/Tests/Readers/Markdown.hs
+++ b/tests/Tests/Readers/Markdown.hs
@@ -4,7 +4,7 @@ module Tests.Readers.Markdown (tests) where
import Text.Pandoc.Definition
import Test.Framework
import Tests.Helpers
-import Tests.Arbitrary()
+import Text.Pandoc.Arbitrary()
import Text.Pandoc.Builder
import qualified Data.Set as Set
-- import Text.Pandoc.Shared ( normalize )
diff --git a/tests/Tests/Readers/Odt.hs b/tests/Tests/Readers/Odt.hs
index cf30b8398..74796d899 100644
--- a/tests/Tests/Readers/Odt.hs
+++ b/tests/Tests/Readers/Odt.hs
@@ -141,7 +141,6 @@ namesOfTestsComparingToMarkdown = [ "bold"
, "footnote"
, "headers"
-- , "horizontalRule"
--- , "image"
, "italic"
-- , "listBlocks"
, "paragraph"
@@ -152,6 +151,9 @@ namesOfTestsComparingToMarkdown = [ "bold"
namesOfTestsComparingToNative :: [ String ]
namesOfTestsComparingToNative = [ "blockquote"
+ , "image"
+ , "imageIndex"
+ , "imageWithCaption"
, "orderedListMixed"
, "orderedListRoman"
, "orderedListSimple"
@@ -162,4 +164,4 @@ namesOfTestsComparingToNative = [ "blockquote"
-- , "table"
, "unicode"
, "unorderedList"
- ] \ No newline at end of file
+ ]
diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs
index d4fedc797..3eab710dc 100644
--- a/tests/Tests/Readers/Org.hs
+++ b/tests/Tests/Readers/Org.hs
@@ -916,6 +916,12 @@ tests =
] =?>
let attr = ("fig:myfig", mempty, mempty)
in para (imageWith attr "blub.png" "fig:" "My figure")
+
+ , "Figure with empty caption" =:
+ unlines [ "#+CAPTION:"
+ , "[[file:guess.jpg]]"
+ ] =?>
+ para (image "guess.jpg" "fig:" "")
]
, "Footnote" =:
@@ -1490,14 +1496,11 @@ tests =
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." ]
+ , lineBlock
+ [ "Habe nun, ach! Philosophie,"
+ , "Juristerei und Medizin,"
+ , "Und leider auch Theologie!"
+ , "Durchaus studiert, mit heißem Bemühn."
]
]
@@ -1508,7 +1511,7 @@ tests =
, "bar"
, "#+END_VERSE"
] =?>
- para ("foo" <> linebreak <> linebreak <> "bar")
+ lineBlock [ "foo", mempty, "bar" ]
, "Verse block with varying indentation" =:
unlines [ "#+BEGIN_VERSE"
@@ -1516,7 +1519,7 @@ tests =
, "my old friend"
, "#+END_VERSE"
] =?>
- para ("\160\160hello darkness" <> linebreak <> "my old friend")
+ lineBlock [ "\160\160hello darkness", "my old friend" ]
, "Raw block LaTeX" =:
unlines [ "#+BEGIN_LaTeX"
diff --git a/tests/Tests/Readers/RST.hs b/tests/Tests/Readers/RST.hs
index 622f5e48b..06a15ad98 100644
--- a/tests/Tests/Readers/RST.hs
+++ b/tests/Tests/Readers/RST.hs
@@ -4,7 +4,7 @@ module Tests.Readers.RST (tests) where
import Text.Pandoc.Definition
import Test.Framework
import Tests.Helpers
-import Tests.Arbitrary()
+import Text.Pandoc.Arbitrary()
import Text.Pandoc.Builder
import Text.Pandoc
import Text.Pandoc.Error
@@ -19,8 +19,7 @@ infix 4 =:
tests :: [Test]
tests = [ "line block with blank line" =:
- "| a\n|\n| b" =?> para (str "a") <>
- para (str "\160b")
+ "| a\n|\n| b" =?> lineBlock [ "a", mempty, "\160b" ]
, testGroup "field list"
[ "general" =: unlines
[ "para"
@@ -135,7 +134,7 @@ tests = [ "line block with blank line" =:
codeBlock "block quotes\n\ncan go on for many lines" <>
para "but must stop here")
, "line block with 3 lines" =: "| a\n| b\n| c"
- =?> para ("a" <> linebreak <> "b" <> linebreak <> "c")
+ =?> lineBlock ["a", "b", "c"]
, "quoted literal block using >" =: "::\n\n> quoted\n> block\n\nOrdinary paragraph"
=?> codeBlock "> quoted\n> block" <> para "Ordinary paragraph"
, "quoted literal block using | (not a line block)" =: "::\n\n| quoted\n| block\n\nOrdinary paragraph"
@@ -164,4 +163,13 @@ tests = [ "line block with blank line" =:
=?> para (codeWith ("", ["lhs", "haskell", "sourceCode"], []) "text")
, "unknown role" =: ":unknown:`text`" =?> para (str "text")
]
+ , testGroup "footnotes"
+ [ "remove space before note" =: unlines
+ [ "foo [1]_"
+ , ""
+ , ".. [1]"
+ , " bar"
+ ] =?>
+ (para $ "foo" <> (note $ para "bar"))
+ ]
]
diff --git a/tests/Tests/Readers/Txt2Tags.hs b/tests/Tests/Readers/Txt2Tags.hs
index e0067c698..e291c3ffe 100644
--- a/tests/Tests/Readers/Txt2Tags.hs
+++ b/tests/Tests/Readers/Txt2Tags.hs
@@ -4,7 +4,7 @@ module Tests.Readers.Txt2Tags (tests) where
import Text.Pandoc.Definition
import Test.Framework
import Tests.Helpers
-import Tests.Arbitrary()
+import Text.Pandoc.Arbitrary()
import Text.Pandoc.Builder
import Text.Pandoc
import Text.Pandoc.Error
diff --git a/tests/Tests/Shared.hs b/tests/Tests/Shared.hs
index 12652e4b7..55f520433 100644
--- a/tests/Tests/Shared.hs
+++ b/tests/Tests/Shared.hs
@@ -4,7 +4,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Test.Framework
import Tests.Helpers
-import Tests.Arbitrary()
+import Text.Pandoc.Arbitrary()
import Test.Framework.Providers.HUnit
import Test.HUnit ( assertBool, (@?=) )
import Text.Pandoc.Builder
diff --git a/tests/Tests/Walk.hs b/tests/Tests/Walk.hs
index c87cc17d7..876d75e30 100644
--- a/tests/Tests/Walk.hs
+++ b/tests/Tests/Walk.hs
@@ -6,7 +6,7 @@ import Text.Pandoc.Walk
import Test.Framework
import Tests.Helpers
import Data.Char (toUpper)
-import Tests.Arbitrary()
+import Text.Pandoc.Arbitrary()
import Data.Generics
tests :: [Test]
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