aboutsummaryrefslogtreecommitdiff
path: root/test/Tests/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'test/Tests/Writers')
-rw-r--r--test/Tests/Writers/AsciiDoc.hs16
-rw-r--r--test/Tests/Writers/Docx.hs3
-rw-r--r--test/Tests/Writers/HTML.hs120
-rw-r--r--test/Tests/Writers/JATS.hs48
-rw-r--r--test/Tests/Writers/Markua.hs40
-rw-r--r--test/Tests/Writers/OOXML.hs78
-rw-r--r--test/Tests/Writers/Powerpoint.hs322
7 files changed, 494 insertions, 133 deletions
diff --git a/test/Tests/Writers/AsciiDoc.hs b/test/Tests/Writers/AsciiDoc.hs
index 04655635f..7b2dd11e8 100644
--- a/test/Tests/Writers/AsciiDoc.hs
+++ b/test/Tests/Writers/AsciiDoc.hs
@@ -38,6 +38,22 @@ tests = [ testGroup "emphasis"
para (singleQuoted (strong (text "foo"))) =?>
"`**foo**'"
]
+ , testGroup "blocks"
+ [ testAsciidoc "code block without line numbers" $
+ codeBlockWith ("", [ "haskell" ], []) "foo" =?> unlines
+ [ "[source,haskell]"
+ , "----"
+ , "foo"
+ , "----"
+ ]
+ , testAsciidoc "code block with line numbers" $
+ codeBlockWith ("", [ "haskell", "numberLines" ], []) "foo" =?> unlines
+ [ "[source%linesnum,haskell]"
+ , "----"
+ , "foo"
+ , "----"
+ ]
+ ]
, testGroup "tables"
[ testAsciidoc "empty cells" $
simpleTable [] [[mempty],[mempty]] =?> unlines
diff --git a/test/Tests/Writers/Docx.hs b/test/Tests/Writers/Docx.hs
index da25b95e0..93b56e1c2 100644
--- a/test/Tests/Writers/Docx.hs
+++ b/test/Tests/Writers/Docx.hs
@@ -31,7 +31,8 @@ tests = [ testGroup "inlines"
"docx/golden/links.docx"
, docxTest
"inline image"
- def
+ def{ writerExtensions =
+ enableExtension Ext_native_numbering (writerExtensions def) }
"docx/image_writer_test.native"
"docx/golden/image.docx"
, docxTest
diff --git a/test/Tests/Writers/HTML.hs b/test/Tests/Writers/HTML.hs
index 404f6da98..a81badae8 100644
--- a/test/Tests/Writers/HTML.hs
+++ b/test/Tests/Writers/HTML.hs
@@ -2,14 +2,18 @@
module Tests.Writers.HTML (tests) where
import Data.Text (unpack)
+import qualified Data.Text as T
import Test.Tasty
import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
+htmlWithOpts :: (ToPandoc a) => WriterOptions -> a -> String
+htmlWithOpts opts = unpack . purely (writeHtml4String opts{ writerWrapText = WrapNone }) . toPandoc
+
html :: (ToPandoc a) => a -> String
-html = unpack . purely (writeHtml4String def{ writerWrapText = WrapNone }) . toPandoc
+html = htmlWithOpts def
htmlQTags :: (ToPandoc a) => a -> String
htmlQTags = unpack
@@ -33,6 +37,21 @@ infix 4 =:
=> String -> (a, String) -> TestTree
(=:) = test html
+noteTestDoc :: Blocks
+noteTestDoc =
+ header 1 "Page title" <>
+ header 2 "First section" <>
+ 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 2 "Second section" <>
+ para "Some more text."
+
tests :: [TestTree]
tests =
[ testGroup "inline code"
@@ -50,7 +69,7 @@ tests =
, testGroup "blocks"
[ "definition list with empty <dt>" =:
definitionList [(mempty, [para $ text "foo bar"])]
- =?> "<dl><dt></dt><dd><p>foo bar</p></dd></dl>"
+ =?> "<dl>\n<dt></dt>\n<dd>\n<p>foo bar</p>\n</dd>\n</dl>"
, "heading with disallowed attributes" =:
headerWith ("", [], [("invalid","1"), ("lang", "en")]) 1 "test"
=?>
@@ -86,6 +105,103 @@ tests =
=?> ("<var><code class=\"sourceCode haskell\">" ++
"<span class=\"op\">&gt;&gt;=</span></code></var>")
]
+ , testGroup "footnotes"
+ [ test (htmlWithOpts def{writerReferenceLocation=EndOfDocument})
+ "at the end of a document" $
+ noteTestDoc =?>
+ T.unlines
+ [ "<h1>Page title</h1>"
+ , "<h2>First section</h2>"
+ , "<p>This is a footnote.<a href=\"#fn1\" class=\"footnote-ref\" id=\"fnref1\"><sup>1</sup></a> And this is a <a href=\"https://www.google.com\">link</a>.</p>"
+ , "<blockquote>"
+ , "<p>A note inside a block quote.<a href=\"#fn2\" class=\"footnote-ref\" id=\"fnref2\"><sup>2</sup></a></p>"
+ , "<p>A second paragraph.</p>"
+ , "</blockquote>"
+ , "<h2>Second section</h2>"
+ , "<p>Some more text.</p>"
+ , "<div class=\"footnotes footnotes-end-of-document\">"
+ , "<hr />"
+ , "<ol>"
+ , "<li id=\"fn1\"><p>Down here.<a href=\"#fnref1\" class=\"footnote-back\">↩︎</a></p></li>"
+ , "<li id=\"fn2\"><p>The second note.<a href=\"#fnref2\" class=\"footnote-back\">↩︎</a></p></li>"
+ , "</ol>"
+ , "</div>"
+ ]
+ , test (htmlWithOpts def{writerReferenceLocation=EndOfBlock})
+ "at the end of a block" $
+ noteTestDoc =?>
+ T.unlines
+ [ "<h1>Page title</h1>"
+ , "<h2>First section</h2>"
+ , "<p>This is a footnote.<a href=\"#fn1\" class=\"footnote-ref\" id=\"fnref1\"><sup>1</sup></a> And this is a <a href=\"https://www.google.com\">link</a>.</p>"
+ , "<div class=\"footnotes footnotes-end-of-block\">"
+ , "<ol>"
+ , "<li id=\"fn1\"><p>Down here.<a href=\"#fnref1\" class=\"footnote-back\">↩︎</a></p></li>"
+ , "</ol>"
+ , "</div>"
+ , "<blockquote>"
+ , "<p>A note inside a block quote.<a href=\"#fn2\" class=\"footnote-ref\" id=\"fnref2\"><sup>2</sup></a></p>"
+ , "<p>A second paragraph.</p>"
+ , "</blockquote>"
+ , "<div class=\"footnotes footnotes-end-of-block\">"
+ , "<ol start=\"2\">"
+ , "<li id=\"fn2\"><p>The second note.<a href=\"#fnref2\" class=\"footnote-back\">↩︎</a></p></li>"
+ , "</ol>"
+ , "</div>"
+ , "<h2>Second section</h2>"
+ , "<p>Some more text.</p>"
+ ]
+ , test (htmlWithOpts def{writerReferenceLocation=EndOfSection})
+ "at the end of a section" $
+ noteTestDoc =?>
+ T.unlines
+ [ "<h1>Page title</h1>"
+ , "<h2>First section</h2>"
+ , "<p>This is a footnote.<a href=\"#fn1\" class=\"footnote-ref\" id=\"fnref1\"><sup>1</sup></a> And this is a <a href=\"https://www.google.com\">link</a>.</p>"
+ , "<blockquote>"
+ , "<p>A note inside a block quote.<a href=\"#fn2\" class=\"footnote-ref\" id=\"fnref2\"><sup>2</sup></a></p>"
+ , "<p>A second paragraph.</p>"
+ , "</blockquote>"
+ , "<div class=\"footnotes footnotes-end-of-section\">"
+ , "<hr />"
+ , "<ol>"
+ , "<li id=\"fn1\"><p>Down here.<a href=\"#fnref1\" class=\"footnote-back\">↩︎</a></p></li>"
+ , "<li id=\"fn2\"><p>The second note.<a href=\"#fnref2\" class=\"footnote-back\">↩︎</a></p></li>"
+ , "</ol>"
+ , "</div>"
+ , "<h2>Second section</h2>"
+ , "<p>Some more text.</p>"
+ ]
+ , test (htmlWithOpts def{writerReferenceLocation=EndOfSection, writerSectionDivs=True})
+ "at the end of a section, with section divs" $
+ noteTestDoc =?>
+ -- Footnotes are rendered _after_ their section (in this case after the level2 section
+ -- that contains it).
+ T.unlines
+ [ "<div class=\"section level1\">"
+ , "<h1>Page title</h1>"
+ , "<div class=\"section level2\">"
+ , "<h2>First section</h2>"
+ , "<p>This is a footnote.<a href=\"#fn1\" class=\"footnote-ref\" id=\"fnref1\"><sup>1</sup></a> And this is a <a href=\"https://www.google.com\">link</a>.</p>"
+ , "<blockquote>"
+ , "<p>A note inside a block quote.<a href=\"#fn2\" class=\"footnote-ref\" id=\"fnref2\"><sup>2</sup></a></p>"
+ , "<p>A second paragraph.</p>"
+ , "</blockquote>"
+ , "</div>"
+ , "<div class=\"footnotes footnotes-end-of-section\">"
+ , "<hr />"
+ , "<ol>"
+ , "<li id=\"fn1\"><p>Down here.<a href=\"#fnref1\" class=\"footnote-back\">↩︎</a></p></li>"
+ , "<li id=\"fn2\"><p>The second note.<a href=\"#fnref2\" class=\"footnote-back\">↩︎</a></p></li>"
+ , "</ol>"
+ , "</div>"
+ , "<div class=\"section level2\">"
+ , "<h2>Second section</h2>"
+ , "<p>Some more text.</p>"
+ , "</div>"
+ , "</div>"
+ ]
+ ]
]
where
tQ :: (ToString a, ToPandoc a)
diff --git a/test/Tests/Writers/JATS.hs b/test/Tests/Writers/JATS.hs
index 5b96ed2ed..e605f55e1 100644
--- a/test/Tests/Writers/JATS.hs
+++ b/test/Tests/Writers/JATS.hs
@@ -61,21 +61,39 @@ tests =
, "</fn></p>"
])
]
- , "bullet list" =: bulletList [ plain $ text "first"
- , plain $ text "second"
- , plain $ text "third"
- ]
- =?> "<list list-type=\"bullet\">\n\
- \ <list-item>\n\
- \ <p>first</p>\n\
- \ </list-item>\n\
- \ <list-item>\n\
- \ <p>second</p>\n\
- \ </list-item>\n\
- \ <list-item>\n\
- \ <p>third</p>\n\
- \ </list-item>\n\
- \</list>"
+ , testGroup "bullet list"
+ [ "plain items" =: bulletList [ plain $ text "first"
+ , plain $ text "second"
+ , plain $ text "third"
+ ]
+ =?> "<list list-type=\"bullet\">\n\
+ \ <list-item>\n\
+ \ <p>first</p>\n\
+ \ </list-item>\n\
+ \ <list-item>\n\
+ \ <p>second</p>\n\
+ \ </list-item>\n\
+ \ <list-item>\n\
+ \ <p>third</p>\n\
+ \ </list-item>\n\
+ \</list>"
+
+ , "item with implicit figure" =:
+ bulletList [ simpleFigure (text "caption") "a.png" "" ] =?>
+ T.unlines
+ [ "<list list-type=\"bullet\">"
+ , " <list-item>"
+ , " <p specific-use=\"wrapper\">"
+ , " <fig>"
+ , " <caption><p>caption</p></caption>"
+ , " <graphic mimetype=\"image\" mime-subtype=\"png\"" <>
+ " xlink:href=\"a.png\" xlink:title=\"\" />"
+ , " </fig>"
+ , " </p>"
+ , " </list-item>"
+ , "</list>"
+ ]
+ ]
, testGroup "definition lists"
[ "with internal link" =: definitionList [(link "#go" "" (str "testing"),
[plain (text "hi there")])] =?>
diff --git a/test/Tests/Writers/Markua.hs b/test/Tests/Writers/Markua.hs
new file mode 100644
index 000000000..62239f3da
--- /dev/null
+++ b/test/Tests/Writers/Markua.hs
@@ -0,0 +1,40 @@
+{-# LANGUAGE OverloadedStrings #-}
+module Tests.Writers.Markua (tests) where
+
+import Test.Tasty
+import Tests.Helpers
+import Text.Pandoc
+import Text.Pandoc.Arbitrary ()
+import Text.Pandoc.Builder
+
+{-
+ "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) -> TestTree
+(=:) = test (purely (writeMarkua def) . toPandoc)
+
+tests :: [TestTree]
+tests = [ testGroup "simple blurb/aside"
+ ["blurb" =: divWith ("",["blurb"],[]) (bulletList [para "blurb content"])
+ =?> "B> * blurb content"
+ ,"aside" =: divWith ("",["aside"],[]) (bulletList [para "aside list"])
+ =?> "A> * aside list"
+ ]
+ ,testGroup "multiclass blurb/aside"
+ ["blurb" =: divWith ("",["blurb", "otherclass"],[]) (bulletList [para "blurb content"])
+ =?> "B> * blurb content"
+ ,"aside" =: divWith ("",["otherclass", "aside"],[]) (bulletList [para "aside list"])
+ =?> "A> * aside list"
+ ]
+ ]
diff --git a/test/Tests/Writers/OOXML.hs b/test/Tests/Writers/OOXML.hs
index 83f05cfec..43543954c 100644
--- a/test/Tests/Writers/OOXML.hs
+++ b/test/Tests/Writers/OOXML.hs
@@ -3,13 +3,15 @@
module Tests.Writers.OOXML (ooxmlTest) where
-import Text.Pandoc
+import Text.Pandoc hiding (Attr)
import Test.Tasty
import Test.Tasty.Golden.Advanced
+import Control.Applicative ((<|>))
import Codec.Archive.Zip
import Text.XML.Light
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BL
+import Data.Foldable (asum)
import qualified Data.Text.IO as T
import Data.List (isSuffixOf, sort, (\\), intercalate, union)
import Data.Maybe (catMaybes, mapMaybe)
@@ -17,34 +19,59 @@ import Tests.Helpers
import Data.Algorithm.Diff
import System.FilePath.Glob (compile, match)
-compareXMLBool :: Content -> Content -> Bool
+compareXML :: Content -> Content -> Maybe XMLDifference
-- We make a special exception for times at the moment, and just pass
-- them because we can't control the utctime when running IO. Besides,
-- so long as we have two times, we're okay.
-compareXMLBool (Elem myElem) (Elem goodElem)
+compareXML (Elem goodElem) (Elem myElem)
| (QName "created" _ (Just "dcterms")) <- elName myElem
, (QName "created" _ (Just "dcterms")) <- elName goodElem =
- True
-compareXMLBool (Elem myElem) (Elem goodElem)
+ Nothing
+compareXML (Elem goodElem) (Elem myElem)
| (QName "modified" _ (Just "dcterms")) <- elName myElem
, (QName "modified" _ (Just "dcterms")) <- elName goodElem =
- True
-compareXMLBool (Elem myElem) (Elem goodElem) =
- elName myElem == elName goodElem &&
- elAttribs myElem == elAttribs goodElem &&
- and (zipWith compareXMLBool (elContent myElem) (elContent goodElem))
-compareXMLBool (Text myCData) (Text goodCData) =
- cdVerbatim myCData == cdVerbatim goodCData &&
- cdData myCData == cdData goodCData &&
- cdLine myCData == cdLine goodCData
-compareXMLBool (CRef myStr) (CRef goodStr) =
- myStr == goodStr
-compareXMLBool _ _ = False
-
-displayDiff :: Content -> Content -> String
+ Nothing
+compareXML (Elem goodElem) (Elem myElem) =
+ (if elName myElem == elName goodElem
+ then Nothing
+ else Just
+ (ElemNamesDiffer
+ (Comparison {mine = elName myElem, good = elName goodElem}))
+ )
+ <|> (if sort (elAttribs myElem) == sort (elAttribs goodElem)
+ then Nothing
+ else Just
+ (ElemAttributesDiffer
+ (Comparison { mine = sort (elAttribs myElem)
+ , good = sort (elAttribs goodElem)
+ })))
+ <|> asum (zipWith compareXML (elContent myElem) (elContent goodElem))
+compareXML (Text goodCData) (Text myCData) =
+ (if cdVerbatim myCData == cdVerbatim goodCData
+ && cdData myCData == cdData goodCData
+ then Nothing
+ else Just (CDatasDiffer (Comparison { mine = myCData, good = goodCData })))
+compareXML (CRef goodStr) (CRef myStr) =
+ if myStr == goodStr
+ then Nothing
+ else Just (CRefsDiffer (Comparison { mine = myStr, good = goodStr }))
+compareXML g m = Just (OtherContentsDiffer (Comparison {mine = m, good = g}))
+
+data XMLDifference
+ = ElemNamesDiffer (Comparison QName)
+ | ElemAttributesDiffer (Comparison [Attr])
+ | CDatasDiffer (Comparison CData)
+ | CRefsDiffer (Comparison String)
+ | OtherContentsDiffer (Comparison Content)
+ deriving (Show)
+
+data Comparison a = Comparison { good :: a, mine :: a }
+ deriving (Show)
+
+displayDiff :: Element -> Element -> String
displayDiff elemA elemB =
showDiff (1,1)
- (getDiff (lines $ showContent elemA) (lines $ showContent elemB))
+ (getDiff (lines $ ppElement elemA) (lines $ ppElement elemB))
goldenArchive :: FilePath -> IO Archive
goldenArchive fp = toArchive . BL.fromStrict <$> BS.readFile fp
@@ -57,6 +84,7 @@ testArchive writerFn opts fp = do
txt <- T.readFile fp
bs <- runIOorExplode $ do
setTranslations "en-US"
+ setVerbosity ERROR -- otherwise test output is confusingly noisy
readNative def txt >>= writerFn opts
return $ toArchive bs
@@ -106,11 +134,13 @@ compareXMLFile' fp goldenArch testArch = do
let testContent = Elem testXMLDoc
goldenContent = Elem goldenXMLDoc
+ display difference = "Non-matching xml in "
+ ++ fp ++ ":\n"
+ ++ "* " ++ show difference ++ "\n"
+ ++ displayDiff testXMLDoc goldenXMLDoc
- if compareXMLBool goldenContent testContent
- then Right ()
- else Left $
- "Non-matching xml in " ++ fp ++ ":\n" ++ displayDiff testContent goldenContent
+
+ maybe (Right ()) (Left . display) (compareXML goldenContent testContent)
compareXMLFile :: FilePath -> Archive -> Archive -> Maybe String
compareXMLFile fp goldenArch testArch =
diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs
index 87ebe990c..0e8ef076b 100644
--- a/test/Tests/Writers/Powerpoint.hs
+++ b/test/Tests/Writers/Powerpoint.hs
@@ -1,5 +1,6 @@
module Tests.Writers.Powerpoint (tests) where
+import Control.Arrow ((***))
import Tests.Writers.OOXML (ooxmlTest)
import Text.Pandoc
import Test.Tasty
@@ -12,13 +13,13 @@ import Data.Text (pack)
-- we want to run all our tests with both default formatting and a
-- template.
-modifyPptxName :: FilePath -> FilePath
-modifyPptxName fp =
- addExtension (dropExtension fp ++ "_templated") "pptx"
+modifyPptxName :: FilePath -> String -> FilePath
+modifyPptxName fp suffix =
+ addExtension (takeDirectory fp ++ suffix) "pptx"
pptxTests :: String -> WriterOptions -> FilePath -> FilePath -> (TestTree, TestTree)
pptxTests name opts native pptx =
- let referenceDoc = "pptx/reference_depth.pptx"
+ let referenceDoc = "pptx/reference-depth.pptx"
in
( ooxmlTest
writePowerpoint
@@ -31,7 +32,7 @@ pptxTests name opts native pptx =
name
opts{writerReferenceDoc=Just referenceDoc}
native
- (modifyPptxName pptx)
+ (modifyPptxName pptx "/templated")
)
groupPptxTests :: [(TestTree, TestTree)] -> [TestTree]
@@ -42,91 +43,230 @@ groupPptxTests pairs =
, testGroup "With `--reference-doc` pptx file" refs
]
+testGroup' :: String -> [(TestTree, TestTree)] -> (TestTree, TestTree)
+testGroup' descr = (testGroup descr *** testGroup descr) . unzip
+
tests :: [TestTree]
-tests = groupPptxTests [ pptxTests "Inline formatting"
- def
- "pptx/inline_formatting.native"
- "pptx/inline_formatting.pptx"
- , pptxTests "Slide breaks (default slide-level)"
- def
- "pptx/slide_breaks.native"
- "pptx/slide_breaks.pptx"
- , pptxTests "slide breaks (slide-level set to 1)"
- def{ writerSlideLevel = Just 1 }
- "pptx/slide_breaks.native"
- "pptx/slide_breaks_slide_level_1.pptx"
- , pptxTests "lists"
- def
- "pptx/lists.native"
- "pptx/lists.pptx"
- , pptxTests "start ordered list at specified num"
- def
- "pptx/start_numbering_at.native"
- "pptx/start_numbering_at.pptx"
- , pptxTests "tables"
- def
- "pptx/tables.native"
- "pptx/tables.pptx"
- , pptxTests "table of contents"
- def{ writerTableOfContents = True }
- "pptx/slide_breaks.native"
- "pptx/slide_breaks_toc.pptx"
- , pptxTests "end notes"
- def
- "pptx/endnotes.native"
- "pptx/endnotes.pptx"
- , pptxTests "end notes, with table of contents"
- def { writerTableOfContents = True }
- "pptx/endnotes.native"
- "pptx/endnotes_toc.pptx"
- , pptxTests "images"
- def
- "pptx/images.native"
- "pptx/images.pptx"
- , pptxTests "two-column layout"
- def
- "pptx/two_column.native"
- "pptx/two_column.pptx"
- , pptxTests "speaker notes"
- def
- "pptx/speaker_notes.native"
- "pptx/speaker_notes.pptx"
- , pptxTests "speaker notes after a separating block"
- def
- "pptx/speaker_notes_afterseps.native"
- "pptx/speaker_notes_afterseps.pptx"
- , pptxTests "speaker notes after a separating header"
- def
- "pptx/speaker_notes_afterheader.native"
- "pptx/speaker_notes_afterheader.pptx"
- , pptxTests "speaker notes after metadata"
- def
- "pptx/speaker_notes_after_metadata.native"
- "pptx/speaker_notes_after_metadata.pptx"
- , pptxTests "remove empty slides"
- def
- "pptx/remove_empty_slides.native"
- "pptx/remove_empty_slides.pptx"
- , pptxTests "raw ooxml"
- def
- "pptx/raw_ooxml.native"
- "pptx/raw_ooxml.pptx"
- , pptxTests "metadata, custom properties"
- def
- "pptx/document-properties.native"
- "pptx/document-properties.pptx"
- , pptxTests "metadata, short description"
- def
- "pptx/document-properties-short-desc.native"
- "pptx/document-properties-short-desc.pptx"
- , pptxTests "inline code and code blocks"
- def
- "pptx/code.native"
- "pptx/code.pptx"
- , pptxTests "inline code and code blocks, custom formatting"
- def { writerVariables = Context $ M.fromList
- [(pack "monofont", toVal $ pack "Consolas")] }
- "pptx/code.native"
- "pptx/code-custom.pptx"
- ]
+tests = let
+ regularTests = groupPptxTests
+ [ pptxTests "Inline formatting"
+ def
+ "pptx/inline-formatting/input.native"
+ "pptx/inline-formatting/output.pptx"
+ , pptxTests "Slide breaks (default slide-level)"
+ def
+ "pptx/slide-breaks/input.native"
+ "pptx/slide-breaks/output.pptx"
+ , pptxTests "slide breaks (slide-level set to 1)"
+ def{ writerSlideLevel = Just 1 }
+ "pptx/slide-breaks/input.native"
+ "pptx/slide-breaks-slide-level-1/output.pptx"
+ , pptxTests "lists"
+ def
+ "pptx/lists/input.native"
+ "pptx/lists/output.pptx"
+ , pptxTests "start ordered list at specified num"
+ def
+ "pptx/start-numbering-at/input.native"
+ "pptx/start-numbering-at/output.pptx"
+ , pptxTests "List continuation paragraph indentation"
+ def
+ "pptx/list-level/input.native"
+ "pptx/list-level/output.pptx"
+ , pptxTests "tables"
+ def
+ "pptx/tables/input.native"
+ "pptx/tables/output.pptx"
+ , pptxTests "table of contents"
+ def{ writerTableOfContents = True }
+ "pptx/slide-breaks/input.native"
+ "pptx/slide-breaks-toc/output.pptx"
+ , pptxTests "end notes"
+ def
+ "pptx/endnotes/input.native"
+ "pptx/endnotes/output.pptx"
+ , pptxTests "end notes, with table of contents"
+ def { writerTableOfContents = True }
+ "pptx/endnotes/input.native"
+ "pptx/endnotes-toc/output.pptx"
+ , pptxTests "images"
+ def
+ "pptx/images/input.native"
+ "pptx/images/output.pptx"
+ , pptxTests "two-column layout"
+ def
+ "pptx/two-column/all-text/input.native"
+ "pptx/two-column/all-text/output.pptx"
+ , pptxTests "two-column (not comparison)"
+ def
+ "pptx/two-column/text-and-image/input.native"
+ "pptx/two-column/text-and-image/output.pptx"
+ , pptxTests "speaker notes"
+ def
+ "pptx/speaker-notes/input.native"
+ "pptx/speaker-notes/output.pptx"
+ , pptxTests "speaker notes after a separating block"
+ def
+ "pptx/speaker-notes-afterseps/input.native"
+ "pptx/speaker-notes-afterseps/output.pptx"
+ , pptxTests "speaker notes after a separating header"
+ def
+ "pptx/speaker-notes-afterheader/input.native"
+ "pptx/speaker-notes-afterheader/output.pptx"
+ , pptxTests "speaker notes after metadata"
+ def
+ "pptx/speaker-notes-after-metadata/input.native"
+ "pptx/speaker-notes-after-metadata/output.pptx"
+ , pptxTests "remove empty slides"
+ def
+ "pptx/remove-empty-slides/input.native"
+ "pptx/remove-empty-slides/output.pptx"
+ , pptxTests "raw ooxml"
+ def
+ "pptx/raw-ooxml/input.native"
+ "pptx/raw-ooxml/output.pptx"
+ , pptxTests "metadata, custom properties"
+ def
+ "pptx/document-properties/input.native"
+ "pptx/document-properties/output.pptx"
+ , pptxTests "metadata, short description"
+ def
+ "pptx/document-properties-short-desc/input.native"
+ "pptx/document-properties-short-desc/output.pptx"
+ , pptxTests "inline code and code blocks"
+ def
+ "pptx/code/input.native"
+ "pptx/code/output.pptx"
+ , pptxTests "inline code and code blocks, custom formatting"
+ def { writerVariables = Context $ M.fromList
+ [(pack "monofont", toVal $ pack "Consolas")] }
+ "pptx/code/input.native"
+ "pptx/code-custom/output.pptx"
+ , testGroup' "Using slide level 0, if the first thing on a slide is"
+ [ pptxTests ("a h1 it's used as the slide title")
+ def { writerSlideLevel = Just 0 }
+ "pptx/slide-level-0/h1-with-image/input.native"
+ "pptx/slide-level-0/h1-with-image/output.pptx"
+ , pptxTests ("a h2 it's used as the "
+ <> "slide title")
+ def { writerSlideLevel = Just 0 }
+ "pptx/slide-level-0/h2-with-image/input.native"
+ "pptx/slide-level-0/h2-with-image/output.pptx"
+ , testGroup' "a heading it's used as the slide title"
+ [ pptxTests "(works with a table)"
+ def { writerSlideLevel = Just 0 }
+ "pptx/slide-level-0/h1-with-table/input.native"
+ "pptx/slide-level-0/h1-with-table/output.pptx"
+ , pptxTests ("(content with caption layout)")
+ def { writerSlideLevel = Just 0 }
+ "pptx/slide-level-0/h1-h2-with-table/input.native"
+ "pptx/slide-level-0/h1-h2-with-table/output.pptx"
+ ]
+ ]
+ , testGroup' "comparison layout"
+ [ testGroup' "comparison layout is used..."
+ [ pptxTests "when two columns contain text + non-text"
+ def
+ "pptx/comparison/both-columns/input.native"
+ "pptx/comparison/both-columns/output.pptx"
+ , pptxTests "even when only one col contains text + non-text"
+ def
+ "pptx/comparison/one-column/input.native"
+ "pptx/comparison/one-column/output.pptx"
+ ]
+ , testGroup' "extra ... in one column gets overlaid"
+ [ pptxTests "text"
+ def
+ "pptx/comparison/extra-text/input.native"
+ "pptx/comparison/extra-text/output.pptx"
+ , pptxTests "image"
+ def
+ "pptx/comparison/extra-image/input.native"
+ "pptx/comparison/extra-image/output.pptx"
+ ]
+ , pptxTests "is not used if the non-text comes first"
+ def
+ "pptx/comparison/non-text-first/input.native"
+ "pptx/comparison/non-text-first/output.pptx"
+ ]
+ , testGroup' "Content with Caption layout is ..."
+ [ pptxTests "used for heading, text, image on the same slide"
+ def
+ "pptx/content-with-caption/heading-text-image/input.native"
+ "pptx/content-with-caption/heading-text-image/output.pptx"
+ , pptxTests "used for text and an image on the same slide"
+ def
+ "pptx/content-with-caption/text-image/input.native"
+ "pptx/content-with-caption/text-image/output.pptx"
+ , pptxTests "not used if the image comes first"
+ def
+ "pptx/content-with-caption/image-text/input.native"
+ "pptx/content-with-caption/image-text/output.pptx"
+ ]
+ , testGroup' "The Blank layout is used if a slide contains only..."
+ [ pptxTests "speaker notes"
+ def
+ "pptx/blanks/just-speaker-notes/input.native"
+ "pptx/blanks/just-speaker-notes/output.pptx"
+ , pptxTests "an empty heading with a body of only NBSPs"
+ def
+ "pptx/blanks/nbsp-in-body/input.native"
+ "pptx/blanks/nbsp-in-body/output.pptx"
+ , pptxTests "a heading containing only non-breaking spaces"
+ def
+ "pptx/blanks/nbsp-in-heading/input.native"
+ "pptx/blanks/nbsp-in-heading/output.pptx"
+ ]
+ , pptxTests ("Incremental lists are supported")
+ def { writerIncremental = True }
+ "pptx/incremental-lists/with-flag/input.native"
+ "pptx/incremental-lists/with-flag/output.pptx"
+ , pptxTests ("One-off incremental lists are supported")
+ def
+ "pptx/incremental-lists/without-flag/input.native"
+ "pptx/incremental-lists/without-flag/output.pptx"
+ , pptxTests "Background images"
+ def
+ "pptx/background-image/input.native"
+ "pptx/background-image/output.pptx"
+ ]
+ referenceSpecificTests =
+ [ ooxmlTest
+ writePowerpoint
+ "Basic footer"
+ def { writerReferenceDoc = Just "pptx/footer/basic/reference.pptx"}
+ "pptx/footer/input.native"
+ "pptx/footer/basic/output.pptx"
+ , ooxmlTest
+ writePowerpoint
+ "Footer with fixed date, replaced by meta block date"
+ def { writerReferenceDoc = Just "pptx/footer/fixed-date/reference.pptx"}
+ "pptx/footer/input.native"
+ "pptx/footer/fixed-date/output.pptx"
+ , ooxmlTest
+ writePowerpoint
+ "Footer not shown on title slide"
+ def { writerReferenceDoc = Just "pptx/footer/no-title-slide/reference.pptx"}
+ "pptx/footer/input.native"
+ "pptx/footer/no-title-slide/output.pptx"
+ , ooxmlTest
+ writePowerpoint
+ "Footer with slide number starting from 3"
+ def { writerReferenceDoc = Just "pptx/footer/higher-slide-number/reference.pptx"}
+ "pptx/footer/input.native"
+ "pptx/footer/higher-slide-number/output.pptx"
+ , ooxmlTest
+ writePowerpoint
+ "Layouts can be moved around in reference doc"
+ def {writerReferenceDoc = Just "pptx/reference-moved-layouts.pptx"}
+ "pptx/layouts/input.native"
+ "pptx/layouts/moved.pptx"
+ , ooxmlTest
+ writePowerpoint
+ "Layouts can be missing from the reference doc"
+ def {writerReferenceDoc = Just "pptx/reference-deleted-layouts.pptx"}
+ "pptx/layouts/input.native"
+ "pptx/layouts/deleted.pptx"
+ ]
+ in regularTests <> referenceSpecificTests