From 4340bd52c49b987087e123de2eae4464b300332f Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sun, 15 Aug 2021 15:05:54 -0700 Subject: Make docx writer sensitive to `native_numbering` extension. Figure and table numbers are now only included if `native_numbering` is enabled. (By default it is disabled.) This is a behavior change with respect to 2.14.1, but the behavior is that of previous versions. The change was necessary to avoid incompatibilities between pandoc's native numbering and third-party cross reference filters like pandoc-crossref. Closes #7499. --- test/Tests/Writers/Docx.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) (limited to 'test/Tests/Writers') 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 -- cgit v1.2.3 From 8474d488a52343d53ee438301d66622aad6e7bb5 Mon Sep 17 00:00:00 2001 From: Emily Bourke Date: Mon, 16 Aug 2021 15:48:28 +0100 Subject: Provide more detailed XML diff in tests MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit I had some failing tests and couldn’t tell what was different in the XML. Updating the comparison to return what’s different made it easier to figure out what was wrong, and I think will be helpful for others in future. --- test/Tests/Writers/OOXML.hs | 72 ++++++++++++++++++++++++++++++++------------- 1 file changed, 51 insertions(+), 21 deletions(-) (limited to 'test/Tests/Writers') diff --git a/test/Tests/Writers/OOXML.hs b/test/Tests/Writers/OOXML.hs index 83f05cfec..299e3e547 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,29 +19,55 @@ 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 myElem) (Elem goodElem) | (QName "created" _ (Just "dcterms")) <- elName myElem , (QName "created" _ (Just "dcterms")) <- elName goodElem = - True -compareXMLBool (Elem myElem) (Elem goodElem) + Nothing +compareXML (Elem myElem) (Elem goodElem) | (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 + Nothing +compareXML (Elem myElem) (Elem goodElem) = + (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 myCData) (Text goodCData) = + (if cdVerbatim myCData == cdVerbatim goodCData + && cdData myCData == cdData goodCData + && cdLine myCData == cdLine goodCData + then Nothing + else Just (CDatasDiffer (Comparison { mine = myCData, good = goodCData }))) +compareXML (CRef myStr) (CRef goodStr) = + if myStr == goodStr + then Nothing + else Just (CRefsDiffer (Comparison { mine = myStr, good = goodStr })) +compareXML m g = 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 :: Content -> Content -> String displayDiff elemA elemB = @@ -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 testContent goldenContent - 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 = -- cgit v1.2.3 From 9204e5c9b1ef5d1f038dbc93928f6bbc71bf6b2f Mon Sep 17 00:00:00 2001 From: Emily Bourke Date: Tue, 17 Aug 2021 11:55:29 +0100 Subject: Don’t compare cdLine in OOXML golden tests MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit The `cdLine` field gives the line of the file some CData was found on. I don’t think this is a difference that should fail these golden tests, as the XML should still be parsable if nothing else has changed. --- test/Tests/Writers/OOXML.hs | 1 - 1 file changed, 1 deletion(-) (limited to 'test/Tests/Writers') diff --git a/test/Tests/Writers/OOXML.hs b/test/Tests/Writers/OOXML.hs index 299e3e547..56a27a4b8 100644 --- a/test/Tests/Writers/OOXML.hs +++ b/test/Tests/Writers/OOXML.hs @@ -49,7 +49,6 @@ compareXML (Elem myElem) (Elem goodElem) = compareXML (Text myCData) (Text goodCData) = (if cdVerbatim myCData == cdVerbatim goodCData && cdData myCData == cdData goodCData - && cdLine myCData == cdLine goodCData then Nothing else Just (CDatasDiffer (Comparison { mine = myCData, good = goodCData }))) compareXML (CRef myStr) (CRef goodStr) = -- cgit v1.2.3 From 72823ad947face43ef45eaeb7e611979531abed6 Mon Sep 17 00:00:00 2001 From: Emily Bourke Date: Tue, 10 Aug 2021 17:20:53 +0100 Subject: pptx: Select layouts from reference doc by name MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Until now, users had to make sure that their reference doc contains layouts in a specific order: the first four layouts in the file had to have a specific structure, or else pandoc would error (or sometimes successfully produce a pptx file, which PowerPoint would then fail to open). This commit changes the layout selection to use the layout names rather than order: users must make sure their reference doc contains four layouts with specific names, and if a layout with the right name isn’t found pandoc will output a warning and use the corresponding layout from the default reference doc as a fallback. I believe the use of names rather than order will be clearer to users, and the clearer errors will help them troubleshoot when things go wrong. - Add tests for moved layouts - Add tests for deleted layouts - Add newly included layouts to slideMaster1.xml to fix tests --- MANUAL.txt | 19 +- src/Text/Pandoc/Writers/Powerpoint/Output.hs | 225 +++++++++++++++++++-- test/Tests/Writers/Powerpoint.hs | 31 ++- test/pptx/code-custom_deleted_layouts.pptx | Bin 0 -> 31033 bytes test/pptx/code-custom_moved_layouts.pptx | Bin 0 -> 41822 bytes test/pptx/code_deleted_layouts.pptx | Bin 0 -> 31032 bytes test/pptx/code_moved_layouts.pptx | Bin 0 -> 41826 bytes ...ment-properties-short-desc_deleted_layouts.pptx | Bin 0 -> 29806 bytes ...cument-properties-short-desc_moved_layouts.pptx | Bin 0 -> 40600 bytes test/pptx/document-properties_deleted_layouts.pptx | Bin 0 -> 30210 bytes test/pptx/document-properties_moved_layouts.pptx | Bin 0 -> 41004 bytes test/pptx/endnotes_deleted_layouts.pptx | Bin 0 -> 29774 bytes test/pptx/endnotes_moved_layouts.pptx | Bin 0 -> 40566 bytes test/pptx/endnotes_toc_deleted_layouts.pptx | Bin 0 -> 30596 bytes test/pptx/endnotes_toc_moved_layouts.pptx | Bin 0 -> 41384 bytes test/pptx/images_deleted_layouts.pptx | Bin 0 -> 47424 bytes test/pptx/images_moved_layouts.pptx | Bin 0 -> 58213 bytes test/pptx/inline_formatting_deleted_layouts.pptx | Bin 0 -> 28966 bytes test/pptx/inline_formatting_moved_layouts.pptx | Bin 0 -> 39758 bytes test/pptx/lists_deleted_layouts.pptx | Bin 0 -> 29861 bytes test/pptx/lists_moved_layouts.pptx | Bin 0 -> 40653 bytes test/pptx/raw_ooxml_deleted_layouts.pptx | Bin 0 -> 29754 bytes test/pptx/raw_ooxml_moved_layouts.pptx | Bin 0 -> 40546 bytes test/pptx/reference_deleted_layouts.pptx | Bin 0 -> 18160 bytes test/pptx/reference_moved_layouts.pptx | Bin 0 -> 44237 bytes test/pptx/remove_empty_slides_deleted_layouts.pptx | Bin 0 -> 46867 bytes test/pptx/remove_empty_slides_moved_layouts.pptx | Bin 0 -> 57656 bytes test/pptx/slide_breaks_deleted_layouts.pptx | Bin 0 -> 31378 bytes test/pptx/slide_breaks_moved_layouts.pptx | Bin 0 -> 42171 bytes ...slide_breaks_slide_level_1_deleted_layouts.pptx | Bin 0 -> 30554 bytes .../slide_breaks_slide_level_1_moved_layouts.pptx | Bin 0 -> 41343 bytes test/pptx/slide_breaks_toc_deleted_layouts.pptx | Bin 0 -> 32328 bytes test/pptx/slide_breaks_toc_moved_layouts.pptx | Bin 0 -> 43118 bytes ...eaker_notes_after_metadata_deleted_layouts.pptx | Bin 0 -> 34473 bytes ...speaker_notes_after_metadata_moved_layouts.pptx | Bin 0 -> 45269 bytes .../speaker_notes_afterheader_deleted_layouts.pptx | Bin 0 -> 33500 bytes .../speaker_notes_afterheader_moved_layouts.pptx | Bin 0 -> 44297 bytes .../speaker_notes_afterseps_deleted_layouts.pptx | Bin 0 -> 54390 bytes .../speaker_notes_afterseps_moved_layouts.pptx | Bin 0 -> 65181 bytes test/pptx/speaker_notes_deleted_layouts.pptx | Bin 0 -> 38203 bytes test/pptx/speaker_notes_moved_layouts.pptx | Bin 0 -> 49002 bytes test/pptx/start_numbering_at_deleted_layouts.pptx | Bin 0 -> 29837 bytes test/pptx/start_numbering_at_moved_layouts.pptx | Bin 0 -> 40630 bytes test/pptx/tables_deleted_layouts.pptx | Bin 0 -> 30381 bytes test/pptx/tables_moved_layouts.pptx | Bin 0 -> 41174 bytes test/pptx/two_column_deleted_layouts.pptx | Bin 0 -> 28883 bytes test/pptx/two_column_moved_layouts.pptx | Bin 0 -> 39676 bytes 47 files changed, 242 insertions(+), 33 deletions(-) create mode 100644 test/pptx/code-custom_deleted_layouts.pptx create mode 100644 test/pptx/code-custom_moved_layouts.pptx create mode 100644 test/pptx/code_deleted_layouts.pptx create mode 100644 test/pptx/code_moved_layouts.pptx create mode 100644 test/pptx/document-properties-short-desc_deleted_layouts.pptx create mode 100644 test/pptx/document-properties-short-desc_moved_layouts.pptx create mode 100644 test/pptx/document-properties_deleted_layouts.pptx create mode 100644 test/pptx/document-properties_moved_layouts.pptx create mode 100644 test/pptx/endnotes_deleted_layouts.pptx create mode 100644 test/pptx/endnotes_moved_layouts.pptx create mode 100644 test/pptx/endnotes_toc_deleted_layouts.pptx create mode 100644 test/pptx/endnotes_toc_moved_layouts.pptx create mode 100644 test/pptx/images_deleted_layouts.pptx create mode 100644 test/pptx/images_moved_layouts.pptx create mode 100644 test/pptx/inline_formatting_deleted_layouts.pptx create mode 100644 test/pptx/inline_formatting_moved_layouts.pptx create mode 100644 test/pptx/lists_deleted_layouts.pptx create mode 100644 test/pptx/lists_moved_layouts.pptx create mode 100644 test/pptx/raw_ooxml_deleted_layouts.pptx create mode 100644 test/pptx/raw_ooxml_moved_layouts.pptx create mode 100644 test/pptx/reference_deleted_layouts.pptx create mode 100644 test/pptx/reference_moved_layouts.pptx create mode 100644 test/pptx/remove_empty_slides_deleted_layouts.pptx create mode 100644 test/pptx/remove_empty_slides_moved_layouts.pptx create mode 100644 test/pptx/slide_breaks_deleted_layouts.pptx create mode 100644 test/pptx/slide_breaks_moved_layouts.pptx create mode 100644 test/pptx/slide_breaks_slide_level_1_deleted_layouts.pptx create mode 100644 test/pptx/slide_breaks_slide_level_1_moved_layouts.pptx create mode 100644 test/pptx/slide_breaks_toc_deleted_layouts.pptx create mode 100644 test/pptx/slide_breaks_toc_moved_layouts.pptx create mode 100644 test/pptx/speaker_notes_after_metadata_deleted_layouts.pptx create mode 100644 test/pptx/speaker_notes_after_metadata_moved_layouts.pptx create mode 100644 test/pptx/speaker_notes_afterheader_deleted_layouts.pptx create mode 100644 test/pptx/speaker_notes_afterheader_moved_layouts.pptx create mode 100644 test/pptx/speaker_notes_afterseps_deleted_layouts.pptx create mode 100644 test/pptx/speaker_notes_afterseps_moved_layouts.pptx create mode 100644 test/pptx/speaker_notes_deleted_layouts.pptx create mode 100644 test/pptx/speaker_notes_moved_layouts.pptx create mode 100644 test/pptx/start_numbering_at_deleted_layouts.pptx create mode 100644 test/pptx/start_numbering_at_moved_layouts.pptx create mode 100644 test/pptx/tables_deleted_layouts.pptx create mode 100644 test/pptx/tables_moved_layouts.pptx create mode 100644 test/pptx/two_column_deleted_layouts.pptx create mode 100644 test/pptx/two_column_moved_layouts.pptx (limited to 'test/Tests/Writers') diff --git a/MANUAL.txt b/MANUAL.txt index bed3b2009..0b1424d47 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -1165,13 +1165,18 @@ header when requesting a document from a URL: `.pptx` or `.potx` extension) are known to work, as are most templates derived from these. - The specific requirement is that the template should begin with - the following first four layouts: - - 1. Title Slide - 2. Title and Content - 3. Section Header - 4. Two Content + The specific requirement is that the template should contain layouts + with the following names (as seen within PowerPoint): + + - Title Slide + - Title and Content + - Section Header + - Two Content + + For each name, the first layout found with that name will be used. + If no layout is found with one of the names, pandoc will output a + warning and use the layout with that name from the default reference + doc instead. All templates included with a recent version of MS PowerPoint will fit these criteria. (You can click on `Layout` under the diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs index 157810216..a757516a8 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {- | @@ -21,14 +22,19 @@ import Control.Monad.Reader import Control.Monad.State import Codec.Archive.Zip import Data.List (intercalate, stripPrefix, nub, union, isPrefixOf, intersperse) +import Data.CaseInsensitive (CI) +import qualified Data.CaseInsensitive as CI import Data.Default +import Data.Foldable (toList) +import Data.List.NonEmpty (nonEmpty, NonEmpty ((:|))) import Data.Text (Text) import qualified Data.Text as T -import qualified Data.Text.Read +import Data.Text.Read (decimal) import Data.Time (formatTime, defaultTimeLocale) import Data.Time.Clock (UTCTime) import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds, posixSecondsToUTCTime) -import System.FilePath.Posix (splitDirectories, splitExtension, takeExtension) +import Data.Traversable (for) +import System.FilePath.Posix (splitDirectories, splitExtension, takeExtension, takeFileName) import Text.Pandoc.XML.Light as XML import Text.Pandoc.Definition import qualified Text.Pandoc.UTF8 as UTF8 @@ -48,11 +54,11 @@ import System.FilePath.Glob import Text.DocTemplates (FromContext(lookupContext), Context) import Text.DocLayout (literal) import Text.TeXMath +import Text.Pandoc.Logging (LogMessage(TemplateWarning)) import Text.Pandoc.Writers.Math (convertMath) import Text.Pandoc.Writers.Powerpoint.Presentation import Text.Pandoc.Shared (tshow, stringify) import Skylighting (fromColor) -import Data.List.NonEmpty (nonEmpty) -- |The 'EMU' type is used to specify sizes in English Metric Units. type EMU = Integer @@ -117,6 +123,7 @@ data WriterEnv = WriterEnv { envRefArchive :: Archive -- no entry in the map for it. , envSpeakerNotesIdMap :: M.Map Int Int , envInSpeakerNotes :: Bool + , envSlideLayouts :: Maybe SlideLayouts } deriving (Show) @@ -136,8 +143,33 @@ instance Default WriterEnv where , envSlideIdMap = mempty , envSpeakerNotesIdMap = mempty , envInSpeakerNotes = False + , envSlideLayouts = Nothing } +type SlideLayouts = SlideLayoutsOf SlideLayout + +data SlideLayoutsOf a = SlideLayouts + { metadata :: a + , title :: a + , content :: a + , twoColumn :: a + } deriving (Show, Functor, Foldable, Traversable) + +data SlideLayout = SlideLayout + { slElement :: Element + , slInReferenceDoc :: Bool + -- ^ True if the layout is in the provided reference doc, False if it's in + -- the default reference doc. + , slPath :: FilePath + , slEntry :: Entry + } deriving (Show) + +getSlideLayouts :: PandocMonad m => P m SlideLayouts +getSlideLayouts = asks envSlideLayouts >>= maybe (throwError e) pure + where + e = PandocSomeError ("Slide layouts aren't defined, even though they should " + <> "always be. This is a bug in pandoc.") + data ContentType = NormalContent | TwoColumnLeftContent | TwoColumnRightContent @@ -264,7 +296,24 @@ presentationToArchiveP p@(Presentation docProps slides) = do T.unlines (map (T.pack . (" " <>)) missingFiles) ) - newArch' <- foldM copyFileToArchive emptyArchive filePaths + newArch <- foldM copyFileToArchive emptyArchive filePaths + + -- Add any layouts taken from the default archive, + -- overwriting any already added. + slideLayouts <- getSlideLayouts + let f layout = + if not (slInReferenceDoc layout) + then addEntryToArchive (slEntry layout) + else id + let newArch' = foldr f newArch slideLayouts + + -- Update the master to make sure it includes any layouts we've just added + master <- getMaster + masterRels <- getMasterRels + let (updatedMasterElem, updatedMasterRelElem) = updateMasterElems slideLayouts master masterRels + updatedMasterEntry <- elemToEntry "ppt/slideMasters/slideMaster1.xml" updatedMasterElem + updatedMasterRelEntry <- elemToEntry "ppt/slideMasters/_rels/slideMaster1.xml.rels" updatedMasterRelElem + -- we make a modified ppt/viewProps.xml out of the presentation viewProps viewPropsEntry <- makeViewPropsEntry -- we make a docProps/core.xml entry out of the presentation docprops @@ -293,9 +342,82 @@ presentationToArchiveP p@(Presentation docProps slides) = do spkNotesEntries <> spkNotesRelEntries <> mediaEntries <> + [updatedMasterEntry, updatedMasterRelEntry] <> [contentTypesEntry, docPropsEntry, docCustomPropsEntry, relsEntry, presEntry, presRelsEntry, viewPropsEntry] +updateMasterElems :: SlideLayouts -> Element -> Element -> (Element, Element) +updateMasterElems layouts master masterRels = (updatedMaster, updatedMasterRels) + where + updatedMaster = master { elContent = updateSldLayoutIdLst <$> elContent master } + (updatedRelationshipIds, updatedMasterRels) = addLayoutRels masterRels + + updateSldLayoutIdLst :: Content -> Content + updateSldLayoutIdLst (Elem e) = case elName e of + (QName "sldLayoutIdLst" _ _) -> let + mkChild relationshipId (lastId, children) = let + thisId = lastId + 1 + newChild = Element + { elName = QName "sldLayoutId" Nothing (Just "p") + , elAttribs = + [ Attr (QName "id" Nothing Nothing) (T.pack (show thisId)) + , Attr (QName "id" Nothing (Just "r")) relationshipId + ] + , elContent = [] + , elLine = Nothing + } + in (thisId, Elem newChild : children) + newChildren = snd (foldr mkChild (maxIdNumber' e, []) updatedRelationshipIds) + in Elem e { elContent = elContent e <> newChildren } + _ -> Elem e + updateSldLayoutIdLst c = c + + addLayoutRels :: + Element -> + ([Text], Element) + addLayoutRels e = let + layoutsToAdd = filter (not . slInReferenceDoc) (toList layouts) + newRelationships = snd (foldr mkRelationship (maxIdNumber e, []) layoutsToAdd) + newRelationshipIds = mapMaybe getRelationshipId newRelationships + mkRelationship layout (lastId, relationships) = let + thisId = lastId + 1 + slideLayoutPath = "../slideLayouts/" <> T.pack (takeFileName (slPath layout)) + newRelationship = Element + { elName = QName "Relationship" Nothing Nothing + , elAttribs = + [ Attr (QName "Id" Nothing Nothing) ("rId" <> T.pack (show thisId)) + , Attr (QName "Type" Nothing Nothing) "http://schemas.openxmlformats.org/officeDocument/2006/relationships/slideLayout" + , Attr (QName "Target" Nothing Nothing) slideLayoutPath + ] + , elContent = [] + , elLine = Nothing + } + in (thisId, Elem newRelationship : relationships) + in (newRelationshipIds, e {elContent = elContent e <> newRelationships}) + + getRelationshipId :: Content -> Maybe Text + getRelationshipId (Elem e) = findAttr (QName "Id" Nothing Nothing) e + getRelationshipId _ = Nothing + + maxIdNumber :: Element -> Integer + maxIdNumber relationships = maximum (0 : idNumbers) + where + idNumbers = fst <$> mapMaybe (hush . decimal . T.drop 3) idAttributes + idAttributes = mapMaybe getIdAttribute (elContent relationships) + getIdAttribute (Elem e) = findAttr (QName "Id" Nothing Nothing) e + getIdAttribute _ = Nothing + + maxIdNumber' :: Element -> Integer + maxIdNumber' sldLayouts = maximum (0 : idNumbers) + where + idNumbers = fst <$> mapMaybe (hush . decimal) idAttributes + idAttributes = mapMaybe getIdAttribute (elContent sldLayouts) + getIdAttribute (Elem e) = findAttr (QName "id" Nothing Nothing) e + getIdAttribute _ = Nothing + + hush :: Either a b -> Maybe b + hush = either (const Nothing) Just + makeSlideIdMap :: Presentation -> M.Map SlideId Int makeSlideIdMap (Presentation _ slides) = M.fromList $ map slideId slides `zip` [1..] @@ -318,6 +440,40 @@ presentationToArchive opts meta pres = do Nothing -> toArchive . BL.fromStrict <$> P.readDataFile "reference.pptx" + let (referenceLayouts, defaultReferenceLayouts) = + (getLayoutsFromArchive refArchive, getLayoutsFromArchive distArchive) + let layoutTitles = SlideLayouts { metadata = "Title Slide" :: Text + , title = "Section Header" + , content = "Title and Content" + , twoColumn = "Two Content" + } + layouts <- for layoutTitles $ \layoutTitle -> do + let layout = M.lookup (CI.mk layoutTitle) referenceLayouts + let defaultLayout = M.lookup (CI.mk layoutTitle) defaultReferenceLayouts + case (layout, defaultLayout) of + (Nothing, Nothing) -> + throwError (PandocSomeError ("Couldn't find layout named \"" + <> layoutTitle <> "\" in the provided " + <> "reference doc or in the default " + <> "reference doc included with pandoc.")) + (Nothing, Just ((element, path, entry) :| _)) -> do + P.logOutput (TemplateWarning ("Couldn't find layout named \"" + <> layoutTitle <> "\" in provided " + <> "reference doc. Falling back to " + <> "the default included with pandoc.")) + pure SlideLayout { slElement = element + , slPath = path + , slEntry = entry + , slInReferenceDoc = False + } + (Just ((element, path, entry) :| _), _ ) -> + pure SlideLayout { slElement = element + , slPath = path + , slEntry = entry + , slInReferenceDoc = True + } + + utctime <- P.getTimestamp presSize <- case getPresentationSize refArchive distArchive of @@ -341,6 +497,7 @@ presentationToArchive opts meta pres = do , envPresentationSize = presSize , envSlideIdMap = makeSlideIdMap pres , envSpeakerNotesIdMap = makeSpeakerNotesMap pres + , envSlideLayouts = Just layouts } let st = def { stMediaGlobalIds = initialGlobalIds refArchive distArchive @@ -348,7 +505,30 @@ presentationToArchive opts meta pres = do runP env st $ presentationToArchiveP pres - +-- | Get all slide layouts from an archive, as a map where the layout's name +-- gives the map key. +-- +-- For each layout, the map contains its XML representation, its path within +-- the archive, and the archive entry. +getLayoutsFromArchive :: Archive -> M.Map (CI Text) (NonEmpty (Element, FilePath, Entry)) +getLayoutsFromArchive archive = + M.fromListWith (<>) ((\t@(e, _, _) -> (CI.mk (name e), pure t)) <$> layouts) + where + layouts :: [(Element, FilePath, Entry)] + layouts = mapMaybe findElementByPath paths + parseXml' entry = case parseXMLElement (UTF8.toTextLazy (fromEntry entry)) of + Left _ -> Nothing + Right element -> Just element + findElementByPath :: FilePath -> Maybe (Element, FilePath, Entry) + findElementByPath path = do + entry <- findEntryByPath path archive + element <- parseXml' entry + pure (element, path, entry) + paths = filter (match (compile "ppt/slideLayouts/slideLayout*.xml")) (filesInArchive archive) + name element = fromMaybe "Untitled layout" $ do + let ns = elemToNameSpaces element + cSld <- findChild (elemName ns "p" "cSld") element + findAttr (QName "name" Nothing Nothing) cSld -------------------------------------------------- @@ -365,15 +545,14 @@ curSlideHasSpeakerNotes = -------------------------------------------------- getLayout :: PandocMonad m => Layout -> P m Element -getLayout layout = do - let layoutpath = case layout of - MetadataSlide{} -> "ppt/slideLayouts/slideLayout1.xml" - TitleSlide{} -> "ppt/slideLayouts/slideLayout3.xml" - ContentSlide{} -> "ppt/slideLayouts/slideLayout2.xml" - TwoColumnSlide{} -> "ppt/slideLayouts/slideLayout4.xml" - refArchive <- asks envRefArchive - distArchive <- asks envDistArchive - parseXml refArchive distArchive layoutpath +getLayout layout = getElement <$> getSlideLayouts + where + getElement = + slElement . case layout of + MetadataSlide{} -> metadata + TitleSlide{} -> title + ContentSlide{} -> content + TwoColumnSlide{} -> twoColumn shapeHasId :: NameSpaces -> T.Text -> Element -> Bool shapeHasId ns ident element @@ -604,6 +783,12 @@ getMaster = do distArchive <- asks envDistArchive parseXml refArchive distArchive "ppt/slideMasters/slideMaster1.xml" +getMasterRels :: PandocMonad m => P m Element +getMasterRels = do + refArchive <- asks envRefArchive + distArchive <- asks envDistArchive + parseXml refArchive distArchive "ppt/slideMasters/_rels/slideMaster1.xml.rels" + -- We want to get the header dimensions, so we can make sure that the -- image goes underneath it. We only use this in a content slide if it -- has a header. @@ -1606,11 +1791,13 @@ speakerNotesSlideRelElement slide = do slideToSlideRelElement :: PandocMonad m => Slide -> P m Element slideToSlideRelElement slide = do idNum <- slideNum slide - let target = case slide of - (Slide _ MetadataSlide{} _) -> "../slideLayouts/slideLayout1.xml" - (Slide _ TitleSlide{} _) -> "../slideLayouts/slideLayout3.xml" - (Slide _ ContentSlide{} _) -> "../slideLayouts/slideLayout2.xml" - (Slide _ TwoColumnSlide{} _) -> "../slideLayouts/slideLayout4.xml" + target <- flip fmap getSlideLayouts $ + T.pack . ("../slideLayouts/" <>) . takeFileName . + slPath . case slide of + (Slide _ MetadataSlide{} _) -> metadata + (Slide _ TitleSlide{} _) -> title + (Slide _ ContentSlide{} _) -> content + (Slide _ TwoColumnSlide{} _) -> twoColumn speakerNotesRels <- maybeToList <$> speakerNotesSlideRelElement slide diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs index 87ebe990c..344d20238 100644 --- a/test/Tests/Writers/Powerpoint.hs +++ b/test/Tests/Writers/Powerpoint.hs @@ -7,18 +7,21 @@ import System.FilePath import Text.DocTemplates (ToContext(toVal), Context(..)) import qualified Data.Map as M import Data.Text (pack) +import Data.List (unzip4) -- templating is important enough, and can break enough things, that -- 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 (dropExtension fp ++ suffix) "pptx" -pptxTests :: String -> WriterOptions -> FilePath -> FilePath -> (TestTree, TestTree) +pptxTests :: String -> WriterOptions -> FilePath -> FilePath -> (TestTree, TestTree, TestTree, TestTree) pptxTests name opts native pptx = let referenceDoc = "pptx/reference_depth.pptx" + movedLayoutsReferenceDoc = "pptx/reference_moved_layouts.pptx" + deletedLayoutsReferenceDoc = "pptx/reference_deleted_layouts.pptx" in ( ooxmlTest writePowerpoint @@ -31,15 +34,29 @@ pptxTests name opts native pptx = name opts{writerReferenceDoc=Just referenceDoc} native - (modifyPptxName pptx) + (modifyPptxName pptx "_templated") + , ooxmlTest + writePowerpoint + name + opts{writerReferenceDoc=Just movedLayoutsReferenceDoc} + native + (modifyPptxName pptx "_moved_layouts") + , ooxmlTest + writePowerpoint + name + opts{writerReferenceDoc=Just deletedLayoutsReferenceDoc} + native + (modifyPptxName pptx "_deleted_layouts") ) -groupPptxTests :: [(TestTree, TestTree)] -> [TestTree] +groupPptxTests :: [(TestTree, TestTree, TestTree, TestTree)] -> [TestTree] groupPptxTests pairs = - let (noRefs, refs) = unzip pairs + let (noRefs, refs, movedLayouts, deletedLayouts) = unzip4 pairs in [ testGroup "Default slide formatting" noRefs , testGroup "With `--reference-doc` pptx file" refs + , testGroup "With layouts in reference doc moved" movedLayouts + , testGroup "With layouts in reference doc deleted" deletedLayouts ] diff --git a/test/pptx/code-custom_deleted_layouts.pptx b/test/pptx/code-custom_deleted_layouts.pptx new file mode 100644 index 000000000..9282e6354 Binary files /dev/null and b/test/pptx/code-custom_deleted_layouts.pptx differ diff --git a/test/pptx/code-custom_moved_layouts.pptx b/test/pptx/code-custom_moved_layouts.pptx new file mode 100644 index 000000000..a14eeb6c8 Binary files /dev/null and b/test/pptx/code-custom_moved_layouts.pptx differ diff --git a/test/pptx/code_deleted_layouts.pptx b/test/pptx/code_deleted_layouts.pptx new file mode 100644 index 000000000..0f503f553 Binary files /dev/null and b/test/pptx/code_deleted_layouts.pptx differ diff --git a/test/pptx/code_moved_layouts.pptx b/test/pptx/code_moved_layouts.pptx new file mode 100644 index 000000000..4d66b1310 Binary files /dev/null and b/test/pptx/code_moved_layouts.pptx differ diff --git a/test/pptx/document-properties-short-desc_deleted_layouts.pptx b/test/pptx/document-properties-short-desc_deleted_layouts.pptx new file mode 100644 index 000000000..e4cf6bd7b Binary files /dev/null and b/test/pptx/document-properties-short-desc_deleted_layouts.pptx differ diff --git a/test/pptx/document-properties-short-desc_moved_layouts.pptx b/test/pptx/document-properties-short-desc_moved_layouts.pptx new file mode 100644 index 000000000..8834f885f Binary files /dev/null and b/test/pptx/document-properties-short-desc_moved_layouts.pptx differ diff --git a/test/pptx/document-properties_deleted_layouts.pptx b/test/pptx/document-properties_deleted_layouts.pptx new file mode 100644 index 000000000..a00c8059d Binary files /dev/null and b/test/pptx/document-properties_deleted_layouts.pptx differ diff --git a/test/pptx/document-properties_moved_layouts.pptx b/test/pptx/document-properties_moved_layouts.pptx new file mode 100644 index 000000000..c1d2d5282 Binary files /dev/null and b/test/pptx/document-properties_moved_layouts.pptx differ diff --git a/test/pptx/endnotes_deleted_layouts.pptx b/test/pptx/endnotes_deleted_layouts.pptx new file mode 100644 index 000000000..5c69a6310 Binary files /dev/null and b/test/pptx/endnotes_deleted_layouts.pptx differ diff --git a/test/pptx/endnotes_moved_layouts.pptx b/test/pptx/endnotes_moved_layouts.pptx new file mode 100644 index 000000000..0d4c491b9 Binary files /dev/null and b/test/pptx/endnotes_moved_layouts.pptx differ diff --git a/test/pptx/endnotes_toc_deleted_layouts.pptx b/test/pptx/endnotes_toc_deleted_layouts.pptx new file mode 100644 index 000000000..46708544c Binary files /dev/null and b/test/pptx/endnotes_toc_deleted_layouts.pptx differ diff --git a/test/pptx/endnotes_toc_moved_layouts.pptx b/test/pptx/endnotes_toc_moved_layouts.pptx new file mode 100644 index 000000000..d1200bd7d Binary files /dev/null and b/test/pptx/endnotes_toc_moved_layouts.pptx differ diff --git a/test/pptx/images_deleted_layouts.pptx b/test/pptx/images_deleted_layouts.pptx new file mode 100644 index 000000000..7a38ea625 Binary files /dev/null and b/test/pptx/images_deleted_layouts.pptx differ diff --git a/test/pptx/images_moved_layouts.pptx b/test/pptx/images_moved_layouts.pptx new file mode 100644 index 000000000..08d1c27e0 Binary files /dev/null and b/test/pptx/images_moved_layouts.pptx differ diff --git a/test/pptx/inline_formatting_deleted_layouts.pptx b/test/pptx/inline_formatting_deleted_layouts.pptx new file mode 100644 index 000000000..bbd5bfeb4 Binary files /dev/null and b/test/pptx/inline_formatting_deleted_layouts.pptx differ diff --git a/test/pptx/inline_formatting_moved_layouts.pptx b/test/pptx/inline_formatting_moved_layouts.pptx new file mode 100644 index 000000000..427492130 Binary files /dev/null and b/test/pptx/inline_formatting_moved_layouts.pptx differ diff --git a/test/pptx/lists_deleted_layouts.pptx b/test/pptx/lists_deleted_layouts.pptx new file mode 100644 index 000000000..6512e44bb Binary files /dev/null and b/test/pptx/lists_deleted_layouts.pptx differ diff --git a/test/pptx/lists_moved_layouts.pptx b/test/pptx/lists_moved_layouts.pptx new file mode 100644 index 000000000..2947c3211 Binary files /dev/null and b/test/pptx/lists_moved_layouts.pptx differ diff --git a/test/pptx/raw_ooxml_deleted_layouts.pptx b/test/pptx/raw_ooxml_deleted_layouts.pptx new file mode 100644 index 000000000..2ea155657 Binary files /dev/null and b/test/pptx/raw_ooxml_deleted_layouts.pptx differ diff --git a/test/pptx/raw_ooxml_moved_layouts.pptx b/test/pptx/raw_ooxml_moved_layouts.pptx new file mode 100644 index 000000000..e58304172 Binary files /dev/null and b/test/pptx/raw_ooxml_moved_layouts.pptx differ diff --git a/test/pptx/reference_deleted_layouts.pptx b/test/pptx/reference_deleted_layouts.pptx new file mode 100644 index 000000000..a9a74ecd5 Binary files /dev/null and b/test/pptx/reference_deleted_layouts.pptx differ diff --git a/test/pptx/reference_moved_layouts.pptx b/test/pptx/reference_moved_layouts.pptx new file mode 100644 index 000000000..72c4f3fd7 Binary files /dev/null and b/test/pptx/reference_moved_layouts.pptx differ diff --git a/test/pptx/remove_empty_slides_deleted_layouts.pptx b/test/pptx/remove_empty_slides_deleted_layouts.pptx new file mode 100644 index 000000000..7ae4a5fab Binary files /dev/null and b/test/pptx/remove_empty_slides_deleted_layouts.pptx differ diff --git a/test/pptx/remove_empty_slides_moved_layouts.pptx b/test/pptx/remove_empty_slides_moved_layouts.pptx new file mode 100644 index 000000000..2572f2447 Binary files /dev/null and b/test/pptx/remove_empty_slides_moved_layouts.pptx differ diff --git a/test/pptx/slide_breaks_deleted_layouts.pptx b/test/pptx/slide_breaks_deleted_layouts.pptx new file mode 100644 index 000000000..86dfad3b2 Binary files /dev/null and b/test/pptx/slide_breaks_deleted_layouts.pptx differ diff --git a/test/pptx/slide_breaks_moved_layouts.pptx b/test/pptx/slide_breaks_moved_layouts.pptx new file mode 100644 index 000000000..90b3b94a6 Binary files /dev/null and b/test/pptx/slide_breaks_moved_layouts.pptx differ diff --git a/test/pptx/slide_breaks_slide_level_1_deleted_layouts.pptx b/test/pptx/slide_breaks_slide_level_1_deleted_layouts.pptx new file mode 100644 index 000000000..2c7fd4d8b Binary files /dev/null and b/test/pptx/slide_breaks_slide_level_1_deleted_layouts.pptx differ diff --git a/test/pptx/slide_breaks_slide_level_1_moved_layouts.pptx b/test/pptx/slide_breaks_slide_level_1_moved_layouts.pptx new file mode 100644 index 000000000..8471b1d10 Binary files /dev/null and b/test/pptx/slide_breaks_slide_level_1_moved_layouts.pptx differ diff --git a/test/pptx/slide_breaks_toc_deleted_layouts.pptx b/test/pptx/slide_breaks_toc_deleted_layouts.pptx new file mode 100644 index 000000000..1e0b76d46 Binary files /dev/null and b/test/pptx/slide_breaks_toc_deleted_layouts.pptx differ diff --git a/test/pptx/slide_breaks_toc_moved_layouts.pptx b/test/pptx/slide_breaks_toc_moved_layouts.pptx new file mode 100644 index 000000000..918264bc5 Binary files /dev/null and b/test/pptx/slide_breaks_toc_moved_layouts.pptx differ diff --git a/test/pptx/speaker_notes_after_metadata_deleted_layouts.pptx b/test/pptx/speaker_notes_after_metadata_deleted_layouts.pptx new file mode 100644 index 000000000..1298870e2 Binary files /dev/null and b/test/pptx/speaker_notes_after_metadata_deleted_layouts.pptx differ diff --git a/test/pptx/speaker_notes_after_metadata_moved_layouts.pptx b/test/pptx/speaker_notes_after_metadata_moved_layouts.pptx new file mode 100644 index 000000000..b844a0b51 Binary files /dev/null and b/test/pptx/speaker_notes_after_metadata_moved_layouts.pptx differ diff --git a/test/pptx/speaker_notes_afterheader_deleted_layouts.pptx b/test/pptx/speaker_notes_afterheader_deleted_layouts.pptx new file mode 100644 index 000000000..853b918cb Binary files /dev/null and b/test/pptx/speaker_notes_afterheader_deleted_layouts.pptx differ diff --git a/test/pptx/speaker_notes_afterheader_moved_layouts.pptx b/test/pptx/speaker_notes_afterheader_moved_layouts.pptx new file mode 100644 index 000000000..9fff9f855 Binary files /dev/null and b/test/pptx/speaker_notes_afterheader_moved_layouts.pptx differ diff --git a/test/pptx/speaker_notes_afterseps_deleted_layouts.pptx b/test/pptx/speaker_notes_afterseps_deleted_layouts.pptx new file mode 100644 index 000000000..1e7f4968d Binary files /dev/null and b/test/pptx/speaker_notes_afterseps_deleted_layouts.pptx differ diff --git a/test/pptx/speaker_notes_afterseps_moved_layouts.pptx b/test/pptx/speaker_notes_afterseps_moved_layouts.pptx new file mode 100644 index 000000000..e092ae444 Binary files /dev/null and b/test/pptx/speaker_notes_afterseps_moved_layouts.pptx differ diff --git a/test/pptx/speaker_notes_deleted_layouts.pptx b/test/pptx/speaker_notes_deleted_layouts.pptx new file mode 100644 index 000000000..6a5ad524f Binary files /dev/null and b/test/pptx/speaker_notes_deleted_layouts.pptx differ diff --git a/test/pptx/speaker_notes_moved_layouts.pptx b/test/pptx/speaker_notes_moved_layouts.pptx new file mode 100644 index 000000000..f95df9622 Binary files /dev/null and b/test/pptx/speaker_notes_moved_layouts.pptx differ diff --git a/test/pptx/start_numbering_at_deleted_layouts.pptx b/test/pptx/start_numbering_at_deleted_layouts.pptx new file mode 100644 index 000000000..d9cf91804 Binary files /dev/null and b/test/pptx/start_numbering_at_deleted_layouts.pptx differ diff --git a/test/pptx/start_numbering_at_moved_layouts.pptx b/test/pptx/start_numbering_at_moved_layouts.pptx new file mode 100644 index 000000000..e1b2d4de8 Binary files /dev/null and b/test/pptx/start_numbering_at_moved_layouts.pptx differ diff --git a/test/pptx/tables_deleted_layouts.pptx b/test/pptx/tables_deleted_layouts.pptx new file mode 100644 index 000000000..a52222551 Binary files /dev/null and b/test/pptx/tables_deleted_layouts.pptx differ diff --git a/test/pptx/tables_moved_layouts.pptx b/test/pptx/tables_moved_layouts.pptx new file mode 100644 index 000000000..56608a039 Binary files /dev/null and b/test/pptx/tables_moved_layouts.pptx differ diff --git a/test/pptx/two_column_deleted_layouts.pptx b/test/pptx/two_column_deleted_layouts.pptx new file mode 100644 index 000000000..60a244f94 Binary files /dev/null and b/test/pptx/two_column_deleted_layouts.pptx differ diff --git a/test/pptx/two_column_moved_layouts.pptx b/test/pptx/two_column_moved_layouts.pptx new file mode 100644 index 000000000..a17f96b18 Binary files /dev/null and b/test/pptx/two_column_moved_layouts.pptx differ -- cgit v1.2.3 From 2e9a8935fb7e27969f7bd878899382b63cac0b3a Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 17 Aug 2021 15:33:10 -0700 Subject: OOXML tests: silence warnings. These can make the test output confusing, making people think tests are failing when they're passing. --- test/Tests/Writers/OOXML.hs | 1 + 1 file changed, 1 insertion(+) (limited to 'test/Tests/Writers') diff --git a/test/Tests/Writers/OOXML.hs b/test/Tests/Writers/OOXML.hs index 56a27a4b8..f2957f7a6 100644 --- a/test/Tests/Writers/OOXML.hs +++ b/test/Tests/Writers/OOXML.hs @@ -84,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 -- cgit v1.2.3 From 8e5a79f264dd1ebe80e048397b6281e318d25e82 Mon Sep 17 00:00:00 2001 From: Emily Bourke Date: Fri, 20 Aug 2021 14:40:09 +0100 Subject: pptx: Make first heading title if slide level is 0 MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Before this commit, the pptx writer adds a slide break before any table, “columns” div, or paragraph starting with an image, unless the only thing before it on the same slide is a heading at the slide level. In that case, the item and heading are kept on the same slide, and the heading is used as the slide title (inserted into the layout’s “title” placeholder). However, if the slide level is set to 0 (as was recently enabled) this makes it impossible to have a slide with a title which contains any of those items in its body. This commit changes this behaviour: now if the slide level is 0, then items will be kept with a heading of any level, if the heading’s the only thing before the item on the same slide. --- src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | 53 +++++++++++---------- test/Tests/Writers/Powerpoint.hs | 25 ++++++++++ test/pptx/slide-level-0-h1-h2-with-table.native | 14 ++++++ test/pptx/slide-level-0-h1-h2-with-table.pptx | Bin 0 -> 26985 bytes ...e-level-0-h1-h2-with-table_deleted_layouts.pptx | Bin 0 -> 29828 bytes ...ide-level-0-h1-h2-with-table_moved_layouts.pptx | Bin 0 -> 40552 bytes .../slide-level-0-h1-h2-with-table_templated.pptx | Bin 0 -> 40052 bytes test/pptx/slide-level-0-h1-with-image.native | 2 + test/pptx/slide-level-0-h1-with-image.pptx | Bin 0 -> 42596 bytes ...lide-level-0-h1-with-image_deleted_layouts.pptx | Bin 0 -> 45433 bytes .../slide-level-0-h1-with-image_moved_layouts.pptx | Bin 0 -> 56156 bytes .../slide-level-0-h1-with-image_templated.pptx | Bin 0 -> 55657 bytes test/pptx/slide-level-0-h1-with-table.native | 13 +++++ test/pptx/slide-level-0-h1-with-table.pptx | Bin 0 -> 26166 bytes ...lide-level-0-h1-with-table_deleted_layouts.pptx | Bin 0 -> 29008 bytes .../slide-level-0-h1-with-table_moved_layouts.pptx | Bin 0 -> 39731 bytes .../slide-level-0-h1-with-table_templated.pptx | Bin 0 -> 39232 bytes test/pptx/slide-level-0-h2-with-image.native | 2 + test/pptx/slide-level-0-h2-with-image.pptx | Bin 0 -> 42596 bytes ...lide-level-0-h2-with-image_deleted_layouts.pptx | Bin 0 -> 45433 bytes .../slide-level-0-h2-with-image_moved_layouts.pptx | Bin 0 -> 56156 bytes .../slide-level-0-h2-with-image_templated.pptx | Bin 0 -> 55657 bytes 22 files changed, 85 insertions(+), 24 deletions(-) create mode 100644 test/pptx/slide-level-0-h1-h2-with-table.native create mode 100644 test/pptx/slide-level-0-h1-h2-with-table.pptx create mode 100644 test/pptx/slide-level-0-h1-h2-with-table_deleted_layouts.pptx create mode 100644 test/pptx/slide-level-0-h1-h2-with-table_moved_layouts.pptx create mode 100644 test/pptx/slide-level-0-h1-h2-with-table_templated.pptx create mode 100644 test/pptx/slide-level-0-h1-with-image.native create mode 100644 test/pptx/slide-level-0-h1-with-image.pptx create mode 100644 test/pptx/slide-level-0-h1-with-image_deleted_layouts.pptx create mode 100644 test/pptx/slide-level-0-h1-with-image_moved_layouts.pptx create mode 100644 test/pptx/slide-level-0-h1-with-image_templated.pptx create mode 100644 test/pptx/slide-level-0-h1-with-table.native create mode 100644 test/pptx/slide-level-0-h1-with-table.pptx create mode 100644 test/pptx/slide-level-0-h1-with-table_deleted_layouts.pptx create mode 100644 test/pptx/slide-level-0-h1-with-table_moved_layouts.pptx create mode 100644 test/pptx/slide-level-0-h1-with-table_templated.pptx create mode 100644 test/pptx/slide-level-0-h2-with-image.native create mode 100644 test/pptx/slide-level-0-h2-with-image.pptx create mode 100644 test/pptx/slide-level-0-h2-with-image_deleted_layouts.pptx create mode 100644 test/pptx/slide-level-0-h2-with-image_moved_layouts.pptx create mode 100644 test/pptx/slide-level-0-h2-with-image_templated.pptx (limited to 'test/Tests/Writers') diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs index 0400783e3..284b9ae62 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs @@ -604,7 +604,7 @@ splitBlocks' cur acc (Para (il:ils) : blks) | isImage il = do then span isNotesDiv blks else ([], blks) case cur of - [Header n _ _] | n == slideLevel -> + [Header n _ _] | n == slideLevel || slideLevel == 0 -> splitBlocks' [] (acc ++ [cur ++ [Para [il]] ++ nts]) (if null ils then blks' else Para ils : blks') @@ -615,14 +615,14 @@ splitBlocks' cur acc (tbl@Table{} : blks) = do slideLevel <- asks envSlideLevel let (nts, blks') = span isNotesDiv blks case cur of - [Header n _ _] | n == slideLevel -> + [Header n _ _] | n == slideLevel || slideLevel == 0 -> splitBlocks' [] (acc ++ [cur ++ [tbl] ++ nts]) blks' _ -> splitBlocks' [] (acc ++ ([cur | not (null cur)]) ++ [tbl : nts]) blks' splitBlocks' cur acc (d@(Div (_, classes, _) _): blks) | "columns" `elem` classes = do slideLevel <- asks envSlideLevel let (nts, blks') = span isNotesDiv blks case cur of - [Header n _ _] | n == slideLevel -> + [Header n _ _] | n == slideLevel || slideLevel == 0 -> splitBlocks' [] (acc ++ [cur ++ [d] ++ nts]) blks' _ -> splitBlocks' [] (acc ++ ([cur | not (null cur)]) ++ [d : nts]) blks' splitBlocks' cur acc (blk : blks) = splitBlocks' (cur ++ [blk]) acc blks @@ -630,25 +630,10 @@ splitBlocks' cur acc (blk : blks) = splitBlocks' (cur ++ [blk]) acc blks splitBlocks :: [Block] -> Pres [[Block]] splitBlocks = splitBlocks' [] [] -blocksToSlide' :: Int -> [Block] -> SpeakerNotes -> Pres Slide -blocksToSlide' lvl (Header n (ident, _, _) ils : blks) spkNotes - | n < lvl = do - registerAnchorId ident - sldId <- asks envCurSlideId - hdr <- inlinesToParElems ils - return $ Slide sldId (TitleSlide hdr) spkNotes - | n == lvl = do - registerAnchorId ident - hdr <- inlinesToParElems ils - -- Now get the slide without the header, and then add the header - -- in. - slide <- blocksToSlide' lvl blks spkNotes - let layout = case slideLayout slide of - ContentSlide _ cont -> ContentSlide hdr cont - TwoColumnSlide _ contL contR -> TwoColumnSlide hdr contL contR - layout' -> layout' - return $ slide{slideLayout = layout} -blocksToSlide' _ (blk : blks) spkNotes +-- | Assuming the slide title is already handled, convert these blocks to the +-- body content for the slide. +bodyBlocksToSlide :: Int -> [Block] -> SpeakerNotes -> Pres Slide +bodyBlocksToSlide _ (blk : blks) spkNotes | Div (_, classes, _) divBlks <- blk , "columns" `elem` classes , Div (_, clsL, _) blksL : Div (_, clsR, _) blksR : remaining <- divBlks @@ -669,7 +654,7 @@ blocksToSlide' _ (blk : blks) spkNotes sldId (TwoColumnSlide [] shapesL shapesR) spkNotes -blocksToSlide' _ (blk : blks) spkNotes = do +bodyBlocksToSlide _ (blk : blks) spkNotes = do inNoteSlide <- asks envInNoteSlide shapes <- if inNoteSlide then forceFontSize noteSize $ blocksToShapes (blk : blks) @@ -680,7 +665,7 @@ blocksToSlide' _ (blk : blks) spkNotes = do sldId (ContentSlide [] shapes) spkNotes -blocksToSlide' _ [] spkNotes = do +bodyBlocksToSlide _ [] spkNotes = do sldId <- asks envCurSlideId return $ Slide @@ -688,6 +673,26 @@ blocksToSlide' _ [] spkNotes = do (ContentSlide [] []) spkNotes +blocksToSlide' :: Int -> [Block] -> SpeakerNotes -> Pres Slide +blocksToSlide' lvl (Header n (ident, _, _) ils : blks) spkNotes + | n < lvl = do + registerAnchorId ident + sldId <- asks envCurSlideId + hdr <- inlinesToParElems ils + return $ Slide sldId (TitleSlide hdr) spkNotes + | n == lvl || lvl == 0 = do + registerAnchorId ident + hdr <- inlinesToParElems ils + -- Now get the slide without the header, and then add the header + -- in. + slide <- bodyBlocksToSlide lvl blks spkNotes + let layout = case slideLayout slide of + ContentSlide _ cont -> ContentSlide hdr cont + TwoColumnSlide _ contL contR -> TwoColumnSlide hdr contL contR + layout' -> layout' + return $ slide{slideLayout = layout} +blocksToSlide' lvl blks spkNotes = bodyBlocksToSlide lvl blks spkNotes + blockToSpeakerNotes :: Block -> Pres SpeakerNotes blockToSpeakerNotes (Div (_, ["notes"], _) blks) = local (\env -> env{envInSpeakerNotes=True}) $ diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs index 344d20238..fd6d01d2d 100644 --- a/test/Tests/Writers/Powerpoint.hs +++ b/test/Tests/Writers/Powerpoint.hs @@ -146,4 +146,29 @@ tests = groupPptxTests [ pptxTests "Inline formatting" [(pack "monofont", toVal $ pack "Consolas")] } "pptx/code.native" "pptx/code-custom.pptx" + , pptxTests ("Using slide level 0, if the first thing on " + <> "a slide is a h1 it's used as the " + <> "slide title") + def { writerSlideLevel = Just 0 } + "pptx/slide-level-0-h1-with-image.native" + "pptx/slide-level-0-h1-with-image.pptx" + , pptxTests ("Using slide level 0, if the first thing on " + <> "a slide is a h2 it's used as the " + <> "slide title") + def { writerSlideLevel = Just 0 } + "pptx/slide-level-0-h2-with-image.native" + "pptx/slide-level-0-h2-with-image.pptx" + , pptxTests ("Using slide level 0, if the first thing on " + <> "a slide is a heading it's used as the " + <> "slide title (works with a table)") + def { writerSlideLevel = Just 0 } + "pptx/slide-level-0-h1-with-table.native" + "pptx/slide-level-0-h1-with-table.pptx" + , pptxTests ("Using slide level 0, if the first thing on " + <> "a slide is a heading it's used as the " + <> "slide title (two headings forces a " + <> "slide break though)") + def { writerSlideLevel = Just 0 } + "pptx/slide-level-0-h1-h2-with-table.native" + "pptx/slide-level-0-h1-h2-with-table.pptx" ] diff --git a/test/pptx/slide-level-0-h1-h2-with-table.native b/test/pptx/slide-level-0-h1-h2-with-table.native new file mode 100644 index 000000000..c6e65ecf5 --- /dev/null +++ b/test/pptx/slide-level-0-h1-h2-with-table.native @@ -0,0 +1,14 @@ +[Header 1 ("hello",[],[]) [Str "Hello"] +,Header 2 ("there",[],[]) [Str "There"] +,Table ("",[],[]) (Caption Nothing + []) + [(AlignDefault,ColWidth 5.555555555555555e-2)] + (TableHead ("",[],[]) + []) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]]]])] + (TableFoot ("",[],[]) + [])] diff --git a/test/pptx/slide-level-0-h1-h2-with-table.pptx b/test/pptx/slide-level-0-h1-h2-with-table.pptx new file mode 100644 index 000000000..197a6833f Binary files /dev/null and b/test/pptx/slide-level-0-h1-h2-with-table.pptx differ diff --git a/test/pptx/slide-level-0-h1-h2-with-table_deleted_layouts.pptx b/test/pptx/slide-level-0-h1-h2-with-table_deleted_layouts.pptx new file mode 100644 index 000000000..5e776e05c Binary files /dev/null and b/test/pptx/slide-level-0-h1-h2-with-table_deleted_layouts.pptx differ diff --git a/test/pptx/slide-level-0-h1-h2-with-table_moved_layouts.pptx b/test/pptx/slide-level-0-h1-h2-with-table_moved_layouts.pptx new file mode 100644 index 000000000..35204de1b Binary files /dev/null and b/test/pptx/slide-level-0-h1-h2-with-table_moved_layouts.pptx differ diff --git a/test/pptx/slide-level-0-h1-h2-with-table_templated.pptx b/test/pptx/slide-level-0-h1-h2-with-table_templated.pptx new file mode 100644 index 000000000..5c659952e Binary files /dev/null and b/test/pptx/slide-level-0-h1-h2-with-table_templated.pptx differ diff --git a/test/pptx/slide-level-0-h1-with-image.native b/test/pptx/slide-level-0-h1-with-image.native new file mode 100644 index 000000000..0f5033b54 --- /dev/null +++ b/test/pptx/slide-level-0-h1-with-image.native @@ -0,0 +1,2 @@ +[Header 1 ("hello",[],[]) [Str "Hello"] +,Para [Image ("",[],[]) [Str "An",Space,Str "image"] ("lalune.jpg","fig:")]] diff --git a/test/pptx/slide-level-0-h1-with-image.pptx b/test/pptx/slide-level-0-h1-with-image.pptx new file mode 100644 index 000000000..2f3a53f5c Binary files /dev/null and b/test/pptx/slide-level-0-h1-with-image.pptx differ diff --git a/test/pptx/slide-level-0-h1-with-image_deleted_layouts.pptx b/test/pptx/slide-level-0-h1-with-image_deleted_layouts.pptx new file mode 100644 index 000000000..16c61d1be Binary files /dev/null and b/test/pptx/slide-level-0-h1-with-image_deleted_layouts.pptx differ diff --git a/test/pptx/slide-level-0-h1-with-image_moved_layouts.pptx b/test/pptx/slide-level-0-h1-with-image_moved_layouts.pptx new file mode 100644 index 000000000..395036069 Binary files /dev/null and b/test/pptx/slide-level-0-h1-with-image_moved_layouts.pptx differ diff --git a/test/pptx/slide-level-0-h1-with-image_templated.pptx b/test/pptx/slide-level-0-h1-with-image_templated.pptx new file mode 100644 index 000000000..d306375e9 Binary files /dev/null and b/test/pptx/slide-level-0-h1-with-image_templated.pptx differ diff --git a/test/pptx/slide-level-0-h1-with-table.native b/test/pptx/slide-level-0-h1-with-table.native new file mode 100644 index 000000000..b961e900d --- /dev/null +++ b/test/pptx/slide-level-0-h1-with-table.native @@ -0,0 +1,13 @@ +[Header 1 ("hello",[],[]) [Str "Hello"] +,Table ("",[],[]) (Caption Nothing + []) + [(AlignDefault,ColWidth 5.555555555555555e-2)] + (TableHead ("",[],[]) + []) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]]]])] + (TableFoot ("",[],[]) + [])] diff --git a/test/pptx/slide-level-0-h1-with-table.pptx b/test/pptx/slide-level-0-h1-with-table.pptx new file mode 100644 index 000000000..44dbbf90c Binary files /dev/null and b/test/pptx/slide-level-0-h1-with-table.pptx differ diff --git a/test/pptx/slide-level-0-h1-with-table_deleted_layouts.pptx b/test/pptx/slide-level-0-h1-with-table_deleted_layouts.pptx new file mode 100644 index 000000000..0eb7c0b08 Binary files /dev/null and b/test/pptx/slide-level-0-h1-with-table_deleted_layouts.pptx differ diff --git a/test/pptx/slide-level-0-h1-with-table_moved_layouts.pptx b/test/pptx/slide-level-0-h1-with-table_moved_layouts.pptx new file mode 100644 index 000000000..197499bc3 Binary files /dev/null and b/test/pptx/slide-level-0-h1-with-table_moved_layouts.pptx differ diff --git a/test/pptx/slide-level-0-h1-with-table_templated.pptx b/test/pptx/slide-level-0-h1-with-table_templated.pptx new file mode 100644 index 000000000..87b45dda2 Binary files /dev/null and b/test/pptx/slide-level-0-h1-with-table_templated.pptx differ diff --git a/test/pptx/slide-level-0-h2-with-image.native b/test/pptx/slide-level-0-h2-with-image.native new file mode 100644 index 000000000..5def0cb92 --- /dev/null +++ b/test/pptx/slide-level-0-h2-with-image.native @@ -0,0 +1,2 @@ +[Header 2 ("hello",[],[]) [Str "Hello"] +,Para [Image ("",[],[]) [Str "An",Space,Str "image"] ("lalune.jpg","fig:")]] diff --git a/test/pptx/slide-level-0-h2-with-image.pptx b/test/pptx/slide-level-0-h2-with-image.pptx new file mode 100644 index 000000000..948659d6a Binary files /dev/null and b/test/pptx/slide-level-0-h2-with-image.pptx differ diff --git a/test/pptx/slide-level-0-h2-with-image_deleted_layouts.pptx b/test/pptx/slide-level-0-h2-with-image_deleted_layouts.pptx new file mode 100644 index 000000000..afc096ce6 Binary files /dev/null and b/test/pptx/slide-level-0-h2-with-image_deleted_layouts.pptx differ diff --git a/test/pptx/slide-level-0-h2-with-image_moved_layouts.pptx b/test/pptx/slide-level-0-h2-with-image_moved_layouts.pptx new file mode 100644 index 000000000..395036069 Binary files /dev/null and b/test/pptx/slide-level-0-h2-with-image_moved_layouts.pptx differ diff --git a/test/pptx/slide-level-0-h2-with-image_templated.pptx b/test/pptx/slide-level-0-h2-with-image_templated.pptx new file mode 100644 index 000000000..d306375e9 Binary files /dev/null and b/test/pptx/slide-level-0-h2-with-image_templated.pptx differ -- cgit v1.2.3 From 8dbea4909211ef7b2acc677288be7c5f10cbb40e Mon Sep 17 00:00:00 2001 From: Emily Bourke Date: Wed, 25 Aug 2021 14:35:19 +0100 Subject: pptx: Restructure tests MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit - Use dashes consistently rather than underscores - Make a folder for each set of tests - List test files explicitly (Cabal doesn’t support ** until version 2.4) --- pandoc.cabal | 55 +++++++++- test/Tests/Writers/Powerpoint.hs | 114 ++++++++++----------- test/pptx/code-custom.pptx | Bin 28184 -> 0 bytes test/pptx/code-custom/deleted-layouts.pptx | Bin 0 -> 31033 bytes test/pptx/code-custom/moved-layouts.pptx | Bin 0 -> 41822 bytes test/pptx/code-custom/output.pptx | Bin 0 -> 28184 bytes test/pptx/code-custom/templated.pptx | Bin 0 -> 41337 bytes test/pptx/code-custom_deleted_layouts.pptx | Bin 31033 -> 0 bytes test/pptx/code-custom_moved_layouts.pptx | Bin 41822 -> 0 bytes test/pptx/code-custom_templated.pptx | Bin 41337 -> 0 bytes test/pptx/code.native | 21 ---- test/pptx/code.pptx | Bin 28183 -> 0 bytes test/pptx/code/deleted-layouts.pptx | Bin 0 -> 31032 bytes test/pptx/code/input.native | 21 ++++ test/pptx/code/moved-layouts.pptx | Bin 0 -> 41826 bytes test/pptx/code/output.pptx | Bin 0 -> 28183 bytes test/pptx/code/templated.pptx | Bin 0 -> 41337 bytes test/pptx/code_deleted_layouts.pptx | Bin 31032 -> 0 bytes test/pptx/code_moved_layouts.pptx | Bin 41826 -> 0 bytes test/pptx/code_templated.pptx | Bin 41337 -> 0 bytes test/pptx/document-properties-short-desc.native | 2 - test/pptx/document-properties-short-desc.pptx | Bin 26967 -> 0 bytes .../deleted-layouts.pptx | Bin 0 -> 29806 bytes .../document-properties-short-desc/input.native | 2 + .../moved-layouts.pptx | Bin 0 -> 40600 bytes .../document-properties-short-desc/output.pptx | Bin 0 -> 26967 bytes .../document-properties-short-desc/templated.pptx | Bin 0 -> 40113 bytes ...ment-properties-short-desc_deleted_layouts.pptx | Bin 29806 -> 0 bytes ...cument-properties-short-desc_moved_layouts.pptx | Bin 40600 -> 0 bytes .../document-properties-short-desc_templated.pptx | Bin 40113 -> 0 bytes test/pptx/document-properties.native | 2 - test/pptx/document-properties.pptx | Bin 27375 -> 0 bytes test/pptx/document-properties/deleted-layouts.pptx | Bin 0 -> 30210 bytes test/pptx/document-properties/input.native | 2 + test/pptx/document-properties/moved-layouts.pptx | Bin 0 -> 41004 bytes test/pptx/document-properties/output.pptx | Bin 0 -> 27375 bytes test/pptx/document-properties/templated.pptx | Bin 0 -> 40517 bytes test/pptx/document-properties_deleted_layouts.pptx | Bin 30210 -> 0 bytes test/pptx/document-properties_moved_layouts.pptx | Bin 41004 -> 0 bytes test/pptx/document-properties_templated.pptx | Bin 40517 -> 0 bytes test/pptx/endnotes-toc/deleted-layouts.pptx | Bin 0 -> 30596 bytes test/pptx/endnotes-toc/moved-layouts.pptx | Bin 0 -> 41384 bytes test/pptx/endnotes-toc/output.pptx | Bin 0 -> 27747 bytes test/pptx/endnotes-toc/templated.pptx | Bin 0 -> 40899 bytes test/pptx/endnotes.native | 2 - test/pptx/endnotes.pptx | Bin 26928 -> 0 bytes test/pptx/endnotes/deleted-layouts.pptx | Bin 0 -> 29774 bytes test/pptx/endnotes/input.native | 2 + test/pptx/endnotes/moved-layouts.pptx | Bin 0 -> 40566 bytes test/pptx/endnotes/output.pptx | Bin 0 -> 26928 bytes test/pptx/endnotes/templated.pptx | Bin 0 -> 40078 bytes test/pptx/endnotes_deleted_layouts.pptx | Bin 29774 -> 0 bytes test/pptx/endnotes_moved_layouts.pptx | Bin 40566 -> 0 bytes test/pptx/endnotes_templated.pptx | Bin 40078 -> 0 bytes test/pptx/endnotes_toc.pptx | Bin 27747 -> 0 bytes test/pptx/endnotes_toc_deleted_layouts.pptx | Bin 30596 -> 0 bytes test/pptx/endnotes_toc_moved_layouts.pptx | Bin 41384 -> 0 bytes test/pptx/endnotes_toc_templated.pptx | Bin 40899 -> 0 bytes test/pptx/images.native | 5 - test/pptx/images.pptx | Bin 44596 -> 0 bytes test/pptx/images/deleted-layouts.pptx | Bin 0 -> 47437 bytes test/pptx/images/input.native | 5 + test/pptx/images/moved-layouts.pptx | Bin 0 -> 58160 bytes test/pptx/images/output.pptx | Bin 0 -> 44596 bytes test/pptx/images/templated.pptx | Bin 0 -> 57660 bytes test/pptx/images_deleted_layouts.pptx | Bin 47437 -> 0 bytes test/pptx/images_moved_layouts.pptx | Bin 58160 -> 0 bytes test/pptx/images_templated.pptx | Bin 57660 -> 0 bytes test/pptx/inline-formatting/deleted-layouts.pptx | Bin 0 -> 28966 bytes test/pptx/inline-formatting/input.native | 5 + test/pptx/inline-formatting/moved-layouts.pptx | Bin 0 -> 39758 bytes test/pptx/inline-formatting/output.pptx | Bin 0 -> 26121 bytes test/pptx/inline-formatting/templated.pptx | Bin 0 -> 39272 bytes test/pptx/inline_formatting.native | 5 - test/pptx/inline_formatting.pptx | Bin 26121 -> 0 bytes test/pptx/inline_formatting_deleted_layouts.pptx | Bin 28966 -> 0 bytes test/pptx/inline_formatting_moved_layouts.pptx | Bin 39758 -> 0 bytes test/pptx/inline_formatting_templated.pptx | Bin 39272 -> 0 bytes test/pptx/lists.native | 18 ---- test/pptx/lists.pptx | Bin 27015 -> 0 bytes test/pptx/lists/deleted-layouts.pptx | Bin 0 -> 29861 bytes test/pptx/lists/input.native | 18 ++++ test/pptx/lists/moved-layouts.pptx | Bin 0 -> 40653 bytes test/pptx/lists/output.pptx | Bin 0 -> 27015 bytes test/pptx/lists/templated.pptx | Bin 0 -> 40166 bytes test/pptx/lists_deleted_layouts.pptx | Bin 29861 -> 0 bytes test/pptx/lists_moved_layouts.pptx | Bin 40653 -> 0 bytes test/pptx/lists_templated.pptx | Bin 40166 -> 0 bytes test/pptx/raw-ooxml/deleted-layouts.pptx | Bin 0 -> 29754 bytes test/pptx/raw-ooxml/input.native | 3 + test/pptx/raw-ooxml/moved-layouts.pptx | Bin 0 -> 40546 bytes test/pptx/raw-ooxml/output.pptx | Bin 0 -> 26908 bytes test/pptx/raw-ooxml/templated.pptx | Bin 0 -> 40059 bytes test/pptx/raw_ooxml.native | 3 - test/pptx/raw_ooxml.pptx | Bin 26908 -> 0 bytes test/pptx/raw_ooxml_deleted_layouts.pptx | Bin 29754 -> 0 bytes test/pptx/raw_ooxml_moved_layouts.pptx | Bin 40546 -> 0 bytes test/pptx/raw_ooxml_templated.pptx | Bin 40059 -> 0 bytes test/pptx/reference-deleted-layouts.pptx | Bin 0 -> 18160 bytes test/pptx/reference-depth.pptx | Bin 0 -> 43743 bytes test/pptx/reference-moved-layouts.pptx | Bin 0 -> 44237 bytes test/pptx/reference_deleted_layouts.pptx | Bin 18160 -> 0 bytes test/pptx/reference_depth.pptx | Bin 43743 -> 0 bytes test/pptx/reference_moved_layouts.pptx | Bin 44237 -> 0 bytes test/pptx/remove-empty-slides/deleted-layouts.pptx | Bin 0 -> 46867 bytes test/pptx/remove-empty-slides/input.native | 5 + test/pptx/remove-empty-slides/moved-layouts.pptx | Bin 0 -> 57656 bytes test/pptx/remove-empty-slides/output.pptx | Bin 0 -> 44025 bytes test/pptx/remove-empty-slides/templated.pptx | Bin 0 -> 57172 bytes test/pptx/remove_empty_slides.native | 5 - test/pptx/remove_empty_slides.pptx | Bin 44025 -> 0 bytes test/pptx/remove_empty_slides_deleted_layouts.pptx | Bin 46867 -> 0 bytes test/pptx/remove_empty_slides_moved_layouts.pptx | Bin 57656 -> 0 bytes test/pptx/remove_empty_slides_templated.pptx | Bin 57172 -> 0 bytes .../deleted-layouts.pptx | Bin 0 -> 30554 bytes .../slide-breaks-slide-level-1/moved-layouts.pptx | Bin 0 -> 41343 bytes test/pptx/slide-breaks-slide-level-1/output.pptx | Bin 0 -> 27705 bytes .../pptx/slide-breaks-slide-level-1/templated.pptx | Bin 0 -> 40858 bytes test/pptx/slide-breaks-toc/deleted-layouts.pptx | Bin 0 -> 32328 bytes test/pptx/slide-breaks-toc/moved-layouts.pptx | Bin 0 -> 43118 bytes test/pptx/slide-breaks-toc/output.pptx | Bin 0 -> 29481 bytes test/pptx/slide-breaks-toc/templated.pptx | Bin 0 -> 42634 bytes test/pptx/slide-breaks/deleted-layouts.pptx | Bin 0 -> 31378 bytes test/pptx/slide-breaks/input.native | 7 ++ test/pptx/slide-breaks/moved-layouts.pptx | Bin 0 -> 42171 bytes test/pptx/slide-breaks/output.pptx | Bin 0 -> 28531 bytes test/pptx/slide-breaks/templated.pptx | Bin 0 -> 41683 bytes test/pptx/slide-level-0-h1-h2-with-table.native | 14 --- test/pptx/slide-level-0-h1-h2-with-table.pptx | Bin 26985 -> 0 bytes ...e-level-0-h1-h2-with-table_deleted_layouts.pptx | Bin 29828 -> 0 bytes ...ide-level-0-h1-h2-with-table_moved_layouts.pptx | Bin 40552 -> 0 bytes .../slide-level-0-h1-h2-with-table_templated.pptx | Bin 40052 -> 0 bytes test/pptx/slide-level-0-h1-with-image.native | 2 - test/pptx/slide-level-0-h1-with-image.pptx | Bin 42596 -> 0 bytes ...lide-level-0-h1-with-image_deleted_layouts.pptx | Bin 45433 -> 0 bytes .../slide-level-0-h1-with-image_moved_layouts.pptx | Bin 56156 -> 0 bytes .../slide-level-0-h1-with-image_templated.pptx | Bin 55657 -> 0 bytes test/pptx/slide-level-0-h1-with-table.native | 13 --- test/pptx/slide-level-0-h1-with-table.pptx | Bin 26166 -> 0 bytes ...lide-level-0-h1-with-table_deleted_layouts.pptx | Bin 29008 -> 0 bytes .../slide-level-0-h1-with-table_moved_layouts.pptx | Bin 39731 -> 0 bytes .../slide-level-0-h1-with-table_templated.pptx | Bin 39232 -> 0 bytes test/pptx/slide-level-0-h2-with-image.native | 2 - test/pptx/slide-level-0-h2-with-image.pptx | Bin 42596 -> 0 bytes ...lide-level-0-h2-with-image_deleted_layouts.pptx | Bin 45433 -> 0 bytes .../slide-level-0-h2-with-image_moved_layouts.pptx | Bin 56156 -> 0 bytes .../slide-level-0-h2-with-image_templated.pptx | Bin 55657 -> 0 bytes .../h1-h2-with-table/deleted-layouts.pptx | Bin 0 -> 29828 bytes .../slide-level-0/h1-h2-with-table/input.native | 14 +++ .../h1-h2-with-table/moved-layouts.pptx | Bin 0 -> 40552 bytes .../slide-level-0/h1-h2-with-table/output.pptx | Bin 0 -> 26985 bytes .../slide-level-0/h1-h2-with-table/templated.pptx | Bin 0 -> 40052 bytes .../h1-with-image/deleted-layouts.pptx | Bin 0 -> 45433 bytes test/pptx/slide-level-0/h1-with-image/input.native | 2 + .../slide-level-0/h1-with-image/moved-layouts.pptx | Bin 0 -> 56156 bytes test/pptx/slide-level-0/h1-with-image/output.pptx | Bin 0 -> 42596 bytes .../slide-level-0/h1-with-image/templated.pptx | Bin 0 -> 55657 bytes .../h1-with-table/deleted-layouts.pptx | Bin 0 -> 29008 bytes test/pptx/slide-level-0/h1-with-table/input.native | 13 +++ .../slide-level-0/h1-with-table/moved-layouts.pptx | Bin 0 -> 39731 bytes test/pptx/slide-level-0/h1-with-table/output.pptx | Bin 0 -> 26166 bytes .../slide-level-0/h1-with-table/templated.pptx | Bin 0 -> 39232 bytes .../h2-with-image/deleted-layouts.pptx | Bin 0 -> 45433 bytes test/pptx/slide-level-0/h2-with-image/input.native | 2 + .../slide-level-0/h2-with-image/moved-layouts.pptx | Bin 0 -> 56156 bytes test/pptx/slide-level-0/h2-with-image/output.pptx | Bin 0 -> 42596 bytes .../slide-level-0/h2-with-image/templated.pptx | Bin 0 -> 55657 bytes test/pptx/slide_breaks.native | 7 -- test/pptx/slide_breaks.pptx | Bin 28531 -> 0 bytes test/pptx/slide_breaks_deleted_layouts.pptx | Bin 31378 -> 0 bytes test/pptx/slide_breaks_moved_layouts.pptx | Bin 42171 -> 0 bytes test/pptx/slide_breaks_slide_level_1.pptx | Bin 27705 -> 0 bytes ...slide_breaks_slide_level_1_deleted_layouts.pptx | Bin 30554 -> 0 bytes .../slide_breaks_slide_level_1_moved_layouts.pptx | Bin 41343 -> 0 bytes .../pptx/slide_breaks_slide_level_1_templated.pptx | Bin 40858 -> 0 bytes test/pptx/slide_breaks_templated.pptx | Bin 41683 -> 0 bytes test/pptx/slide_breaks_toc.pptx | Bin 29481 -> 0 bytes test/pptx/slide_breaks_toc_deleted_layouts.pptx | Bin 32328 -> 0 bytes test/pptx/slide_breaks_toc_moved_layouts.pptx | Bin 43118 -> 0 bytes test/pptx/slide_breaks_toc_templated.pptx | Bin 42634 -> 0 bytes .../deleted-layouts.pptx | Bin 0 -> 34473 bytes .../pptx/speaker-notes-after-metadata/input.native | 5 + .../moved-layouts.pptx | Bin 0 -> 45269 bytes test/pptx/speaker-notes-after-metadata/output.pptx | Bin 0 -> 31636 bytes .../speaker-notes-after-metadata/templated.pptx | Bin 0 -> 44775 bytes .../speaker-notes-afterheader/deleted-layouts.pptx | Bin 0 -> 33500 bytes test/pptx/speaker-notes-afterheader/input.native | 3 + .../speaker-notes-afterheader/moved-layouts.pptx | Bin 0 -> 44297 bytes test/pptx/speaker-notes-afterheader/output.pptx | Bin 0 -> 30657 bytes test/pptx/speaker-notes-afterheader/templated.pptx | Bin 0 -> 43803 bytes .../speaker-notes-afterseps/deleted-layouts.pptx | Bin 0 -> 54396 bytes test/pptx/speaker-notes-afterseps/input.native | 63 ++++++++++++ .../speaker-notes-afterseps/moved-layouts.pptx | Bin 0 -> 65121 bytes test/pptx/speaker-notes-afterseps/output.pptx | Bin 0 -> 51557 bytes test/pptx/speaker-notes-afterseps/templated.pptx | Bin 0 -> 64619 bytes test/pptx/speaker-notes/deleted-layouts.pptx | Bin 0 -> 38203 bytes test/pptx/speaker-notes/input.native | 17 +++ test/pptx/speaker-notes/moved-layouts.pptx | Bin 0 -> 49002 bytes test/pptx/speaker-notes/output.pptx | Bin 0 -> 35360 bytes test/pptx/speaker-notes/templated.pptx | Bin 0 -> 48507 bytes test/pptx/speaker_notes.native | 17 --- test/pptx/speaker_notes.pptx | Bin 35360 -> 0 bytes test/pptx/speaker_notes_after_metadata.native | 5 - test/pptx/speaker_notes_after_metadata.pptx | Bin 31636 -> 0 bytes ...eaker_notes_after_metadata_deleted_layouts.pptx | Bin 34473 -> 0 bytes ...speaker_notes_after_metadata_moved_layouts.pptx | Bin 45269 -> 0 bytes .../speaker_notes_after_metadata_templated.pptx | Bin 44775 -> 0 bytes test/pptx/speaker_notes_afterheader.native | 3 - test/pptx/speaker_notes_afterheader.pptx | Bin 30657 -> 0 bytes .../speaker_notes_afterheader_deleted_layouts.pptx | Bin 33500 -> 0 bytes .../speaker_notes_afterheader_moved_layouts.pptx | Bin 44297 -> 0 bytes test/pptx/speaker_notes_afterheader_templated.pptx | Bin 43803 -> 0 bytes test/pptx/speaker_notes_afterseps.native | 63 ------------ test/pptx/speaker_notes_afterseps.pptx | Bin 51557 -> 0 bytes .../speaker_notes_afterseps_deleted_layouts.pptx | Bin 54396 -> 0 bytes .../speaker_notes_afterseps_moved_layouts.pptx | Bin 65121 -> 0 bytes test/pptx/speaker_notes_afterseps_templated.pptx | Bin 64619 -> 0 bytes test/pptx/speaker_notes_deleted_layouts.pptx | Bin 38203 -> 0 bytes test/pptx/speaker_notes_moved_layouts.pptx | Bin 49002 -> 0 bytes test/pptx/speaker_notes_templated.pptx | Bin 48507 -> 0 bytes test/pptx/start-numbering-at/deleted-layouts.pptx | Bin 0 -> 29837 bytes test/pptx/start-numbering-at/input.native | 9 ++ test/pptx/start-numbering-at/moved-layouts.pptx | Bin 0 -> 40630 bytes test/pptx/start-numbering-at/output.pptx | Bin 0 -> 26991 bytes test/pptx/start-numbering-at/templated.pptx | Bin 0 -> 40142 bytes test/pptx/start_numbering_at.native | 9 -- test/pptx/start_numbering_at.pptx | Bin 26991 -> 0 bytes test/pptx/start_numbering_at_deleted_layouts.pptx | Bin 29837 -> 0 bytes test/pptx/start_numbering_at_moved_layouts.pptx | Bin 40630 -> 0 bytes test/pptx/start_numbering_at_templated.pptx | Bin 40142 -> 0 bytes test/pptx/tables.native | 95 ----------------- test/pptx/tables.pptx | Bin 27532 -> 0 bytes test/pptx/tables/deleted-layouts.pptx | Bin 0 -> 30381 bytes test/pptx/tables/input.native | 95 +++++++++++++++++ test/pptx/tables/moved-layouts.pptx | Bin 0 -> 41174 bytes test/pptx/tables/output.pptx | Bin 0 -> 27532 bytes test/pptx/tables/templated.pptx | Bin 0 -> 40686 bytes test/pptx/tables_deleted_layouts.pptx | Bin 30381 -> 0 bytes test/pptx/tables_moved_layouts.pptx | Bin 41174 -> 0 bytes test/pptx/tables_templated.pptx | Bin 40686 -> 0 bytes test/pptx/two-column/deleted-layouts.pptx | Bin 0 -> 28883 bytes test/pptx/two-column/input.native | 9 ++ test/pptx/two-column/moved-layouts.pptx | Bin 0 -> 39676 bytes test/pptx/two-column/output.pptx | Bin 0 -> 26038 bytes test/pptx/two-column/templated.pptx | Bin 0 -> 39189 bytes test/pptx/two_column.native | 9 -- test/pptx/two_column.pptx | Bin 26038 -> 0 bytes test/pptx/two_column_deleted_layouts.pptx | Bin 28883 -> 0 bytes test/pptx/two_column_moved_layouts.pptx | Bin 39676 -> 0 bytes test/pptx/two_column_templated.pptx | Bin 39189 -> 0 bytes 250 files changed, 413 insertions(+), 360 deletions(-) delete mode 100644 test/pptx/code-custom.pptx create mode 100644 test/pptx/code-custom/deleted-layouts.pptx create mode 100644 test/pptx/code-custom/moved-layouts.pptx create mode 100644 test/pptx/code-custom/output.pptx create mode 100644 test/pptx/code-custom/templated.pptx delete mode 100644 test/pptx/code-custom_deleted_layouts.pptx delete mode 100644 test/pptx/code-custom_moved_layouts.pptx delete mode 100644 test/pptx/code-custom_templated.pptx delete mode 100644 test/pptx/code.native delete mode 100644 test/pptx/code.pptx create mode 100644 test/pptx/code/deleted-layouts.pptx create mode 100644 test/pptx/code/input.native create mode 100644 test/pptx/code/moved-layouts.pptx create mode 100644 test/pptx/code/output.pptx create mode 100644 test/pptx/code/templated.pptx delete mode 100644 test/pptx/code_deleted_layouts.pptx delete mode 100644 test/pptx/code_moved_layouts.pptx delete mode 100644 test/pptx/code_templated.pptx delete mode 100644 test/pptx/document-properties-short-desc.native delete mode 100644 test/pptx/document-properties-short-desc.pptx create mode 100644 test/pptx/document-properties-short-desc/deleted-layouts.pptx create mode 100644 test/pptx/document-properties-short-desc/input.native create mode 100644 test/pptx/document-properties-short-desc/moved-layouts.pptx create mode 100644 test/pptx/document-properties-short-desc/output.pptx create mode 100644 test/pptx/document-properties-short-desc/templated.pptx delete mode 100644 test/pptx/document-properties-short-desc_deleted_layouts.pptx delete mode 100644 test/pptx/document-properties-short-desc_moved_layouts.pptx delete mode 100644 test/pptx/document-properties-short-desc_templated.pptx delete mode 100644 test/pptx/document-properties.native delete mode 100644 test/pptx/document-properties.pptx create mode 100644 test/pptx/document-properties/deleted-layouts.pptx create mode 100644 test/pptx/document-properties/input.native create mode 100644 test/pptx/document-properties/moved-layouts.pptx create mode 100644 test/pptx/document-properties/output.pptx create mode 100644 test/pptx/document-properties/templated.pptx delete mode 100644 test/pptx/document-properties_deleted_layouts.pptx delete mode 100644 test/pptx/document-properties_moved_layouts.pptx delete mode 100644 test/pptx/document-properties_templated.pptx create mode 100644 test/pptx/endnotes-toc/deleted-layouts.pptx create mode 100644 test/pptx/endnotes-toc/moved-layouts.pptx create mode 100644 test/pptx/endnotes-toc/output.pptx create mode 100644 test/pptx/endnotes-toc/templated.pptx delete mode 100644 test/pptx/endnotes.native delete mode 100644 test/pptx/endnotes.pptx create mode 100644 test/pptx/endnotes/deleted-layouts.pptx create mode 100644 test/pptx/endnotes/input.native create mode 100644 test/pptx/endnotes/moved-layouts.pptx create mode 100644 test/pptx/endnotes/output.pptx create mode 100644 test/pptx/endnotes/templated.pptx delete mode 100644 test/pptx/endnotes_deleted_layouts.pptx delete mode 100644 test/pptx/endnotes_moved_layouts.pptx delete mode 100644 test/pptx/endnotes_templated.pptx delete mode 100644 test/pptx/endnotes_toc.pptx delete mode 100644 test/pptx/endnotes_toc_deleted_layouts.pptx delete mode 100644 test/pptx/endnotes_toc_moved_layouts.pptx delete mode 100644 test/pptx/endnotes_toc_templated.pptx delete mode 100644 test/pptx/images.native delete mode 100644 test/pptx/images.pptx create mode 100644 test/pptx/images/deleted-layouts.pptx create mode 100644 test/pptx/images/input.native create mode 100644 test/pptx/images/moved-layouts.pptx create mode 100644 test/pptx/images/output.pptx create mode 100644 test/pptx/images/templated.pptx delete mode 100644 test/pptx/images_deleted_layouts.pptx delete mode 100644 test/pptx/images_moved_layouts.pptx delete mode 100644 test/pptx/images_templated.pptx create mode 100644 test/pptx/inline-formatting/deleted-layouts.pptx create mode 100644 test/pptx/inline-formatting/input.native create mode 100644 test/pptx/inline-formatting/moved-layouts.pptx create mode 100644 test/pptx/inline-formatting/output.pptx create mode 100644 test/pptx/inline-formatting/templated.pptx delete mode 100644 test/pptx/inline_formatting.native delete mode 100644 test/pptx/inline_formatting.pptx delete mode 100644 test/pptx/inline_formatting_deleted_layouts.pptx delete mode 100644 test/pptx/inline_formatting_moved_layouts.pptx delete mode 100644 test/pptx/inline_formatting_templated.pptx delete mode 100644 test/pptx/lists.native delete mode 100644 test/pptx/lists.pptx create mode 100644 test/pptx/lists/deleted-layouts.pptx create mode 100644 test/pptx/lists/input.native create mode 100644 test/pptx/lists/moved-layouts.pptx create mode 100644 test/pptx/lists/output.pptx create mode 100644 test/pptx/lists/templated.pptx delete mode 100644 test/pptx/lists_deleted_layouts.pptx delete mode 100644 test/pptx/lists_moved_layouts.pptx delete mode 100644 test/pptx/lists_templated.pptx create mode 100644 test/pptx/raw-ooxml/deleted-layouts.pptx create mode 100644 test/pptx/raw-ooxml/input.native create mode 100644 test/pptx/raw-ooxml/moved-layouts.pptx create mode 100644 test/pptx/raw-ooxml/output.pptx create mode 100644 test/pptx/raw-ooxml/templated.pptx delete mode 100644 test/pptx/raw_ooxml.native delete mode 100644 test/pptx/raw_ooxml.pptx delete mode 100644 test/pptx/raw_ooxml_deleted_layouts.pptx delete mode 100644 test/pptx/raw_ooxml_moved_layouts.pptx delete mode 100644 test/pptx/raw_ooxml_templated.pptx create mode 100644 test/pptx/reference-deleted-layouts.pptx create mode 100644 test/pptx/reference-depth.pptx create mode 100644 test/pptx/reference-moved-layouts.pptx delete mode 100644 test/pptx/reference_deleted_layouts.pptx delete mode 100644 test/pptx/reference_depth.pptx delete mode 100644 test/pptx/reference_moved_layouts.pptx create mode 100644 test/pptx/remove-empty-slides/deleted-layouts.pptx create mode 100644 test/pptx/remove-empty-slides/input.native create mode 100644 test/pptx/remove-empty-slides/moved-layouts.pptx create mode 100644 test/pptx/remove-empty-slides/output.pptx create mode 100644 test/pptx/remove-empty-slides/templated.pptx delete mode 100644 test/pptx/remove_empty_slides.native delete mode 100644 test/pptx/remove_empty_slides.pptx delete mode 100644 test/pptx/remove_empty_slides_deleted_layouts.pptx delete mode 100644 test/pptx/remove_empty_slides_moved_layouts.pptx delete mode 100644 test/pptx/remove_empty_slides_templated.pptx create mode 100644 test/pptx/slide-breaks-slide-level-1/deleted-layouts.pptx create mode 100644 test/pptx/slide-breaks-slide-level-1/moved-layouts.pptx create mode 100644 test/pptx/slide-breaks-slide-level-1/output.pptx create mode 100644 test/pptx/slide-breaks-slide-level-1/templated.pptx create mode 100644 test/pptx/slide-breaks-toc/deleted-layouts.pptx create mode 100644 test/pptx/slide-breaks-toc/moved-layouts.pptx create mode 100644 test/pptx/slide-breaks-toc/output.pptx create mode 100644 test/pptx/slide-breaks-toc/templated.pptx create mode 100644 test/pptx/slide-breaks/deleted-layouts.pptx create mode 100644 test/pptx/slide-breaks/input.native create mode 100644 test/pptx/slide-breaks/moved-layouts.pptx create mode 100644 test/pptx/slide-breaks/output.pptx create mode 100644 test/pptx/slide-breaks/templated.pptx delete mode 100644 test/pptx/slide-level-0-h1-h2-with-table.native delete mode 100644 test/pptx/slide-level-0-h1-h2-with-table.pptx delete mode 100644 test/pptx/slide-level-0-h1-h2-with-table_deleted_layouts.pptx delete mode 100644 test/pptx/slide-level-0-h1-h2-with-table_moved_layouts.pptx delete mode 100644 test/pptx/slide-level-0-h1-h2-with-table_templated.pptx delete mode 100644 test/pptx/slide-level-0-h1-with-image.native delete mode 100644 test/pptx/slide-level-0-h1-with-image.pptx delete mode 100644 test/pptx/slide-level-0-h1-with-image_deleted_layouts.pptx delete mode 100644 test/pptx/slide-level-0-h1-with-image_moved_layouts.pptx delete mode 100644 test/pptx/slide-level-0-h1-with-image_templated.pptx delete mode 100644 test/pptx/slide-level-0-h1-with-table.native delete mode 100644 test/pptx/slide-level-0-h1-with-table.pptx delete mode 100644 test/pptx/slide-level-0-h1-with-table_deleted_layouts.pptx delete mode 100644 test/pptx/slide-level-0-h1-with-table_moved_layouts.pptx delete mode 100644 test/pptx/slide-level-0-h1-with-table_templated.pptx delete mode 100644 test/pptx/slide-level-0-h2-with-image.native delete mode 100644 test/pptx/slide-level-0-h2-with-image.pptx delete mode 100644 test/pptx/slide-level-0-h2-with-image_deleted_layouts.pptx delete mode 100644 test/pptx/slide-level-0-h2-with-image_moved_layouts.pptx delete mode 100644 test/pptx/slide-level-0-h2-with-image_templated.pptx create mode 100644 test/pptx/slide-level-0/h1-h2-with-table/deleted-layouts.pptx create mode 100644 test/pptx/slide-level-0/h1-h2-with-table/input.native create mode 100644 test/pptx/slide-level-0/h1-h2-with-table/moved-layouts.pptx create mode 100644 test/pptx/slide-level-0/h1-h2-with-table/output.pptx create mode 100644 test/pptx/slide-level-0/h1-h2-with-table/templated.pptx create mode 100644 test/pptx/slide-level-0/h1-with-image/deleted-layouts.pptx create mode 100644 test/pptx/slide-level-0/h1-with-image/input.native create mode 100644 test/pptx/slide-level-0/h1-with-image/moved-layouts.pptx create mode 100644 test/pptx/slide-level-0/h1-with-image/output.pptx create mode 100644 test/pptx/slide-level-0/h1-with-image/templated.pptx create mode 100644 test/pptx/slide-level-0/h1-with-table/deleted-layouts.pptx create mode 100644 test/pptx/slide-level-0/h1-with-table/input.native create mode 100644 test/pptx/slide-level-0/h1-with-table/moved-layouts.pptx create mode 100644 test/pptx/slide-level-0/h1-with-table/output.pptx create mode 100644 test/pptx/slide-level-0/h1-with-table/templated.pptx create mode 100644 test/pptx/slide-level-0/h2-with-image/deleted-layouts.pptx create mode 100644 test/pptx/slide-level-0/h2-with-image/input.native create mode 100644 test/pptx/slide-level-0/h2-with-image/moved-layouts.pptx create mode 100644 test/pptx/slide-level-0/h2-with-image/output.pptx create mode 100644 test/pptx/slide-level-0/h2-with-image/templated.pptx delete mode 100644 test/pptx/slide_breaks.native delete mode 100644 test/pptx/slide_breaks.pptx delete mode 100644 test/pptx/slide_breaks_deleted_layouts.pptx delete mode 100644 test/pptx/slide_breaks_moved_layouts.pptx delete mode 100644 test/pptx/slide_breaks_slide_level_1.pptx delete mode 100644 test/pptx/slide_breaks_slide_level_1_deleted_layouts.pptx delete mode 100644 test/pptx/slide_breaks_slide_level_1_moved_layouts.pptx delete mode 100644 test/pptx/slide_breaks_slide_level_1_templated.pptx delete mode 100644 test/pptx/slide_breaks_templated.pptx delete mode 100644 test/pptx/slide_breaks_toc.pptx delete mode 100644 test/pptx/slide_breaks_toc_deleted_layouts.pptx delete mode 100644 test/pptx/slide_breaks_toc_moved_layouts.pptx delete mode 100644 test/pptx/slide_breaks_toc_templated.pptx create mode 100644 test/pptx/speaker-notes-after-metadata/deleted-layouts.pptx create mode 100644 test/pptx/speaker-notes-after-metadata/input.native create mode 100644 test/pptx/speaker-notes-after-metadata/moved-layouts.pptx create mode 100644 test/pptx/speaker-notes-after-metadata/output.pptx create mode 100644 test/pptx/speaker-notes-after-metadata/templated.pptx create mode 100644 test/pptx/speaker-notes-afterheader/deleted-layouts.pptx create mode 100644 test/pptx/speaker-notes-afterheader/input.native create mode 100644 test/pptx/speaker-notes-afterheader/moved-layouts.pptx create mode 100644 test/pptx/speaker-notes-afterheader/output.pptx create mode 100644 test/pptx/speaker-notes-afterheader/templated.pptx create mode 100644 test/pptx/speaker-notes-afterseps/deleted-layouts.pptx create mode 100644 test/pptx/speaker-notes-afterseps/input.native create mode 100644 test/pptx/speaker-notes-afterseps/moved-layouts.pptx create mode 100644 test/pptx/speaker-notes-afterseps/output.pptx create mode 100644 test/pptx/speaker-notes-afterseps/templated.pptx create mode 100644 test/pptx/speaker-notes/deleted-layouts.pptx create mode 100644 test/pptx/speaker-notes/input.native create mode 100644 test/pptx/speaker-notes/moved-layouts.pptx create mode 100644 test/pptx/speaker-notes/output.pptx create mode 100644 test/pptx/speaker-notes/templated.pptx delete mode 100644 test/pptx/speaker_notes.native delete mode 100644 test/pptx/speaker_notes.pptx delete mode 100644 test/pptx/speaker_notes_after_metadata.native delete mode 100644 test/pptx/speaker_notes_after_metadata.pptx delete mode 100644 test/pptx/speaker_notes_after_metadata_deleted_layouts.pptx delete mode 100644 test/pptx/speaker_notes_after_metadata_moved_layouts.pptx delete mode 100644 test/pptx/speaker_notes_after_metadata_templated.pptx delete mode 100644 test/pptx/speaker_notes_afterheader.native delete mode 100644 test/pptx/speaker_notes_afterheader.pptx delete mode 100644 test/pptx/speaker_notes_afterheader_deleted_layouts.pptx delete mode 100644 test/pptx/speaker_notes_afterheader_moved_layouts.pptx delete mode 100644 test/pptx/speaker_notes_afterheader_templated.pptx delete mode 100644 test/pptx/speaker_notes_afterseps.native delete mode 100644 test/pptx/speaker_notes_afterseps.pptx delete mode 100644 test/pptx/speaker_notes_afterseps_deleted_layouts.pptx delete mode 100644 test/pptx/speaker_notes_afterseps_moved_layouts.pptx delete mode 100644 test/pptx/speaker_notes_afterseps_templated.pptx delete mode 100644 test/pptx/speaker_notes_deleted_layouts.pptx delete mode 100644 test/pptx/speaker_notes_moved_layouts.pptx delete mode 100644 test/pptx/speaker_notes_templated.pptx create mode 100644 test/pptx/start-numbering-at/deleted-layouts.pptx create mode 100644 test/pptx/start-numbering-at/input.native create mode 100644 test/pptx/start-numbering-at/moved-layouts.pptx create mode 100644 test/pptx/start-numbering-at/output.pptx create mode 100644 test/pptx/start-numbering-at/templated.pptx delete mode 100644 test/pptx/start_numbering_at.native delete mode 100644 test/pptx/start_numbering_at.pptx delete mode 100644 test/pptx/start_numbering_at_deleted_layouts.pptx delete mode 100644 test/pptx/start_numbering_at_moved_layouts.pptx delete mode 100644 test/pptx/start_numbering_at_templated.pptx delete mode 100644 test/pptx/tables.native delete mode 100644 test/pptx/tables.pptx create mode 100644 test/pptx/tables/deleted-layouts.pptx create mode 100644 test/pptx/tables/input.native create mode 100644 test/pptx/tables/moved-layouts.pptx create mode 100644 test/pptx/tables/output.pptx create mode 100644 test/pptx/tables/templated.pptx delete mode 100644 test/pptx/tables_deleted_layouts.pptx delete mode 100644 test/pptx/tables_moved_layouts.pptx delete mode 100644 test/pptx/tables_templated.pptx create mode 100644 test/pptx/two-column/deleted-layouts.pptx create mode 100644 test/pptx/two-column/input.native create mode 100644 test/pptx/two-column/moved-layouts.pptx create mode 100644 test/pptx/two-column/output.pptx create mode 100644 test/pptx/two-column/templated.pptx delete mode 100644 test/pptx/two_column.native delete mode 100644 test/pptx/two_column.pptx delete mode 100644 test/pptx/two_column_deleted_layouts.pptx delete mode 100644 test/pptx/two_column_moved_layouts.pptx delete mode 100644 test/pptx/two_column_templated.pptx (limited to 'test/Tests/Writers') diff --git a/pandoc.cabal b/pandoc.cabal index da53cb1cd..7fb951488 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -380,7 +380,60 @@ extra-source-files: test/rtf/*.native test/rtf/*.rtf test/pptx/*.pptx - test/pptx/*.native + test/pptx/code-custom/*.pptx + test/pptx/code/input.native + test/pptx/code/*.pptx + test/pptx/comparison-both-columns/input.native + test/pptx/comparison-both-columns/*.pptx + test/pptx/comparison-extra-text/input.native + test/pptx/comparison-extra-text/*.pptx + test/pptx/comparison-non-text-first/input.native + test/pptx/comparison-non-text-first/*.pptx + test/pptx/comparison-one-column/input.native + test/pptx/comparison-one-column/*.pptx + test/pptx/document-properties-short-desc/input.native + test/pptx/document-properties-short-desc/*.pptx + test/pptx/document-properties/input.native + test/pptx/document-properties/*.pptx + test/pptx/endnotes-toc/*.pptx + test/pptx/endnotes/input.native + test/pptx/endnotes/*.pptx + test/pptx/images/input.native + test/pptx/images/*.pptx + test/pptx/inline-formatting/input.native + test/pptx/inline-formatting/*.pptx + test/pptx/lists/input.native + test/pptx/lists/*.pptx + test/pptx/raw-ooxml/input.native + test/pptx/raw-ooxml/*.pptx + test/pptx/remove-empty-slides/input.native + test/pptx/remove-empty-slides/*.pptx + test/pptx/slide-breaks-slide-level-1/*.pptx + test/pptx/slide-breaks-toc/*.pptx + test/pptx/slide-breaks/input.native + test/pptx/slide-breaks/*.pptx + test/pptx/slide-level-0/h1-h2-with-table/input.native + test/pptx/slide-level-0/h1-h2-with-table/*.pptx + test/pptx/slide-level-0/h1-with-image/input.native + test/pptx/slide-level-0/h1-with-image/*.pptx + test/pptx/slide-level-0/h1-with-table/input.native + test/pptx/slide-level-0/h1-with-table/*.pptx + test/pptx/slide-level-0/h2-with-image/input.native + test/pptx/slide-level-0/h2-with-image/*.pptx + test/pptx/speaker-notes-after-metadata/input.native + test/pptx/speaker-notes-after-metadata/*.pptx + test/pptx/speaker-notes-afterheader/input.native + test/pptx/speaker-notes-afterheader/*.pptx + test/pptx/speaker-notes-afterseps/input.native + test/pptx/speaker-notes-afterseps/*.pptx + test/pptx/speaker-notes/input.native + test/pptx/speaker-notes/*.pptx + test/pptx/start-numbering-at/input.native + test/pptx/start-numbering-at/*.pptx + test/pptx/tables/input.native + test/pptx/tables/*.pptx + test/pptx/two-column/input.native + test/pptx/two-column/*.pptx test/ipynb/*.in.native test/ipynb/*.out.native test/ipynb/*.ipynb diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs index fd6d01d2d..fd9871659 100644 --- a/test/Tests/Writers/Powerpoint.hs +++ b/test/Tests/Writers/Powerpoint.hs @@ -15,13 +15,13 @@ import Data.List (unzip4) modifyPptxName :: FilePath -> String -> FilePath modifyPptxName fp suffix = - addExtension (dropExtension fp ++ suffix) "pptx" + addExtension (takeDirectory fp ++ suffix) "pptx" pptxTests :: String -> WriterOptions -> FilePath -> FilePath -> (TestTree, TestTree, TestTree, TestTree) pptxTests name opts native pptx = - let referenceDoc = "pptx/reference_depth.pptx" - movedLayoutsReferenceDoc = "pptx/reference_moved_layouts.pptx" - deletedLayoutsReferenceDoc = "pptx/reference_deleted_layouts.pptx" + let referenceDoc = "pptx/reference-depth.pptx" + movedLayoutsReferenceDoc = "pptx/reference-moved-layouts.pptx" + deletedLayoutsReferenceDoc = "pptx/reference-deleted-layouts.pptx" in ( ooxmlTest writePowerpoint @@ -34,19 +34,19 @@ pptxTests name opts native pptx = name opts{writerReferenceDoc=Just referenceDoc} native - (modifyPptxName pptx "_templated") + (modifyPptxName pptx "/templated") , ooxmlTest writePowerpoint name opts{writerReferenceDoc=Just movedLayoutsReferenceDoc} native - (modifyPptxName pptx "_moved_layouts") + (modifyPptxName pptx "/moved-layouts") , ooxmlTest writePowerpoint name opts{writerReferenceDoc=Just deletedLayoutsReferenceDoc} native - (modifyPptxName pptx "_deleted_layouts") + (modifyPptxName pptx "/deleted-layouts") ) groupPptxTests :: [(TestTree, TestTree, TestTree, TestTree)] -> [TestTree] @@ -63,112 +63,112 @@ groupPptxTests pairs = tests :: [TestTree] tests = groupPptxTests [ pptxTests "Inline formatting" def - "pptx/inline_formatting.native" - "pptx/inline_formatting.pptx" + "pptx/inline-formatting/input.native" + "pptx/inline-formatting/output.pptx" , pptxTests "Slide breaks (default slide-level)" def - "pptx/slide_breaks.native" - "pptx/slide_breaks.pptx" + "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.native" - "pptx/slide_breaks_slide_level_1.pptx" + "pptx/slide-breaks/input.native" + "pptx/slide-breaks-slide-level-1/output.pptx" , pptxTests "lists" def - "pptx/lists.native" - "pptx/lists.pptx" + "pptx/lists/input.native" + "pptx/lists/output.pptx" , pptxTests "start ordered list at specified num" def - "pptx/start_numbering_at.native" - "pptx/start_numbering_at.pptx" + "pptx/start-numbering-at/input.native" + "pptx/start-numbering-at/output.pptx" , pptxTests "tables" def - "pptx/tables.native" - "pptx/tables.pptx" + "pptx/tables/input.native" + "pptx/tables/output.pptx" , pptxTests "table of contents" def{ writerTableOfContents = True } - "pptx/slide_breaks.native" - "pptx/slide_breaks_toc.pptx" + "pptx/slide-breaks/input.native" + "pptx/slide-breaks-toc/output.pptx" , pptxTests "end notes" def - "pptx/endnotes.native" - "pptx/endnotes.pptx" + "pptx/endnotes/input.native" + "pptx/endnotes/output.pptx" , pptxTests "end notes, with table of contents" def { writerTableOfContents = True } - "pptx/endnotes.native" - "pptx/endnotes_toc.pptx" + "pptx/endnotes/input.native" + "pptx/endnotes-toc/output.pptx" , pptxTests "images" def - "pptx/images.native" - "pptx/images.pptx" + "pptx/images/input.native" + "pptx/images/output.pptx" , pptxTests "two-column layout" def - "pptx/two_column.native" - "pptx/two_column.pptx" + "pptx/two-column/input.native" + "pptx/two-column/output.pptx" , pptxTests "speaker notes" def - "pptx/speaker_notes.native" - "pptx/speaker_notes.pptx" + "pptx/speaker-notes/input.native" + "pptx/speaker-notes/output.pptx" , pptxTests "speaker notes after a separating block" def - "pptx/speaker_notes_afterseps.native" - "pptx/speaker_notes_afterseps.pptx" + "pptx/speaker-notes-afterseps/input.native" + "pptx/speaker-notes-afterseps/output.pptx" , pptxTests "speaker notes after a separating header" def - "pptx/speaker_notes_afterheader.native" - "pptx/speaker_notes_afterheader.pptx" + "pptx/speaker-notes-afterheader/input.native" + "pptx/speaker-notes-afterheader/output.pptx" , pptxTests "speaker notes after metadata" def - "pptx/speaker_notes_after_metadata.native" - "pptx/speaker_notes_after_metadata.pptx" + "pptx/speaker-notes-after-metadata/input.native" + "pptx/speaker-notes-after-metadata/output.pptx" , pptxTests "remove empty slides" def - "pptx/remove_empty_slides.native" - "pptx/remove_empty_slides.pptx" + "pptx/remove-empty-slides/input.native" + "pptx/remove-empty-slides/output.pptx" , pptxTests "raw ooxml" def - "pptx/raw_ooxml.native" - "pptx/raw_ooxml.pptx" + "pptx/raw-ooxml/input.native" + "pptx/raw-ooxml/output.pptx" , pptxTests "metadata, custom properties" def - "pptx/document-properties.native" - "pptx/document-properties.pptx" + "pptx/document-properties/input.native" + "pptx/document-properties/output.pptx" , pptxTests "metadata, short description" def - "pptx/document-properties-short-desc.native" - "pptx/document-properties-short-desc.pptx" + "pptx/document-properties-short-desc/input.native" + "pptx/document-properties-short-desc/output.pptx" , pptxTests "inline code and code blocks" def - "pptx/code.native" - "pptx/code.pptx" + "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.native" - "pptx/code-custom.pptx" + "pptx/code/input.native" + "pptx/code-custom/output.pptx" , pptxTests ("Using slide level 0, if the first thing on " <> "a slide is a h1 it's used as the " <> "slide title") def { writerSlideLevel = Just 0 } - "pptx/slide-level-0-h1-with-image.native" - "pptx/slide-level-0-h1-with-image.pptx" + "pptx/slide-level-0/h1-with-image/input.native" + "pptx/slide-level-0/h1-with-image/output.pptx" , pptxTests ("Using slide level 0, if the first thing on " <> "a slide is a h2 it's used as the " <> "slide title") def { writerSlideLevel = Just 0 } - "pptx/slide-level-0-h2-with-image.native" - "pptx/slide-level-0-h2-with-image.pptx" + "pptx/slide-level-0/h2-with-image/input.native" + "pptx/slide-level-0/h2-with-image/output.pptx" , pptxTests ("Using slide level 0, if the first thing on " <> "a slide is a heading it's used as the " <> "slide title (works with a table)") def { writerSlideLevel = Just 0 } - "pptx/slide-level-0-h1-with-table.native" - "pptx/slide-level-0-h1-with-table.pptx" + "pptx/slide-level-0/h1-with-table/input.native" + "pptx/slide-level-0/h1-with-table/output.pptx" , pptxTests ("Using slide level 0, if the first thing on " <> "a slide is a heading it's used as the " <> "slide title (two headings forces a " <> "slide break though)") def { writerSlideLevel = Just 0 } - "pptx/slide-level-0-h1-h2-with-table.native" - "pptx/slide-level-0-h1-h2-with-table.pptx" + "pptx/slide-level-0/h1-h2-with-table/input.native" + "pptx/slide-level-0/h1-h2-with-table/output.pptx" ] diff --git a/test/pptx/code-custom.pptx b/test/pptx/code-custom.pptx deleted file mode 100644 index 5e9c2c630..000000000 Binary files a/test/pptx/code-custom.pptx and /dev/null differ diff --git a/test/pptx/code-custom/deleted-layouts.pptx b/test/pptx/code-custom/deleted-layouts.pptx new file mode 100644 index 000000000..9282e6354 Binary files /dev/null and b/test/pptx/code-custom/deleted-layouts.pptx differ diff --git a/test/pptx/code-custom/moved-layouts.pptx b/test/pptx/code-custom/moved-layouts.pptx new file mode 100644 index 000000000..a14eeb6c8 Binary files /dev/null and b/test/pptx/code-custom/moved-layouts.pptx differ diff --git a/test/pptx/code-custom/output.pptx b/test/pptx/code-custom/output.pptx new file mode 100644 index 000000000..5e9c2c630 Binary files /dev/null and b/test/pptx/code-custom/output.pptx differ diff --git a/test/pptx/code-custom/templated.pptx b/test/pptx/code-custom/templated.pptx new file mode 100644 index 000000000..0e640f373 Binary files /dev/null and b/test/pptx/code-custom/templated.pptx differ diff --git a/test/pptx/code-custom_deleted_layouts.pptx b/test/pptx/code-custom_deleted_layouts.pptx deleted file mode 100644 index 9282e6354..000000000 Binary files a/test/pptx/code-custom_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/code-custom_moved_layouts.pptx b/test/pptx/code-custom_moved_layouts.pptx deleted file mode 100644 index a14eeb6c8..000000000 Binary files a/test/pptx/code-custom_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/code-custom_templated.pptx b/test/pptx/code-custom_templated.pptx deleted file mode 100644 index 0e640f373..000000000 Binary files a/test/pptx/code-custom_templated.pptx and /dev/null differ diff --git a/test/pptx/code.native b/test/pptx/code.native deleted file mode 100644 index be7f512f7..000000000 --- a/test/pptx/code.native +++ /dev/null @@ -1,21 +0,0 @@ -[Header 1 ("header-with-inline-code",[],[]) [Str "Header",Space,Str "with",Space,Code ("",[],[]) "inline code"] -,CodeBlock ("",[],[]) "Code at level 0" -,BulletList - [[Para [Str "Bullet",Space,Str "item",Space,Str "with",Space,Code ("",[],[]) "inline code"] - ,CodeBlock ("",[],[]) "Code block at level 1" - ,BulletList - [[Para [Str "with",Space,Code ("",[],[]) "nested"] - ,CodeBlock ("",[],[]) "lvl2\nlvl2\nlvl2" - ,Header 2 ("second-heading-level-with-code",[],[]) [Str "Second",Space,Str "heading",Space,Str "level",Space,Str "with",Space,Code ("",[],[]) "code"]]]]] -,Header 1 ("syntax-highlighting",[],[]) [Str "Syntax",Space,Str "highlighting"] -,CodeBlock ("",["haskell"],[]) "id :: a -> a\nid x = x" -,BulletList - [[Para [Str "Nested"] - ,CodeBlock ("",["haskell"],[]) "g :: Int -> Int\ng x = x * 3"]] -,Header 1 ("two-column-slide",[],[]) [Str "Two",Space,Str "column",Space,Str "slide"] -,Div ("",["columns"],[]) - [Div ("",["column"],[("width","50%")]) - [BulletList - [[Plain [Str "A",Space,Str "total",Space,Str "alternative",Space,Str "for",Space,Code ("",[],[]) "head"]]]] - ,Div ("",["column"],[("width","50%")]) - [CodeBlock ("",[],[]) "safeHead :: [a] -> Maybe a\nsafeHead [] = Nothing\nsafeHead (x:_) = Just x"]]] diff --git a/test/pptx/code.pptx b/test/pptx/code.pptx deleted file mode 100644 index aab0cc6f5..000000000 Binary files a/test/pptx/code.pptx and /dev/null differ diff --git a/test/pptx/code/deleted-layouts.pptx b/test/pptx/code/deleted-layouts.pptx new file mode 100644 index 000000000..0f503f553 Binary files /dev/null and b/test/pptx/code/deleted-layouts.pptx differ diff --git a/test/pptx/code/input.native b/test/pptx/code/input.native new file mode 100644 index 000000000..be7f512f7 --- /dev/null +++ b/test/pptx/code/input.native @@ -0,0 +1,21 @@ +[Header 1 ("header-with-inline-code",[],[]) [Str "Header",Space,Str "with",Space,Code ("",[],[]) "inline code"] +,CodeBlock ("",[],[]) "Code at level 0" +,BulletList + [[Para [Str "Bullet",Space,Str "item",Space,Str "with",Space,Code ("",[],[]) "inline code"] + ,CodeBlock ("",[],[]) "Code block at level 1" + ,BulletList + [[Para [Str "with",Space,Code ("",[],[]) "nested"] + ,CodeBlock ("",[],[]) "lvl2\nlvl2\nlvl2" + ,Header 2 ("second-heading-level-with-code",[],[]) [Str "Second",Space,Str "heading",Space,Str "level",Space,Str "with",Space,Code ("",[],[]) "code"]]]]] +,Header 1 ("syntax-highlighting",[],[]) [Str "Syntax",Space,Str "highlighting"] +,CodeBlock ("",["haskell"],[]) "id :: a -> a\nid x = x" +,BulletList + [[Para [Str "Nested"] + ,CodeBlock ("",["haskell"],[]) "g :: Int -> Int\ng x = x * 3"]] +,Header 1 ("two-column-slide",[],[]) [Str "Two",Space,Str "column",Space,Str "slide"] +,Div ("",["columns"],[]) + [Div ("",["column"],[("width","50%")]) + [BulletList + [[Plain [Str "A",Space,Str "total",Space,Str "alternative",Space,Str "for",Space,Code ("",[],[]) "head"]]]] + ,Div ("",["column"],[("width","50%")]) + [CodeBlock ("",[],[]) "safeHead :: [a] -> Maybe a\nsafeHead [] = Nothing\nsafeHead (x:_) = Just x"]]] diff --git a/test/pptx/code/moved-layouts.pptx b/test/pptx/code/moved-layouts.pptx new file mode 100644 index 000000000..4d66b1310 Binary files /dev/null and b/test/pptx/code/moved-layouts.pptx differ diff --git a/test/pptx/code/output.pptx b/test/pptx/code/output.pptx new file mode 100644 index 000000000..aab0cc6f5 Binary files /dev/null and b/test/pptx/code/output.pptx differ diff --git a/test/pptx/code/templated.pptx b/test/pptx/code/templated.pptx new file mode 100644 index 000000000..a03109217 Binary files /dev/null and b/test/pptx/code/templated.pptx differ diff --git a/test/pptx/code_deleted_layouts.pptx b/test/pptx/code_deleted_layouts.pptx deleted file mode 100644 index 0f503f553..000000000 Binary files a/test/pptx/code_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/code_moved_layouts.pptx b/test/pptx/code_moved_layouts.pptx deleted file mode 100644 index 4d66b1310..000000000 Binary files a/test/pptx/code_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/code_templated.pptx b/test/pptx/code_templated.pptx deleted file mode 100644 index a03109217..000000000 Binary files a/test/pptx/code_templated.pptx and /dev/null differ diff --git a/test/pptx/document-properties-short-desc.native b/test/pptx/document-properties-short-desc.native deleted file mode 100644 index fe3193dc1..000000000 --- a/test/pptx/document-properties-short-desc.native +++ /dev/null @@ -1,2 +0,0 @@ -Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "A.",Space,Str "M."]]),("description",MetaInlines [Str "Short",Space,RawInline (Format "html") "",Str "description",RawInline (Format "html") "",Space,Str "&."]),("keywords",MetaList [MetaInlines [Str "keyword",Space,Str "1"],MetaInlines [Str "keyword",Space,Str "2"]]),("subject",MetaInlines [Str "This",Space,Str "is",Space,Str "the",Space,Str "subject"]),("title",MetaInlines [Str "Testing",Space,Str "custom",Space,Str "properties"])]}) -[Para [Str "Testing",Space,Str "document",Space,Str "properties"]] diff --git a/test/pptx/document-properties-short-desc.pptx b/test/pptx/document-properties-short-desc.pptx deleted file mode 100644 index de5e68151..000000000 Binary files a/test/pptx/document-properties-short-desc.pptx and /dev/null differ diff --git a/test/pptx/document-properties-short-desc/deleted-layouts.pptx b/test/pptx/document-properties-short-desc/deleted-layouts.pptx new file mode 100644 index 000000000..e4cf6bd7b Binary files /dev/null and b/test/pptx/document-properties-short-desc/deleted-layouts.pptx differ diff --git a/test/pptx/document-properties-short-desc/input.native b/test/pptx/document-properties-short-desc/input.native new file mode 100644 index 000000000..fe3193dc1 --- /dev/null +++ b/test/pptx/document-properties-short-desc/input.native @@ -0,0 +1,2 @@ +Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "A.",Space,Str "M."]]),("description",MetaInlines [Str "Short",Space,RawInline (Format "html") "",Str "description",RawInline (Format "html") "",Space,Str "&."]),("keywords",MetaList [MetaInlines [Str "keyword",Space,Str "1"],MetaInlines [Str "keyword",Space,Str "2"]]),("subject",MetaInlines [Str "This",Space,Str "is",Space,Str "the",Space,Str "subject"]),("title",MetaInlines [Str "Testing",Space,Str "custom",Space,Str "properties"])]}) +[Para [Str "Testing",Space,Str "document",Space,Str "properties"]] diff --git a/test/pptx/document-properties-short-desc/moved-layouts.pptx b/test/pptx/document-properties-short-desc/moved-layouts.pptx new file mode 100644 index 000000000..8834f885f Binary files /dev/null and b/test/pptx/document-properties-short-desc/moved-layouts.pptx differ diff --git a/test/pptx/document-properties-short-desc/output.pptx b/test/pptx/document-properties-short-desc/output.pptx new file mode 100644 index 000000000..de5e68151 Binary files /dev/null and b/test/pptx/document-properties-short-desc/output.pptx differ diff --git a/test/pptx/document-properties-short-desc/templated.pptx b/test/pptx/document-properties-short-desc/templated.pptx new file mode 100644 index 000000000..d39dc0c91 Binary files /dev/null and b/test/pptx/document-properties-short-desc/templated.pptx differ diff --git a/test/pptx/document-properties-short-desc_deleted_layouts.pptx b/test/pptx/document-properties-short-desc_deleted_layouts.pptx deleted file mode 100644 index e4cf6bd7b..000000000 Binary files a/test/pptx/document-properties-short-desc_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/document-properties-short-desc_moved_layouts.pptx b/test/pptx/document-properties-short-desc_moved_layouts.pptx deleted file mode 100644 index 8834f885f..000000000 Binary files a/test/pptx/document-properties-short-desc_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/document-properties-short-desc_templated.pptx b/test/pptx/document-properties-short-desc_templated.pptx deleted file mode 100644 index d39dc0c91..000000000 Binary files a/test/pptx/document-properties-short-desc_templated.pptx and /dev/null differ diff --git a/test/pptx/document-properties.native b/test/pptx/document-properties.native deleted file mode 100644 index 59ca53f4d..000000000 --- a/test/pptx/document-properties.native +++ /dev/null @@ -1,2 +0,0 @@ -Pandoc (Meta {unMeta = fromList [("Company",MetaInlines [Str "My",Space,Str "Company"]),("Second Custom Property",MetaInlines [Str "Second",Space,Str "custom",Space,Str "property",Space,Str "value"]),("abstract",MetaBlocks [Plain [Str "Quite",Space,Str "a",Space,Str "long",Space,Str "description",SoftBreak,Str "spanning",Space,Str "several",Space,Str "lines"]]),("author",MetaList [MetaInlines [Str "A.",Space,Str "M."]]),("category",MetaInlines [Str "My",Space,Str "Category"]),("custom1",MetaInlines [Str "First",Space,Str "custom",Space,Str "property",Space,Str "value"]),("custom3",MetaInlines [Str "Escaping",Space,Str "amp",Space,Str "&",Space,Str "."]),("custom4",MetaInlines [Str "Escaping",Space,Str "LT,GT",Space,Str "<",Space,Str "asdf",Space,Str ">",Space,Str "<"]),("custom5",MetaInlines [Str "Escaping",Space,Str "html",Space,RawInline (Format "html") "",Str "asdf",RawInline (Format "html") ""]),("custom6",MetaInlines [Str "Escaping",Space,Emph [Str "MD"],Space,Str "\225",Space,Str "a"]),("custom9",MetaInlines [Str "Extended",Space,Str "chars:",Space,Str "\8364",Space,Str "\225",Space,Str "\233",Space,Str "\237",Space,Str "\243",Space,Str "\250",Space,Str "$"]),("description",MetaBlocks [Para [Str "Long",Space,Str "description",Space,Str "spanning",SoftBreak,Str "several",Space,Str "lines."],Plain [Str "This",Space,Str "is",Space,Str "\225",Space,Str "second",Space,RawInline (Format "html") "",Str "line",RawInline (Format "html") "",Str "."]]),("keywords",MetaList [MetaInlines [Str "keyword",Space,Str "1"],MetaInlines [Str "keyword",Space,Str "2"]]),("lang",MetaInlines [Str "en-US"]),("nested-custom",MetaList [MetaMap (fromList [("custom 7",MetaInlines [Str "Nested",Space,Str "Custom",Space,Str "value",Space,Str "7"])]),MetaMap (fromList [("custom 8",MetaInlines [Str "Nested",Space,Str "Custom",Space,Str "value",Space,Str "8"])])]),("subject",MetaInlines [Str "This",Space,Str "is",Space,Str "the",Space,Str "subject"]),("subtitle",MetaInlines [Str "This",Space,Str "is",Space,Str "a",Space,Str "subtitle"]),("title",MetaInlines [Str "Testing",Space,Str "custom",Space,Str "properties"])]}) -[Para [Str "Testing",Space,Str "document",Space,Str "properties"]] diff --git a/test/pptx/document-properties.pptx b/test/pptx/document-properties.pptx deleted file mode 100644 index 6bcbd1b9c..000000000 Binary files a/test/pptx/document-properties.pptx and /dev/null differ diff --git a/test/pptx/document-properties/deleted-layouts.pptx b/test/pptx/document-properties/deleted-layouts.pptx new file mode 100644 index 000000000..a00c8059d Binary files /dev/null and b/test/pptx/document-properties/deleted-layouts.pptx differ diff --git a/test/pptx/document-properties/input.native b/test/pptx/document-properties/input.native new file mode 100644 index 000000000..59ca53f4d --- /dev/null +++ b/test/pptx/document-properties/input.native @@ -0,0 +1,2 @@ +Pandoc (Meta {unMeta = fromList [("Company",MetaInlines [Str "My",Space,Str "Company"]),("Second Custom Property",MetaInlines [Str "Second",Space,Str "custom",Space,Str "property",Space,Str "value"]),("abstract",MetaBlocks [Plain [Str "Quite",Space,Str "a",Space,Str "long",Space,Str "description",SoftBreak,Str "spanning",Space,Str "several",Space,Str "lines"]]),("author",MetaList [MetaInlines [Str "A.",Space,Str "M."]]),("category",MetaInlines [Str "My",Space,Str "Category"]),("custom1",MetaInlines [Str "First",Space,Str "custom",Space,Str "property",Space,Str "value"]),("custom3",MetaInlines [Str "Escaping",Space,Str "amp",Space,Str "&",Space,Str "."]),("custom4",MetaInlines [Str "Escaping",Space,Str "LT,GT",Space,Str "<",Space,Str "asdf",Space,Str ">",Space,Str "<"]),("custom5",MetaInlines [Str "Escaping",Space,Str "html",Space,RawInline (Format "html") "",Str "asdf",RawInline (Format "html") ""]),("custom6",MetaInlines [Str "Escaping",Space,Emph [Str "MD"],Space,Str "\225",Space,Str "a"]),("custom9",MetaInlines [Str "Extended",Space,Str "chars:",Space,Str "\8364",Space,Str "\225",Space,Str "\233",Space,Str "\237",Space,Str "\243",Space,Str "\250",Space,Str "$"]),("description",MetaBlocks [Para [Str "Long",Space,Str "description",Space,Str "spanning",SoftBreak,Str "several",Space,Str "lines."],Plain [Str "This",Space,Str "is",Space,Str "\225",Space,Str "second",Space,RawInline (Format "html") "",Str "line",RawInline (Format "html") "",Str "."]]),("keywords",MetaList [MetaInlines [Str "keyword",Space,Str "1"],MetaInlines [Str "keyword",Space,Str "2"]]),("lang",MetaInlines [Str "en-US"]),("nested-custom",MetaList [MetaMap (fromList [("custom 7",MetaInlines [Str "Nested",Space,Str "Custom",Space,Str "value",Space,Str "7"])]),MetaMap (fromList [("custom 8",MetaInlines [Str "Nested",Space,Str "Custom",Space,Str "value",Space,Str "8"])])]),("subject",MetaInlines [Str "This",Space,Str "is",Space,Str "the",Space,Str "subject"]),("subtitle",MetaInlines [Str "This",Space,Str "is",Space,Str "a",Space,Str "subtitle"]),("title",MetaInlines [Str "Testing",Space,Str "custom",Space,Str "properties"])]}) +[Para [Str "Testing",Space,Str "document",Space,Str "properties"]] diff --git a/test/pptx/document-properties/moved-layouts.pptx b/test/pptx/document-properties/moved-layouts.pptx new file mode 100644 index 000000000..c1d2d5282 Binary files /dev/null and b/test/pptx/document-properties/moved-layouts.pptx differ diff --git a/test/pptx/document-properties/output.pptx b/test/pptx/document-properties/output.pptx new file mode 100644 index 000000000..6bcbd1b9c Binary files /dev/null and b/test/pptx/document-properties/output.pptx differ diff --git a/test/pptx/document-properties/templated.pptx b/test/pptx/document-properties/templated.pptx new file mode 100644 index 000000000..841ae8c42 Binary files /dev/null and b/test/pptx/document-properties/templated.pptx differ diff --git a/test/pptx/document-properties_deleted_layouts.pptx b/test/pptx/document-properties_deleted_layouts.pptx deleted file mode 100644 index a00c8059d..000000000 Binary files a/test/pptx/document-properties_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/document-properties_moved_layouts.pptx b/test/pptx/document-properties_moved_layouts.pptx deleted file mode 100644 index c1d2d5282..000000000 Binary files a/test/pptx/document-properties_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/document-properties_templated.pptx b/test/pptx/document-properties_templated.pptx deleted file mode 100644 index 841ae8c42..000000000 Binary files a/test/pptx/document-properties_templated.pptx and /dev/null differ diff --git a/test/pptx/endnotes-toc/deleted-layouts.pptx b/test/pptx/endnotes-toc/deleted-layouts.pptx new file mode 100644 index 000000000..46708544c Binary files /dev/null and b/test/pptx/endnotes-toc/deleted-layouts.pptx differ diff --git a/test/pptx/endnotes-toc/moved-layouts.pptx b/test/pptx/endnotes-toc/moved-layouts.pptx new file mode 100644 index 000000000..d1200bd7d Binary files /dev/null and b/test/pptx/endnotes-toc/moved-layouts.pptx differ diff --git a/test/pptx/endnotes-toc/output.pptx b/test/pptx/endnotes-toc/output.pptx new file mode 100644 index 000000000..a028b346f Binary files /dev/null and b/test/pptx/endnotes-toc/output.pptx differ diff --git a/test/pptx/endnotes-toc/templated.pptx b/test/pptx/endnotes-toc/templated.pptx new file mode 100644 index 000000000..38a0c437d Binary files /dev/null and b/test/pptx/endnotes-toc/templated.pptx differ diff --git a/test/pptx/endnotes.native b/test/pptx/endnotes.native deleted file mode 100644 index f6caeb62f..000000000 --- a/test/pptx/endnotes.native +++ /dev/null @@ -1,2 +0,0 @@ -Pandoc (Meta {unMeta = fromList []}) -[Para [Str "Here",Space,Str "is",Space,Str "one",Space,Str "note.",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "note."]],Space,Str "And",Space,Str "one",Space,Str "more",Space,Str "note.",Note [Para [Str "And",Space,Str "another",Space,Str "note."]]]] diff --git a/test/pptx/endnotes.pptx b/test/pptx/endnotes.pptx deleted file mode 100644 index 9d46036fe..000000000 Binary files a/test/pptx/endnotes.pptx and /dev/null differ diff --git a/test/pptx/endnotes/deleted-layouts.pptx b/test/pptx/endnotes/deleted-layouts.pptx new file mode 100644 index 000000000..5c69a6310 Binary files /dev/null and b/test/pptx/endnotes/deleted-layouts.pptx differ diff --git a/test/pptx/endnotes/input.native b/test/pptx/endnotes/input.native new file mode 100644 index 000000000..f6caeb62f --- /dev/null +++ b/test/pptx/endnotes/input.native @@ -0,0 +1,2 @@ +Pandoc (Meta {unMeta = fromList []}) +[Para [Str "Here",Space,Str "is",Space,Str "one",Space,Str "note.",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "note."]],Space,Str "And",Space,Str "one",Space,Str "more",Space,Str "note.",Note [Para [Str "And",Space,Str "another",Space,Str "note."]]]] diff --git a/test/pptx/endnotes/moved-layouts.pptx b/test/pptx/endnotes/moved-layouts.pptx new file mode 100644 index 000000000..0d4c491b9 Binary files /dev/null and b/test/pptx/endnotes/moved-layouts.pptx differ diff --git a/test/pptx/endnotes/output.pptx b/test/pptx/endnotes/output.pptx new file mode 100644 index 000000000..9d46036fe Binary files /dev/null and b/test/pptx/endnotes/output.pptx differ diff --git a/test/pptx/endnotes/templated.pptx b/test/pptx/endnotes/templated.pptx new file mode 100644 index 000000000..863cc29d4 Binary files /dev/null and b/test/pptx/endnotes/templated.pptx differ diff --git a/test/pptx/endnotes_deleted_layouts.pptx b/test/pptx/endnotes_deleted_layouts.pptx deleted file mode 100644 index 5c69a6310..000000000 Binary files a/test/pptx/endnotes_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/endnotes_moved_layouts.pptx b/test/pptx/endnotes_moved_layouts.pptx deleted file mode 100644 index 0d4c491b9..000000000 Binary files a/test/pptx/endnotes_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/endnotes_templated.pptx b/test/pptx/endnotes_templated.pptx deleted file mode 100644 index 863cc29d4..000000000 Binary files a/test/pptx/endnotes_templated.pptx and /dev/null differ diff --git a/test/pptx/endnotes_toc.pptx b/test/pptx/endnotes_toc.pptx deleted file mode 100644 index a028b346f..000000000 Binary files a/test/pptx/endnotes_toc.pptx and /dev/null differ diff --git a/test/pptx/endnotes_toc_deleted_layouts.pptx b/test/pptx/endnotes_toc_deleted_layouts.pptx deleted file mode 100644 index 46708544c..000000000 Binary files a/test/pptx/endnotes_toc_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/endnotes_toc_moved_layouts.pptx b/test/pptx/endnotes_toc_moved_layouts.pptx deleted file mode 100644 index d1200bd7d..000000000 Binary files a/test/pptx/endnotes_toc_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/endnotes_toc_templated.pptx b/test/pptx/endnotes_toc_templated.pptx deleted file mode 100644 index 38a0c437d..000000000 Binary files a/test/pptx/endnotes_toc_templated.pptx and /dev/null differ diff --git a/test/pptx/images.native b/test/pptx/images.native deleted file mode 100644 index 54827e5cc..000000000 --- a/test/pptx/images.native +++ /dev/null @@ -1,5 +0,0 @@ -Pandoc (Meta {unMeta = fromList []}) -[Para [Image ("",[],[]) [] ("lalune.jpg","")] -,Para [Image ("",[],[]) [Str "The",Space,Str "Moon"] ("lalune.jpg","fig:")] -,Header 1 ("one-more",[],[]) [Str "One",Space,Str "More"] -,Para [Image ("",[],[]) [Str "The",Space,Str "Moon"] ("lalune.jpg","fig:")]] diff --git a/test/pptx/images.pptx b/test/pptx/images.pptx deleted file mode 100644 index 89325e577..000000000 Binary files a/test/pptx/images.pptx and /dev/null differ diff --git a/test/pptx/images/deleted-layouts.pptx b/test/pptx/images/deleted-layouts.pptx new file mode 100644 index 000000000..053928863 Binary files /dev/null and b/test/pptx/images/deleted-layouts.pptx differ diff --git a/test/pptx/images/input.native b/test/pptx/images/input.native new file mode 100644 index 000000000..54827e5cc --- /dev/null +++ b/test/pptx/images/input.native @@ -0,0 +1,5 @@ +Pandoc (Meta {unMeta = fromList []}) +[Para [Image ("",[],[]) [] ("lalune.jpg","")] +,Para [Image ("",[],[]) [Str "The",Space,Str "Moon"] ("lalune.jpg","fig:")] +,Header 1 ("one-more",[],[]) [Str "One",Space,Str "More"] +,Para [Image ("",[],[]) [Str "The",Space,Str "Moon"] ("lalune.jpg","fig:")]] diff --git a/test/pptx/images/moved-layouts.pptx b/test/pptx/images/moved-layouts.pptx new file mode 100644 index 000000000..7951a09f6 Binary files /dev/null and b/test/pptx/images/moved-layouts.pptx differ diff --git a/test/pptx/images/output.pptx b/test/pptx/images/output.pptx new file mode 100644 index 000000000..89325e577 Binary files /dev/null and b/test/pptx/images/output.pptx differ diff --git a/test/pptx/images/templated.pptx b/test/pptx/images/templated.pptx new file mode 100644 index 000000000..7c0ed9a17 Binary files /dev/null and b/test/pptx/images/templated.pptx differ diff --git a/test/pptx/images_deleted_layouts.pptx b/test/pptx/images_deleted_layouts.pptx deleted file mode 100644 index 053928863..000000000 Binary files a/test/pptx/images_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/images_moved_layouts.pptx b/test/pptx/images_moved_layouts.pptx deleted file mode 100644 index 7951a09f6..000000000 Binary files a/test/pptx/images_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/images_templated.pptx b/test/pptx/images_templated.pptx deleted file mode 100644 index 7c0ed9a17..000000000 Binary files a/test/pptx/images_templated.pptx and /dev/null differ diff --git a/test/pptx/inline-formatting/deleted-layouts.pptx b/test/pptx/inline-formatting/deleted-layouts.pptx new file mode 100644 index 000000000..bbd5bfeb4 Binary files /dev/null and b/test/pptx/inline-formatting/deleted-layouts.pptx differ diff --git a/test/pptx/inline-formatting/input.native b/test/pptx/inline-formatting/input.native new file mode 100644 index 000000000..164176af2 --- /dev/null +++ b/test/pptx/inline-formatting/input.native @@ -0,0 +1,5 @@ +[Para [Str "Here",Space,Str "are",Space,Str "examples",Space,Str "of",Space,Emph [Str "italics"],Str ",",Space,Strong [Str "bold"],Str ",",Space,Str "and",Space,Strong [Emph [Str "bold",Space,Str "italics"]],Str "."] +,Para [Str "Here",Space,Str "is",Space,Strikeout [Str "strook-three"],Space,Str "strike-through",Space,Str "and",Space,SmallCaps [Str "small",Space,Str "caps"],Str "."] +,Para [Str "Here",Space,Str "is",Space,Span ("",["underline"],[]) [Str "some",Space,Emph [Str "underlined"],Space,Strong [Str "text"]],Str "."] +,Para [Str "We",Space,Str "can",Space,Str "also",Space,Str "do",Space,Str "subscripts",Space,Str "(H",Subscript [Str "2"],Str "0)",Space,Str "and",Space,Str "super",Superscript [Str "script"],Str "."] +,RawBlock (Format "html") ""] diff --git a/test/pptx/inline-formatting/moved-layouts.pptx b/test/pptx/inline-formatting/moved-layouts.pptx new file mode 100644 index 000000000..427492130 Binary files /dev/null and b/test/pptx/inline-formatting/moved-layouts.pptx differ diff --git a/test/pptx/inline-formatting/output.pptx b/test/pptx/inline-formatting/output.pptx new file mode 100644 index 000000000..473b9498d Binary files /dev/null and b/test/pptx/inline-formatting/output.pptx differ diff --git a/test/pptx/inline-formatting/templated.pptx b/test/pptx/inline-formatting/templated.pptx new file mode 100644 index 000000000..dd778a102 Binary files /dev/null and b/test/pptx/inline-formatting/templated.pptx differ diff --git a/test/pptx/inline_formatting.native b/test/pptx/inline_formatting.native deleted file mode 100644 index 164176af2..000000000 --- a/test/pptx/inline_formatting.native +++ /dev/null @@ -1,5 +0,0 @@ -[Para [Str "Here",Space,Str "are",Space,Str "examples",Space,Str "of",Space,Emph [Str "italics"],Str ",",Space,Strong [Str "bold"],Str ",",Space,Str "and",Space,Strong [Emph [Str "bold",Space,Str "italics"]],Str "."] -,Para [Str "Here",Space,Str "is",Space,Strikeout [Str "strook-three"],Space,Str "strike-through",Space,Str "and",Space,SmallCaps [Str "small",Space,Str "caps"],Str "."] -,Para [Str "Here",Space,Str "is",Space,Span ("",["underline"],[]) [Str "some",Space,Emph [Str "underlined"],Space,Strong [Str "text"]],Str "."] -,Para [Str "We",Space,Str "can",Space,Str "also",Space,Str "do",Space,Str "subscripts",Space,Str "(H",Subscript [Str "2"],Str "0)",Space,Str "and",Space,Str "super",Superscript [Str "script"],Str "."] -,RawBlock (Format "html") ""] diff --git a/test/pptx/inline_formatting.pptx b/test/pptx/inline_formatting.pptx deleted file mode 100644 index 473b9498d..000000000 Binary files a/test/pptx/inline_formatting.pptx and /dev/null differ diff --git a/test/pptx/inline_formatting_deleted_layouts.pptx b/test/pptx/inline_formatting_deleted_layouts.pptx deleted file mode 100644 index bbd5bfeb4..000000000 Binary files a/test/pptx/inline_formatting_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/inline_formatting_moved_layouts.pptx b/test/pptx/inline_formatting_moved_layouts.pptx deleted file mode 100644 index 427492130..000000000 Binary files a/test/pptx/inline_formatting_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/inline_formatting_templated.pptx b/test/pptx/inline_formatting_templated.pptx deleted file mode 100644 index dd778a102..000000000 Binary files a/test/pptx/inline_formatting_templated.pptx and /dev/null differ diff --git a/test/pptx/lists.native b/test/pptx/lists.native deleted file mode 100644 index 61249c7fe..000000000 --- a/test/pptx/lists.native +++ /dev/null @@ -1,18 +0,0 @@ -[Header 1 ("lists",[],[]) [Str "Lists"] -,BulletList - [[Para [Str "Bulleted",Space,Str "bulleted",Space,Str "lists."]] - ,[Para [Str "And",Space,Str "go",Space,Str "to",Space,Str "arbitrary",Space,Str "depth."] - ,BulletList - [[Para [Str "Like",Space,Str "this"] - ,BulletList - [[Plain [Str "Or",Space,Str "this"]]]] - ,[Para [Str "Back",Space,Str "to",Space,Str "here."]]]]] -,Header 1 ("lists-continued",[],[]) [Str "Lists",Space,Str "(continued)"] -,Para [Str "Lists",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "numbered:"] -,OrderedList (1,Decimal,Period) - [[Para [Str "Tomatoes"]] - ,[Para [Str "Potatoes",Space,Str "of",Space,Str "various",Space,Str "sorts"] - ,OrderedList (1,LowerAlpha,Period) - [[Para [Str "sweet",Space,Str "potatoes"]] - ,[Para [Str "russet",Space,Str "potates"]]]] - ,[Para [Str "Tornadoes,",Space,Str "for",Space,Str "the",Space,Str "rhyme."]]]] diff --git a/test/pptx/lists.pptx b/test/pptx/lists.pptx deleted file mode 100644 index ffc2eb9f7..000000000 Binary files a/test/pptx/lists.pptx and /dev/null differ diff --git a/test/pptx/lists/deleted-layouts.pptx b/test/pptx/lists/deleted-layouts.pptx new file mode 100644 index 000000000..6512e44bb Binary files /dev/null and b/test/pptx/lists/deleted-layouts.pptx differ diff --git a/test/pptx/lists/input.native b/test/pptx/lists/input.native new file mode 100644 index 000000000..61249c7fe --- /dev/null +++ b/test/pptx/lists/input.native @@ -0,0 +1,18 @@ +[Header 1 ("lists",[],[]) [Str "Lists"] +,BulletList + [[Para [Str "Bulleted",Space,Str "bulleted",Space,Str "lists."]] + ,[Para [Str "And",Space,Str "go",Space,Str "to",Space,Str "arbitrary",Space,Str "depth."] + ,BulletList + [[Para [Str "Like",Space,Str "this"] + ,BulletList + [[Plain [Str "Or",Space,Str "this"]]]] + ,[Para [Str "Back",Space,Str "to",Space,Str "here."]]]]] +,Header 1 ("lists-continued",[],[]) [Str "Lists",Space,Str "(continued)"] +,Para [Str "Lists",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "numbered:"] +,OrderedList (1,Decimal,Period) + [[Para [Str "Tomatoes"]] + ,[Para [Str "Potatoes",Space,Str "of",Space,Str "various",Space,Str "sorts"] + ,OrderedList (1,LowerAlpha,Period) + [[Para [Str "sweet",Space,Str "potatoes"]] + ,[Para [Str "russet",Space,Str "potates"]]]] + ,[Para [Str "Tornadoes,",Space,Str "for",Space,Str "the",Space,Str "rhyme."]]]] diff --git a/test/pptx/lists/moved-layouts.pptx b/test/pptx/lists/moved-layouts.pptx new file mode 100644 index 000000000..2947c3211 Binary files /dev/null and b/test/pptx/lists/moved-layouts.pptx differ diff --git a/test/pptx/lists/output.pptx b/test/pptx/lists/output.pptx new file mode 100644 index 000000000..ffc2eb9f7 Binary files /dev/null and b/test/pptx/lists/output.pptx differ diff --git a/test/pptx/lists/templated.pptx b/test/pptx/lists/templated.pptx new file mode 100644 index 000000000..2493e7890 Binary files /dev/null and b/test/pptx/lists/templated.pptx differ diff --git a/test/pptx/lists_deleted_layouts.pptx b/test/pptx/lists_deleted_layouts.pptx deleted file mode 100644 index 6512e44bb..000000000 Binary files a/test/pptx/lists_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/lists_moved_layouts.pptx b/test/pptx/lists_moved_layouts.pptx deleted file mode 100644 index 2947c3211..000000000 Binary files a/test/pptx/lists_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/lists_templated.pptx b/test/pptx/lists_templated.pptx deleted file mode 100644 index 2493e7890..000000000 Binary files a/test/pptx/lists_templated.pptx and /dev/null differ diff --git a/test/pptx/raw-ooxml/deleted-layouts.pptx b/test/pptx/raw-ooxml/deleted-layouts.pptx new file mode 100644 index 000000000..2ea155657 Binary files /dev/null and b/test/pptx/raw-ooxml/deleted-layouts.pptx differ diff --git a/test/pptx/raw-ooxml/input.native b/test/pptx/raw-ooxml/input.native new file mode 100644 index 000000000..ae5bdd140 --- /dev/null +++ b/test/pptx/raw-ooxml/input.native @@ -0,0 +1,3 @@ +[Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "text,",Space,Str "written",Space,Str "as",Space,Str "a",Space,Str "raw",Space,Str "inline:",Space,RawInline (Format "openxml") "Here are examples of italics, bold"] +,HorizontalRule +,RawBlock (Format "openxml") "\n \n \n \n \n \n \n \n \n \n \n \n \n \n \n \n \n \n Bulleted bulleted lists.\n \n \n \n \n \n \n And go to arbitrary depth.\n \n \n \n \n \n \n Like this\n \n \n \n \n \n \n Or this\n \n \n \n \n \n \n Back to here.\n \n \n \n "] diff --git a/test/pptx/raw-ooxml/moved-layouts.pptx b/test/pptx/raw-ooxml/moved-layouts.pptx new file mode 100644 index 000000000..e58304172 Binary files /dev/null and b/test/pptx/raw-ooxml/moved-layouts.pptx differ diff --git a/test/pptx/raw-ooxml/output.pptx b/test/pptx/raw-ooxml/output.pptx new file mode 100644 index 000000000..29164af15 Binary files /dev/null and b/test/pptx/raw-ooxml/output.pptx differ diff --git a/test/pptx/raw-ooxml/templated.pptx b/test/pptx/raw-ooxml/templated.pptx new file mode 100644 index 000000000..0f20f9826 Binary files /dev/null and b/test/pptx/raw-ooxml/templated.pptx differ diff --git a/test/pptx/raw_ooxml.native b/test/pptx/raw_ooxml.native deleted file mode 100644 index ae5bdd140..000000000 --- a/test/pptx/raw_ooxml.native +++ /dev/null @@ -1,3 +0,0 @@ -[Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "text,",Space,Str "written",Space,Str "as",Space,Str "a",Space,Str "raw",Space,Str "inline:",Space,RawInline (Format "openxml") "Here are examples of italics, bold"] -,HorizontalRule -,RawBlock (Format "openxml") "\n \n \n \n \n \n \n \n \n \n \n \n \n \n \n \n \n \n Bulleted bulleted lists.\n \n \n \n \n \n \n And go to arbitrary depth.\n \n \n \n \n \n \n Like this\n \n \n \n \n \n \n Or this\n \n \n \n \n \n \n Back to here.\n \n \n \n "] diff --git a/test/pptx/raw_ooxml.pptx b/test/pptx/raw_ooxml.pptx deleted file mode 100644 index 29164af15..000000000 Binary files a/test/pptx/raw_ooxml.pptx and /dev/null differ diff --git a/test/pptx/raw_ooxml_deleted_layouts.pptx b/test/pptx/raw_ooxml_deleted_layouts.pptx deleted file mode 100644 index 2ea155657..000000000 Binary files a/test/pptx/raw_ooxml_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/raw_ooxml_moved_layouts.pptx b/test/pptx/raw_ooxml_moved_layouts.pptx deleted file mode 100644 index e58304172..000000000 Binary files a/test/pptx/raw_ooxml_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/raw_ooxml_templated.pptx b/test/pptx/raw_ooxml_templated.pptx deleted file mode 100644 index 0f20f9826..000000000 Binary files a/test/pptx/raw_ooxml_templated.pptx and /dev/null differ diff --git a/test/pptx/reference-deleted-layouts.pptx b/test/pptx/reference-deleted-layouts.pptx new file mode 100644 index 000000000..a9a74ecd5 Binary files /dev/null and b/test/pptx/reference-deleted-layouts.pptx differ diff --git a/test/pptx/reference-depth.pptx b/test/pptx/reference-depth.pptx new file mode 100644 index 000000000..97f444788 Binary files /dev/null and b/test/pptx/reference-depth.pptx differ diff --git a/test/pptx/reference-moved-layouts.pptx b/test/pptx/reference-moved-layouts.pptx new file mode 100644 index 000000000..72c4f3fd7 Binary files /dev/null and b/test/pptx/reference-moved-layouts.pptx differ diff --git a/test/pptx/reference_deleted_layouts.pptx b/test/pptx/reference_deleted_layouts.pptx deleted file mode 100644 index a9a74ecd5..000000000 Binary files a/test/pptx/reference_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/reference_depth.pptx b/test/pptx/reference_depth.pptx deleted file mode 100644 index 97f444788..000000000 Binary files a/test/pptx/reference_depth.pptx and /dev/null differ diff --git a/test/pptx/reference_moved_layouts.pptx b/test/pptx/reference_moved_layouts.pptx deleted file mode 100644 index 72c4f3fd7..000000000 Binary files a/test/pptx/reference_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/remove-empty-slides/deleted-layouts.pptx b/test/pptx/remove-empty-slides/deleted-layouts.pptx new file mode 100644 index 000000000..7ae4a5fab Binary files /dev/null and b/test/pptx/remove-empty-slides/deleted-layouts.pptx differ diff --git a/test/pptx/remove-empty-slides/input.native b/test/pptx/remove-empty-slides/input.native new file mode 100644 index 000000000..51c042281 --- /dev/null +++ b/test/pptx/remove-empty-slides/input.native @@ -0,0 +1,5 @@ +[Para [Str "Content"] +,Para [Image ("",[],[]) [] ("lalune.jpg",""),Space,RawInline (Format "html") ""] +,HorizontalRule +,HorizontalRule +,Para [Str "More",Space,Str "content"]] diff --git a/test/pptx/remove-empty-slides/moved-layouts.pptx b/test/pptx/remove-empty-slides/moved-layouts.pptx new file mode 100644 index 000000000..2572f2447 Binary files /dev/null and b/test/pptx/remove-empty-slides/moved-layouts.pptx differ diff --git a/test/pptx/remove-empty-slides/output.pptx b/test/pptx/remove-empty-slides/output.pptx new file mode 100644 index 000000000..c6df8e18e Binary files /dev/null and b/test/pptx/remove-empty-slides/output.pptx differ diff --git a/test/pptx/remove-empty-slides/templated.pptx b/test/pptx/remove-empty-slides/templated.pptx new file mode 100644 index 000000000..1df48c5ad Binary files /dev/null and b/test/pptx/remove-empty-slides/templated.pptx differ diff --git a/test/pptx/remove_empty_slides.native b/test/pptx/remove_empty_slides.native deleted file mode 100644 index 51c042281..000000000 --- a/test/pptx/remove_empty_slides.native +++ /dev/null @@ -1,5 +0,0 @@ -[Para [Str "Content"] -,Para [Image ("",[],[]) [] ("lalune.jpg",""),Space,RawInline (Format "html") ""] -,HorizontalRule -,HorizontalRule -,Para [Str "More",Space,Str "content"]] diff --git a/test/pptx/remove_empty_slides.pptx b/test/pptx/remove_empty_slides.pptx deleted file mode 100644 index c6df8e18e..000000000 Binary files a/test/pptx/remove_empty_slides.pptx and /dev/null differ diff --git a/test/pptx/remove_empty_slides_deleted_layouts.pptx b/test/pptx/remove_empty_slides_deleted_layouts.pptx deleted file mode 100644 index 7ae4a5fab..000000000 Binary files a/test/pptx/remove_empty_slides_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/remove_empty_slides_moved_layouts.pptx b/test/pptx/remove_empty_slides_moved_layouts.pptx deleted file mode 100644 index 2572f2447..000000000 Binary files a/test/pptx/remove_empty_slides_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/remove_empty_slides_templated.pptx b/test/pptx/remove_empty_slides_templated.pptx deleted file mode 100644 index 1df48c5ad..000000000 Binary files a/test/pptx/remove_empty_slides_templated.pptx and /dev/null differ diff --git a/test/pptx/slide-breaks-slide-level-1/deleted-layouts.pptx b/test/pptx/slide-breaks-slide-level-1/deleted-layouts.pptx new file mode 100644 index 000000000..2c7fd4d8b Binary files /dev/null and b/test/pptx/slide-breaks-slide-level-1/deleted-layouts.pptx differ diff --git a/test/pptx/slide-breaks-slide-level-1/moved-layouts.pptx b/test/pptx/slide-breaks-slide-level-1/moved-layouts.pptx new file mode 100644 index 000000000..8471b1d10 Binary files /dev/null and b/test/pptx/slide-breaks-slide-level-1/moved-layouts.pptx differ diff --git a/test/pptx/slide-breaks-slide-level-1/output.pptx b/test/pptx/slide-breaks-slide-level-1/output.pptx new file mode 100644 index 000000000..449339778 Binary files /dev/null and b/test/pptx/slide-breaks-slide-level-1/output.pptx differ diff --git a/test/pptx/slide-breaks-slide-level-1/templated.pptx b/test/pptx/slide-breaks-slide-level-1/templated.pptx new file mode 100644 index 000000000..e2815159a Binary files /dev/null and b/test/pptx/slide-breaks-slide-level-1/templated.pptx differ diff --git a/test/pptx/slide-breaks-toc/deleted-layouts.pptx b/test/pptx/slide-breaks-toc/deleted-layouts.pptx new file mode 100644 index 000000000..1e0b76d46 Binary files /dev/null and b/test/pptx/slide-breaks-toc/deleted-layouts.pptx differ diff --git a/test/pptx/slide-breaks-toc/moved-layouts.pptx b/test/pptx/slide-breaks-toc/moved-layouts.pptx new file mode 100644 index 000000000..918264bc5 Binary files /dev/null and b/test/pptx/slide-breaks-toc/moved-layouts.pptx differ diff --git a/test/pptx/slide-breaks-toc/output.pptx b/test/pptx/slide-breaks-toc/output.pptx new file mode 100644 index 000000000..9dbfa41a0 Binary files /dev/null and b/test/pptx/slide-breaks-toc/output.pptx differ diff --git a/test/pptx/slide-breaks-toc/templated.pptx b/test/pptx/slide-breaks-toc/templated.pptx new file mode 100644 index 000000000..b83f3f596 Binary files /dev/null and b/test/pptx/slide-breaks-toc/templated.pptx differ diff --git a/test/pptx/slide-breaks/deleted-layouts.pptx b/test/pptx/slide-breaks/deleted-layouts.pptx new file mode 100644 index 000000000..86dfad3b2 Binary files /dev/null and b/test/pptx/slide-breaks/deleted-layouts.pptx differ diff --git a/test/pptx/slide-breaks/input.native b/test/pptx/slide-breaks/input.native new file mode 100644 index 000000000..084c61737 --- /dev/null +++ b/test/pptx/slide-breaks/input.native @@ -0,0 +1,7 @@ +Pandoc (Meta {unMeta = fromList []}) +[Para [Str "Break",Space,Str "with",Space,Str "a",Space,Str "new",Space,Str "section-level",Space,Str "header"] +,Header 1 ("below-section-level",[],[]) [Str "Below",Space,Str "section-level"] +,Header 2 ("section-level",[],[]) [Str "Section-level"] +,Para [Str "Third",Space,Str "slide",Space,Str "(with",Space,Str "a",Space,Str "section-level",Space,Str "of",Space,Str "2)"] +,HorizontalRule +,Para [Str "This",Space,Str "is",Space,Str "another",Space,Str "slide."]] diff --git a/test/pptx/slide-breaks/moved-layouts.pptx b/test/pptx/slide-breaks/moved-layouts.pptx new file mode 100644 index 000000000..90b3b94a6 Binary files /dev/null and b/test/pptx/slide-breaks/moved-layouts.pptx differ diff --git a/test/pptx/slide-breaks/output.pptx b/test/pptx/slide-breaks/output.pptx new file mode 100644 index 000000000..e06d9079d Binary files /dev/null and b/test/pptx/slide-breaks/output.pptx differ diff --git a/test/pptx/slide-breaks/templated.pptx b/test/pptx/slide-breaks/templated.pptx new file mode 100644 index 000000000..71ba99701 Binary files /dev/null and b/test/pptx/slide-breaks/templated.pptx differ diff --git a/test/pptx/slide-level-0-h1-h2-with-table.native b/test/pptx/slide-level-0-h1-h2-with-table.native deleted file mode 100644 index c6e65ecf5..000000000 --- a/test/pptx/slide-level-0-h1-h2-with-table.native +++ /dev/null @@ -1,14 +0,0 @@ -[Header 1 ("hello",[],[]) [Str "Hello"] -,Header 2 ("there",[],[]) [Str "There"] -,Table ("",[],[]) (Caption Nothing - []) - [(AlignDefault,ColWidth 5.555555555555555e-2)] - (TableHead ("",[],[]) - []) - [(TableBody ("",[],[]) (RowHeadColumns 0) - [] - [Row ("",[],[]) - [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "1"]]]])] - (TableFoot ("",[],[]) - [])] diff --git a/test/pptx/slide-level-0-h1-h2-with-table.pptx b/test/pptx/slide-level-0-h1-h2-with-table.pptx deleted file mode 100644 index 197a6833f..000000000 Binary files a/test/pptx/slide-level-0-h1-h2-with-table.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0-h1-h2-with-table_deleted_layouts.pptx b/test/pptx/slide-level-0-h1-h2-with-table_deleted_layouts.pptx deleted file mode 100644 index 5e776e05c..000000000 Binary files a/test/pptx/slide-level-0-h1-h2-with-table_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0-h1-h2-with-table_moved_layouts.pptx b/test/pptx/slide-level-0-h1-h2-with-table_moved_layouts.pptx deleted file mode 100644 index 35204de1b..000000000 Binary files a/test/pptx/slide-level-0-h1-h2-with-table_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0-h1-h2-with-table_templated.pptx b/test/pptx/slide-level-0-h1-h2-with-table_templated.pptx deleted file mode 100644 index 5c659952e..000000000 Binary files a/test/pptx/slide-level-0-h1-h2-with-table_templated.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0-h1-with-image.native b/test/pptx/slide-level-0-h1-with-image.native deleted file mode 100644 index 0f5033b54..000000000 --- a/test/pptx/slide-level-0-h1-with-image.native +++ /dev/null @@ -1,2 +0,0 @@ -[Header 1 ("hello",[],[]) [Str "Hello"] -,Para [Image ("",[],[]) [Str "An",Space,Str "image"] ("lalune.jpg","fig:")]] diff --git a/test/pptx/slide-level-0-h1-with-image.pptx b/test/pptx/slide-level-0-h1-with-image.pptx deleted file mode 100644 index 2f3a53f5c..000000000 Binary files a/test/pptx/slide-level-0-h1-with-image.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0-h1-with-image_deleted_layouts.pptx b/test/pptx/slide-level-0-h1-with-image_deleted_layouts.pptx deleted file mode 100644 index 16c61d1be..000000000 Binary files a/test/pptx/slide-level-0-h1-with-image_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0-h1-with-image_moved_layouts.pptx b/test/pptx/slide-level-0-h1-with-image_moved_layouts.pptx deleted file mode 100644 index 395036069..000000000 Binary files a/test/pptx/slide-level-0-h1-with-image_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0-h1-with-image_templated.pptx b/test/pptx/slide-level-0-h1-with-image_templated.pptx deleted file mode 100644 index d306375e9..000000000 Binary files a/test/pptx/slide-level-0-h1-with-image_templated.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0-h1-with-table.native b/test/pptx/slide-level-0-h1-with-table.native deleted file mode 100644 index b961e900d..000000000 --- a/test/pptx/slide-level-0-h1-with-table.native +++ /dev/null @@ -1,13 +0,0 @@ -[Header 1 ("hello",[],[]) [Str "Hello"] -,Table ("",[],[]) (Caption Nothing - []) - [(AlignDefault,ColWidth 5.555555555555555e-2)] - (TableHead ("",[],[]) - []) - [(TableBody ("",[],[]) (RowHeadColumns 0) - [] - [Row ("",[],[]) - [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "1"]]]])] - (TableFoot ("",[],[]) - [])] diff --git a/test/pptx/slide-level-0-h1-with-table.pptx b/test/pptx/slide-level-0-h1-with-table.pptx deleted file mode 100644 index 44dbbf90c..000000000 Binary files a/test/pptx/slide-level-0-h1-with-table.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0-h1-with-table_deleted_layouts.pptx b/test/pptx/slide-level-0-h1-with-table_deleted_layouts.pptx deleted file mode 100644 index 0eb7c0b08..000000000 Binary files a/test/pptx/slide-level-0-h1-with-table_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0-h1-with-table_moved_layouts.pptx b/test/pptx/slide-level-0-h1-with-table_moved_layouts.pptx deleted file mode 100644 index 197499bc3..000000000 Binary files a/test/pptx/slide-level-0-h1-with-table_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0-h1-with-table_templated.pptx b/test/pptx/slide-level-0-h1-with-table_templated.pptx deleted file mode 100644 index 87b45dda2..000000000 Binary files a/test/pptx/slide-level-0-h1-with-table_templated.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0-h2-with-image.native b/test/pptx/slide-level-0-h2-with-image.native deleted file mode 100644 index 5def0cb92..000000000 --- a/test/pptx/slide-level-0-h2-with-image.native +++ /dev/null @@ -1,2 +0,0 @@ -[Header 2 ("hello",[],[]) [Str "Hello"] -,Para [Image ("",[],[]) [Str "An",Space,Str "image"] ("lalune.jpg","fig:")]] diff --git a/test/pptx/slide-level-0-h2-with-image.pptx b/test/pptx/slide-level-0-h2-with-image.pptx deleted file mode 100644 index 948659d6a..000000000 Binary files a/test/pptx/slide-level-0-h2-with-image.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0-h2-with-image_deleted_layouts.pptx b/test/pptx/slide-level-0-h2-with-image_deleted_layouts.pptx deleted file mode 100644 index afc096ce6..000000000 Binary files a/test/pptx/slide-level-0-h2-with-image_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0-h2-with-image_moved_layouts.pptx b/test/pptx/slide-level-0-h2-with-image_moved_layouts.pptx deleted file mode 100644 index 395036069..000000000 Binary files a/test/pptx/slide-level-0-h2-with-image_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0-h2-with-image_templated.pptx b/test/pptx/slide-level-0-h2-with-image_templated.pptx deleted file mode 100644 index d306375e9..000000000 Binary files a/test/pptx/slide-level-0-h2-with-image_templated.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0/h1-h2-with-table/deleted-layouts.pptx b/test/pptx/slide-level-0/h1-h2-with-table/deleted-layouts.pptx new file mode 100644 index 000000000..5e776e05c Binary files /dev/null and b/test/pptx/slide-level-0/h1-h2-with-table/deleted-layouts.pptx differ diff --git a/test/pptx/slide-level-0/h1-h2-with-table/input.native b/test/pptx/slide-level-0/h1-h2-with-table/input.native new file mode 100644 index 000000000..c6e65ecf5 --- /dev/null +++ b/test/pptx/slide-level-0/h1-h2-with-table/input.native @@ -0,0 +1,14 @@ +[Header 1 ("hello",[],[]) [Str "Hello"] +,Header 2 ("there",[],[]) [Str "There"] +,Table ("",[],[]) (Caption Nothing + []) + [(AlignDefault,ColWidth 5.555555555555555e-2)] + (TableHead ("",[],[]) + []) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]]]])] + (TableFoot ("",[],[]) + [])] diff --git a/test/pptx/slide-level-0/h1-h2-with-table/moved-layouts.pptx b/test/pptx/slide-level-0/h1-h2-with-table/moved-layouts.pptx new file mode 100644 index 000000000..35204de1b Binary files /dev/null and b/test/pptx/slide-level-0/h1-h2-with-table/moved-layouts.pptx differ diff --git a/test/pptx/slide-level-0/h1-h2-with-table/output.pptx b/test/pptx/slide-level-0/h1-h2-with-table/output.pptx new file mode 100644 index 000000000..197a6833f Binary files /dev/null and b/test/pptx/slide-level-0/h1-h2-with-table/output.pptx differ diff --git a/test/pptx/slide-level-0/h1-h2-with-table/templated.pptx b/test/pptx/slide-level-0/h1-h2-with-table/templated.pptx new file mode 100644 index 000000000..5c659952e Binary files /dev/null and b/test/pptx/slide-level-0/h1-h2-with-table/templated.pptx differ diff --git a/test/pptx/slide-level-0/h1-with-image/deleted-layouts.pptx b/test/pptx/slide-level-0/h1-with-image/deleted-layouts.pptx new file mode 100644 index 000000000..16c61d1be Binary files /dev/null and b/test/pptx/slide-level-0/h1-with-image/deleted-layouts.pptx differ diff --git a/test/pptx/slide-level-0/h1-with-image/input.native b/test/pptx/slide-level-0/h1-with-image/input.native new file mode 100644 index 000000000..0f5033b54 --- /dev/null +++ b/test/pptx/slide-level-0/h1-with-image/input.native @@ -0,0 +1,2 @@ +[Header 1 ("hello",[],[]) [Str "Hello"] +,Para [Image ("",[],[]) [Str "An",Space,Str "image"] ("lalune.jpg","fig:")]] diff --git a/test/pptx/slide-level-0/h1-with-image/moved-layouts.pptx b/test/pptx/slide-level-0/h1-with-image/moved-layouts.pptx new file mode 100644 index 000000000..395036069 Binary files /dev/null and b/test/pptx/slide-level-0/h1-with-image/moved-layouts.pptx differ diff --git a/test/pptx/slide-level-0/h1-with-image/output.pptx b/test/pptx/slide-level-0/h1-with-image/output.pptx new file mode 100644 index 000000000..2f3a53f5c Binary files /dev/null and b/test/pptx/slide-level-0/h1-with-image/output.pptx differ diff --git a/test/pptx/slide-level-0/h1-with-image/templated.pptx b/test/pptx/slide-level-0/h1-with-image/templated.pptx new file mode 100644 index 000000000..d306375e9 Binary files /dev/null and b/test/pptx/slide-level-0/h1-with-image/templated.pptx differ diff --git a/test/pptx/slide-level-0/h1-with-table/deleted-layouts.pptx b/test/pptx/slide-level-0/h1-with-table/deleted-layouts.pptx new file mode 100644 index 000000000..0eb7c0b08 Binary files /dev/null and b/test/pptx/slide-level-0/h1-with-table/deleted-layouts.pptx differ diff --git a/test/pptx/slide-level-0/h1-with-table/input.native b/test/pptx/slide-level-0/h1-with-table/input.native new file mode 100644 index 000000000..b961e900d --- /dev/null +++ b/test/pptx/slide-level-0/h1-with-table/input.native @@ -0,0 +1,13 @@ +[Header 1 ("hello",[],[]) [Str "Hello"] +,Table ("",[],[]) (Caption Nothing + []) + [(AlignDefault,ColWidth 5.555555555555555e-2)] + (TableHead ("",[],[]) + []) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]]]])] + (TableFoot ("",[],[]) + [])] diff --git a/test/pptx/slide-level-0/h1-with-table/moved-layouts.pptx b/test/pptx/slide-level-0/h1-with-table/moved-layouts.pptx new file mode 100644 index 000000000..197499bc3 Binary files /dev/null and b/test/pptx/slide-level-0/h1-with-table/moved-layouts.pptx differ diff --git a/test/pptx/slide-level-0/h1-with-table/output.pptx b/test/pptx/slide-level-0/h1-with-table/output.pptx new file mode 100644 index 000000000..44dbbf90c Binary files /dev/null and b/test/pptx/slide-level-0/h1-with-table/output.pptx differ diff --git a/test/pptx/slide-level-0/h1-with-table/templated.pptx b/test/pptx/slide-level-0/h1-with-table/templated.pptx new file mode 100644 index 000000000..87b45dda2 Binary files /dev/null and b/test/pptx/slide-level-0/h1-with-table/templated.pptx differ diff --git a/test/pptx/slide-level-0/h2-with-image/deleted-layouts.pptx b/test/pptx/slide-level-0/h2-with-image/deleted-layouts.pptx new file mode 100644 index 000000000..afc096ce6 Binary files /dev/null and b/test/pptx/slide-level-0/h2-with-image/deleted-layouts.pptx differ diff --git a/test/pptx/slide-level-0/h2-with-image/input.native b/test/pptx/slide-level-0/h2-with-image/input.native new file mode 100644 index 000000000..5def0cb92 --- /dev/null +++ b/test/pptx/slide-level-0/h2-with-image/input.native @@ -0,0 +1,2 @@ +[Header 2 ("hello",[],[]) [Str "Hello"] +,Para [Image ("",[],[]) [Str "An",Space,Str "image"] ("lalune.jpg","fig:")]] diff --git a/test/pptx/slide-level-0/h2-with-image/moved-layouts.pptx b/test/pptx/slide-level-0/h2-with-image/moved-layouts.pptx new file mode 100644 index 000000000..395036069 Binary files /dev/null and b/test/pptx/slide-level-0/h2-with-image/moved-layouts.pptx differ diff --git a/test/pptx/slide-level-0/h2-with-image/output.pptx b/test/pptx/slide-level-0/h2-with-image/output.pptx new file mode 100644 index 000000000..948659d6a Binary files /dev/null and b/test/pptx/slide-level-0/h2-with-image/output.pptx differ diff --git a/test/pptx/slide-level-0/h2-with-image/templated.pptx b/test/pptx/slide-level-0/h2-with-image/templated.pptx new file mode 100644 index 000000000..d306375e9 Binary files /dev/null and b/test/pptx/slide-level-0/h2-with-image/templated.pptx differ diff --git a/test/pptx/slide_breaks.native b/test/pptx/slide_breaks.native deleted file mode 100644 index 084c61737..000000000 --- a/test/pptx/slide_breaks.native +++ /dev/null @@ -1,7 +0,0 @@ -Pandoc (Meta {unMeta = fromList []}) -[Para [Str "Break",Space,Str "with",Space,Str "a",Space,Str "new",Space,Str "section-level",Space,Str "header"] -,Header 1 ("below-section-level",[],[]) [Str "Below",Space,Str "section-level"] -,Header 2 ("section-level",[],[]) [Str "Section-level"] -,Para [Str "Third",Space,Str "slide",Space,Str "(with",Space,Str "a",Space,Str "section-level",Space,Str "of",Space,Str "2)"] -,HorizontalRule -,Para [Str "This",Space,Str "is",Space,Str "another",Space,Str "slide."]] diff --git a/test/pptx/slide_breaks.pptx b/test/pptx/slide_breaks.pptx deleted file mode 100644 index e06d9079d..000000000 Binary files a/test/pptx/slide_breaks.pptx and /dev/null differ diff --git a/test/pptx/slide_breaks_deleted_layouts.pptx b/test/pptx/slide_breaks_deleted_layouts.pptx deleted file mode 100644 index 86dfad3b2..000000000 Binary files a/test/pptx/slide_breaks_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/slide_breaks_moved_layouts.pptx b/test/pptx/slide_breaks_moved_layouts.pptx deleted file mode 100644 index 90b3b94a6..000000000 Binary files a/test/pptx/slide_breaks_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/slide_breaks_slide_level_1.pptx b/test/pptx/slide_breaks_slide_level_1.pptx deleted file mode 100644 index 449339778..000000000 Binary files a/test/pptx/slide_breaks_slide_level_1.pptx and /dev/null differ diff --git a/test/pptx/slide_breaks_slide_level_1_deleted_layouts.pptx b/test/pptx/slide_breaks_slide_level_1_deleted_layouts.pptx deleted file mode 100644 index 2c7fd4d8b..000000000 Binary files a/test/pptx/slide_breaks_slide_level_1_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/slide_breaks_slide_level_1_moved_layouts.pptx b/test/pptx/slide_breaks_slide_level_1_moved_layouts.pptx deleted file mode 100644 index 8471b1d10..000000000 Binary files a/test/pptx/slide_breaks_slide_level_1_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/slide_breaks_slide_level_1_templated.pptx b/test/pptx/slide_breaks_slide_level_1_templated.pptx deleted file mode 100644 index e2815159a..000000000 Binary files a/test/pptx/slide_breaks_slide_level_1_templated.pptx and /dev/null differ diff --git a/test/pptx/slide_breaks_templated.pptx b/test/pptx/slide_breaks_templated.pptx deleted file mode 100644 index 71ba99701..000000000 Binary files a/test/pptx/slide_breaks_templated.pptx and /dev/null differ diff --git a/test/pptx/slide_breaks_toc.pptx b/test/pptx/slide_breaks_toc.pptx deleted file mode 100644 index 9dbfa41a0..000000000 Binary files a/test/pptx/slide_breaks_toc.pptx and /dev/null differ diff --git a/test/pptx/slide_breaks_toc_deleted_layouts.pptx b/test/pptx/slide_breaks_toc_deleted_layouts.pptx deleted file mode 100644 index 1e0b76d46..000000000 Binary files a/test/pptx/slide_breaks_toc_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/slide_breaks_toc_moved_layouts.pptx b/test/pptx/slide_breaks_toc_moved_layouts.pptx deleted file mode 100644 index 918264bc5..000000000 Binary files a/test/pptx/slide_breaks_toc_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/slide_breaks_toc_templated.pptx b/test/pptx/slide_breaks_toc_templated.pptx deleted file mode 100644 index b83f3f596..000000000 Binary files a/test/pptx/slide_breaks_toc_templated.pptx and /dev/null differ diff --git a/test/pptx/speaker-notes-after-metadata/deleted-layouts.pptx b/test/pptx/speaker-notes-after-metadata/deleted-layouts.pptx new file mode 100644 index 000000000..1298870e2 Binary files /dev/null and b/test/pptx/speaker-notes-after-metadata/deleted-layouts.pptx differ diff --git a/test/pptx/speaker-notes-after-metadata/input.native b/test/pptx/speaker-notes-after-metadata/input.native new file mode 100644 index 000000000..6fda4b1ab --- /dev/null +++ b/test/pptx/speaker-notes-after-metadata/input.native @@ -0,0 +1,5 @@ +Pandoc (Meta {unMeta = fromList [("author",MetaInlines [Str "Jesse",Space,Str "Rosenthal"]),("title",MetaInlines [Str "Testing"])]}) +[Div ("",["notes"],[]) + [Para [Str "Some",Space,Str "speaker",Space,Str "notes"]] +,Header 1 ("a-header",[],[]) [Str "A",Space,Str "header"] +,Para [Str "And",Space,Str "a",Space,Str "new",Space,Str "slide."]] diff --git a/test/pptx/speaker-notes-after-metadata/moved-layouts.pptx b/test/pptx/speaker-notes-after-metadata/moved-layouts.pptx new file mode 100644 index 000000000..b844a0b51 Binary files /dev/null and b/test/pptx/speaker-notes-after-metadata/moved-layouts.pptx differ diff --git a/test/pptx/speaker-notes-after-metadata/output.pptx b/test/pptx/speaker-notes-after-metadata/output.pptx new file mode 100644 index 000000000..6343bffe4 Binary files /dev/null and b/test/pptx/speaker-notes-after-metadata/output.pptx differ diff --git a/test/pptx/speaker-notes-after-metadata/templated.pptx b/test/pptx/speaker-notes-after-metadata/templated.pptx new file mode 100644 index 000000000..8d27c4c68 Binary files /dev/null and b/test/pptx/speaker-notes-after-metadata/templated.pptx differ diff --git a/test/pptx/speaker-notes-afterheader/deleted-layouts.pptx b/test/pptx/speaker-notes-afterheader/deleted-layouts.pptx new file mode 100644 index 000000000..853b918cb Binary files /dev/null and b/test/pptx/speaker-notes-afterheader/deleted-layouts.pptx differ diff --git a/test/pptx/speaker-notes-afterheader/input.native b/test/pptx/speaker-notes-afterheader/input.native new file mode 100644 index 000000000..0f7dd95d7 --- /dev/null +++ b/test/pptx/speaker-notes-afterheader/input.native @@ -0,0 +1,3 @@ +[Header 1 ("here-is-a-single-header",[],[]) [Str "Here",Space,Str "is",Space,Str "a",Space,Str "single",Space,Str "header"] +,Div ("",["notes"],[]) + [Para [Str "and",Space,Str "here",Space,Str "are",Space,Str "some",Space,Str "notes"]]] diff --git a/test/pptx/speaker-notes-afterheader/moved-layouts.pptx b/test/pptx/speaker-notes-afterheader/moved-layouts.pptx new file mode 100644 index 000000000..9fff9f855 Binary files /dev/null and b/test/pptx/speaker-notes-afterheader/moved-layouts.pptx differ diff --git a/test/pptx/speaker-notes-afterheader/output.pptx b/test/pptx/speaker-notes-afterheader/output.pptx new file mode 100644 index 000000000..d581681aa Binary files /dev/null and b/test/pptx/speaker-notes-afterheader/output.pptx differ diff --git a/test/pptx/speaker-notes-afterheader/templated.pptx b/test/pptx/speaker-notes-afterheader/templated.pptx new file mode 100644 index 000000000..d8d8481df Binary files /dev/null and b/test/pptx/speaker-notes-afterheader/templated.pptx differ diff --git a/test/pptx/speaker-notes-afterseps/deleted-layouts.pptx b/test/pptx/speaker-notes-afterseps/deleted-layouts.pptx new file mode 100644 index 000000000..9fec1c279 Binary files /dev/null and b/test/pptx/speaker-notes-afterseps/deleted-layouts.pptx differ diff --git a/test/pptx/speaker-notes-afterseps/input.native b/test/pptx/speaker-notes-afterseps/input.native new file mode 100644 index 000000000..4fd7b1ccb --- /dev/null +++ b/test/pptx/speaker-notes-afterseps/input.native @@ -0,0 +1,63 @@ +[Para [Image ("",[],[]) [Str "The",Space,Str "moon"] ("lalune.jpg","fig:")] +,Div ("",["notes"],[]) + [Para [Str "chicken",Space,Str "and",Space,Str "dumplings"]] +,Table ("",[],[]) (Caption Nothing + [Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax,",Space,Str "with",Space,Str "alignment"]]) + [(AlignRight,ColWidthDefault) + ,(AlignLeft,ColWidthDefault) + ,(AlignCenter,ColWidthDefault) + ,(AlignDefault,ColWidthDefault)] + (TableHead ("",[],[]) + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "Right"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "Left"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "Center"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "Default"]]]]) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "12"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "12"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "12"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "123"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "123"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "123"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]]]])] + (TableFoot ("",[],[]) + []) +,Div ("",["notes"],[]) + [Para [Str "foo",Space,Str "bar"]] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [BulletList + [[Para [Str "some",Space,Str "stuff"]] + ,[Para [Str "some",Space,Str "more",Space,Str "stuff"]]] + ,Div ("",["notes"],[]) + [Para [Str "Some",Space,Str "notes",Space,Str "inside",Space,Str "a",Space,Str "column"]]] + ,Div ("",["column"],[]) + [Para [Str "Some",Space,Str "other",Space,Emph [Str "stuff"]]]] +,Div ("",["notes"],[]) + [Para [Str "Some",Space,Str "notes",Space,Str "outside",Space,Str "the",Space,Str "column"]]] \ No newline at end of file diff --git a/test/pptx/speaker-notes-afterseps/moved-layouts.pptx b/test/pptx/speaker-notes-afterseps/moved-layouts.pptx new file mode 100644 index 000000000..de697cbd8 Binary files /dev/null and b/test/pptx/speaker-notes-afterseps/moved-layouts.pptx differ diff --git a/test/pptx/speaker-notes-afterseps/output.pptx b/test/pptx/speaker-notes-afterseps/output.pptx new file mode 100644 index 000000000..9542fe8b5 Binary files /dev/null and b/test/pptx/speaker-notes-afterseps/output.pptx differ diff --git a/test/pptx/speaker-notes-afterseps/templated.pptx b/test/pptx/speaker-notes-afterseps/templated.pptx new file mode 100644 index 000000000..5a3d15d57 Binary files /dev/null and b/test/pptx/speaker-notes-afterseps/templated.pptx differ diff --git a/test/pptx/speaker-notes/deleted-layouts.pptx b/test/pptx/speaker-notes/deleted-layouts.pptx new file mode 100644 index 000000000..6a5ad524f Binary files /dev/null and b/test/pptx/speaker-notes/deleted-layouts.pptx differ diff --git a/test/pptx/speaker-notes/input.native b/test/pptx/speaker-notes/input.native new file mode 100644 index 000000000..4eeca2107 --- /dev/null +++ b/test/pptx/speaker-notes/input.native @@ -0,0 +1,17 @@ +[Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "slide."] +,Div ("",["notes"],[]) + [Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "note."] + ,Para [Str "Here",Space,Str "is",Space,Emph [Str "some"],Space,Strong [Str "other"],Space,Str "formatting."]] +,HorizontalRule +,Para [Str "A",Space,Str "page",Space,Str "with",Space,Str "no",Space,Str "speaker",Space,Str "notes"] +,HorizontalRule +,Div ("",["notes"],[]) + [Para [Str "The",Space,Str "first",Space,Str "note",Space,Str "div"]] +,Para [Str "A",Space,Str "page",Space,Str "with",Space,Str "two",Space,Str "notes."] +,Div ("",["notes"],[]) + [Para [Str "The",Space,Str "second",Space,Str "note",Space,Str "div"]] +,HorizontalRule +,Para [Str "Strip",Space,Str "links",Space,Str "and",Space,Str "footnotes."] +,Div ("",["notes"],[]) + [Para [Str "No",Space,Link ("",[],[]) [Str "link"] ("https://www.google.com",""),Space,Str "here."] + ,Para [Str "No",Space,Str "note",Space,Str "here.",Note [Para [Str "You\8217ll",Space,Str "never",Space,Str "read",Space,Str "this"]]]]] diff --git a/test/pptx/speaker-notes/moved-layouts.pptx b/test/pptx/speaker-notes/moved-layouts.pptx new file mode 100644 index 000000000..f95df9622 Binary files /dev/null and b/test/pptx/speaker-notes/moved-layouts.pptx differ diff --git a/test/pptx/speaker-notes/output.pptx b/test/pptx/speaker-notes/output.pptx new file mode 100644 index 000000000..0ab1302da Binary files /dev/null and b/test/pptx/speaker-notes/output.pptx differ diff --git a/test/pptx/speaker-notes/templated.pptx b/test/pptx/speaker-notes/templated.pptx new file mode 100644 index 000000000..930377fbf Binary files /dev/null and b/test/pptx/speaker-notes/templated.pptx differ diff --git a/test/pptx/speaker_notes.native b/test/pptx/speaker_notes.native deleted file mode 100644 index 4eeca2107..000000000 --- a/test/pptx/speaker_notes.native +++ /dev/null @@ -1,17 +0,0 @@ -[Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "slide."] -,Div ("",["notes"],[]) - [Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "note."] - ,Para [Str "Here",Space,Str "is",Space,Emph [Str "some"],Space,Strong [Str "other"],Space,Str "formatting."]] -,HorizontalRule -,Para [Str "A",Space,Str "page",Space,Str "with",Space,Str "no",Space,Str "speaker",Space,Str "notes"] -,HorizontalRule -,Div ("",["notes"],[]) - [Para [Str "The",Space,Str "first",Space,Str "note",Space,Str "div"]] -,Para [Str "A",Space,Str "page",Space,Str "with",Space,Str "two",Space,Str "notes."] -,Div ("",["notes"],[]) - [Para [Str "The",Space,Str "second",Space,Str "note",Space,Str "div"]] -,HorizontalRule -,Para [Str "Strip",Space,Str "links",Space,Str "and",Space,Str "footnotes."] -,Div ("",["notes"],[]) - [Para [Str "No",Space,Link ("",[],[]) [Str "link"] ("https://www.google.com",""),Space,Str "here."] - ,Para [Str "No",Space,Str "note",Space,Str "here.",Note [Para [Str "You\8217ll",Space,Str "never",Space,Str "read",Space,Str "this"]]]]] diff --git a/test/pptx/speaker_notes.pptx b/test/pptx/speaker_notes.pptx deleted file mode 100644 index 0ab1302da..000000000 Binary files a/test/pptx/speaker_notes.pptx and /dev/null differ diff --git a/test/pptx/speaker_notes_after_metadata.native b/test/pptx/speaker_notes_after_metadata.native deleted file mode 100644 index 6fda4b1ab..000000000 --- a/test/pptx/speaker_notes_after_metadata.native +++ /dev/null @@ -1,5 +0,0 @@ -Pandoc (Meta {unMeta = fromList [("author",MetaInlines [Str "Jesse",Space,Str "Rosenthal"]),("title",MetaInlines [Str "Testing"])]}) -[Div ("",["notes"],[]) - [Para [Str "Some",Space,Str "speaker",Space,Str "notes"]] -,Header 1 ("a-header",[],[]) [Str "A",Space,Str "header"] -,Para [Str "And",Space,Str "a",Space,Str "new",Space,Str "slide."]] diff --git a/test/pptx/speaker_notes_after_metadata.pptx b/test/pptx/speaker_notes_after_metadata.pptx deleted file mode 100644 index 6343bffe4..000000000 Binary files a/test/pptx/speaker_notes_after_metadata.pptx and /dev/null differ diff --git a/test/pptx/speaker_notes_after_metadata_deleted_layouts.pptx b/test/pptx/speaker_notes_after_metadata_deleted_layouts.pptx deleted file mode 100644 index 1298870e2..000000000 Binary files a/test/pptx/speaker_notes_after_metadata_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/speaker_notes_after_metadata_moved_layouts.pptx b/test/pptx/speaker_notes_after_metadata_moved_layouts.pptx deleted file mode 100644 index b844a0b51..000000000 Binary files a/test/pptx/speaker_notes_after_metadata_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/speaker_notes_after_metadata_templated.pptx b/test/pptx/speaker_notes_after_metadata_templated.pptx deleted file mode 100644 index 8d27c4c68..000000000 Binary files a/test/pptx/speaker_notes_after_metadata_templated.pptx and /dev/null differ diff --git a/test/pptx/speaker_notes_afterheader.native b/test/pptx/speaker_notes_afterheader.native deleted file mode 100644 index 0f7dd95d7..000000000 --- a/test/pptx/speaker_notes_afterheader.native +++ /dev/null @@ -1,3 +0,0 @@ -[Header 1 ("here-is-a-single-header",[],[]) [Str "Here",Space,Str "is",Space,Str "a",Space,Str "single",Space,Str "header"] -,Div ("",["notes"],[]) - [Para [Str "and",Space,Str "here",Space,Str "are",Space,Str "some",Space,Str "notes"]]] diff --git a/test/pptx/speaker_notes_afterheader.pptx b/test/pptx/speaker_notes_afterheader.pptx deleted file mode 100644 index d581681aa..000000000 Binary files a/test/pptx/speaker_notes_afterheader.pptx and /dev/null differ diff --git a/test/pptx/speaker_notes_afterheader_deleted_layouts.pptx b/test/pptx/speaker_notes_afterheader_deleted_layouts.pptx deleted file mode 100644 index 853b918cb..000000000 Binary files a/test/pptx/speaker_notes_afterheader_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/speaker_notes_afterheader_moved_layouts.pptx b/test/pptx/speaker_notes_afterheader_moved_layouts.pptx deleted file mode 100644 index 9fff9f855..000000000 Binary files a/test/pptx/speaker_notes_afterheader_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/speaker_notes_afterheader_templated.pptx b/test/pptx/speaker_notes_afterheader_templated.pptx deleted file mode 100644 index d8d8481df..000000000 Binary files a/test/pptx/speaker_notes_afterheader_templated.pptx and /dev/null differ diff --git a/test/pptx/speaker_notes_afterseps.native b/test/pptx/speaker_notes_afterseps.native deleted file mode 100644 index 4fd7b1ccb..000000000 --- a/test/pptx/speaker_notes_afterseps.native +++ /dev/null @@ -1,63 +0,0 @@ -[Para [Image ("",[],[]) [Str "The",Space,Str "moon"] ("lalune.jpg","fig:")] -,Div ("",["notes"],[]) - [Para [Str "chicken",Space,Str "and",Space,Str "dumplings"]] -,Table ("",[],[]) (Caption Nothing - [Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax,",Space,Str "with",Space,Str "alignment"]]) - [(AlignRight,ColWidthDefault) - ,(AlignLeft,ColWidthDefault) - ,(AlignCenter,ColWidthDefault) - ,(AlignDefault,ColWidthDefault)] - (TableHead ("",[],[]) - [Row ("",[],[]) - [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "Right"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "Left"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "Center"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "Default"]]]]) - [(TableBody ("",[],[]) (RowHeadColumns 0) - [] - [Row ("",[],[]) - [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "12"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "12"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "12"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "12"]]] - ,Row ("",[],[]) - [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "123"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "123"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "123"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "123"]]] - ,Row ("",[],[]) - [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "1"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "1"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "1"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "1"]]]])] - (TableFoot ("",[],[]) - []) -,Div ("",["notes"],[]) - [Para [Str "foo",Space,Str "bar"]] -,Div ("",["columns"],[]) - [Div ("",["column"],[]) - [BulletList - [[Para [Str "some",Space,Str "stuff"]] - ,[Para [Str "some",Space,Str "more",Space,Str "stuff"]]] - ,Div ("",["notes"],[]) - [Para [Str "Some",Space,Str "notes",Space,Str "inside",Space,Str "a",Space,Str "column"]]] - ,Div ("",["column"],[]) - [Para [Str "Some",Space,Str "other",Space,Emph [Str "stuff"]]]] -,Div ("",["notes"],[]) - [Para [Str "Some",Space,Str "notes",Space,Str "outside",Space,Str "the",Space,Str "column"]]] \ No newline at end of file diff --git a/test/pptx/speaker_notes_afterseps.pptx b/test/pptx/speaker_notes_afterseps.pptx deleted file mode 100644 index 9542fe8b5..000000000 Binary files a/test/pptx/speaker_notes_afterseps.pptx and /dev/null differ diff --git a/test/pptx/speaker_notes_afterseps_deleted_layouts.pptx b/test/pptx/speaker_notes_afterseps_deleted_layouts.pptx deleted file mode 100644 index 9fec1c279..000000000 Binary files a/test/pptx/speaker_notes_afterseps_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/speaker_notes_afterseps_moved_layouts.pptx b/test/pptx/speaker_notes_afterseps_moved_layouts.pptx deleted file mode 100644 index de697cbd8..000000000 Binary files a/test/pptx/speaker_notes_afterseps_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/speaker_notes_afterseps_templated.pptx b/test/pptx/speaker_notes_afterseps_templated.pptx deleted file mode 100644 index 5a3d15d57..000000000 Binary files a/test/pptx/speaker_notes_afterseps_templated.pptx and /dev/null differ diff --git a/test/pptx/speaker_notes_deleted_layouts.pptx b/test/pptx/speaker_notes_deleted_layouts.pptx deleted file mode 100644 index 6a5ad524f..000000000 Binary files a/test/pptx/speaker_notes_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/speaker_notes_moved_layouts.pptx b/test/pptx/speaker_notes_moved_layouts.pptx deleted file mode 100644 index f95df9622..000000000 Binary files a/test/pptx/speaker_notes_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/speaker_notes_templated.pptx b/test/pptx/speaker_notes_templated.pptx deleted file mode 100644 index 930377fbf..000000000 Binary files a/test/pptx/speaker_notes_templated.pptx and /dev/null differ diff --git a/test/pptx/start-numbering-at/deleted-layouts.pptx b/test/pptx/start-numbering-at/deleted-layouts.pptx new file mode 100644 index 000000000..d9cf91804 Binary files /dev/null and b/test/pptx/start-numbering-at/deleted-layouts.pptx differ diff --git a/test/pptx/start-numbering-at/input.native b/test/pptx/start-numbering-at/input.native new file mode 100644 index 000000000..ecffbb0ef --- /dev/null +++ b/test/pptx/start-numbering-at/input.native @@ -0,0 +1,9 @@ +[Header 2 ("example-numbering-mwe",[],[]) [Str "Example",Space,Str "numbering",Space,Str "MWE"] +,Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "slide",Space,Str "with",Space,Str "examples",Space,Str "in",Space,Str "(1)",Space,Str "and",Space,Str "(2)"] +,OrderedList (1,Example,TwoParens) + [[Plain [Str "First"]] + ,[Plain [Str "Second"]]] +,Header 2 ("a-second-slide",[],[]) [Str "A",Space,Str "second",Space,Str "slide"] +,Para [Str "This",Space,Str "second",Space,Str "slide",Space,Str "has",Space,Str "a",Space,Str "third",Space,Str "example",Space,Str "in",Space,Str "(3)."] +,OrderedList (3,Example,TwoParens) + [[Plain [Str "Third"]]]] diff --git a/test/pptx/start-numbering-at/moved-layouts.pptx b/test/pptx/start-numbering-at/moved-layouts.pptx new file mode 100644 index 000000000..e1b2d4de8 Binary files /dev/null and b/test/pptx/start-numbering-at/moved-layouts.pptx differ diff --git a/test/pptx/start-numbering-at/output.pptx b/test/pptx/start-numbering-at/output.pptx new file mode 100644 index 000000000..4320128b3 Binary files /dev/null and b/test/pptx/start-numbering-at/output.pptx differ diff --git a/test/pptx/start-numbering-at/templated.pptx b/test/pptx/start-numbering-at/templated.pptx new file mode 100644 index 000000000..efc56ac7a Binary files /dev/null and b/test/pptx/start-numbering-at/templated.pptx differ diff --git a/test/pptx/start_numbering_at.native b/test/pptx/start_numbering_at.native deleted file mode 100644 index ecffbb0ef..000000000 --- a/test/pptx/start_numbering_at.native +++ /dev/null @@ -1,9 +0,0 @@ -[Header 2 ("example-numbering-mwe",[],[]) [Str "Example",Space,Str "numbering",Space,Str "MWE"] -,Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "slide",Space,Str "with",Space,Str "examples",Space,Str "in",Space,Str "(1)",Space,Str "and",Space,Str "(2)"] -,OrderedList (1,Example,TwoParens) - [[Plain [Str "First"]] - ,[Plain [Str "Second"]]] -,Header 2 ("a-second-slide",[],[]) [Str "A",Space,Str "second",Space,Str "slide"] -,Para [Str "This",Space,Str "second",Space,Str "slide",Space,Str "has",Space,Str "a",Space,Str "third",Space,Str "example",Space,Str "in",Space,Str "(3)."] -,OrderedList (3,Example,TwoParens) - [[Plain [Str "Third"]]]] diff --git a/test/pptx/start_numbering_at.pptx b/test/pptx/start_numbering_at.pptx deleted file mode 100644 index 4320128b3..000000000 Binary files a/test/pptx/start_numbering_at.pptx and /dev/null differ diff --git a/test/pptx/start_numbering_at_deleted_layouts.pptx b/test/pptx/start_numbering_at_deleted_layouts.pptx deleted file mode 100644 index d9cf91804..000000000 Binary files a/test/pptx/start_numbering_at_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/start_numbering_at_moved_layouts.pptx b/test/pptx/start_numbering_at_moved_layouts.pptx deleted file mode 100644 index e1b2d4de8..000000000 Binary files a/test/pptx/start_numbering_at_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/start_numbering_at_templated.pptx b/test/pptx/start_numbering_at_templated.pptx deleted file mode 100644 index efc56ac7a..000000000 Binary files a/test/pptx/start_numbering_at_templated.pptx and /dev/null differ diff --git a/test/pptx/tables.native b/test/pptx/tables.native deleted file mode 100644 index 27b843f2b..000000000 --- a/test/pptx/tables.native +++ /dev/null @@ -1,95 +0,0 @@ -[Header 2 ("a-table-with-a-caption",[],[]) [Str "A",Space,Str "Table,",Space,Str "with",Space,Str "a",Space,Str "caption"] -,Table ("",[],[]) (Caption Nothing - [Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax,",Space,Str "with",Space,Str "alignment"]]) - [(AlignRight,ColWidthDefault) - ,(AlignLeft,ColWidthDefault) - ,(AlignCenter,ColWidthDefault) - ,(AlignDefault,ColWidthDefault)] - (TableHead ("",[],[]) - [Row ("",[],[]) - [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "Right"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "Left"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "Center"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "Default"]]]]) - [(TableBody ("",[],[]) (RowHeadColumns 0) - [] - [Row ("",[],[]) - [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "12"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "12"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "12"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "12"]]] - ,Row ("",[],[]) - [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "123"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "123"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "123"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "123"]]] - ,Row ("",[],[]) - [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "1"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "1"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "1"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "1"]]]])] - (TableFoot ("",[],[]) - []) -,Table ("",[],[]) (Caption Nothing - []) - [(AlignRight,ColWidthDefault) - ,(AlignLeft,ColWidthDefault) - ,(AlignCenter,ColWidthDefault) - ,(AlignDefault,ColWidthDefault)] - (TableHead ("",[],[]) - [Row ("",[],[]) - [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "Right"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "Left"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "Center"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "Default"]]]]) - [(TableBody ("",[],[]) (RowHeadColumns 0) - [] - [Row ("",[],[]) - [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "12"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "12"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "12"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "12"]]] - ,Row ("",[],[]) - [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "123"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "123"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "123"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "123"]]] - ,Row ("",[],[]) - [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "1"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "1"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "1"]] - ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) - [Plain [Str "1"]]]])] - (TableFoot ("",[],[]) - [])] \ No newline at end of file diff --git a/test/pptx/tables.pptx b/test/pptx/tables.pptx deleted file mode 100644 index e41219844..000000000 Binary files a/test/pptx/tables.pptx and /dev/null differ diff --git a/test/pptx/tables/deleted-layouts.pptx b/test/pptx/tables/deleted-layouts.pptx new file mode 100644 index 000000000..a52222551 Binary files /dev/null and b/test/pptx/tables/deleted-layouts.pptx differ diff --git a/test/pptx/tables/input.native b/test/pptx/tables/input.native new file mode 100644 index 000000000..27b843f2b --- /dev/null +++ b/test/pptx/tables/input.native @@ -0,0 +1,95 @@ +[Header 2 ("a-table-with-a-caption",[],[]) [Str "A",Space,Str "Table,",Space,Str "with",Space,Str "a",Space,Str "caption"] +,Table ("",[],[]) (Caption Nothing + [Para [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax,",Space,Str "with",Space,Str "alignment"]]) + [(AlignRight,ColWidthDefault) + ,(AlignLeft,ColWidthDefault) + ,(AlignCenter,ColWidthDefault) + ,(AlignDefault,ColWidthDefault)] + (TableHead ("",[],[]) + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "Right"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "Left"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "Center"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "Default"]]]]) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "12"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "12"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "12"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "123"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "123"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "123"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]]]])] + (TableFoot ("",[],[]) + []) +,Table ("",[],[]) (Caption Nothing + []) + [(AlignRight,ColWidthDefault) + ,(AlignLeft,ColWidthDefault) + ,(AlignCenter,ColWidthDefault) + ,(AlignDefault,ColWidthDefault)] + (TableHead ("",[],[]) + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "Right"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "Left"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "Center"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "Default"]]]]) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "12"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "12"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "12"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "12"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "123"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "123"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "123"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "123"]]] + ,Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]]]])] + (TableFoot ("",[],[]) + [])] \ No newline at end of file diff --git a/test/pptx/tables/moved-layouts.pptx b/test/pptx/tables/moved-layouts.pptx new file mode 100644 index 000000000..56608a039 Binary files /dev/null and b/test/pptx/tables/moved-layouts.pptx differ diff --git a/test/pptx/tables/output.pptx b/test/pptx/tables/output.pptx new file mode 100644 index 000000000..e41219844 Binary files /dev/null and b/test/pptx/tables/output.pptx differ diff --git a/test/pptx/tables/templated.pptx b/test/pptx/tables/templated.pptx new file mode 100644 index 000000000..0a8c3e8d9 Binary files /dev/null and b/test/pptx/tables/templated.pptx differ diff --git a/test/pptx/tables_deleted_layouts.pptx b/test/pptx/tables_deleted_layouts.pptx deleted file mode 100644 index a52222551..000000000 Binary files a/test/pptx/tables_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/tables_moved_layouts.pptx b/test/pptx/tables_moved_layouts.pptx deleted file mode 100644 index 56608a039..000000000 Binary files a/test/pptx/tables_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/tables_templated.pptx b/test/pptx/tables_templated.pptx deleted file mode 100644 index 0a8c3e8d9..000000000 Binary files a/test/pptx/tables_templated.pptx and /dev/null differ diff --git a/test/pptx/two-column/deleted-layouts.pptx b/test/pptx/two-column/deleted-layouts.pptx new file mode 100644 index 000000000..60a244f94 Binary files /dev/null and b/test/pptx/two-column/deleted-layouts.pptx differ diff --git a/test/pptx/two-column/input.native b/test/pptx/two-column/input.native new file mode 100644 index 000000000..086f74889 --- /dev/null +++ b/test/pptx/two-column/input.native @@ -0,0 +1,9 @@ +Pandoc (Meta {unMeta = fromList []}) +[Header 1 ("two-column-layout",[],[]) [Str "Two-Column",Space,Str "Layout"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Str "One",Space,Str "paragraph."] + ,Para [Str "Another",Space,Str "paragraph."]] + ,Div ("",["column"],[]) + [Para [Str "Second",Space,Str "column",Space,Str "paragraph."] + ,Para [Str "Another",Space,Str "second",Space,Str "paragraph."]]]] diff --git a/test/pptx/two-column/moved-layouts.pptx b/test/pptx/two-column/moved-layouts.pptx new file mode 100644 index 000000000..a17f96b18 Binary files /dev/null and b/test/pptx/two-column/moved-layouts.pptx differ diff --git a/test/pptx/two-column/output.pptx b/test/pptx/two-column/output.pptx new file mode 100644 index 000000000..270a7eeac Binary files /dev/null and b/test/pptx/two-column/output.pptx differ diff --git a/test/pptx/two-column/templated.pptx b/test/pptx/two-column/templated.pptx new file mode 100644 index 000000000..6d9470372 Binary files /dev/null and b/test/pptx/two-column/templated.pptx differ diff --git a/test/pptx/two_column.native b/test/pptx/two_column.native deleted file mode 100644 index 086f74889..000000000 --- a/test/pptx/two_column.native +++ /dev/null @@ -1,9 +0,0 @@ -Pandoc (Meta {unMeta = fromList []}) -[Header 1 ("two-column-layout",[],[]) [Str "Two-Column",Space,Str "Layout"] -,Div ("",["columns"],[]) - [Div ("",["column"],[]) - [Para [Str "One",Space,Str "paragraph."] - ,Para [Str "Another",Space,Str "paragraph."]] - ,Div ("",["column"],[]) - [Para [Str "Second",Space,Str "column",Space,Str "paragraph."] - ,Para [Str "Another",Space,Str "second",Space,Str "paragraph."]]]] diff --git a/test/pptx/two_column.pptx b/test/pptx/two_column.pptx deleted file mode 100644 index 270a7eeac..000000000 Binary files a/test/pptx/two_column.pptx and /dev/null differ diff --git a/test/pptx/two_column_deleted_layouts.pptx b/test/pptx/two_column_deleted_layouts.pptx deleted file mode 100644 index 60a244f94..000000000 Binary files a/test/pptx/two_column_deleted_layouts.pptx and /dev/null differ diff --git a/test/pptx/two_column_moved_layouts.pptx b/test/pptx/two_column_moved_layouts.pptx deleted file mode 100644 index a17f96b18..000000000 Binary files a/test/pptx/two_column_moved_layouts.pptx and /dev/null differ diff --git a/test/pptx/two_column_templated.pptx b/test/pptx/two_column_templated.pptx deleted file mode 100644 index 6d9470372..000000000 Binary files a/test/pptx/two_column_templated.pptx and /dev/null differ -- cgit v1.2.3 From b82a01b6883c1f6a9ce5d3edd80d5a2453ecef9e Mon Sep 17 00:00:00 2001 From: Emily Bourke Date: Thu, 19 Aug 2021 15:53:21 +0100 Subject: pptx: Add support for more layouts MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Until now, the pptx writer only supported four slide layouts: “Title Slide” (used for the automatically generated metadata slide), “Section Header” (used for headings above the slide level), “Two Column” (used when there’s a columns div containing at least two column divs), and “Title and Content” (used for all other slides). This commit adds support for three more layouts: Comparison, Content with Caption, and Blank. - Support “Comparison” slide layout This layout is used when a slide contains at least two columns, at least one of which contains some text followed by some non-text (e.g. an image or table). The text in each column is inserted into the “body” placeholder for that column, and the non-text is inserted into the ObjType placeholder. Any extra content after the non-text is overlaid on top of the preceding content, rather than dropping it completely (as currently happens for the two-column layout). + Accept straightforward test changes Adding the new layout means the “-deleted-layouts” tests have an additional layout added to the master and master rels. + Add new tests for the comparison layout + Add new tests to pandoc.cabal - Support “Content with Caption” slide layout This layout is used when a slide’s body contains some text, followed by non-text (e.g. and image or a table). Before now, in this case the image or table would break onto a new slide: to get that output again, users can add a horizontal rule before the image or table. + Accept straightforward tests The “-deleted-layouts” tests all have an extra layout and relationship in the master for the Content with Caption layout. + Accept remove-empty-slides test Empty slides are still removed, but the Content with Caption layout is now used. + Change slide-level-0/h1-h2-with-text description This test now triggers the content with caption layout, giving a different (but still correct) result. + Add new tests for the new layout + Add new tests to the cabal file - Support “Blank” slide layout This layout is used when a slide contains only blank content (e.g. non-breaking spaces). No content is inserted into any placeholders in the layout. Fixes #5097. + Accept straightforward test changes Blank layout now copied over from reference doc as well, when layouts have been deleted. + Add some new tests A slide should use the blank layout if: - It contains only speaker notes - It contains only an empty heading with a body of nbsps - It contains only a heading containing only nbsps - Change ContentType -> Placeholder This type was starting to have a constructor for each placeholder on each slide (e.g. `ComparisonUpperLeftContent`). I’ve changed it instead to identify a placeholder by type and index, as I think that’s clearer and less redundant. - Describe layout-choosing logic in manual --- MANUAL.txt | 52 +++++- pandoc.cabal | 30 +++- src/Text/Pandoc/Writers/Powerpoint/Output.hs | 179 ++++++++++++++++--- src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | 189 +++++++++++++++++---- test/Tests/Writers/Powerpoint.hs | 61 ++++++- .../blanks/just-speaker-notes/deleted-layouts.pptx | Bin 0 -> 35181 bytes test/pptx/blanks/just-speaker-notes/input.native | 7 + .../blanks/just-speaker-notes/moved-layouts.pptx | Bin 0 -> 45873 bytes test/pptx/blanks/just-speaker-notes/output.pptx | Bin 0 -> 32304 bytes test/pptx/blanks/just-speaker-notes/templated.pptx | Bin 0 -> 45369 bytes test/pptx/blanks/nbsp-in-body/deleted-layouts.pptx | Bin 0 -> 30444 bytes test/pptx/blanks/nbsp-in-body/input.native | 6 + test/pptx/blanks/nbsp-in-body/moved-layouts.pptx | Bin 0 -> 41131 bytes test/pptx/blanks/nbsp-in-body/output.pptx | Bin 0 -> 27562 bytes test/pptx/blanks/nbsp-in-body/templated.pptx | Bin 0 -> 40630 bytes .../blanks/nbsp-in-heading/deleted-layouts.pptx | Bin 0 -> 30444 bytes test/pptx/blanks/nbsp-in-heading/input.native | 5 + .../pptx/blanks/nbsp-in-heading/moved-layouts.pptx | Bin 0 -> 41131 bytes test/pptx/blanks/nbsp-in-heading/output.pptx | Bin 0 -> 27562 bytes test/pptx/blanks/nbsp-in-heading/templated.pptx | Bin 0 -> 40630 bytes test/pptx/code-custom/deleted-layouts.pptx | Bin 31033 -> 31069 bytes test/pptx/code/deleted-layouts.pptx | Bin 31032 -> 31068 bytes .../comparison/both-columns/deleted-layouts.pptx | Bin 0 -> 45804 bytes test/pptx/comparison/both-columns/input.native | 23 +++ .../comparison/both-columns/moved-layouts.pptx | Bin 0 -> 56524 bytes test/pptx/comparison/both-columns/output.pptx | Bin 0 -> 42932 bytes test/pptx/comparison/both-columns/templated.pptx | Bin 0 -> 56025 bytes .../comparison/extra-image/deleted-layouts.pptx | Bin 0 -> 45833 bytes test/pptx/comparison/extra-image/input.native | 24 +++ .../pptx/comparison/extra-image/moved-layouts.pptx | Bin 0 -> 56552 bytes test/pptx/comparison/extra-image/output.pptx | Bin 0 -> 42961 bytes test/pptx/comparison/extra-image/templated.pptx | Bin 0 -> 56053 bytes .../comparison/extra-text/deleted-layouts.pptx | Bin 0 -> 45804 bytes test/pptx/comparison/extra-text/input.native | 23 +++ test/pptx/comparison/extra-text/moved-layouts.pptx | Bin 0 -> 56524 bytes test/pptx/comparison/extra-text/output.pptx | Bin 0 -> 42932 bytes test/pptx/comparison/extra-text/templated.pptx | Bin 0 -> 56025 bytes .../comparison/non-text-first/deleted-layouts.pptx | Bin 0 -> 45717 bytes test/pptx/comparison/non-text-first/input.native | 21 +++ .../comparison/non-text-first/moved-layouts.pptx | Bin 0 -> 56417 bytes test/pptx/comparison/non-text-first/output.pptx | Bin 0 -> 42845 bytes test/pptx/comparison/non-text-first/templated.pptx | Bin 0 -> 55918 bytes .../comparison/one-column/deleted-layouts.pptx | Bin 0 -> 29136 bytes test/pptx/comparison/one-column/input.native | 21 +++ test/pptx/comparison/one-column/moved-layouts.pptx | Bin 0 -> 39856 bytes test/pptx/comparison/one-column/output.pptx | Bin 0 -> 26258 bytes test/pptx/comparison/one-column/templated.pptx | Bin 0 -> 39357 bytes .../heading-text-image/deleted-layouts.pptx | Bin 0 -> 45549 bytes .../heading-text-image/input.native | 3 + .../heading-text-image/moved-layouts.pptx | Bin 0 -> 56248 bytes .../heading-text-image/output.pptx | Bin 0 -> 42677 bytes .../heading-text-image/templated.pptx | Bin 0 -> 55749 bytes .../image-text/deleted-layouts.pptx | Bin 0 -> 46248 bytes .../content-with-caption/image-text/input.native | 2 + .../image-text/moved-layouts.pptx | Bin 0 -> 56934 bytes .../content-with-caption/image-text/output.pptx | Bin 0 -> 43374 bytes .../content-with-caption/image-text/templated.pptx | Bin 0 -> 56435 bytes .../text-image/deleted-layouts.pptx | Bin 0 -> 45488 bytes .../content-with-caption/text-image/input.native | 2 + .../text-image/moved-layouts.pptx | Bin 0 -> 56188 bytes .../content-with-caption/text-image/output.pptx | Bin 0 -> 42616 bytes .../content-with-caption/text-image/templated.pptx | Bin 0 -> 55689 bytes .../deleted-layouts.pptx | Bin 29806 -> 29842 bytes test/pptx/document-properties/deleted-layouts.pptx | Bin 30210 -> 30246 bytes test/pptx/endnotes-toc/deleted-layouts.pptx | Bin 30596 -> 30632 bytes test/pptx/endnotes/deleted-layouts.pptx | Bin 29774 -> 29810 bytes test/pptx/images/deleted-layouts.pptx | Bin 47437 -> 47473 bytes test/pptx/inline-formatting/deleted-layouts.pptx | Bin 28966 -> 29002 bytes test/pptx/lists/deleted-layouts.pptx | Bin 29861 -> 29897 bytes test/pptx/raw-ooxml/deleted-layouts.pptx | Bin 29754 -> 29790 bytes test/pptx/remove-empty-slides/deleted-layouts.pptx | Bin 46867 -> 46218 bytes test/pptx/remove-empty-slides/moved-layouts.pptx | Bin 57656 -> 56903 bytes test/pptx/remove-empty-slides/output.pptx | Bin 44025 -> 43346 bytes test/pptx/remove-empty-slides/templated.pptx | Bin 57172 -> 56404 bytes .../deleted-layouts.pptx | Bin 30554 -> 30590 bytes test/pptx/slide-breaks-toc/deleted-layouts.pptx | Bin 32328 -> 32364 bytes test/pptx/slide-breaks/deleted-layouts.pptx | Bin 31378 -> 31414 bytes .../h1-h2-with-table/deleted-layouts.pptx | Bin 29828 -> 29137 bytes .../h1-h2-with-table/moved-layouts.pptx | Bin 40552 -> 39829 bytes .../slide-level-0/h1-h2-with-table/output.pptx | Bin 26985 -> 26259 bytes .../slide-level-0/h1-h2-with-table/templated.pptx | Bin 40052 -> 39330 bytes .../h1-with-image/deleted-layouts.pptx | Bin 45433 -> 45469 bytes .../h1-with-table/deleted-layouts.pptx | Bin 29008 -> 29044 bytes .../h2-with-image/deleted-layouts.pptx | Bin 45433 -> 45469 bytes .../deleted-layouts.pptx | Bin 34473 -> 34509 bytes .../speaker-notes-afterheader/deleted-layouts.pptx | Bin 33500 -> 33536 bytes .../speaker-notes-afterseps/deleted-layouts.pptx | Bin 54396 -> 54432 bytes test/pptx/speaker-notes/deleted-layouts.pptx | Bin 38203 -> 38239 bytes test/pptx/start-numbering-at/deleted-layouts.pptx | Bin 29837 -> 29873 bytes test/pptx/tables/deleted-layouts.pptx | Bin 30381 -> 30417 bytes test/pptx/two-column/deleted-layouts.pptx | Bin 28883 -> 28919 bytes 91 files changed, 580 insertions(+), 68 deletions(-) create mode 100644 test/pptx/blanks/just-speaker-notes/deleted-layouts.pptx create mode 100644 test/pptx/blanks/just-speaker-notes/input.native create mode 100644 test/pptx/blanks/just-speaker-notes/moved-layouts.pptx create mode 100644 test/pptx/blanks/just-speaker-notes/output.pptx create mode 100644 test/pptx/blanks/just-speaker-notes/templated.pptx create mode 100644 test/pptx/blanks/nbsp-in-body/deleted-layouts.pptx create mode 100644 test/pptx/blanks/nbsp-in-body/input.native create mode 100644 test/pptx/blanks/nbsp-in-body/moved-layouts.pptx create mode 100644 test/pptx/blanks/nbsp-in-body/output.pptx create mode 100644 test/pptx/blanks/nbsp-in-body/templated.pptx create mode 100644 test/pptx/blanks/nbsp-in-heading/deleted-layouts.pptx create mode 100644 test/pptx/blanks/nbsp-in-heading/input.native create mode 100644 test/pptx/blanks/nbsp-in-heading/moved-layouts.pptx create mode 100644 test/pptx/blanks/nbsp-in-heading/output.pptx create mode 100644 test/pptx/blanks/nbsp-in-heading/templated.pptx create mode 100644 test/pptx/comparison/both-columns/deleted-layouts.pptx create mode 100644 test/pptx/comparison/both-columns/input.native create mode 100644 test/pptx/comparison/both-columns/moved-layouts.pptx create mode 100644 test/pptx/comparison/both-columns/output.pptx create mode 100644 test/pptx/comparison/both-columns/templated.pptx create mode 100644 test/pptx/comparison/extra-image/deleted-layouts.pptx create mode 100644 test/pptx/comparison/extra-image/input.native create mode 100644 test/pptx/comparison/extra-image/moved-layouts.pptx create mode 100644 test/pptx/comparison/extra-image/output.pptx create mode 100644 test/pptx/comparison/extra-image/templated.pptx create mode 100644 test/pptx/comparison/extra-text/deleted-layouts.pptx create mode 100644 test/pptx/comparison/extra-text/input.native create mode 100644 test/pptx/comparison/extra-text/moved-layouts.pptx create mode 100644 test/pptx/comparison/extra-text/output.pptx create mode 100644 test/pptx/comparison/extra-text/templated.pptx create mode 100644 test/pptx/comparison/non-text-first/deleted-layouts.pptx create mode 100644 test/pptx/comparison/non-text-first/input.native create mode 100644 test/pptx/comparison/non-text-first/moved-layouts.pptx create mode 100644 test/pptx/comparison/non-text-first/output.pptx create mode 100644 test/pptx/comparison/non-text-first/templated.pptx create mode 100644 test/pptx/comparison/one-column/deleted-layouts.pptx create mode 100644 test/pptx/comparison/one-column/input.native create mode 100644 test/pptx/comparison/one-column/moved-layouts.pptx create mode 100644 test/pptx/comparison/one-column/output.pptx create mode 100644 test/pptx/comparison/one-column/templated.pptx create mode 100644 test/pptx/content-with-caption/heading-text-image/deleted-layouts.pptx create mode 100644 test/pptx/content-with-caption/heading-text-image/input.native create mode 100644 test/pptx/content-with-caption/heading-text-image/moved-layouts.pptx create mode 100644 test/pptx/content-with-caption/heading-text-image/output.pptx create mode 100644 test/pptx/content-with-caption/heading-text-image/templated.pptx create mode 100644 test/pptx/content-with-caption/image-text/deleted-layouts.pptx create mode 100644 test/pptx/content-with-caption/image-text/input.native create mode 100644 test/pptx/content-with-caption/image-text/moved-layouts.pptx create mode 100644 test/pptx/content-with-caption/image-text/output.pptx create mode 100644 test/pptx/content-with-caption/image-text/templated.pptx create mode 100644 test/pptx/content-with-caption/text-image/deleted-layouts.pptx create mode 100644 test/pptx/content-with-caption/text-image/input.native create mode 100644 test/pptx/content-with-caption/text-image/moved-layouts.pptx create mode 100644 test/pptx/content-with-caption/text-image/output.pptx create mode 100644 test/pptx/content-with-caption/text-image/templated.pptx (limited to 'test/Tests/Writers') diff --git a/MANUAL.txt b/MANUAL.txt index f81f4c70b..afdd66ddd 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -1182,11 +1182,15 @@ header when requesting a document from a URL: - Title and Content - Section Header - Two Content + - Comparison + - Content with Caption + - Blank For each name, the first layout found with that name will be used. If no layout is found with one of the names, pandoc will output a warning and use the layout with that name from the default reference - doc instead. + doc instead. (How these layouts are used is described in [PowerPoint + layout choice](#powerpoint-layout-choice).) All templates included with a recent version of MS PowerPoint will fit these criteria. (You can click on `Layout` under the @@ -1195,8 +1199,8 @@ header when requesting a document from a URL: You can also modify the default `reference.pptx`: first run `pandoc -o custom-reference.pptx --print-default-data-file reference.pptx`, and then modify `custom-reference.pptx` - in MS PowerPoint (pandoc will use the first four layout - slides, as mentioned above). + in MS PowerPoint (pandoc will use the layouts with the names + listed above). `--epub-cover-image=`*FILE* @@ -5833,6 +5837,48 @@ you use deeper nesting of section levels with reveal.js unless you set `--slide-level=0` (which lets reveal.js produce a one-dimensional layout and only interprets horizontal rules as slide boundaries). +### PowerPoint layout choice + +When creating slides, the pptx writer chooses from a number of pre-defined +layouts, based on the content of the slide: + +Title Slide +: This layout is used for the initial slide, which is generated and + filled from the metadata fields `date`, `author`, and `title`, if + they are present. + +Section Header +: This layout is used for what pandoc calls “title slides”, i.e. + slides which start with a header which is above the slide level in + the hierarchy. + +Two Content +: This layout is used for two-column slides, i.e. slides containing a + div with class `columns` which contains at least two divs with class + `column`. + +Comparison +: This layout is used instead of “Two Content” for any two-column + slides in which at least one column contains text followed by + non-text (e.g. an image or a table). + +Content with Caption +: This layout is used for any non-two-column slides which contain text + followed by non-text (e.g. an image or a table). + +Blank +: This layout is used for any slides which only contain blank content, + e.g. a slide containing only speaker notes, or a slide containing + only a non-breaking space. + +Title and Content +: This layout is used for all slides which do not match the criteria + for another layout. + +These layouts are chosen from the default pptx reference doc included with +pandoc, unless an alternative reference doc is specified using +`--reference-doc`. + ## Incremental lists By default, these writers produce lists that display "all at once." diff --git a/pandoc.cabal b/pandoc.cabal index 7fb951488..3de7da39c 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -380,17 +380,31 @@ extra-source-files: test/rtf/*.native test/rtf/*.rtf test/pptx/*.pptx + test/pptx/blanks/just-speaker-notes/input.native + test/pptx/blanks/just-speaker-notes/*.pptx + test/pptx/blanks/nbsp-in-body/input.native + test/pptx/blanks/nbsp-in-body/*.pptx + test/pptx/blanks/nbsp-in-heading/input.native + test/pptx/blanks/nbsp-in-heading/*.pptx test/pptx/code-custom/*.pptx test/pptx/code/input.native test/pptx/code/*.pptx - test/pptx/comparison-both-columns/input.native - test/pptx/comparison-both-columns/*.pptx - test/pptx/comparison-extra-text/input.native - test/pptx/comparison-extra-text/*.pptx - test/pptx/comparison-non-text-first/input.native - test/pptx/comparison-non-text-first/*.pptx - test/pptx/comparison-one-column/input.native - test/pptx/comparison-one-column/*.pptx + test/pptx/content-with-caption/heading-text-image/input.native + test/pptx/content-with-caption/heading-text-image/*.pptx + test/pptx/content-with-caption/image-text/input.native + test/pptx/content-with-caption/image-text/*.pptx + test/pptx/content-with-caption/text-image/input.native + test/pptx/content-with-caption/text-image/*.pptx + test/pptx/comparison/both-columns/input.native + test/pptx/comparison/both-columns/*.pptx + test/pptx/comparison/extra-image/input.native + test/pptx/comparison/extra-image/*.pptx + test/pptx/comparison/extra-text/input.native + test/pptx/comparison/extra-text/*.pptx + test/pptx/comparison/non-text-first/input.native + test/pptx/comparison/non-text-first/*.pptx + test/pptx/comparison/one-column/input.native + test/pptx/comparison/one-column/*.pptx test/pptx/document-properties-short-desc/input.native test/pptx/document-properties-short-desc/*.pptx test/pptx/document-properties/input.native diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs index 0e6a67861..d83fb2182 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs @@ -1,6 +1,7 @@ {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} +{-# LANGUAGE RecordWildCards #-} {- | Module : Text.Pandoc.Writers.Powerpoint.Output Copyright : Copyright (C) 2017-2020 Jesse Rosenthal @@ -115,7 +116,7 @@ data WriterEnv = WriterEnv { envRefArchive :: Archive -- the end of the slide file name and -- the rId number , envSlideIdOffset :: Int - , envContentType :: ContentType + , envPlaceholder :: Placeholder , envSlideIdMap :: M.Map SlideId Int -- maps the slide number to the -- corresponding notes id number. If there @@ -139,7 +140,7 @@ instance Default WriterEnv where , envInNoteSlide = False , envCurSlideId = 1 , envSlideIdOffset = 1 - , envContentType = NormalContent + , envPlaceholder = Placeholder ObjType 0 , envSlideIdMap = mempty , envSpeakerNotesIdMap = mempty , envInSpeakerNotes = False @@ -153,6 +154,9 @@ data SlideLayoutsOf a = SlideLayouts , title :: a , content :: a , twoColumn :: a + , comparison :: a + , contentWithCaption :: a + , blank :: a } deriving (Show, Functor, Foldable, Traversable) data SlideLayout = SlideLayout @@ -170,10 +174,14 @@ getSlideLayouts = asks envSlideLayouts >>= maybe (throwError e) pure e = PandocSomeError ("Slide layouts aren't defined, even though they should " <> "always be. This is a bug in pandoc.") -data ContentType = NormalContent - | TwoColumnLeftContent - | TwoColumnRightContent - deriving (Show, Eq) +-- | A placeholder within a layout, identified by type and index. +-- +-- E.g., @Placeholder ObjType 2@ is the third placeholder of type 'ObjType' in +-- the layout. +data Placeholder = Placeholder + { placeholderType :: PHType + , index :: Int + } deriving (Show, Eq) data MediaInfo = MediaInfo { mInfoFilePath :: FilePath , mInfoLocalId :: Int @@ -446,6 +454,9 @@ presentationToArchive opts meta pres = do , title = "Section Header" , content = "Title and Content" , twoColumn = "Two Content" + , comparison = "Comparison" + , contentWithCaption = "Content with Caption" + , blank = "Blank" } layouts <- for layoutTitles $ \layoutTitle -> do let layout = M.lookup (CI.mk layoutTitle) referenceLayouts @@ -550,10 +561,13 @@ getLayout layout = getElement <$> getSlideLayouts where getElement = slElement . case layout of - MetadataSlide{} -> metadata - TitleSlide{} -> title - ContentSlide{} -> content - TwoColumnSlide{} -> twoColumn + MetadataSlide{} -> metadata + TitleSlide{} -> title + ContentSlide{} -> content + TwoColumnSlide{} -> twoColumn + ComparisonSlide{} -> comparison + ContentWithCaptionSlide{} -> contentWithCaption + BlankSlide{} -> blank shapeHasId :: NameSpaces -> T.Text -> Element -> Bool shapeHasId ns ident element @@ -566,17 +580,31 @@ shapeHasId ns ident element getContentShape :: PandocMonad m => NameSpaces -> Element -> P m Element getContentShape ns spTreeElem | isElem ns "p" "spTree" spTreeElem = do - contentType <- asks envContentType - let contentShapes = getShapesByPlaceHolderType ns spTreeElem ObjType - case contentType of - NormalContent | (sp : _) <- contentShapes -> return sp - TwoColumnLeftContent | (sp : _) <- contentShapes -> return sp - TwoColumnRightContent | (_ : sp : _) <- contentShapes -> return sp - _ -> throwError $ PandocSomeError - "Could not find shape for Powerpoint content" + ph@Placeholder{..} <- asks envPlaceholder + case drop index (getShapesByPlaceHolderType ns spTreeElem placeholderType) of + sp : _ -> return sp + [] -> throwError $ PandocSomeError $ missingPlaceholderMessage ph getContentShape _ _ = throwError $ PandocSomeError "Attempted to find content on non shapeTree" +missingPlaceholderMessage :: Placeholder -> Text +missingPlaceholderMessage Placeholder{..} = + "Could not find a " <> ordinal + <> " placeholder of type " <> placeholderText + where + ordinal = T.pack (show index) <> + case (index `mod` 100, index `mod` 10) of + (11, _) -> "th" + (12, _) -> "th" + (13, _) -> "th" + (_, 1) -> "st" + (_, 2) -> "nd" + (_, 3) -> "rd" + _ -> "th" + placeholderText = case placeholderType of + ObjType -> "obj (or nothing)" + PHType t -> t + getShapeDimensions :: NameSpaces -> Element -> Maybe ((Integer, Integer), (Integer, Integer)) @@ -1302,7 +1330,7 @@ contentToElement layout hdrShape shapes element <- nonBodyTextToElement layout [PHType "title"] hdrShape let hdrShapeElements = [Elem element | not (null hdrShape)] contentElements <- local - (\env -> env {envContentType = NormalContent}) + (\env -> env {envPlaceholder = Placeholder ObjType 0}) (shapesToElements layout shapes) return $ buildSpTree ns spTree (hdrShapeElements <> contentElements) contentToElement _ _ _ = return $ mknode "p:sp" [] () @@ -1315,10 +1343,10 @@ twoColumnToElement layout hdrShape shapesL shapesR element <- nonBodyTextToElement layout [PHType "title"] hdrShape let hdrShapeElements = [Elem element | not (null hdrShape)] contentElementsL <- local - (\env -> env {envContentType =TwoColumnLeftContent}) + (\env -> env {envPlaceholder = Placeholder ObjType 0}) (shapesToElements layout shapesL) contentElementsR <- local - (\env -> env {envContentType =TwoColumnRightContent}) + (\env -> env {envPlaceholder = Placeholder ObjType 1}) (shapesToElements layout shapesR) -- let contentElementsL' = map (setIdx ns "1") contentElementsL -- contentElementsR' = map (setIdx ns "2") contentElementsR @@ -1326,6 +1354,76 @@ twoColumnToElement layout hdrShape shapesL shapesR hdrShapeElements <> contentElementsL <> contentElementsR twoColumnToElement _ _ _ _= return $ mknode "p:sp" [] () +comparisonToElement :: + PandocMonad m => + Element -> + [ParaElem] -> + ([Shape], [Shape]) -> + ([Shape], [Shape]) -> + P m Element +comparisonToElement layout hdrShape (shapesL1, shapesL2) (shapesR1, shapesR2) + | ns <- elemToNameSpaces layout + , Just cSld <- findChild (elemName ns "p" "cSld") layout + , Just spTree <- findChild (elemName ns "p" "spTree") cSld = do + element <- nonBodyTextToElement layout [PHType "title"] hdrShape + let hdrShapeElements = [Elem element | not (null hdrShape)] + contentElementsL1 <- local + (\env -> env {envPlaceholder = Placeholder (PHType "body") 0}) + (shapesToElements layout shapesL1) + contentElementsL2 <- local + (\env -> env {envPlaceholder = Placeholder ObjType 0}) + (shapesToElements layout shapesL2) + contentElementsR1 <- local + (\env -> env {envPlaceholder = Placeholder (PHType "body") 1}) + (shapesToElements layout shapesR1) + contentElementsR2 <- local + (\env -> env {envPlaceholder = Placeholder ObjType 1}) + (shapesToElements layout shapesR2) + return $ buildSpTree ns spTree $ + mconcat [ hdrShapeElements + , contentElementsL1 + , contentElementsL2 + , contentElementsR1 + , contentElementsR2 + ] +comparisonToElement _ _ _ _= return $ mknode "p:sp" [] () + +contentWithCaptionToElement :: + PandocMonad m => + Element -> + [ParaElem] -> + [Shape] -> + [Shape] -> + P m Element +contentWithCaptionToElement layout hdrShape textShapes contentShapes + | ns <- elemToNameSpaces layout + , Just cSld <- findChild (elemName ns "p" "cSld") layout + , Just spTree <- findChild (elemName ns "p" "spTree") cSld = do + element <- nonBodyTextToElement layout [PHType "title"] hdrShape + let hdrShapeElements = [Elem element | not (null hdrShape)] + textElements <- local + (\env -> env {envPlaceholder = Placeholder (PHType "body") 0}) + (shapesToElements layout textShapes) + contentElements <- local + (\env -> env {envPlaceholder = Placeholder ObjType 0}) + (shapesToElements layout contentShapes) + return $ buildSpTree ns spTree $ + mconcat [ hdrShapeElements + , textElements + , contentElements + ] +contentWithCaptionToElement _ _ _ _ = return $ mknode "p:sp" [] () + +blankToElement :: + PandocMonad m => + Element -> + P m Element +blankToElement layout + | ns <- elemToNameSpaces layout + , Just cSld <- findChild (elemName ns "p" "cSld") layout + , Just spTree <- findChild (elemName ns "p" "spTree") cSld = do + return $ buildSpTree ns spTree [] +blankToElement _ = return $ mknode "p:sp" [] () titleToElement :: PandocMonad m => Element -> [ParaElem] -> P m Element titleToElement layout titleElems @@ -1380,6 +1478,17 @@ slideToElement (Slide _ l@(TwoColumnSlide hdrElems shapesL shapesR) _) = do ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") ] [mknode "p:cSld" [] [spTree]] +slideToElement (Slide _ l@(ComparisonSlide hdrElems shapesL shapesR) _) = do + layout <- getLayout l + spTree <- local (\env -> if null hdrElems + then env + else env{envSlideHasHeader=True}) $ + comparisonToElement layout hdrElems shapesL shapesR + return $ mknode "p:sld" + [ ("xmlns:a", "http://schemas.openxmlformats.org/drawingml/2006/main"), + ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), + ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") + ] [mknode "p:cSld" [] [spTree]] slideToElement (Slide _ l@(TitleSlide hdrElems) _) = do layout <- getLayout l spTree <- titleToElement layout hdrElems @@ -1396,7 +1505,22 @@ slideToElement (Slide _ l@(MetadataSlide titleElems subtitleElems authorElems da ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") ] [mknode "p:cSld" [] [spTree]] - +slideToElement (Slide _ l@(ContentWithCaptionSlide hdrElems captionShapes contentShapes) _) = do + layout <- getLayout l + spTree <- contentWithCaptionToElement layout hdrElems captionShapes contentShapes + return $ mknode "p:sld" + [ ("xmlns:a", "http://schemas.openxmlformats.org/drawingml/2006/main"), + ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), + ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") + ] [mknode "p:cSld" [] [spTree]] +slideToElement (Slide _ BlankSlide _) = do + layout <- getLayout BlankSlide + spTree <- blankToElement layout + return $ mknode "p:sld" + [ ("xmlns:a", "http://schemas.openxmlformats.org/drawingml/2006/main"), + ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), + ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") + ] [mknode "p:cSld" [] [spTree]] -------------------------------------------------------------------- -- Notes: @@ -1800,10 +1924,13 @@ slideToSlideRelElement slide = do target <- flip fmap getSlideLayouts $ T.pack . ("../slideLayouts/" <>) . takeFileName . slPath . case slide of - (Slide _ MetadataSlide{} _) -> metadata - (Slide _ TitleSlide{} _) -> title - (Slide _ ContentSlide{} _) -> content - (Slide _ TwoColumnSlide{} _) -> twoColumn + (Slide _ MetadataSlide{} _) -> metadata + (Slide _ TitleSlide{} _) -> title + (Slide _ ContentSlide{} _) -> content + (Slide _ TwoColumnSlide{} _) -> twoColumn + (Slide _ ComparisonSlide{} _) -> comparison + (Slide _ ContentWithCaptionSlide{} _) -> contentWithCaption + (Slide _ BlankSlide _) -> blank speakerNotesRels <- maybeToList <$> speakerNotesSlideRelElement slide diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs index 284b9ae62..10060d975 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs @@ -2,6 +2,7 @@ {-# LANGUAGE PatternGuards #-} {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE LambdaCase #-} {- | Module : Text.Pandoc.Writers.Powerpoint.Presentation Copyright : Copyright (C) 2017-2020 Jesse Rosenthal @@ -61,11 +62,13 @@ import Text.Pandoc.Writers.Shared (lookupMetaInlines, lookupMetaBlocks , toLegacyTable) import qualified Data.Map as M import qualified Data.Set as S -import Data.Maybe (maybeToList, fromMaybe) +import Data.Maybe (maybeToList, fromMaybe, listToMaybe) import Text.Pandoc.Highlighting import qualified Data.Text as T import Control.Applicative ((<|>)) import Skylighting +import Data.Bifunctor (bimap) +import Data.Char (isSpace) data WriterEnv = WriterEnv { envMetadata :: Meta , envRunProps :: RunProps @@ -195,6 +198,11 @@ data Layout = MetadataSlide [ParaElem] [ParaElem] [[ParaElem]] [ParaElem] -- heading content | TwoColumnSlide [ParaElem] [Shape] [Shape] -- heading left right + | ComparisonSlide [ParaElem] ([Shape], [Shape]) ([Shape], [Shape]) + -- heading left@(text, content) right@(text, content) + | ContentWithCaptionSlide [ParaElem] [Shape] [Shape] + -- heading text content + | BlankSlide deriving (Show, Eq) data Shape = Pic PicProps FilePath T.Text [ParaElem] @@ -584,7 +592,30 @@ isImage Image{} = True isImage (Link _ (Image{} : _) _) = True isImage _ = False -splitBlocks' :: [Block] -> [[Block]] -> [Block] -> Pres [[Block]] +plainOrPara :: Block -> Maybe [Inline] +plainOrPara (Plain ils) = Just ils +plainOrPara (Para ils) = Just ils +plainOrPara _ = Nothing + +notText :: Block -> Bool +notText block | startsWithImage block = True +notText Table{} = True +notText _ = False + +startsWithImage :: Block -> Bool +startsWithImage block = fromMaybe False $ do + inline <- plainOrPara block >>= listToMaybe + pure (isImage inline) + +-- | Group blocks into a number of "splits" +splitBlocks' :: + -- | Blocks so far in the current split + [Block] -> + -- | Splits so far + [[Block]] -> + -- | All remaining blocks + [Block] -> + Pres [[Block]] splitBlocks' cur acc [] = return $ acc ++ ([cur | not (null cur)]) splitBlocks' cur acc (HorizontalRule : blks) = splitBlocks' [] (acc ++ ([cur | not (null cur)])) blks @@ -609,7 +640,9 @@ splitBlocks' cur acc (Para (il:ils) : blks) | isImage il = do (acc ++ [cur ++ [Para [il]] ++ nts]) (if null ils then blks' else Para ils : blks') _ -> splitBlocks' [] - (acc ++ ([cur | not (null cur)]) ++ [Para [il] : nts]) + (if any notText cur + then acc ++ ([cur | not (null cur)]) ++ [Para [il] : nts] + else acc ++ [cur ++ [Para [il]] ++ nts]) (if null ils then blks' else Para ils : blks') splitBlocks' cur acc (tbl@Table{} : blks) = do slideLevel <- asks envSlideLevel @@ -617,7 +650,11 @@ splitBlocks' cur acc (tbl@Table{} : blks) = do case cur of [Header n _ _] | n == slideLevel || slideLevel == 0 -> splitBlocks' [] (acc ++ [cur ++ [tbl] ++ nts]) blks' - _ -> splitBlocks' [] (acc ++ ([cur | not (null cur)]) ++ [tbl : nts]) blks' + _ -> splitBlocks' [] + (if any notText cur + then acc ++ ([cur | not (null cur)]) ++ [tbl : nts] + else acc ++ ([cur ++ [tbl] ++ nts])) + blks' splitBlocks' cur acc (d@(Div (_, classes, _) _): blks) | "columns" `elem` classes = do slideLevel <- asks envSlideLevel let (nts, blks') = span isNotesDiv blks @@ -639,38 +676,56 @@ bodyBlocksToSlide _ (blk : blks) spkNotes , Div (_, clsL, _) blksL : Div (_, clsR, _) blksR : remaining <- divBlks , "column" `elem` clsL, "column" `elem` clsR = do mapM_ (addLogMessage . BlockNotRendered) (blks ++ remaining) - mbSplitBlksL <- splitBlocks blksL - mbSplitBlksR <- splitBlocks blksR - let blksL' = case mbSplitBlksL of - bs : _ -> bs - [] -> [] - let blksR' = case mbSplitBlksR of - bs : _ -> bs - [] -> [] - shapesL <- blocksToShapes blksL' - shapesR <- blocksToShapes blksR' - sldId <- asks envCurSlideId - return $ Slide - sldId - (TwoColumnSlide [] shapesL shapesR) - spkNotes + let mkTwoColumn left right = do + blksL' <- join . take 1 <$> splitBlocks left + blksR' <- join . take 1 <$> splitBlocks right + shapesL <- blocksToShapes blksL' + shapesR <- blocksToShapes blksR' + sldId <- asks envCurSlideId + return $ Slide + sldId + (TwoColumnSlide [] shapesL shapesR) + spkNotes + let mkComparison blksL1 blksL2 blksR1 blksR2 = do + shapesL1 <- blocksToShapes blksL1 + shapesL2 <- blocksToShapes blksL2 + shapesR1 <- blocksToShapes blksR1 + shapesR2 <- blocksToShapes blksR2 + sldId <- asks envCurSlideId + return $ Slide + sldId + (ComparisonSlide [] (shapesL1, shapesL2) (shapesR1, shapesR2)) + spkNotes + case (break notText blksL, break notText blksR) of + ((_, []), (_, [])) -> mkTwoColumn blksL blksR + (([], _), ([], _)) -> mkTwoColumn blksL blksR + ((blksL1, blksL2), (blksR1, blksR2)) -> mkComparison blksL1 blksL2 blksR1 blksR2 bodyBlocksToSlide _ (blk : blks) spkNotes = do - inNoteSlide <- asks envInNoteSlide - shapes <- if inNoteSlide - then forceFontSize noteSize $ blocksToShapes (blk : blks) - else blocksToShapes (blk : blks) sldId <- asks envCurSlideId - return $ - Slide - sldId - (ContentSlide [] shapes) - spkNotes + inNoteSlide <- asks envInNoteSlide + let mkSlide s = + Slide sldId s spkNotes + if inNoteSlide + then mkSlide . ContentSlide [] <$> + forceFontSize noteSize (blocksToShapes (blk : blks)) + else let + contentOrBlankSlide = + if makesBlankSlide (blk : blks) + then pure (mkSlide BlankSlide) + else mkSlide . ContentSlide [] <$> blocksToShapes (blk : blks) + in case break notText (blk : blks) of + ([], _) -> contentOrBlankSlide + (_, []) -> contentOrBlankSlide + (textBlocks, contentBlocks) -> do + textShapes <- blocksToShapes textBlocks + contentShapes <- blocksToShapes contentBlocks + return (mkSlide (ContentWithCaptionSlide [] textShapes contentShapes)) bodyBlocksToSlide _ [] spkNotes = do sldId <- asks envCurSlideId return $ Slide sldId - (ContentSlide [] []) + BlankSlide spkNotes blocksToSlide' :: Int -> [Block] -> SpeakerNotes -> Pres Slide @@ -689,6 +744,9 @@ blocksToSlide' lvl (Header n (ident, _, _) ils : blks) spkNotes let layout = case slideLayout slide of ContentSlide _ cont -> ContentSlide hdr cont TwoColumnSlide _ contL contR -> TwoColumnSlide hdr contL contR + ComparisonSlide _ contL contR -> ComparisonSlide hdr contL contR + ContentWithCaptionSlide _ text content -> ContentWithCaptionSlide hdr text content + BlankSlide -> if all inlineIsBlank ils then BlankSlide else ContentSlide hdr [] layout' -> layout' return $ slide{slideLayout = layout} blocksToSlide' lvl blks spkNotes = bodyBlocksToSlide lvl blks spkNotes @@ -834,6 +892,19 @@ applyToLayout f (TwoColumnSlide hdr contentL contentR) = do contentL' <- mapM (applyToShape f) contentL contentR' <- mapM (applyToShape f) contentR return $ TwoColumnSlide hdr' contentL' contentR' +applyToLayout f (ComparisonSlide hdr (contentL1, contentL2) (contentR1, contentR2)) = do + hdr' <- mapM f hdr + contentL1' <- mapM (applyToShape f) contentL1 + contentL2' <- mapM (applyToShape f) contentL2 + contentR1' <- mapM (applyToShape f) contentR1 + contentR2' <- mapM (applyToShape f) contentR2 + return $ ComparisonSlide hdr' (contentL1', contentL2') (contentR1', contentR2') +applyToLayout f (ContentWithCaptionSlide hdr textShapes contentShapes) = do + hdr' <- mapM f hdr + textShapes' <- mapM (applyToShape f) textShapes + contentShapes' <- mapM (applyToShape f) contentShapes + return $ ContentWithCaptionSlide hdr' textShapes' contentShapes' +applyToLayout _ BlankSlide = pure BlankSlide applyToSlide :: Monad m => (ParaElem -> m ParaElem) -> Slide -> m Slide applyToSlide f slide = do @@ -885,10 +956,70 @@ emptyLayout layout = case layout of all emptyParaElem hdr && all emptyShape shapes1 && all emptyShape shapes2 + ComparisonSlide hdr (shapesL1, shapesL2) (shapesR1, shapesR2) -> + all emptyParaElem hdr && + all emptyShape shapesL1 && + all emptyShape shapesL2 && + all emptyShape shapesR1 && + all emptyShape shapesR2 + ContentWithCaptionSlide hdr textShapes contentShapes -> + all emptyParaElem hdr && + all emptyShape textShapes && + all emptyShape contentShapes + BlankSlide -> False + emptySlide :: Slide -> Bool emptySlide (Slide _ layout notes) = (notes == mempty) && emptyLayout layout +makesBlankSlide :: [Block] -> Bool +makesBlankSlide = all blockIsBlank + +blockIsBlank :: Block -> Bool +blockIsBlank + = \case + Plain ins -> all inlineIsBlank ins + Para ins -> all inlineIsBlank ins + LineBlock inss -> all (all inlineIsBlank) inss + CodeBlock _ txt -> textIsBlank txt + RawBlock _ txt -> textIsBlank txt + BlockQuote bls -> all blockIsBlank bls + OrderedList _ blss -> all (all blockIsBlank) blss + BulletList blss -> all (all blockIsBlank) blss + DefinitionList ds -> all (uncurry (&&) . bimap (all inlineIsBlank) (all (all blockIsBlank))) ds + Header _ _ ils -> all inlineIsBlank ils + HorizontalRule -> True + Table{} -> False + Div _ bls -> all blockIsBlank bls + Null -> True + +textIsBlank :: T.Text -> Bool +textIsBlank = T.all isSpace + +inlineIsBlank :: Inline -> Bool +inlineIsBlank + = \case + (Str txt) -> textIsBlank txt + (Emph ins) -> all inlineIsBlank ins + (Underline ins) -> all inlineIsBlank ins + (Strong ins) -> all inlineIsBlank ins + (Strikeout ins) -> all inlineIsBlank ins + (Superscript ins) -> all inlineIsBlank ins + (Subscript ins) -> all inlineIsBlank ins + (SmallCaps ins) -> all inlineIsBlank ins + (Quoted _ ins) -> all inlineIsBlank ins + (Cite _ _) -> False + (Code _ txt) -> textIsBlank txt + Space -> True + SoftBreak -> True + LineBreak -> True + (Math _ txt) -> textIsBlank txt + (RawInline _ txt) -> textIsBlank txt + (Link _ ins (t1, t2)) -> all inlineIsBlank ins && textIsBlank t1 && textIsBlank t2 + (Image _ ins (t1, t2)) -> all inlineIsBlank ins && textIsBlank t1 && textIsBlank t2 + (Note bls) -> all blockIsBlank bls + (Span _ ins) -> all inlineIsBlank ins + blocksToPresentationSlides :: [Block] -> Pres [Slide] blocksToPresentationSlides blks = do opts <- asks envOpts diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs index fd9871659..256ee1f7f 100644 --- a/test/Tests/Writers/Powerpoint.hs +++ b/test/Tests/Writers/Powerpoint.hs @@ -166,9 +166,66 @@ tests = groupPptxTests [ pptxTests "Inline formatting" "pptx/slide-level-0/h1-with-table/output.pptx" , pptxTests ("Using slide level 0, if the first thing on " <> "a slide is a heading it's used as the " - <> "slide title (two headings forces a " - <> "slide break though)") + <> "slide title (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" + , pptxTests ("comparison layout used when two columns " + <> "contain text plus non-text") + def + "pptx/comparison/both-columns/input.native" + "pptx/comparison/both-columns/output.pptx" + , pptxTests ("comparison layout used even when only one " + <> "column contains text plus non-text") + def + "pptx/comparison/one-column/input.native" + "pptx/comparison/one-column/output.pptx" + , pptxTests ("extra text in one column in comparison " + <> "layout gets overlaid") + def + "pptx/comparison/extra-text/input.native" + "pptx/comparison/extra-text/output.pptx" + , pptxTests ("extra image in one column in comparison " + <> "layout gets overlaid") + def + "pptx/comparison/extra-image/input.native" + "pptx/comparison/extra-image/output.pptx" + , pptxTests "comparison not used if the non-text comes first" + def + "pptx/comparison/non-text-first/input.native" + "pptx/comparison/non-text-first/output.pptx" + , pptxTests ("Heading, text and an image on the same " + <> "slide uses the Content with Caption " + <> "layout") + def + "pptx/content-with-caption/heading-text-image/input.native" + "pptx/content-with-caption/heading-text-image/output.pptx" + , pptxTests ("Text and an image on the same " + <> "slide uses the Content with Caption " + <> "layout") + def + "pptx/content-with-caption/text-image/input.native" + "pptx/content-with-caption/text-image/output.pptx" + , pptxTests ("If the image comes first, Content with " + <> "Caption is not used") + def + "pptx/content-with-caption/image-text/input.native" + "pptx/content-with-caption/image-text/output.pptx" + , pptxTests ("If a slide contains only speaker notes, the " + <> "Blank layout is used") + def + "pptx/blanks/just-speaker-notes/input.native" + "pptx/blanks/just-speaker-notes/output.pptx" + , pptxTests ("If a slide contains only an empty heading " + <> "with a body of only non-breaking spaces" + <> ", the Blank layout is used") + def + "pptx/blanks/nbsp-in-body/input.native" + "pptx/blanks/nbsp-in-body/output.pptx" + , pptxTests ("If a slide contains only a heading " + <> "containing only non-breaking spaces, " + <> "the Blank layout is used") + def + "pptx/blanks/nbsp-in-heading/input.native" + "pptx/blanks/nbsp-in-heading/output.pptx" ] diff --git a/test/pptx/blanks/just-speaker-notes/deleted-layouts.pptx b/test/pptx/blanks/just-speaker-notes/deleted-layouts.pptx new file mode 100644 index 000000000..82800a074 Binary files /dev/null and b/test/pptx/blanks/just-speaker-notes/deleted-layouts.pptx differ diff --git a/test/pptx/blanks/just-speaker-notes/input.native b/test/pptx/blanks/just-speaker-notes/input.native new file mode 100644 index 000000000..d2e2cfbe2 --- /dev/null +++ b/test/pptx/blanks/just-speaker-notes/input.native @@ -0,0 +1,7 @@ +[Header 1 ("first-slide",[],[]) [Str "First",Space,Str "slide"] +,Para [Str "Nothing",Space,Str "to",Space,Str "see",Space,Str "here"] +,Header 1 ("section",[],[]) [] +,Div ("",["notes"],[]) + [Para [Str "Some",Space,Str "notes",Space,Str "here:",Space,Str "this",Space,Str "first",Space,Str "slide",Space,Str "should",Space,Str "use",Space,Str "the",Space,Str "Blank",Space,Str "template"]] +,Header 1 ("third-slide",[],[]) [Str "Third",Space,Str "slide"] +,Para [Str "The",Space,Str "second",Space,Str "slide",Space,Str "should",Space,Str "be",Space,Str "blank"]] diff --git a/test/pptx/blanks/just-speaker-notes/moved-layouts.pptx b/test/pptx/blanks/just-speaker-notes/moved-layouts.pptx new file mode 100644 index 000000000..f5ef1d7bd Binary files /dev/null and b/test/pptx/blanks/just-speaker-notes/moved-layouts.pptx differ diff --git a/test/pptx/blanks/just-speaker-notes/output.pptx b/test/pptx/blanks/just-speaker-notes/output.pptx new file mode 100644 index 000000000..59a643c3e Binary files /dev/null and b/test/pptx/blanks/just-speaker-notes/output.pptx differ diff --git a/test/pptx/blanks/just-speaker-notes/templated.pptx b/test/pptx/blanks/just-speaker-notes/templated.pptx new file mode 100644 index 000000000..8cc7be75b Binary files /dev/null and b/test/pptx/blanks/just-speaker-notes/templated.pptx differ diff --git a/test/pptx/blanks/nbsp-in-body/deleted-layouts.pptx b/test/pptx/blanks/nbsp-in-body/deleted-layouts.pptx new file mode 100644 index 000000000..98a1586df Binary files /dev/null and b/test/pptx/blanks/nbsp-in-body/deleted-layouts.pptx differ diff --git a/test/pptx/blanks/nbsp-in-body/input.native b/test/pptx/blanks/nbsp-in-body/input.native new file mode 100644 index 000000000..56c105fb0 --- /dev/null +++ b/test/pptx/blanks/nbsp-in-body/input.native @@ -0,0 +1,6 @@ +[Header 1 ("first-slide",[],[]) [Str "First",Space,Str "slide"] +,Para [Str "Uninteresting,",Space,Str "normal"] +,Header 1 ("section",[],[]) [] +,Para [Str "\160"] +,Header 1 ("third-slide",[],[]) [Str "Third",Space,Str "slide"] +,Para [Str "Was",Space,Str "the",Space,Str "previous",Space,Str "one",Space,Str "blank?"]] diff --git a/test/pptx/blanks/nbsp-in-body/moved-layouts.pptx b/test/pptx/blanks/nbsp-in-body/moved-layouts.pptx new file mode 100644 index 000000000..fca99b672 Binary files /dev/null and b/test/pptx/blanks/nbsp-in-body/moved-layouts.pptx differ diff --git a/test/pptx/blanks/nbsp-in-body/output.pptx b/test/pptx/blanks/nbsp-in-body/output.pptx new file mode 100644 index 000000000..ed5c77e05 Binary files /dev/null and b/test/pptx/blanks/nbsp-in-body/output.pptx differ diff --git a/test/pptx/blanks/nbsp-in-body/templated.pptx b/test/pptx/blanks/nbsp-in-body/templated.pptx new file mode 100644 index 000000000..4104f6230 Binary files /dev/null and b/test/pptx/blanks/nbsp-in-body/templated.pptx differ diff --git a/test/pptx/blanks/nbsp-in-heading/deleted-layouts.pptx b/test/pptx/blanks/nbsp-in-heading/deleted-layouts.pptx new file mode 100644 index 000000000..98a1586df Binary files /dev/null and b/test/pptx/blanks/nbsp-in-heading/deleted-layouts.pptx differ diff --git a/test/pptx/blanks/nbsp-in-heading/input.native b/test/pptx/blanks/nbsp-in-heading/input.native new file mode 100644 index 000000000..a5c7fc1ca --- /dev/null +++ b/test/pptx/blanks/nbsp-in-heading/input.native @@ -0,0 +1,5 @@ +[Header 1 ("first-slide",[],[]) [Str "First",Space,Str "slide"] +,Para [Str "Uninteresting,",Space,Str "normal"] +,Header 1 ("section",[],[]) [Str "\160"] +,Header 1 ("third-slide",[],[]) [Str "Third",Space,Str "slide"] +,Para [Str "Was",Space,Str "the",Space,Str "previous",Space,Str "one",Space,Str "blank?"]] diff --git a/test/pptx/blanks/nbsp-in-heading/moved-layouts.pptx b/test/pptx/blanks/nbsp-in-heading/moved-layouts.pptx new file mode 100644 index 000000000..fca99b672 Binary files /dev/null and b/test/pptx/blanks/nbsp-in-heading/moved-layouts.pptx differ diff --git a/test/pptx/blanks/nbsp-in-heading/output.pptx b/test/pptx/blanks/nbsp-in-heading/output.pptx new file mode 100644 index 000000000..ed5c77e05 Binary files /dev/null and b/test/pptx/blanks/nbsp-in-heading/output.pptx differ diff --git a/test/pptx/blanks/nbsp-in-heading/templated.pptx b/test/pptx/blanks/nbsp-in-heading/templated.pptx new file mode 100644 index 000000000..4104f6230 Binary files /dev/null and b/test/pptx/blanks/nbsp-in-heading/templated.pptx differ diff --git a/test/pptx/code-custom/deleted-layouts.pptx b/test/pptx/code-custom/deleted-layouts.pptx index 9282e6354..fdcc7ce1d 100644 Binary files a/test/pptx/code-custom/deleted-layouts.pptx and b/test/pptx/code-custom/deleted-layouts.pptx differ diff --git a/test/pptx/code/deleted-layouts.pptx b/test/pptx/code/deleted-layouts.pptx index 0f503f553..c7f78ac40 100644 Binary files a/test/pptx/code/deleted-layouts.pptx and b/test/pptx/code/deleted-layouts.pptx differ diff --git a/test/pptx/comparison/both-columns/deleted-layouts.pptx b/test/pptx/comparison/both-columns/deleted-layouts.pptx new file mode 100644 index 000000000..6a5affdbf Binary files /dev/null and b/test/pptx/comparison/both-columns/deleted-layouts.pptx differ diff --git a/test/pptx/comparison/both-columns/input.native b/test/pptx/comparison/both-columns/input.native new file mode 100644 index 000000000..2557880d4 --- /dev/null +++ b/test/pptx/comparison/both-columns/input.native @@ -0,0 +1,23 @@ +[Header 1 ("a-slide",[],[]) [Str "A",Space,Str "slide"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Str "A",Space,Str "paragraph",Space,Str "here"] + ,Table ("",[],[]) (Caption Nothing + []) + [(AlignDefault,ColWidth 0.125) + ,(AlignDefault,ColWidth 0.125)] + (TableHead ("",[],[]) + []) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "plus"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "a",Space,Str "table"]]]])] + (TableFoot ("",[],[]) + []) + ,Para [Str "Then",Space,Str "some",Space,Str "more",Space,Str "text"]] + ,Div ("",["column"],[]) + [Para [Str "A",Space,Str "paragraph",Space,Str "here"] + ,Para [Image ("",[],[]) [Str "Plus",Space,Str "an",Space,Str "image"] ("lalune.jpg","fig:")]]]] diff --git a/test/pptx/comparison/both-columns/moved-layouts.pptx b/test/pptx/comparison/both-columns/moved-layouts.pptx new file mode 100644 index 000000000..88282fabb Binary files /dev/null and b/test/pptx/comparison/both-columns/moved-layouts.pptx differ diff --git a/test/pptx/comparison/both-columns/output.pptx b/test/pptx/comparison/both-columns/output.pptx new file mode 100644 index 000000000..477072fb4 Binary files /dev/null and b/test/pptx/comparison/both-columns/output.pptx differ diff --git a/test/pptx/comparison/both-columns/templated.pptx b/test/pptx/comparison/both-columns/templated.pptx new file mode 100644 index 000000000..431d22392 Binary files /dev/null and b/test/pptx/comparison/both-columns/templated.pptx differ diff --git a/test/pptx/comparison/extra-image/deleted-layouts.pptx b/test/pptx/comparison/extra-image/deleted-layouts.pptx new file mode 100644 index 000000000..beed077f7 Binary files /dev/null and b/test/pptx/comparison/extra-image/deleted-layouts.pptx differ diff --git a/test/pptx/comparison/extra-image/input.native b/test/pptx/comparison/extra-image/input.native new file mode 100644 index 000000000..34aeb8f2b --- /dev/null +++ b/test/pptx/comparison/extra-image/input.native @@ -0,0 +1,24 @@ +[Header 1 ("a-slide",[],[]) [Str "A",Space,Str "slide"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Str "A",Space,Str "paragraph",Space,Str "here"] + ,Table ("",[],[]) (Caption Nothing + []) + [(AlignDefault,ColWidth 0.125) + ,(AlignDefault,ColWidth 0.125)] + (TableHead ("",[],[]) + []) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "plus"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "a",Space,Str "table"]]]])] + (TableFoot ("",[],[]) + []) + ,Para [Str "Then",Space,Str "some",Space,Str "more",Space,Str "text"]] + ,Div ("",["column"],[]) + [Para [Str "A",Space,Str "paragraph",Space,Str "here"] + ,Para [Image ("",[],[]) [Str "Plus",Space,Str "an",Space,Str "image"] ("lalune.jpg","fig:")] + ,Para [Image ("",[],[]) [Str "And",Space,Str "another",Space,Str "image"] ("lalune.jpg","fig:")]]]] diff --git a/test/pptx/comparison/extra-image/moved-layouts.pptx b/test/pptx/comparison/extra-image/moved-layouts.pptx new file mode 100644 index 000000000..f86f5b043 Binary files /dev/null and b/test/pptx/comparison/extra-image/moved-layouts.pptx differ diff --git a/test/pptx/comparison/extra-image/output.pptx b/test/pptx/comparison/extra-image/output.pptx new file mode 100644 index 000000000..a0eb5e847 Binary files /dev/null and b/test/pptx/comparison/extra-image/output.pptx differ diff --git a/test/pptx/comparison/extra-image/templated.pptx b/test/pptx/comparison/extra-image/templated.pptx new file mode 100644 index 000000000..a434ba29f Binary files /dev/null and b/test/pptx/comparison/extra-image/templated.pptx differ diff --git a/test/pptx/comparison/extra-text/deleted-layouts.pptx b/test/pptx/comparison/extra-text/deleted-layouts.pptx new file mode 100644 index 000000000..6a5affdbf Binary files /dev/null and b/test/pptx/comparison/extra-text/deleted-layouts.pptx differ diff --git a/test/pptx/comparison/extra-text/input.native b/test/pptx/comparison/extra-text/input.native new file mode 100644 index 000000000..2557880d4 --- /dev/null +++ b/test/pptx/comparison/extra-text/input.native @@ -0,0 +1,23 @@ +[Header 1 ("a-slide",[],[]) [Str "A",Space,Str "slide"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Str "A",Space,Str "paragraph",Space,Str "here"] + ,Table ("",[],[]) (Caption Nothing + []) + [(AlignDefault,ColWidth 0.125) + ,(AlignDefault,ColWidth 0.125)] + (TableHead ("",[],[]) + []) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "plus"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "a",Space,Str "table"]]]])] + (TableFoot ("",[],[]) + []) + ,Para [Str "Then",Space,Str "some",Space,Str "more",Space,Str "text"]] + ,Div ("",["column"],[]) + [Para [Str "A",Space,Str "paragraph",Space,Str "here"] + ,Para [Image ("",[],[]) [Str "Plus",Space,Str "an",Space,Str "image"] ("lalune.jpg","fig:")]]]] diff --git a/test/pptx/comparison/extra-text/moved-layouts.pptx b/test/pptx/comparison/extra-text/moved-layouts.pptx new file mode 100644 index 000000000..88282fabb Binary files /dev/null and b/test/pptx/comparison/extra-text/moved-layouts.pptx differ diff --git a/test/pptx/comparison/extra-text/output.pptx b/test/pptx/comparison/extra-text/output.pptx new file mode 100644 index 000000000..8de7d23b2 Binary files /dev/null and b/test/pptx/comparison/extra-text/output.pptx differ diff --git a/test/pptx/comparison/extra-text/templated.pptx b/test/pptx/comparison/extra-text/templated.pptx new file mode 100644 index 000000000..431d22392 Binary files /dev/null and b/test/pptx/comparison/extra-text/templated.pptx differ diff --git a/test/pptx/comparison/non-text-first/deleted-layouts.pptx b/test/pptx/comparison/non-text-first/deleted-layouts.pptx new file mode 100644 index 000000000..bd7aa69b7 Binary files /dev/null and b/test/pptx/comparison/non-text-first/deleted-layouts.pptx differ diff --git a/test/pptx/comparison/non-text-first/input.native b/test/pptx/comparison/non-text-first/input.native new file mode 100644 index 000000000..a8caad151 --- /dev/null +++ b/test/pptx/comparison/non-text-first/input.native @@ -0,0 +1,21 @@ +[Header 1 ("a-slide",[],[]) [Str "A",Space,Str "slide"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Table ("",[],[]) (Caption Nothing + []) + [(AlignDefault,ColWidth 0.125) + ,(AlignDefault,ColWidth 0.125)] + (TableHead ("",[],[]) + []) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "a"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "table"]]]])] + (TableFoot ("",[],[]) + []) + ,Para [Str "Plus",Space,Str "a",Space,Str "paragraph",Space,Str "here"]] + ,Div ("",["column"],[]) + [Para [Image ("",[],[]) [Str "Just",Space,Str "an",Space,Str "image",Space,Str "on",Space,Str "this",Space,Str "side"] ("lalune.jpg","fig:")]]]] diff --git a/test/pptx/comparison/non-text-first/moved-layouts.pptx b/test/pptx/comparison/non-text-first/moved-layouts.pptx new file mode 100644 index 000000000..a01def95c Binary files /dev/null and b/test/pptx/comparison/non-text-first/moved-layouts.pptx differ diff --git a/test/pptx/comparison/non-text-first/output.pptx b/test/pptx/comparison/non-text-first/output.pptx new file mode 100644 index 000000000..cb7843fce Binary files /dev/null and b/test/pptx/comparison/non-text-first/output.pptx differ diff --git a/test/pptx/comparison/non-text-first/templated.pptx b/test/pptx/comparison/non-text-first/templated.pptx new file mode 100644 index 000000000..32db19cbf Binary files /dev/null and b/test/pptx/comparison/non-text-first/templated.pptx differ diff --git a/test/pptx/comparison/one-column/deleted-layouts.pptx b/test/pptx/comparison/one-column/deleted-layouts.pptx new file mode 100644 index 000000000..5fd7cf9b6 Binary files /dev/null and b/test/pptx/comparison/one-column/deleted-layouts.pptx differ diff --git a/test/pptx/comparison/one-column/input.native b/test/pptx/comparison/one-column/input.native new file mode 100644 index 000000000..b99740a14 --- /dev/null +++ b/test/pptx/comparison/one-column/input.native @@ -0,0 +1,21 @@ +[Header 1 ("a-slide",[],[]) [Str "A",Space,Str "slide"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Str "A",Space,Str "paragraph",Space,Str "here"] + ,Table ("",[],[]) (Caption Nothing + []) + [(AlignDefault,ColWidth 0.125) + ,(AlignDefault,ColWidth 0.125)] + (TableHead ("",[],[]) + []) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "plus"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "a",Space,Str "table"]]]])] + (TableFoot ("",[],[]) + [])] + ,Div ("",["column"],[]) + [Para [Str "Only",Space,Str "a",Space,Str "paragraph",Space,Str "here"]]]] diff --git a/test/pptx/comparison/one-column/moved-layouts.pptx b/test/pptx/comparison/one-column/moved-layouts.pptx new file mode 100644 index 000000000..d5df2b751 Binary files /dev/null and b/test/pptx/comparison/one-column/moved-layouts.pptx differ diff --git a/test/pptx/comparison/one-column/output.pptx b/test/pptx/comparison/one-column/output.pptx new file mode 100644 index 000000000..6914162ff Binary files /dev/null and b/test/pptx/comparison/one-column/output.pptx differ diff --git a/test/pptx/comparison/one-column/templated.pptx b/test/pptx/comparison/one-column/templated.pptx new file mode 100644 index 000000000..a30a24453 Binary files /dev/null and b/test/pptx/comparison/one-column/templated.pptx differ diff --git a/test/pptx/content-with-caption/heading-text-image/deleted-layouts.pptx b/test/pptx/content-with-caption/heading-text-image/deleted-layouts.pptx new file mode 100644 index 000000000..b5afcc021 Binary files /dev/null and b/test/pptx/content-with-caption/heading-text-image/deleted-layouts.pptx differ diff --git a/test/pptx/content-with-caption/heading-text-image/input.native b/test/pptx/content-with-caption/heading-text-image/input.native new file mode 100644 index 000000000..576bc1658 --- /dev/null +++ b/test/pptx/content-with-caption/heading-text-image/input.native @@ -0,0 +1,3 @@ +[Header 1 ("a-slide",[],[]) [Str "A",Space,Str "slide"] +,Para [Str "Some",Space,Str "text",Space,Str "here"] +,Para [Image ("",[],[]) [Str "Followed",Space,Str "by",Space,Str "a",Space,Str "picture"] ("lalune.jpg","fig:")]] diff --git a/test/pptx/content-with-caption/heading-text-image/moved-layouts.pptx b/test/pptx/content-with-caption/heading-text-image/moved-layouts.pptx new file mode 100644 index 000000000..05806a767 Binary files /dev/null and b/test/pptx/content-with-caption/heading-text-image/moved-layouts.pptx differ diff --git a/test/pptx/content-with-caption/heading-text-image/output.pptx b/test/pptx/content-with-caption/heading-text-image/output.pptx new file mode 100644 index 000000000..b3e89757b Binary files /dev/null and b/test/pptx/content-with-caption/heading-text-image/output.pptx differ diff --git a/test/pptx/content-with-caption/heading-text-image/templated.pptx b/test/pptx/content-with-caption/heading-text-image/templated.pptx new file mode 100644 index 000000000..3b0fe64c3 Binary files /dev/null and b/test/pptx/content-with-caption/heading-text-image/templated.pptx differ diff --git a/test/pptx/content-with-caption/image-text/deleted-layouts.pptx b/test/pptx/content-with-caption/image-text/deleted-layouts.pptx new file mode 100644 index 000000000..e9e0551ac Binary files /dev/null and b/test/pptx/content-with-caption/image-text/deleted-layouts.pptx differ diff --git a/test/pptx/content-with-caption/image-text/input.native b/test/pptx/content-with-caption/image-text/input.native new file mode 100644 index 000000000..2ffbf0888 --- /dev/null +++ b/test/pptx/content-with-caption/image-text/input.native @@ -0,0 +1,2 @@ +[Para [Image ("",[],[]) [Str "The",Space,Str "picture",Space,Str "first"] ("lalune.jpg","fig:")] +,Para [Str "Then",Space,Str "some",Space,Str "text",Space,Str "here"]] diff --git a/test/pptx/content-with-caption/image-text/moved-layouts.pptx b/test/pptx/content-with-caption/image-text/moved-layouts.pptx new file mode 100644 index 000000000..77d706ed3 Binary files /dev/null and b/test/pptx/content-with-caption/image-text/moved-layouts.pptx differ diff --git a/test/pptx/content-with-caption/image-text/output.pptx b/test/pptx/content-with-caption/image-text/output.pptx new file mode 100644 index 000000000..94a2e8b88 Binary files /dev/null and b/test/pptx/content-with-caption/image-text/output.pptx differ diff --git a/test/pptx/content-with-caption/image-text/templated.pptx b/test/pptx/content-with-caption/image-text/templated.pptx new file mode 100644 index 000000000..bef1921a7 Binary files /dev/null and b/test/pptx/content-with-caption/image-text/templated.pptx differ diff --git a/test/pptx/content-with-caption/text-image/deleted-layouts.pptx b/test/pptx/content-with-caption/text-image/deleted-layouts.pptx new file mode 100644 index 000000000..68d3d7b9b Binary files /dev/null and b/test/pptx/content-with-caption/text-image/deleted-layouts.pptx differ diff --git a/test/pptx/content-with-caption/text-image/input.native b/test/pptx/content-with-caption/text-image/input.native new file mode 100644 index 000000000..762d18426 --- /dev/null +++ b/test/pptx/content-with-caption/text-image/input.native @@ -0,0 +1,2 @@ +[Para [Str "Some",Space,Str "text",Space,Str "here"] +,Para [Image ("",[],[]) [Str "Followed",Space,Str "by",Space,Str "a",Space,Str "picture"] ("lalune.jpg","fig:")]] diff --git a/test/pptx/content-with-caption/text-image/moved-layouts.pptx b/test/pptx/content-with-caption/text-image/moved-layouts.pptx new file mode 100644 index 000000000..feade1096 Binary files /dev/null and b/test/pptx/content-with-caption/text-image/moved-layouts.pptx differ diff --git a/test/pptx/content-with-caption/text-image/output.pptx b/test/pptx/content-with-caption/text-image/output.pptx new file mode 100644 index 000000000..efa814d65 Binary files /dev/null and b/test/pptx/content-with-caption/text-image/output.pptx differ diff --git a/test/pptx/content-with-caption/text-image/templated.pptx b/test/pptx/content-with-caption/text-image/templated.pptx new file mode 100644 index 000000000..ebd552252 Binary files /dev/null and b/test/pptx/content-with-caption/text-image/templated.pptx differ diff --git a/test/pptx/document-properties-short-desc/deleted-layouts.pptx b/test/pptx/document-properties-short-desc/deleted-layouts.pptx index e4cf6bd7b..a866f3c1f 100644 Binary files a/test/pptx/document-properties-short-desc/deleted-layouts.pptx and b/test/pptx/document-properties-short-desc/deleted-layouts.pptx differ diff --git a/test/pptx/document-properties/deleted-layouts.pptx b/test/pptx/document-properties/deleted-layouts.pptx index a00c8059d..1f52481f3 100644 Binary files a/test/pptx/document-properties/deleted-layouts.pptx and b/test/pptx/document-properties/deleted-layouts.pptx differ diff --git a/test/pptx/endnotes-toc/deleted-layouts.pptx b/test/pptx/endnotes-toc/deleted-layouts.pptx index 46708544c..60110a64e 100644 Binary files a/test/pptx/endnotes-toc/deleted-layouts.pptx and b/test/pptx/endnotes-toc/deleted-layouts.pptx differ diff --git a/test/pptx/endnotes/deleted-layouts.pptx b/test/pptx/endnotes/deleted-layouts.pptx index 5c69a6310..0b0bd2f53 100644 Binary files a/test/pptx/endnotes/deleted-layouts.pptx and b/test/pptx/endnotes/deleted-layouts.pptx differ diff --git a/test/pptx/images/deleted-layouts.pptx b/test/pptx/images/deleted-layouts.pptx index 053928863..2f8754e90 100644 Binary files a/test/pptx/images/deleted-layouts.pptx and b/test/pptx/images/deleted-layouts.pptx differ diff --git a/test/pptx/inline-formatting/deleted-layouts.pptx b/test/pptx/inline-formatting/deleted-layouts.pptx index bbd5bfeb4..2fbe21a45 100644 Binary files a/test/pptx/inline-formatting/deleted-layouts.pptx and b/test/pptx/inline-formatting/deleted-layouts.pptx differ diff --git a/test/pptx/lists/deleted-layouts.pptx b/test/pptx/lists/deleted-layouts.pptx index 6512e44bb..e527d3c5f 100644 Binary files a/test/pptx/lists/deleted-layouts.pptx and b/test/pptx/lists/deleted-layouts.pptx differ diff --git a/test/pptx/raw-ooxml/deleted-layouts.pptx b/test/pptx/raw-ooxml/deleted-layouts.pptx index 2ea155657..2da1b7a63 100644 Binary files a/test/pptx/raw-ooxml/deleted-layouts.pptx and b/test/pptx/raw-ooxml/deleted-layouts.pptx differ diff --git a/test/pptx/remove-empty-slides/deleted-layouts.pptx b/test/pptx/remove-empty-slides/deleted-layouts.pptx index 7ae4a5fab..51981b241 100644 Binary files a/test/pptx/remove-empty-slides/deleted-layouts.pptx and b/test/pptx/remove-empty-slides/deleted-layouts.pptx differ diff --git a/test/pptx/remove-empty-slides/moved-layouts.pptx b/test/pptx/remove-empty-slides/moved-layouts.pptx index 2572f2447..ddca32a52 100644 Binary files a/test/pptx/remove-empty-slides/moved-layouts.pptx and b/test/pptx/remove-empty-slides/moved-layouts.pptx differ diff --git a/test/pptx/remove-empty-slides/output.pptx b/test/pptx/remove-empty-slides/output.pptx index c6df8e18e..9e8b5eed2 100644 Binary files a/test/pptx/remove-empty-slides/output.pptx and b/test/pptx/remove-empty-slides/output.pptx differ diff --git a/test/pptx/remove-empty-slides/templated.pptx b/test/pptx/remove-empty-slides/templated.pptx index 1df48c5ad..579467452 100644 Binary files a/test/pptx/remove-empty-slides/templated.pptx and b/test/pptx/remove-empty-slides/templated.pptx differ diff --git a/test/pptx/slide-breaks-slide-level-1/deleted-layouts.pptx b/test/pptx/slide-breaks-slide-level-1/deleted-layouts.pptx index 2c7fd4d8b..2c891cd1d 100644 Binary files a/test/pptx/slide-breaks-slide-level-1/deleted-layouts.pptx and b/test/pptx/slide-breaks-slide-level-1/deleted-layouts.pptx differ diff --git a/test/pptx/slide-breaks-toc/deleted-layouts.pptx b/test/pptx/slide-breaks-toc/deleted-layouts.pptx index 1e0b76d46..b63994cce 100644 Binary files a/test/pptx/slide-breaks-toc/deleted-layouts.pptx and b/test/pptx/slide-breaks-toc/deleted-layouts.pptx differ diff --git a/test/pptx/slide-breaks/deleted-layouts.pptx b/test/pptx/slide-breaks/deleted-layouts.pptx index 86dfad3b2..fbf4054be 100644 Binary files a/test/pptx/slide-breaks/deleted-layouts.pptx and b/test/pptx/slide-breaks/deleted-layouts.pptx differ diff --git a/test/pptx/slide-level-0/h1-h2-with-table/deleted-layouts.pptx b/test/pptx/slide-level-0/h1-h2-with-table/deleted-layouts.pptx index 5e776e05c..217b000b6 100644 Binary files a/test/pptx/slide-level-0/h1-h2-with-table/deleted-layouts.pptx and b/test/pptx/slide-level-0/h1-h2-with-table/deleted-layouts.pptx differ diff --git a/test/pptx/slide-level-0/h1-h2-with-table/moved-layouts.pptx b/test/pptx/slide-level-0/h1-h2-with-table/moved-layouts.pptx index 35204de1b..d8a6c90fe 100644 Binary files a/test/pptx/slide-level-0/h1-h2-with-table/moved-layouts.pptx and b/test/pptx/slide-level-0/h1-h2-with-table/moved-layouts.pptx differ diff --git a/test/pptx/slide-level-0/h1-h2-with-table/output.pptx b/test/pptx/slide-level-0/h1-h2-with-table/output.pptx index 197a6833f..512b324bf 100644 Binary files a/test/pptx/slide-level-0/h1-h2-with-table/output.pptx and b/test/pptx/slide-level-0/h1-h2-with-table/output.pptx differ diff --git a/test/pptx/slide-level-0/h1-h2-with-table/templated.pptx b/test/pptx/slide-level-0/h1-h2-with-table/templated.pptx index 5c659952e..5ab88e94c 100644 Binary files a/test/pptx/slide-level-0/h1-h2-with-table/templated.pptx and b/test/pptx/slide-level-0/h1-h2-with-table/templated.pptx differ diff --git a/test/pptx/slide-level-0/h1-with-image/deleted-layouts.pptx b/test/pptx/slide-level-0/h1-with-image/deleted-layouts.pptx index 16c61d1be..5be799e3b 100644 Binary files a/test/pptx/slide-level-0/h1-with-image/deleted-layouts.pptx and b/test/pptx/slide-level-0/h1-with-image/deleted-layouts.pptx differ diff --git a/test/pptx/slide-level-0/h1-with-table/deleted-layouts.pptx b/test/pptx/slide-level-0/h1-with-table/deleted-layouts.pptx index 0eb7c0b08..127dcea01 100644 Binary files a/test/pptx/slide-level-0/h1-with-table/deleted-layouts.pptx and b/test/pptx/slide-level-0/h1-with-table/deleted-layouts.pptx differ diff --git a/test/pptx/slide-level-0/h2-with-image/deleted-layouts.pptx b/test/pptx/slide-level-0/h2-with-image/deleted-layouts.pptx index afc096ce6..5be799e3b 100644 Binary files a/test/pptx/slide-level-0/h2-with-image/deleted-layouts.pptx and b/test/pptx/slide-level-0/h2-with-image/deleted-layouts.pptx differ diff --git a/test/pptx/speaker-notes-after-metadata/deleted-layouts.pptx b/test/pptx/speaker-notes-after-metadata/deleted-layouts.pptx index 1298870e2..33304ae3e 100644 Binary files a/test/pptx/speaker-notes-after-metadata/deleted-layouts.pptx and b/test/pptx/speaker-notes-after-metadata/deleted-layouts.pptx differ diff --git a/test/pptx/speaker-notes-afterheader/deleted-layouts.pptx b/test/pptx/speaker-notes-afterheader/deleted-layouts.pptx index 853b918cb..00f05fae5 100644 Binary files a/test/pptx/speaker-notes-afterheader/deleted-layouts.pptx and b/test/pptx/speaker-notes-afterheader/deleted-layouts.pptx differ diff --git a/test/pptx/speaker-notes-afterseps/deleted-layouts.pptx b/test/pptx/speaker-notes-afterseps/deleted-layouts.pptx index 9fec1c279..139af783b 100644 Binary files a/test/pptx/speaker-notes-afterseps/deleted-layouts.pptx and b/test/pptx/speaker-notes-afterseps/deleted-layouts.pptx differ diff --git a/test/pptx/speaker-notes/deleted-layouts.pptx b/test/pptx/speaker-notes/deleted-layouts.pptx index 6a5ad524f..c63125d8a 100644 Binary files a/test/pptx/speaker-notes/deleted-layouts.pptx and b/test/pptx/speaker-notes/deleted-layouts.pptx differ diff --git a/test/pptx/start-numbering-at/deleted-layouts.pptx b/test/pptx/start-numbering-at/deleted-layouts.pptx index d9cf91804..68b4215df 100644 Binary files a/test/pptx/start-numbering-at/deleted-layouts.pptx and b/test/pptx/start-numbering-at/deleted-layouts.pptx differ diff --git a/test/pptx/tables/deleted-layouts.pptx b/test/pptx/tables/deleted-layouts.pptx index a52222551..d533d3c28 100644 Binary files a/test/pptx/tables/deleted-layouts.pptx and b/test/pptx/tables/deleted-layouts.pptx differ diff --git a/test/pptx/two-column/deleted-layouts.pptx b/test/pptx/two-column/deleted-layouts.pptx index 60a244f94..9622ed2cd 100644 Binary files a/test/pptx/two-column/deleted-layouts.pptx and b/test/pptx/two-column/deleted-layouts.pptx differ -- cgit v1.2.3 From 99a4d1d0b06bb68e4d7a10acd642d439842004d1 Mon Sep 17 00:00:00 2001 From: Francesco Mazzoli Date: Fri, 10 Sep 2021 18:30:05 +0200 Subject: Support `--reference-location` for HTML output (#7461) The HTML writer now supports `EndOfBlock`, `EndOfSection`, and `EndOfDocument` for reference locations. EPUB and HTML slide show formats are also affected by this change. This works similarly to the markdown writer, but with special care taken to skipping section divs with what regards to the block level. The change also takes care to not modify the output if `EndOfDocument` is used. --- MANUAL.txt | 2 +- man/pandoc.1 | 2 +- src/Text/Pandoc/Writers/HTML.hs | 121 +++++++++++++++++++++++++++++----------- test/Tests/Writers/HTML.hs | 75 ++++++++++++++++++++++++- test/command/4235.md | 2 +- test/command/7006.md | 2 +- test/writer.html4 | 2 +- test/writer.html5 | 2 +- 8 files changed, 169 insertions(+), 39 deletions(-) (limited to 'test/Tests/Writers') diff --git a/MANUAL.txt b/MANUAL.txt index afdd66ddd..57b9f3b2c 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -972,7 +972,7 @@ header when requesting a document from a URL: : Specify whether footnotes (and references, if `reference-links` is set) are placed at the end of the current (top-level) block, the current section, or the document. The default is - `document`. Currently only affects the markdown writer. + `document`. Currently only affects the markdown and HTML writers. `--markdown-headings=setext`|`atx` diff --git a/man/pandoc.1 b/man/pandoc.1 index a0092b385..e901f60b3 100644 --- a/man/pandoc.1 +++ b/man/pandoc.1 @@ -995,7 +995,7 @@ Specify whether footnotes (and references, if \f[C]reference-links\f[R] is set) are placed at the end of the current (top-level) block, the current section, or the document. The default is \f[C]document\f[R]. -Currently only affects the markdown writer. +Currently only affects the markdown and HTML writers. .TP \f[B]\f[CB]--markdown-headings=setext\f[B]\f[R]|\f[B]\f[CB]atx\f[B]\f[R] Specify whether to use ATX-style (\f[C]#\f[R]-prefixed) or Setext-style diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 89fc110ef..c96d4622a 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -74,9 +74,11 @@ import Text.TeXMath import Text.XML.Light (elChildren, unode, unqual) import qualified Text.XML.Light as XML import Text.XML.Light.Output +import Data.String (fromString) data WriterState = WriterState { stNotes :: [Html] -- ^ List of notes + , stEmittedNotes :: Int -- ^ How many notes we've already pushed out to the HTML , stMath :: Bool -- ^ Math is used in document , stQuotes :: Bool -- ^ tag is used , stHighlighting :: Bool -- ^ Syntax highlighting is used @@ -88,10 +90,11 @@ data WriterState = WriterState , stCodeBlockNum :: Int -- ^ Number of code block , stCsl :: Bool -- ^ Has CSL references , stCslEntrySpacing :: Maybe Int -- ^ CSL entry spacing + , stBlockLevel :: Int -- ^ Current block depth, excluding section divs } defaultWriterState :: WriterState -defaultWriterState = WriterState {stNotes= [], stMath = False, stQuotes = False, +defaultWriterState = WriterState {stNotes= [], stEmittedNotes = 0, stMath = False, stQuotes = False, stHighlighting = False, stHtml5 = False, stEPUBVersion = Nothing, @@ -100,7 +103,8 @@ defaultWriterState = WriterState {stNotes= [], stMath = False, stQuotes = False, stInSection = False, stCodeBlockNum = 0, stCsl = False, - stCslEntrySpacing = Nothing} + stCslEntrySpacing = Nothing, + stBlockLevel = 0} -- Helpers to render HTML with the appropriate function. @@ -266,8 +270,16 @@ pandocToHtml opts (Pandoc meta blocks) = do then fmap renderHtml' <$> tableOfContents opts sects else return Nothing blocks' <- blockListToHtml opts sects + notes <- do + -- make the st private just to be safe, since we modify it right afterwards + st <- get + if null (stNotes st) + then return mempty + else do + notes <- footnoteSection opts EndOfDocument (stEmittedNotes st + 1) (reverse (stNotes st)) + modify (\st' -> st'{ stNotes = mempty, stEmittedNotes = stEmittedNotes st' + length (stNotes st') }) + return notes st <- get - notes <- footnoteSection opts (reverse (stNotes st)) let thebody = blocks' >> notes let math = case writerHTMLMathMethod opts of MathJax url @@ -490,28 +502,43 @@ tableOfContents opts sects = do -- | Convert list of Note blocks to a footnote
. -- Assumes notes are sorted. -footnoteSection :: PandocMonad m - => WriterOptions -> [Html] -> StateT WriterState m Html -footnoteSection opts notes = do +footnoteSection :: + PandocMonad m => WriterOptions -> ReferenceLocation -> Int -> [Html] -> StateT WriterState m Html +footnoteSection opts refLocation startCounter notes = do html5 <- gets stHtml5 slideVariant <- gets stSlideVariant - let hrtag = if html5 then H5.hr else H.hr + let hrtag = if refLocation /= EndOfBlock then (if html5 then H5.hr else H.hr) else mempty + let additionalClassName = case refLocation of + EndOfBlock -> "footnotes-end-of-block" + EndOfDocument -> "footnotes-end-of-document" + EndOfSection -> "footnotes-end-of-section" + let className = "footnotes " <> additionalClassName epubVersion <- gets stEPUBVersion let container x | html5 , epubVersion == Just EPUB3 - = H5.section ! A.class_ "footnotes" + = H5.section ! A.class_ className ! customAttribute "epub:type" "footnotes" $ x - | html5 = H5.section ! A.class_ "footnotes" + | html5 = H5.section ! A.class_ className ! customAttribute "role" "doc-endnotes" $ x | slideVariant /= NoSlides = H.div ! A.class_ "footnotes slide" $ x - | otherwise = H.div ! A.class_ "footnotes" $ x + | otherwise = H.div ! A.class_ className $ x return $ if null notes then mempty - else nl opts >> container (nl opts >> hrtag >> nl opts >> - H.ol (mconcat notes >> nl opts) >> nl opts) + else do + nl opts + container $ do + nl opts + hrtag + nl opts + -- Keep the previous output exactly the same if we don't + -- have multiple notes sections + if startCounter == 1 + then H.ol $ mconcat notes >> nl opts + else H.ol ! A.start (fromString (show startCounter)) $ mconcat notes >> nl opts + nl opts -- | Parse a mailto link; return Just (name, domain) or Nothing. parseMailto :: Text -> Maybe (Text, Text) @@ -702,11 +729,10 @@ adjustNumbers opts doc = fixnum x = x showSecNum = T.intercalate "." . map tshow --- | Convert Pandoc block element to HTML. -blockToHtml :: PandocMonad m => WriterOptions -> Block -> StateT WriterState m Html -blockToHtml _ Null = return mempty -blockToHtml opts (Plain lst) = inlineListToHtml opts lst -blockToHtml opts (Para [Image attr@(_,classes,_) txt (src,tit)]) +blockToHtmlInner :: PandocMonad m => WriterOptions -> Block -> StateT WriterState m Html +blockToHtmlInner _ Null = return mempty +blockToHtmlInner opts (Plain lst) = inlineListToHtml opts lst +blockToHtmlInner opts (Para [Image attr@(_,classes,_) txt (src,tit)]) | "stretch" `elem` classes = do slideVariant <- gets stSlideVariant case slideVariant of @@ -716,20 +742,20 @@ blockToHtml opts (Para [Image attr@(_,classes,_) txt (src,tit)]) inlineToHtml opts (Image attr txt (src, tit)) _ -> figure opts attr txt (src, tit) -- title beginning with fig: indicates that the image is a figure -blockToHtml opts (Para [Image attr txt (s,T.stripPrefix "fig:" -> Just tit)]) = +blockToHtmlInner opts (Para [Image attr txt (s,T.stripPrefix "fig:" -> Just tit)]) = figure opts attr txt (s,tit) -blockToHtml opts (Para lst) = do +blockToHtmlInner opts (Para lst) = do contents <- inlineListToHtml opts lst case contents of Empty _ | not (isEnabled Ext_empty_paragraphs opts) -> return mempty _ -> return $ H.p contents -blockToHtml opts (LineBlock lns) = +blockToHtmlInner opts (LineBlock lns) = if writerWrapText opts == WrapNone then blockToHtml opts $ linesToPara lns else do htmlLines <- inlineListToHtml opts $ intercalate [LineBreak] lns return $ H.div ! A.class_ "line-block" $ htmlLines -blockToHtml opts (Div (ident, "section":dclasses, dkvs) +blockToHtmlInner opts (Div (ident, "section":dclasses, dkvs) (Header level hattr@(hident,hclasses,hkvs) ils : xs)) = do slideVariant <- gets stSlideVariant @@ -810,7 +836,7 @@ blockToHtml opts (Div (ident, "section":dclasses, dkvs) if null innerSecs then mempty else nl opts <> innerContents -blockToHtml opts (Div attr@(ident, classes, kvs') bs) = do +blockToHtmlInner opts (Div attr@(ident, classes, kvs') bs) = do html5 <- gets stHtml5 slideVariant <- gets stSlideVariant let isCslBibBody = ident == "refs" || "csl-bib-body" `elem` classes @@ -864,7 +890,7 @@ blockToHtml opts (Div attr@(ident, classes, kvs') bs) = do _ -> return mempty else addAttrs opts (ident, classes'', kvs) $ divtag contents' -blockToHtml opts (RawBlock f str) = do +blockToHtmlInner opts (RawBlock f str) = do ishtml <- isRawHtml f if ishtml then return $ preEscapedText str @@ -875,10 +901,10 @@ blockToHtml opts (RawBlock f str) = do else do report $ BlockNotRendered (RawBlock f str) return mempty -blockToHtml _ HorizontalRule = do +blockToHtmlInner _ HorizontalRule = do html5 <- gets stHtml5 return $ if html5 then H5.hr else H.hr -blockToHtml opts (CodeBlock (id',classes,keyvals) rawCode) = do +blockToHtmlInner opts (CodeBlock (id',classes,keyvals) rawCode) = do id'' <- if T.null id' then do modify $ \st -> st{ stCodeBlockNum = stCodeBlockNum st + 1 } @@ -910,7 +936,7 @@ blockToHtml opts (CodeBlock (id',classes,keyvals) rawCode) = do -- we set writerIdentifierPrefix to "" since id'' already -- includes it: addAttrs opts{writerIdentifierPrefix = ""} (id'',[],keyvals) h -blockToHtml opts (BlockQuote blocks) = do +blockToHtmlInner opts (BlockQuote blocks) = do -- in S5, treat list in blockquote specially -- if default is incremental, make it nonincremental; -- otherwise incremental @@ -932,7 +958,7 @@ blockToHtml opts (BlockQuote blocks) = do else do contents <- blockListToHtml opts blocks return $ H.blockquote $ nl opts >> contents >> nl opts -blockToHtml opts (Header level (ident,classes,kvs) lst) = do +blockToHtmlInner opts (Header level (ident,classes,kvs) lst) = do contents <- inlineListToHtml opts lst let secnum = fromMaybe mempty $ lookup "number" kvs let contents' = if writerNumberSections opts && not (T.null secnum) @@ -955,12 +981,12 @@ blockToHtml opts (Header level (ident,classes,kvs) lst) = do 5 -> H.h5 contents' 6 -> H.h6 contents' _ -> H.p ! A.class_ "heading" $ contents' -blockToHtml opts (BulletList lst) = do +blockToHtmlInner opts (BulletList lst) = do contents <- mapM (listItemToHtml opts) lst let isTaskList = not (null lst) && all isTaskListItem lst (if isTaskList then (! A.class_ "task-list") else id) <$> unordList opts contents -blockToHtml opts (OrderedList (startnum, numstyle, _) lst) = do +blockToHtmlInner opts (OrderedList (startnum, numstyle, _) lst) = do contents <- mapM (listItemToHtml opts) lst html5 <- gets stHtml5 let numstyle' = case numstyle of @@ -983,7 +1009,7 @@ blockToHtml opts (OrderedList (startnum, numstyle, _) lst) = do else []) l <- ordList opts contents return $ foldl' (!) l attribs -blockToHtml opts (DefinitionList lst) = do +blockToHtmlInner opts (DefinitionList lst) = do contents <- mapM (\(term, defs) -> do term' <- liftM H.dt $ inlineListToHtml opts term defs' <- mapM (liftM (\x -> H.dd (x >> nl opts)) . @@ -991,9 +1017,39 @@ blockToHtml opts (DefinitionList lst) = do return $ mconcat $ nl opts : term' : nl opts : intersperse (nl opts) defs') lst defList opts contents -blockToHtml opts (Table attr caption colspecs thead tbody tfoot) = +blockToHtmlInner opts (Table attr caption colspecs thead tbody tfoot) = tableToHtml opts (Ann.toTable attr caption colspecs thead tbody tfoot) +-- | Convert Pandoc block element to HTML. All the legwork is done by +-- 'blockToHtmlInner', this just takes care of emitting the notes after +-- the block if necessary. +blockToHtml :: PandocMonad m => WriterOptions -> Block -> StateT WriterState m Html +blockToHtml opts block = do + -- Ignore inserted section divs -- they are not blocks as they came from + -- the document itself (at least not when coming from markdown) + let isSection = case block of + Div (_, classes, _) _ | "section" `elem` classes -> True + _ -> False + let increaseLevel = not isSection + when increaseLevel $ + modify (\st -> st{ stBlockLevel = stBlockLevel st + 1 }) + doc <- blockToHtmlInner opts block + st <- get + let emitNotes = + (writerReferenceLocation opts == EndOfBlock && stBlockLevel st == 1) || + (writerReferenceLocation opts == EndOfSection && isSection) + res <- if emitNotes + then do + notes <- if null (stNotes st) + then return mempty + else footnoteSection opts (writerReferenceLocation opts) (stEmittedNotes st + 1) (reverse (stNotes st)) + modify (\st' -> st'{ stNotes = mempty, stEmittedNotes = stEmittedNotes st' + length (stNotes st') }) + return (doc <> notes) + else return doc + when increaseLevel $ + modify (\st' -> st'{ stBlockLevel = stBlockLevel st' - 1 }) + return res + tableToHtml :: PandocMonad m => WriterOptions -> Ann.Table @@ -1468,7 +1524,8 @@ inlineToHtml opts inline = do -- note: null title included, as in Markdown.pl (Note contents) -> do notes <- gets stNotes - let number = length notes + 1 + emittedNotes <- gets stEmittedNotes + let number = emittedNotes + length notes + 1 let ref = tshow number htmlContents <- blockListToNote opts ref contents epubVersion <- gets stEPUBVersion diff --git a/test/Tests/Writers/HTML.hs b/test/Tests/Writers/HTML.hs index 404f6da98..50775b171 100644 --- a/test/Tests/Writers/HTML.hs +++ b/test/Tests/Writers/HTML.hs @@ -8,8 +8,11 @@ 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 +36,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" @@ -86,6 +104,61 @@ tests = =?> ("" ++ ">>=") ] + , testGroup "footnotes" + [ test (htmlWithOpts def{writerReferenceLocation=EndOfDocument}) + "at the end of a document" $ + noteTestDoc =?> + concat + [ "

Page title

" + , "

First section

" + , "

This is a footnote.1 And this is a link.

" + , "

A note inside a block quote.2

A second paragraph.

" + , "

Second section

" + , "

Some more text.

" + , "

  1. Down here.↩︎

  2. The second note.↩︎

" + ] + , test (htmlWithOpts def{writerReferenceLocation=EndOfBlock}) + "at the end of a block" $ + noteTestDoc =?> + concat + [ "

Page title

" + , "

First section

" + , "

This is a footnote.1 And this is a link.

" + , "
  1. Down here.↩︎

" + , "

A note inside a block quote.2

A second paragraph.

" + , "
  1. The second note.↩︎

" + , "

Second section

" + , "

Some more text.

" + ] + , test (htmlWithOpts def{writerReferenceLocation=EndOfSection}) + "at the end of a section" $ + noteTestDoc =?> + concat + [ "

Page title

" + , "

First section

" + , "

This is a footnote.1 And this is a link.

" + , "

A note inside a block quote.2

A second paragraph.

" + , "

  1. Down here.↩︎

  2. The second note.↩︎

" + , "

Second section

" + , "

Some more text.

" + ] + , 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). + concat + [ "
" + , "

Page title

" + , "
" + , "

First section

" + , "

This is a footnote.1 And this is a link.

A note inside a block quote.2

A second paragraph.

" + , "
" + , "

  1. Down here.↩︎

  2. The second note.↩︎

" + , "

Second section

Some more text.

" + , "
" + ] + ] ] where tQ :: (ToString a, ToPandoc a) diff --git a/test/command/4235.md b/test/command/4235.md index 8bbf43ff9..4f2644dd6 100644 --- a/test/command/4235.md +++ b/test/command/4235.md @@ -3,7 +3,7 @@ This.^[Has a footnote.] ^D

This.1

-
+

  1. Has a footnote.↩︎

  2. diff --git a/test/command/7006.md b/test/command/7006.md index e7951fb1a..7e2215cdf 100644 --- a/test/command/7006.md +++ b/test/command/7006.md @@ -7,7 +7,7 @@ Test.[^fn] ![Caption.](/image.jpg) ^D

    Test.1

    -
    +

    1. Foo:

      diff --git a/test/writer.html4 b/test/writer.html4 index 215a1efb9..257d86ddb 100644 --- a/test/writer.html4 +++ b/test/writer.html4 @@ -665,7 +665,7 @@ Blah
    2. And in list items.5

    This paragraph should not be part of the note, as it is not indented.

    -
    +

    1. Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.↩︎

    2. diff --git a/test/writer.html5 b/test/writer.html5 index 387df4058..0141bf9fe 100644 --- a/test/writer.html5 +++ b/test/writer.html5 @@ -667,7 +667,7 @@ Blah
    3. And in list items.5

    This paragraph should not be part of the note, as it is not indented.

    -
    +

    1. Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.↩︎

    2. -- cgit v1.2.3 From 0ebe65e651766a2b3d006d3dee4afdfd43a386d5 Mon Sep 17 00:00:00 2001 From: Emily Bourke Date: Wed, 8 Sep 2021 14:05:22 +0100 Subject: pptx: Fix logic for choosing Comparison layout There was a mistake in the logic used to choose between the Comparison and Two Content layouts: if one column contained only non-text (an image or a table) and the other contained only text, the Comparison layout was chosen instead of the desired Two Content layout. This commit fixes that logic: > If either column contains text followed by non-text, use Comparison. Otherwise, use Two Content. It also adds a test asserting this behaviour. --- pandoc.cabal | 6 ++++-- src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | 9 +++++---- test/Tests/Writers/Powerpoint.hs | 8 ++++++-- test/pptx/two-column/all-text/deleted-layouts.pptx | Bin 0 -> 30568 bytes test/pptx/two-column/all-text/input.native | 9 +++++++++ test/pptx/two-column/all-text/moved-layouts.pptx | Bin 0 -> 41256 bytes test/pptx/two-column/all-text/output.pptx | Bin 0 -> 27689 bytes test/pptx/two-column/all-text/templated.pptx | Bin 0 -> 40756 bytes test/pptx/two-column/deleted-layouts.pptx | Bin 30568 -> 0 bytes test/pptx/two-column/input.native | 9 --------- test/pptx/two-column/moved-layouts.pptx | Bin 41256 -> 0 bytes test/pptx/two-column/output.pptx | Bin 27689 -> 0 bytes test/pptx/two-column/templated.pptx | Bin 40756 -> 0 bytes .../pptx/two-column/text-and-image/deleted-layouts.pptx | Bin 0 -> 48392 bytes test/pptx/two-column/text-and-image/input.native | 12 ++++++++++++ test/pptx/two-column/text-and-image/moved-layouts.pptx | Bin 0 -> 59086 bytes test/pptx/two-column/text-and-image/output.pptx | Bin 0 -> 45520 bytes test/pptx/two-column/text-and-image/templated.pptx | Bin 0 -> 58586 bytes 18 files changed, 36 insertions(+), 17 deletions(-) create mode 100644 test/pptx/two-column/all-text/deleted-layouts.pptx create mode 100644 test/pptx/two-column/all-text/input.native create mode 100644 test/pptx/two-column/all-text/moved-layouts.pptx create mode 100644 test/pptx/two-column/all-text/output.pptx create mode 100644 test/pptx/two-column/all-text/templated.pptx delete mode 100644 test/pptx/two-column/deleted-layouts.pptx delete mode 100644 test/pptx/two-column/input.native delete mode 100644 test/pptx/two-column/moved-layouts.pptx delete mode 100644 test/pptx/two-column/output.pptx delete mode 100644 test/pptx/two-column/templated.pptx create mode 100644 test/pptx/two-column/text-and-image/deleted-layouts.pptx create mode 100644 test/pptx/two-column/text-and-image/input.native create mode 100644 test/pptx/two-column/text-and-image/moved-layouts.pptx create mode 100644 test/pptx/two-column/text-and-image/output.pptx create mode 100644 test/pptx/two-column/text-and-image/templated.pptx (limited to 'test/Tests/Writers') diff --git a/pandoc.cabal b/pandoc.cabal index 3de7da39c..347c33d51 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -446,8 +446,10 @@ extra-source-files: test/pptx/start-numbering-at/*.pptx test/pptx/tables/input.native test/pptx/tables/*.pptx - test/pptx/two-column/input.native - test/pptx/two-column/*.pptx + test/pptx/two-column/all-text/input.native + test/pptx/two-column/all-text/*.pptx + test/pptx/two-column/text-and-image/input.native + test/pptx/two-column/text-and-image/*.pptx test/ipynb/*.in.native test/ipynb/*.out.native test/ipynb/*.ipynb diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs index 10060d975..015e2cbdd 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs @@ -696,10 +696,11 @@ bodyBlocksToSlide _ (blk : blks) spkNotes sldId (ComparisonSlide [] (shapesL1, shapesL2) (shapesR1, shapesR2)) spkNotes - case (break notText blksL, break notText blksR) of - ((_, []), (_, [])) -> mkTwoColumn blksL blksR - (([], _), ([], _)) -> mkTwoColumn blksL blksR - ((blksL1, blksL2), (blksR1, blksR2)) -> mkComparison blksL1 blksL2 blksR1 blksR2 + let (blksL1, blksL2) = break notText blksL + (blksR1, blksR2) = break notText blksR + if (any null [blksL1, blksL2]) && (any null [blksR1, blksR2]) + then mkTwoColumn blksL blksR + else mkComparison blksL1 blksL2 blksR1 blksR2 bodyBlocksToSlide _ (blk : blks) spkNotes = do sldId <- asks envCurSlideId inNoteSlide <- asks envInNoteSlide diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs index 256ee1f7f..dd3846fef 100644 --- a/test/Tests/Writers/Powerpoint.hs +++ b/test/Tests/Writers/Powerpoint.hs @@ -103,8 +103,12 @@ tests = groupPptxTests [ pptxTests "Inline formatting" "pptx/images/output.pptx" , pptxTests "two-column layout" def - "pptx/two-column/input.native" - "pptx/two-column/output.pptx" + "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" diff --git a/test/pptx/two-column/all-text/deleted-layouts.pptx b/test/pptx/two-column/all-text/deleted-layouts.pptx new file mode 100644 index 000000000..1d7bd87d3 Binary files /dev/null and b/test/pptx/two-column/all-text/deleted-layouts.pptx differ diff --git a/test/pptx/two-column/all-text/input.native b/test/pptx/two-column/all-text/input.native new file mode 100644 index 000000000..086f74889 --- /dev/null +++ b/test/pptx/two-column/all-text/input.native @@ -0,0 +1,9 @@ +Pandoc (Meta {unMeta = fromList []}) +[Header 1 ("two-column-layout",[],[]) [Str "Two-Column",Space,Str "Layout"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Str "One",Space,Str "paragraph."] + ,Para [Str "Another",Space,Str "paragraph."]] + ,Div ("",["column"],[]) + [Para [Str "Second",Space,Str "column",Space,Str "paragraph."] + ,Para [Str "Another",Space,Str "second",Space,Str "paragraph."]]]] diff --git a/test/pptx/two-column/all-text/moved-layouts.pptx b/test/pptx/two-column/all-text/moved-layouts.pptx new file mode 100644 index 000000000..71760268c Binary files /dev/null and b/test/pptx/two-column/all-text/moved-layouts.pptx differ diff --git a/test/pptx/two-column/all-text/output.pptx b/test/pptx/two-column/all-text/output.pptx new file mode 100644 index 000000000..396dc2a74 Binary files /dev/null and b/test/pptx/two-column/all-text/output.pptx differ diff --git a/test/pptx/two-column/all-text/templated.pptx b/test/pptx/two-column/all-text/templated.pptx new file mode 100644 index 000000000..8901695b1 Binary files /dev/null and b/test/pptx/two-column/all-text/templated.pptx differ diff --git a/test/pptx/two-column/deleted-layouts.pptx b/test/pptx/two-column/deleted-layouts.pptx deleted file mode 100644 index 1d7bd87d3..000000000 Binary files a/test/pptx/two-column/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/two-column/input.native b/test/pptx/two-column/input.native deleted file mode 100644 index 086f74889..000000000 --- a/test/pptx/two-column/input.native +++ /dev/null @@ -1,9 +0,0 @@ -Pandoc (Meta {unMeta = fromList []}) -[Header 1 ("two-column-layout",[],[]) [Str "Two-Column",Space,Str "Layout"] -,Div ("",["columns"],[]) - [Div ("",["column"],[]) - [Para [Str "One",Space,Str "paragraph."] - ,Para [Str "Another",Space,Str "paragraph."]] - ,Div ("",["column"],[]) - [Para [Str "Second",Space,Str "column",Space,Str "paragraph."] - ,Para [Str "Another",Space,Str "second",Space,Str "paragraph."]]]] diff --git a/test/pptx/two-column/moved-layouts.pptx b/test/pptx/two-column/moved-layouts.pptx deleted file mode 100644 index 71760268c..000000000 Binary files a/test/pptx/two-column/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/two-column/output.pptx b/test/pptx/two-column/output.pptx deleted file mode 100644 index 396dc2a74..000000000 Binary files a/test/pptx/two-column/output.pptx and /dev/null differ diff --git a/test/pptx/two-column/templated.pptx b/test/pptx/two-column/templated.pptx deleted file mode 100644 index 8901695b1..000000000 Binary files a/test/pptx/two-column/templated.pptx and /dev/null differ diff --git a/test/pptx/two-column/text-and-image/deleted-layouts.pptx b/test/pptx/two-column/text-and-image/deleted-layouts.pptx new file mode 100644 index 000000000..297fd6bad Binary files /dev/null and b/test/pptx/two-column/text-and-image/deleted-layouts.pptx differ diff --git a/test/pptx/two-column/text-and-image/input.native b/test/pptx/two-column/text-and-image/input.native new file mode 100644 index 000000000..796c2c7f4 --- /dev/null +++ b/test/pptx/two-column/text-and-image/input.native @@ -0,0 +1,12 @@ +[Header 1 ("slide-1",[],[]) [Str "Slide",Space,Str "1"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Image ("",[],[]) [Str "an",Space,Str "image"] ("lalune.jpg","fig:")]] + ,Div ("",["column"],[]) + [Para [Str "This",Space,Str "should",Space,Str "use",Space,Str "Two",Space,Str "Content,",Space,Emph [Str "not"],Space,Str "Comparison!"]]] +,Header 1 ("slide-2",[],[]) [Str "Slide",Space,Str "2"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Str "This",Space,Str "should",Space,Str "also",Space,Str "use",Space,Str "Two",Space,Str "Content"]] + ,Div ("",["column"],[]) + [Para [Image ("",[],[]) [Str "an",Space,Str "image"] ("lalune.jpg","fig:")]]]] diff --git a/test/pptx/two-column/text-and-image/moved-layouts.pptx b/test/pptx/two-column/text-and-image/moved-layouts.pptx new file mode 100644 index 000000000..c9a6e577e Binary files /dev/null and b/test/pptx/two-column/text-and-image/moved-layouts.pptx differ diff --git a/test/pptx/two-column/text-and-image/output.pptx b/test/pptx/two-column/text-and-image/output.pptx new file mode 100644 index 000000000..bfd532ed9 Binary files /dev/null and b/test/pptx/two-column/text-and-image/output.pptx differ diff --git a/test/pptx/two-column/text-and-image/templated.pptx b/test/pptx/two-column/text-and-image/templated.pptx new file mode 100644 index 000000000..23e6b283f Binary files /dev/null and b/test/pptx/two-column/text-and-image/templated.pptx differ -- cgit v1.2.3 From 0fb6474a55427b52bf9aebd179f7b26f30c7dbaf Mon Sep 17 00:00:00 2001 From: Emily Bourke Date: Tue, 7 Sep 2021 13:38:47 +0100 Subject: pptx: Add support for incremental lists MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit - Support -i option - Support incremental/noincremental divs - Support older block quote syntax - Add tests One thing not clear from the manual is what should happen when the input uses a combination of these things. For example, what should the following produce? ```md ::: {.incremental .nonincremental} - are - these - incremental? ::: ::: incremental ::::: nonincremental - or - these? ::::: ::: ::: nonincremental > - how > - about > - these? ::: ``` In this commit I’ve taken the following approach, matching the observed behaviour for beamer and reveal.js output: - if a div with both classes, incremental wins - the innermost incremental/nonincremental div is the one which takes effect - a block quote containing a list as its first element inverts whether the list is incremental, whether or not the quote is inside an incremental/non-incremental div I’ve added some tests to verify this behaviour. This commit closes issue #5689 (https://github.com/jgm/pandoc/issues/5689). --- MANUAL.txt | 3 - pandoc.cabal | 4 + src/Text/Pandoc/Writers/Powerpoint/Output.hs | 566 +++++++++++++++------ src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | 51 +- test/Tests/Writers/Powerpoint.hs | 8 + .../with-flag/deleted-layouts.pptx | Bin 0 -> 80172 bytes test/pptx/incremental-lists/with-flag/input.native | 139 +++++ .../incremental-lists/with-flag/moved-layouts.pptx | Bin 0 -> 90917 bytes test/pptx/incremental-lists/with-flag/output.pptx | Bin 0 -> 77298 bytes .../incremental-lists/with-flag/templated.pptx | Bin 0 -> 90414 bytes .../without-flag/deleted-layouts.pptx | Bin 0 -> 78405 bytes .../incremental-lists/without-flag/input.native | 137 +++++ .../without-flag/moved-layouts.pptx | Bin 0 -> 89148 bytes .../incremental-lists/without-flag/output.pptx | Bin 0 -> 75533 bytes .../incremental-lists/without-flag/templated.pptx | Bin 0 -> 88645 bytes 15 files changed, 743 insertions(+), 165 deletions(-) create mode 100644 test/pptx/incremental-lists/with-flag/deleted-layouts.pptx create mode 100644 test/pptx/incremental-lists/with-flag/input.native create mode 100644 test/pptx/incremental-lists/with-flag/moved-layouts.pptx create mode 100644 test/pptx/incremental-lists/with-flag/output.pptx create mode 100644 test/pptx/incremental-lists/with-flag/templated.pptx create mode 100644 test/pptx/incremental-lists/without-flag/deleted-layouts.pptx create mode 100644 test/pptx/incremental-lists/without-flag/input.native create mode 100644 test/pptx/incremental-lists/without-flag/moved-layouts.pptx create mode 100644 test/pptx/incremental-lists/without-flag/output.pptx create mode 100644 test/pptx/incremental-lists/without-flag/templated.pptx (limited to 'test/Tests/Writers') diff --git a/MANUAL.txt b/MANUAL.txt index b65e45bfe..82fc21684 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -5919,9 +5919,6 @@ option): Both methods allow incremental and nonincremental lists to be mixed in a single document. -Note: Neither the `-i/--incremental` option nor any of the -methods described here currently works for PowerPoint output. - ## Inserting pauses You can add "pauses" within a slide by including a paragraph containing diff --git a/pandoc.cabal b/pandoc.cabal index 347c33d51..6fcc384f9 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -414,6 +414,10 @@ extra-source-files: test/pptx/endnotes/*.pptx test/pptx/images/input.native test/pptx/images/*.pptx + test/pptx/incremental-lists/with-flag/input.native + test/pptx/incremental-lists/with-flag/*.pptx + test/pptx/incremental-lists/without-flag/input.native + test/pptx/incremental-lists/without-flag/*.pptx test/pptx/inline-formatting/input.native test/pptx/inline-formatting/*.pptx test/pptx/lists/input.native diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs index 14cd82fdf..5eadf1312 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs @@ -1,7 +1,9 @@ {-# LANGUAGE DeriveTraversable #-} +{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE TupleSections #-} {- | Module : Text.Pandoc.Writers.Powerpoint.Output Copyright : Copyright (C) 2017-2020 Jesse Rosenthal @@ -23,6 +25,7 @@ import Control.Monad.Reader import Control.Monad.State import Codec.Archive.Zip import Data.List (intercalate, stripPrefix, nub, union, isPrefixOf, intersperse) +import Data.Bifunctor (bimap) import Data.CaseInsensitive (CI) import qualified Data.CaseInsensitive as CI import Data.Default @@ -415,7 +418,7 @@ updateMasterElems layouts master masterRels = (updatedMaster, updatedMasterRels) maxIdNumber :: Element -> Integer maxIdNumber relationships = maximum (0 : idNumbers) where - idNumbers = fst <$> mapMaybe (hush . decimal . T.drop 3) idAttributes + idNumbers = mapMaybe (readTextAsInteger . T.drop 3) idAttributes idAttributes = mapMaybe getIdAttribute (elContent relationships) getIdAttribute (Elem e) = findAttr (QName "Id" Nothing Nothing) e getIdAttribute _ = Nothing @@ -423,14 +426,11 @@ updateMasterElems layouts master masterRels = (updatedMaster, updatedMasterRels) maxIdNumber' :: Element -> Integer maxIdNumber' sldLayouts = maximum (0 : idNumbers) where - idNumbers = fst <$> mapMaybe (hush . decimal) idAttributes + idNumbers = mapMaybe readTextAsInteger idAttributes idAttributes = mapMaybe getIdAttribute (elContent sldLayouts) getIdAttribute (Elem e) = findAttr (QName "id" Nothing Nothing) e getIdAttribute _ = Nothing -hush :: Either a b -> Maybe b -hush = either (const Nothing) Just - makeSlideIdMap :: Presentation -> M.Map SlideId Int makeSlideIdMap (Presentation _ slides) = M.fromList $ map slideId slides `zip` [1..] @@ -575,19 +575,24 @@ getLayout layout = getElement <$> getSlideLayouts BlankSlide{} -> blank shapeHasId :: NameSpaces -> T.Text -> Element -> Bool -shapeHasId ns ident element - | Just nvSpPr <- findChild (elemName ns "p" "nvSpPr") element - , Just cNvPr <- findChild (elemName ns "p" "cNvPr") nvSpPr - , Just nm <- findAttr (QName "id" Nothing Nothing) cNvPr = - nm == ident - | otherwise = False +shapeHasId ns ident element = getShapeId ns element == Just ident + +getShapeId :: NameSpaces -> Element -> Maybe Text +getShapeId ns element = do + nvSpPr <- findChild (elemName ns "p" "nvSpPr") element + cNvPr <- findChild (elemName ns "p" "cNvPr") nvSpPr + findAttr (QName "id" Nothing Nothing) cNvPr -getContentShape :: PandocMonad m => NameSpaces -> Element -> P m Element +type ShapeId = Integer + +getContentShape :: PandocMonad m => NameSpaces -> Element -> P m (Maybe ShapeId, Element) getContentShape ns spTreeElem | isElem ns "p" "spTree" spTreeElem = do - ph@Placeholder{..} <- asks envPlaceholder + ph@Placeholder{index, placeholderType} <- asks envPlaceholder case drop index (getShapesByPlaceHolderType ns spTreeElem placeholderType) of - sp : _ -> return sp + sp : _ -> let + shapeId = getShapeId ns sp >>= readTextAsInteger + in return (shapeId, sp) [] -> throwError $ PandocSomeError $ missingPlaceholderMessage ph getContentShape _ _ = throwError $ PandocSomeError "Attempted to find content on non shapeTree" @@ -651,7 +656,7 @@ getContentShapeSize ns layout master | isElem ns "p" "sldLayout" layout , Just cSld <- findChild (elemName ns "p" "cSld") layout , Just spTree <- findChild (elemName ns "p" "spTree") cSld = do - sp <- getContentShape ns spTree + (_, sp) <- getContentShape ns spTree case getShapeDimensions ns sp of Just sz -> return sz Nothing -> do let mbSz = @@ -873,33 +878,35 @@ captionHeight = 40 createCaption :: PandocMonad m => ((Integer, Integer), (Integer, Integer)) -> [ParaElem] - -> P m Element + -> P m (ShapeId, Element) createCaption contentShapeDimensions paraElements = do let para = Paragraph def{pPropAlign = Just AlgnCenter} paraElements elements <- mapM paragraphToElement [para] let ((x, y), (cx, cy)) = contentShapeDimensions let txBody = mknode "p:txBody" [] $ [mknode "a:bodyPr" [] (), mknode "a:lstStyle" [] ()] <> elements - return $ - mknode "p:sp" [] [ mknode "p:nvSpPr" [] - [ mknode "p:cNvPr" [("id","1"), ("name","TextBox 3")] () - , mknode "p:cNvSpPr" [("txBox", "1")] () - , mknode "p:nvPr" [] () - ] - , mknode "p:spPr" [] - [ mknode "a:xfrm" [] - [ mknode "a:off" [("x", tshow $ 12700 * x), - ("y", tshow $ 12700 * (y + cy - captionHeight))] () - , mknode "a:ext" [("cx", tshow $ 12700 * cx), - ("cy", tshow $ 12700 * captionHeight)] () - ] - , mknode "a:prstGeom" [("prst", "rect")] - [ mknode "a:avLst" [] () - ] - , mknode "a:noFill" [] () - ] - , txBody - ] + return + ( 1 + , mknode "p:sp" [] [ mknode "p:nvSpPr" [] + [ mknode "p:cNvPr" [("id","1"), ("name","TextBox 3")] () + , mknode "p:cNvSpPr" [("txBox", "1")] () + , mknode "p:nvPr" [] () + ] + , mknode "p:spPr" [] + [ mknode "a:xfrm" [] + [ mknode "a:off" [("x", tshow $ 12700 * x), + ("y", tshow $ 12700 * (y + cy - captionHeight))] () + , mknode "a:ext" [("cx", tshow $ 12700 * cx), + ("cy", tshow $ 12700 * captionHeight)] () + ] + , mknode "a:prstGeom" [("prst", "rect")] + [ mknode "a:avLst" [] () + ] + , mknode "a:noFill" [] () + ] + , txBody + ] + ) makePicElements :: PandocMonad m => Element @@ -907,7 +914,7 @@ makePicElements :: PandocMonad m -> MediaInfo -> Text -> [ParaElem] - -> P m [Element] + -> P m [(ShapeId, Element)] makePicElements layout picProps mInfo titleText alt = do opts <- asks envOpts (pageWidth, pageHeight) <- asks envPresentationSize @@ -975,10 +982,12 @@ makePicElements layout picProps mInfo titleText alt = do let spPr = mknode "p:spPr" [("bwMode","auto")] [xfrm, prstGeom, mknode "a:noFill" [] (), ln] - let picShape = mknode "p:pic" [] - [ nvPicPr - , blipFill - , spPr ] + let picShape = ( 0 + , mknode "p:pic" [] + [ nvPicPr + , blipFill + , spPr ] + ) -- And now, maybe create the caption: if hasCaption @@ -1125,44 +1134,50 @@ paragraphToElement par = do return $ mknode "a:p" [] $ [Elem $ mknode "a:pPr" attrs props] <> concat paras -shapeToElement :: PandocMonad m => Element -> Shape -> P m Element +shapeToElement :: PandocMonad m => Element -> Shape -> P m (Maybe ShapeId, Element) shapeToElement layout (TextBox paras) | ns <- elemToNameSpaces layout , Just cSld <- findChild (elemName ns "p" "cSld") layout , Just spTree <- findChild (elemName ns "p" "spTree") cSld = do - sp <- getContentShape ns spTree + (shapeId, sp) <- getContentShape ns spTree elements <- mapM paragraphToElement paras let txBody = mknode "p:txBody" [] $ [mknode "a:bodyPr" [] (), mknode "a:lstStyle" [] ()] <> elements emptySpPr = mknode "p:spPr" [] () return + . (shapeId,) . surroundWithMathAlternate . replaceNamedChildren ns "p" "txBody" [txBody] . replaceNamedChildren ns "p" "spPr" [emptySpPr] $ sp -- GraphicFrame and Pic should never reach this. -shapeToElement _ _ = return $ mknode "p:sp" [] () +shapeToElement _ _ = return (Nothing, mknode "p:sp" [] ()) -shapeToElements :: PandocMonad m => Element -> Shape -> P m [Content] +shapeToElements :: PandocMonad m => Element -> Shape -> P m [(Maybe ShapeId, Content)] shapeToElements layout (Pic picProps fp titleText alt) = do mInfo <- registerMedia fp alt case mInfoExt mInfo of - Just _ -> map Elem <$> + Just _ -> map (bimap Just Elem) <$> makePicElements layout picProps mInfo titleText alt Nothing -> shapeToElements layout $ TextBox [Paragraph def alt] -shapeToElements layout (GraphicFrame tbls cptn) = map Elem <$> +shapeToElements layout (GraphicFrame tbls cptn) = map (bimap Just Elem) <$> graphicFrameToElements layout tbls cptn shapeToElements _ (RawOOXMLShape str) = return - [Text (CData CDataRaw str Nothing)] + [(Nothing, Text (CData CDataRaw str Nothing))] shapeToElements layout shp = do - element <- shapeToElement layout shp - return [Elem element] + (shapeId, element) <- shapeToElement layout shp + return [(shapeId, Elem element)] -shapesToElements :: PandocMonad m => Element -> [Shape] -> P m [Content] +shapesToElements :: PandocMonad m => Element -> [Shape] -> P m [(Maybe ShapeId, Content)] shapesToElements layout shps = concat <$> mapM (shapeToElements layout) shps -graphicFrameToElements :: PandocMonad m => Element -> [Graphic] -> [ParaElem] -> P m [Element] +graphicFrameToElements :: + PandocMonad m => + Element -> + [Graphic] -> + [ParaElem] -> + P m [(ShapeId, Element)] graphicFrameToElements layout tbls caption = do -- get the sizing master <- getMaster @@ -1176,21 +1191,23 @@ graphicFrameToElements layout tbls caption = do elements <- mapM (graphicToElement cx) tbls let graphicFrameElts = - mknode "p:graphicFrame" [] $ - [ mknode "p:nvGraphicFramePr" [] - [ mknode "p:cNvPr" [("id", "6"), ("name", "Content Placeholder 5")] () - , mknode "p:cNvGraphicFramePr" [] - [mknode "a:graphicFrameLocks" [("noGrp", "1")] ()] - , mknode "p:nvPr" [] - [mknode "p:ph" [("idx", "1")] ()] - ] - , mknode "p:xfrm" [] - [ mknode "a:off" [("x", tshow $ 12700 * x), - ("y", tshow $ 12700 * y)] () - , mknode "a:ext" [("cx", tshow $ 12700 * cx), - ("cy", tshow $ 12700 * cy)] () - ] - ] <> elements + ( 6 + , mknode "p:graphicFrame" [] $ + [ mknode "p:nvGraphicFramePr" [] + [ mknode "p:cNvPr" [("id", "6"), ("name", "Content Placeholder 5")] () + , mknode "p:cNvGraphicFramePr" [] + [mknode "a:graphicFrameLocks" [("noGrp", "1")] ()] + , mknode "p:nvPr" [] + [mknode "p:ph" [("idx", "1")] ()] + ] + , mknode "p:xfrm" [] + [ mknode "a:off" [("x", tshow $ 12700 * x), + ("y", tshow $ 12700 * y)] () + , mknode "a:ext" [("cx", tshow $ 12700 * cx), + ("cy", tshow $ 12700 * cy)] () + ] + ] <> elements + ) if not $ null caption then do capElt <- createCaption ((x, y), (cx, cytmp)) caption @@ -1312,52 +1329,101 @@ getShapeByPlaceHolderTypes ns spTreeElem (s:ss) = Just element -> Just element Nothing -> getShapeByPlaceHolderTypes ns spTreeElem ss -nonBodyTextToElement :: PandocMonad m => Element -> [PHType] -> [ParaElem] -> P m Element +nonBodyTextToElement :: + PandocMonad m => + Element -> + [PHType] -> + [ParaElem] -> + P m (Maybe ShapeId, Element) nonBodyTextToElement layout phTypes paraElements | ns <- elemToNameSpaces layout , Just cSld <- findChild (elemName ns "p" "cSld") layout , Just spTree <- findChild (elemName ns "p" "spTree") cSld - , Just sp <- getShapeByPlaceHolderTypes ns spTree phTypes = do + , Just sp <- getShapeByPlaceHolderTypes ns spTree phTypes + , Just nvSpPr <- findChild (elemName ns "p" "nvSpPr") sp + , Just cNvPr <- findChild (elemName ns "p" "cNvPr") nvSpPr + , Just shapeId <- findAttr (nodename "id") cNvPr + , Right (shapeIdNum, _) <- decimal shapeId = do let hdrPara = Paragraph def paraElements element <- paragraphToElement hdrPara let txBody = mknode "p:txBody" [] $ [mknode "a:bodyPr" [] (), mknode "a:lstStyle" [] ()] <> [element] - return $ replaceNamedChildren ns "p" "txBody" [txBody] sp + return (Just shapeIdNum, replaceNamedChildren ns "p" "txBody" [txBody] sp) -- XXX: TODO - | otherwise = return $ mknode "p:sp" [] () + | otherwise = return (Nothing, mknode "p:sp" [] ()) -contentToElement :: PandocMonad m => Element -> [ParaElem] -> [Shape] -> P m Element +data ContentShapeIds = ContentShapeIds + { contentHeaderId :: Maybe ShapeId + , contentContentIds :: [ShapeId] + } + +contentToElement :: + PandocMonad m => + Element -> + [ParaElem] -> + [Shape] -> + P m (Maybe ContentShapeIds, Element) contentToElement layout hdrShape shapes | ns <- elemToNameSpaces layout , Just cSld <- findChild (elemName ns "p" "cSld") layout , Just spTree <- findChild (elemName ns "p" "spTree") cSld = do - element <- nonBodyTextToElement layout [PHType "title"] hdrShape + (shapeId, element) <- nonBodyTextToElement layout [PHType "title"] hdrShape let hdrShapeElements = [Elem element | not (null hdrShape)] - contentElements <- local + contentHeaderId = if null hdrShape then Nothing else shapeId + content <- local (\env -> env {envPlaceholder = Placeholder ObjType 0}) (shapesToElements layout shapes) - return $ buildSpTree ns spTree (hdrShapeElements <> contentElements) -contentToElement _ _ _ = return $ mknode "p:sp" [] () - -twoColumnToElement :: PandocMonad m => Element -> [ParaElem] -> [Shape] -> [Shape] -> P m Element + let contentContentIds = mapMaybe fst content + contentElements = snd <$> content + return ( Just ContentShapeIds{..} + , buildSpTree ns spTree (hdrShapeElements <> contentElements) + ) +contentToElement _ _ _ = return (Nothing, mknode "p:sp" [] ()) + +data TwoColumnShapeIds = TwoColumnShapeIds + { twoColumnHeaderId :: Maybe ShapeId + , twoColumnLeftIds :: [ShapeId] + , twoColumnRightIds :: [ShapeId] + } + +twoColumnToElement :: + PandocMonad m => + Element -> + [ParaElem] -> + [Shape] -> + [Shape] -> + P m (Maybe TwoColumnShapeIds, Element) twoColumnToElement layout hdrShape shapesL shapesR | ns <- elemToNameSpaces layout , Just cSld <- findChild (elemName ns "p" "cSld") layout , Just spTree <- findChild (elemName ns "p" "spTree") cSld = do - element <- nonBodyTextToElement layout [PHType "title"] hdrShape + (headerId, element) <- nonBodyTextToElement layout [PHType "title"] hdrShape let hdrShapeElements = [Elem element | not (null hdrShape)] - contentElementsL <- local - (\env -> env {envPlaceholder = Placeholder ObjType 0}) - (shapesToElements layout shapesL) - contentElementsR <- local - (\env -> env {envPlaceholder = Placeholder ObjType 1}) - (shapesToElements layout shapesR) + twoColumnHeaderId = if null hdrShape then Nothing else headerId + contentL <- local (\env -> env {envPlaceholder = Placeholder ObjType 0}) + (shapesToElements layout shapesL) + let twoColumnLeftIds = mapMaybe fst contentL + contentElementsL = snd <$> contentL + contentR <- local (\env -> env {envPlaceholder = Placeholder ObjType 1}) + (shapesToElements layout shapesR) + let (twoColumnRightIds) = (mapMaybe fst contentR) + contentElementsR = snd <$> contentR -- let contentElementsL' = map (setIdx ns "1") contentElementsL -- contentElementsR' = map (setIdx ns "2") contentElementsR - return $ buildSpTree ns spTree $ - hdrShapeElements <> contentElementsL <> contentElementsR -twoColumnToElement _ _ _ _= return $ mknode "p:sp" [] () + return + $ (Just TwoColumnShapeIds{..}, ) + $ buildSpTree ns spTree + $ hdrShapeElements <> contentElementsL <> contentElementsR +twoColumnToElement _ _ _ _ = return (Nothing, mknode "p:sp" [] ()) + +data ComparisonShapeIds = ComparisonShapeIds + { comparisonHeaderId :: Maybe ShapeId + , comparisonLeftTextIds :: [ShapeId] + , comparisonLeftContentIds :: [ShapeId] + , comparisonRightTextIds :: [ShapeId] + , comparisonRightContentIds :: [ShapeId] + } comparisonToElement :: PandocMonad m => @@ -1365,33 +1431,46 @@ comparisonToElement :: [ParaElem] -> ([Shape], [Shape]) -> ([Shape], [Shape]) -> - P m Element + P m (Maybe ComparisonShapeIds, Element) comparisonToElement layout hdrShape (shapesL1, shapesL2) (shapesR1, shapesR2) | ns <- elemToNameSpaces layout , Just cSld <- findChild (elemName ns "p" "cSld") layout , Just spTree <- findChild (elemName ns "p" "spTree") cSld = do - element <- nonBodyTextToElement layout [PHType "title"] hdrShape + (headerShapeId, element) <- nonBodyTextToElement layout [PHType "title"] hdrShape let hdrShapeElements = [Elem element | not (null hdrShape)] - contentElementsL1 <- local - (\env -> env {envPlaceholder = Placeholder (PHType "body") 0}) - (shapesToElements layout shapesL1) - contentElementsL2 <- local - (\env -> env {envPlaceholder = Placeholder ObjType 0}) - (shapesToElements layout shapesL2) - contentElementsR1 <- local - (\env -> env {envPlaceholder = Placeholder (PHType "body") 1}) - (shapesToElements layout shapesR1) - contentElementsR2 <- local - (\env -> env {envPlaceholder = Placeholder ObjType 1}) - (shapesToElements layout shapesR2) - return $ buildSpTree ns spTree $ - mconcat [ hdrShapeElements - , contentElementsL1 - , contentElementsL2 - , contentElementsR1 - , contentElementsR2 - ] -comparisonToElement _ _ _ _= return $ mknode "p:sp" [] () + comparisonHeaderId = if null hdrShape then Nothing else headerShapeId + contentL1 <- local (\env -> env {envPlaceholder = Placeholder (PHType "body") 0}) + (shapesToElements layout shapesL1) + let comparisonLeftTextIds = mapMaybe fst contentL1 + contentElementsL1 = snd <$> contentL1 + contentL2 <- local (\env -> env {envPlaceholder = Placeholder ObjType 0}) + (shapesToElements layout shapesL2) + let comparisonLeftContentIds = mapMaybe fst contentL2 + contentElementsL2 = snd <$> contentL2 + contentR1 <- local (\env -> env {envPlaceholder = Placeholder (PHType "body") 1}) + (shapesToElements layout shapesR1) + let comparisonRightTextIds = mapMaybe fst contentR1 + contentElementsR1 = snd <$> contentR1 + contentR2 <- local (\env -> env {envPlaceholder = Placeholder ObjType 1}) + (shapesToElements layout shapesR2) + let comparisonRightContentIds = mapMaybe fst contentR2 + contentElementsR2 = snd <$> contentR2 + return + $ (Just ComparisonShapeIds{..}, ) + $ buildSpTree ns spTree + $ mconcat [ hdrShapeElements + , contentElementsL1 + , contentElementsL2 + , contentElementsR1 + , contentElementsR2 + ] +comparisonToElement _ _ _ _= return (Nothing, mknode "p:sp" [] ()) + +data ContentWithCaptionShapeIds = ContentWithCaptionShapeIds + { contentWithCaptionHeaderId :: Maybe ShapeId + , contentWithCaptionCaptionIds :: [ShapeId] + , contentWithCaptionContentIds :: [ShapeId] + } contentWithCaptionToElement :: PandocMonad m => @@ -1399,25 +1478,30 @@ contentWithCaptionToElement :: [ParaElem] -> [Shape] -> [Shape] -> - P m Element + P m (Maybe ContentWithCaptionShapeIds, Element) contentWithCaptionToElement layout hdrShape textShapes contentShapes | ns <- elemToNameSpaces layout , Just cSld <- findChild (elemName ns "p" "cSld") layout , Just spTree <- findChild (elemName ns "p" "spTree") cSld = do - element <- nonBodyTextToElement layout [PHType "title"] hdrShape + (shapeId, element) <- nonBodyTextToElement layout [PHType "title"] hdrShape let hdrShapeElements = [Elem element | not (null hdrShape)] - textElements <- local - (\env -> env {envPlaceholder = Placeholder (PHType "body") 0}) - (shapesToElements layout textShapes) - contentElements <- local - (\env -> env {envPlaceholder = Placeholder ObjType 0}) - (shapesToElements layout contentShapes) - return $ buildSpTree ns spTree $ - mconcat [ hdrShapeElements - , textElements - , contentElements - ] -contentWithCaptionToElement _ _ _ _ = return $ mknode "p:sp" [] () + contentWithCaptionHeaderId = if null hdrShape then Nothing else shapeId + text <- local (\env -> env {envPlaceholder = Placeholder (PHType "body") 0}) + (shapesToElements layout textShapes) + let contentWithCaptionCaptionIds = mapMaybe fst text + textElements = snd <$> text + content <- local (\env -> env {envPlaceholder = Placeholder ObjType 0}) + (shapesToElements layout contentShapes) + let contentWithCaptionContentIds = mapMaybe fst content + contentElements = snd <$> content + return + $ (Just ContentWithCaptionShapeIds{..}, ) + $ buildSpTree ns spTree + $ mconcat [ hdrShapeElements + , textElements + , contentElements + ] +contentWithCaptionToElement _ _ _ _ = return (Nothing, mknode "p:sp" [] ()) blankToElement :: PandocMonad m => @@ -1430,73 +1514,116 @@ blankToElement layout return $ buildSpTree ns spTree [] blankToElement _ = return $ mknode "p:sp" [] () -titleToElement :: PandocMonad m => Element -> [ParaElem] -> P m Element +newtype TitleShapeIds = TitleShapeIds + { titleHeaderId :: Maybe ShapeId + } + +titleToElement :: + PandocMonad m => + Element -> + [ParaElem] -> + P m (Maybe TitleShapeIds, Element) titleToElement layout titleElems | ns <- elemToNameSpaces layout , Just cSld <- findChild (elemName ns "p" "cSld") layout , Just spTree <- findChild (elemName ns "p" "spTree") cSld = do - element <- nonBodyTextToElement layout [PHType "title", PHType "ctrTitle"] titleElems + (shapeId, element) <- nonBodyTextToElement layout [PHType "title", PHType "ctrTitle"] titleElems let titleShapeElements = [Elem element | not (null titleElems)] - return $ buildSpTree ns spTree titleShapeElements -titleToElement _ _ = return $ mknode "p:sp" [] () + titleHeaderId = if null titleElems then Nothing else shapeId + return $ (Just TitleShapeIds{..}, ) $ buildSpTree ns spTree titleShapeElements +titleToElement _ _ = return (Nothing, mknode "p:sp" [] ()) + +data MetadataShapeIds = MetadataShapeIds + { metadataTitleId :: Maybe ShapeId + , metadataSubtitleId :: Maybe ShapeId + , metadataDateId :: Maybe ShapeId + } -metadataToElement :: PandocMonad m => Element -> [ParaElem] -> [ParaElem] -> [[ParaElem]] -> [ParaElem] -> P m Element +metadataToElement :: + PandocMonad m => + Element -> + [ParaElem] -> + [ParaElem] -> + [[ParaElem]] -> + [ParaElem] -> + P m (Maybe MetadataShapeIds, Element) metadataToElement layout titleElems subtitleElems authorsElems dateElems | ns <- elemToNameSpaces layout , Just cSld <- findChild (elemName ns "p" "cSld") layout , Just spTree <- findChild (elemName ns "p" "spTree") cSld = do - titleShapeElements <- if null titleElems - then return [] - else sequence [nonBodyTextToElement layout [PHType "ctrTitle"] titleElems] let combinedAuthorElems = intercalate [Break] authorsElems subtitleAndAuthorElems = intercalate [Break, Break] [subtitleElems, combinedAuthorElems] - subtitleShapeElements <- if null subtitleAndAuthorElems - then return [] - else sequence [nonBodyTextToElement layout [PHType "subTitle"] subtitleAndAuthorElems] - dateShapeElements <- if null dateElems - then return [] - else sequence [nonBodyTextToElement layout [PHType "dt"] dateElems] - return . buildSpTree ns spTree . map Elem $ - (titleShapeElements <> subtitleShapeElements <> dateShapeElements) -metadataToElement _ _ _ _ _ = return $ mknode "p:sp" [] () + (titleId, titleElement) <- nonBodyTextToElement layout [PHType "ctrTitle"] titleElems + (subtitleId, subtitleElement) <- nonBodyTextToElement layout [PHType "subTitle"] subtitleAndAuthorElems + (dateId, dateElement) <- nonBodyTextToElement layout [PHType "dt"] dateElems + let titleShapeElements = [titleElement | not (null titleElems)] + metadataTitleId = if null titleElems then Nothing else titleId + subtitleShapeElements = [subtitleElement | not (null subtitleAndAuthorElems)] + metadataSubtitleId = if null subtitleAndAuthorElems then Nothing else subtitleId + dateShapeElements = [dateElement | not (null dateElems)] + metadataDateId = if null dateElems then Nothing else dateId + return + $ (Just MetadataShapeIds{..}, ) + $ buildSpTree ns spTree + $ map Elem + $ titleShapeElements <> subtitleShapeElements <> dateShapeElements +metadataToElement _ _ _ _ _ = return (Nothing, mknode "p:sp" [] ()) slideToElement :: PandocMonad m => Slide -> P m Element slideToElement (Slide _ l@(ContentSlide hdrElems shapes) _ )= do layout <- getLayout l - spTree <- local (\env -> if null hdrElems - then env - else env{envSlideHasHeader=True}) $ - contentToElement layout hdrElems shapes + (shapeIds, spTree) + <- local (\env -> if null hdrElems + then env + else env{envSlideHasHeader=True}) + (contentToElement layout hdrElems shapes) + let animations = case shapeIds of + Nothing -> [] + Just ContentShapeIds{..} -> + slideToIncrementalAnimations (zip contentContentIds shapes) return $ mknode "p:sld" [ ("xmlns:a", "http://schemas.openxmlformats.org/drawingml/2006/main"), ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") - ] [mknode "p:cSld" [] [spTree]] + ] (mknode "p:cSld" [] [spTree] : animations) slideToElement (Slide _ l@(TwoColumnSlide hdrElems shapesL shapesR) _) = do layout <- getLayout l - spTree <- local (\env -> if null hdrElems + (shapeIds, spTree) <- local (\env -> if null hdrElems then env else env{envSlideHasHeader=True}) $ twoColumnToElement layout hdrElems shapesL shapesR + let animations = case shapeIds of + Nothing -> [] + Just TwoColumnShapeIds{..} -> + slideToIncrementalAnimations (zip twoColumnLeftIds shapesL + <> zip twoColumnRightIds shapesR) return $ mknode "p:sld" [ ("xmlns:a", "http://schemas.openxmlformats.org/drawingml/2006/main"), ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") - ] [mknode "p:cSld" [] [spTree]] + ] (mknode "p:cSld" [] [spTree] : animations) slideToElement (Slide _ l@(ComparisonSlide hdrElems shapesL shapesR) _) = do layout <- getLayout l - spTree <- local (\env -> if null hdrElems + (shapeIds, spTree) <- local (\env -> if null hdrElems then env else env{envSlideHasHeader=True}) $ comparisonToElement layout hdrElems shapesL shapesR + let animations = case shapeIds of + Nothing -> [] + Just ComparisonShapeIds{..} -> + slideToIncrementalAnimations + (zip comparisonLeftTextIds (fst shapesL) + <> zip comparisonLeftContentIds (snd shapesL) + <> zip comparisonRightTextIds (fst shapesR) + <> zip comparisonRightContentIds (snd shapesR)) return $ mknode "p:sld" [ ("xmlns:a", "http://schemas.openxmlformats.org/drawingml/2006/main"), ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") - ] [mknode "p:cSld" [] [spTree]] + ] (mknode "p:cSld" [] [spTree] : animations) slideToElement (Slide _ l@(TitleSlide hdrElems) _) = do layout <- getLayout l - spTree <- titleToElement layout hdrElems + (_, spTree) <- titleToElement layout hdrElems return $ mknode "p:sld" [ ("xmlns:a", "http://schemas.openxmlformats.org/drawingml/2006/main"), ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), @@ -1504,7 +1631,7 @@ slideToElement (Slide _ l@(TitleSlide hdrElems) _) = do ] [mknode "p:cSld" [] [spTree]] slideToElement (Slide _ l@(MetadataSlide titleElems subtitleElems authorElems dateElems) _) = do layout <- getLayout l - spTree <- metadataToElement layout titleElems subtitleElems authorElems dateElems + (_, spTree) <- metadataToElement layout titleElems subtitleElems authorElems dateElems return $ mknode "p:sld" [ ("xmlns:a", "http://schemas.openxmlformats.org/drawingml/2006/main"), ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), @@ -1512,12 +1639,18 @@ slideToElement (Slide _ l@(MetadataSlide titleElems subtitleElems authorElems da ] [mknode "p:cSld" [] [spTree]] slideToElement (Slide _ l@(ContentWithCaptionSlide hdrElems captionShapes contentShapes) _) = do layout <- getLayout l - spTree <- contentWithCaptionToElement layout hdrElems captionShapes contentShapes + (shapeIds, spTree) <- contentWithCaptionToElement layout hdrElems captionShapes contentShapes + let animations = case shapeIds of + Nothing -> [] + Just ContentWithCaptionShapeIds{..} -> + slideToIncrementalAnimations + (zip contentWithCaptionCaptionIds captionShapes + <> zip contentWithCaptionContentIds contentShapes) return $ mknode "p:sld" [ ("xmlns:a", "http://schemas.openxmlformats.org/drawingml/2006/main"), ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") - ] [mknode "p:cSld" [] [spTree]] + ] (mknode "p:cSld" [] [spTree] : animations) slideToElement (Slide _ BlankSlide _) = do layout <- getLayout BlankSlide spTree <- blankToElement layout @@ -1527,6 +1660,27 @@ slideToElement (Slide _ BlankSlide _) = do ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") ] [mknode "p:cSld" [] [spTree]] +slideToIncrementalAnimations :: + [(ShapeId, Shape)] -> + [Element] +slideToIncrementalAnimations shapes = let + incrementals :: [(ShapeId, [Bool])] + incrementals = do + (shapeId, TextBox ps) <- shapes + pure . (shapeId,) $ do + Paragraph ParaProps{pPropIncremental} _ <- ps + pure pPropIncremental + toIndices :: [Bool] -> Maybe (NonEmpty (Integer, Integer)) + toIndices bs = do + let indexed = zip [0..] bs + ts <- nonEmpty (filter snd indexed) + pure (fmap (\(n, _) -> (n, n)) ts) + indices :: [(ShapeId, NonEmpty (Integer, Integer))] + indices = do + (shapeId, bs) <- incrementals + toList ((,) shapeId <$> toIndices bs) + in toList (incrementalAnimation <$> nonEmpty indices) + -------------------------------------------------------------------- -- Notes: @@ -2080,9 +2234,10 @@ presentationToPresentationElement presentationUpdateRIdData pres = do updateRIdAttribute :: XML.Attr -> XML.Attr updateRIdAttribute attr = fromMaybe attr $ do - (oldValue, _) <- case attrKey attr of + oldValue <- case attrKey attr of QName "id" _ (Just "r") -> - T.stripPrefix "rId" (attrVal attr) >>= (hush . decimal) + T.stripPrefix "rId" (attrVal attr) + >>= fmap fromIntegral . readTextAsInteger _ -> Nothing let newValue = updatePresentationRId presentationUpdateRIdData oldValue pure attr {attrVal = "rId" <> T.pack (show newValue)} @@ -2316,3 +2471,102 @@ autoNumAttrs (startNum, numStyle, numDelim) = OneParen -> "ParenR" TwoParens -> "ParenBoth" _ -> "Period" + +-- | The XML required to insert an "appear" animation for each of the given +-- groups of paragraphs, identified by index. +incrementalAnimation :: + -- | (ShapeId, [(startParagraphIndex, endParagraphIndex)]) + NonEmpty (ShapeId, NonEmpty (Integer, Integer)) -> + Element +incrementalAnimation indices = mknode "p:timing" [] [tnLst, bldLst] + where + triples :: NonEmpty (ShapeId, Integer, Integer) + triples = do + (shapeId, paragraphIds) <- indices + (start, end) <- paragraphIds + pure (shapeId, start, end) + + tnLst = mknode "p:tnLst" [] + $ mknode "p:par" [] + $ mknode "p:cTn" [ ("id", "1") + , ("dur", "indefinite") + , ("restart", "never") + , ("nodeType", "tmRoot") + ] + $ mknode "p:childTnLst" [] + $ mknode "p:seq" [ ("concurrent", "1") + , ("nextAc", "seek") + ] + [ mknode "p:cTn" [ ("id", "2") + , ("dur", "indefinite") + , ("nodeType", "mainSeq") + ] + $ mknode "p:childTnLst" [] + $ zipWith makePar [3, 7 ..] (toList triples) + , mknode "p:prevCondLst" [] + $ mknode "p:cond" ([("evt", "onPrev"), ("delay", "0")]) + $ mknode "p:tgtEl" [] + $ mknode "p:sldTgt" [] () + , mknode "p:nextCondLst" [] + $ mknode "p:cond" ([("evt", "onNext"), ("delay", "0")]) + $ mknode "p:tgtEl" [] + $ mknode "p:sldTgt" [] () + ] + bldLst = mknode "p:bldLst" [] + [ mknode "p:bldP" [ ("spid", T.pack (show shapeId)) + , ("grpId", "0") + , ("uiExpand", "1") + , ("build", "p") + ] + () | (shapeId, _) <- toList indices + ] + + makePar :: Integer -> (ShapeId, Integer, Integer) -> Element + makePar nextId (shapeId, start, end) = + mknode "p:par" [] + $ mknode "p:cTn" [("id", T.pack (show nextId)), ("fill", "hold")] + [ mknode "p:stCondLst" [] + $ mknode "p:cond" [("delay", "indefinite")] () + , mknode "p:childTnLst" [] + $ mknode "p:par" [] + $ mknode "p:cTn" [ ("id", T.pack (show (nextId + 1))) + , ("fill", "hold") + ] + [ mknode "p:stCondLst" [] + $ mknode "p:cond" [("delay", "0")] () + , mknode "p:childTnLst" [] + $ mknode "p:par" [] + $ mknode "p:cTn" [ ("id", T.pack (show (nextId + 2))) + , ("presetID", "1") + , ("presetClass", "entr") + , ("presetSubtype", "0") + , ("fill", "hold") + , ("grpId", "0") + , ("nodeType", "clickEffect") + ] + [ mknode "p:stCondLst" [] + $ mknode "p:cond" [("delay", "0")] () + , mknode "p:childTnLst" [] + $ mknode "p:set" [] + [ mknode "p:cBhvr" [] + [ mknode "p:cTn" [ ("id", T.pack (show (nextId + 3))) + , ("dur", "1") + , ("fill", "hold") + ] + $ mknode "p:stCondLst" [] + $ mknode "p:cond" [("delay", "0")] () + , mknode "p:tgtEl" [] + $ mknode "p:spTgt" [("spid", T.pack (show shapeId))] + $ mknode "p:txEl" [] + $ mknode "p:pRg" [ ("st", T.pack (show start)) + , ("end", T.pack (show end))] + () + , mknode "p:attrNameLst" [] + $ mknode "p:attrName" [] ("style.visibility" :: Text) + ] + , mknode "p:to" [] + $ mknode "p:strVal" [("val", "visible")] () + ] + ] + ] + ] diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs index 015e2cbdd..a7660fc5e 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs @@ -1,8 +1,9 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE ViewPatterns #-} -{-# LANGUAGE GeneralizedNewtypeDeriving #-} -{-# LANGUAGE LambdaCase #-} {- | Module : Text.Pandoc.Writers.Powerpoint.Presentation Copyright : Copyright (C) 2017-2020 Jesse Rosenthal @@ -80,6 +81,8 @@ data WriterEnv = WriterEnv { envMetadata :: Meta , envInNoteSlide :: Bool , envCurSlideId :: SlideId , envInSpeakerNotes :: Bool + , envInIncrementalDiv :: Maybe InIncrementalDiv + , envInListInBlockQuote :: Bool } deriving (Show) @@ -94,6 +97,8 @@ instance Default WriterEnv where , envInNoteSlide = False , envCurSlideId = SlideId "Default" , envInSpeakerNotes = False + , envInIncrementalDiv = Nothing + , envInListInBlockQuote = False } @@ -114,6 +119,23 @@ instance Default WriterState where , stSpeakerNotes = mempty } +data InIncrementalDiv + = InIncremental + -- ^ The current content is contained within an "incremental" div. + | InNonIncremental + -- ^ The current content is contained within a "nonincremental" div. + deriving (Show) + +listShouldBeIncremental :: Pres Bool +listShouldBeIncremental = do + incrementalOption <- asks (writerIncremental . envOpts) + inIncrementalDiv <- asks envInIncrementalDiv + inBlockQuote <- asks envInListInBlockQuote + let toBoolean = (\case InIncremental -> True + InNonIncremental -> False) + maybeInvert = if inBlockQuote then not else id + pure (maybeInvert (maybe incrementalOption toBoolean inIncrementalDiv)) + metadataSlideId :: SlideId metadataSlideId = SlideId "Metadata" @@ -227,7 +249,7 @@ data Graphic = Tbl TableProps [TableCell] [[TableCell]] data Paragraph = Paragraph { paraProps :: ParaProps - , paraElems :: [ParaElem] + , paraElems :: [ParaElem] } deriving (Show, Eq) data BulletType = Bullet @@ -244,6 +266,7 @@ data ParaProps = ParaProps { pPropMarginLeft :: Maybe Pixels , pPropAlign :: Maybe Algnment , pPropSpaceBefore :: Maybe Pixels , pPropIndent :: Maybe Pixels + , pPropIncremental :: Bool } deriving (Show, Eq) instance Default ParaProps where @@ -254,6 +277,7 @@ instance Default ParaProps where , pPropAlign = Nothing , pPropSpaceBefore = Nothing , pPropIndent = Just 0 + , pPropIncremental = False } newtype TeXString = TeXString {unTeXString :: T.Text} @@ -449,7 +473,8 @@ blockToParagraphs (CodeBlock attr str) = do -- (BlockQuote List) as a list to maintain compatibility with other -- formats. blockToParagraphs (BlockQuote (blk : blks)) | isListType blk = do - ps <- blockToParagraphs blk + ps <- local (\env -> env { envInListInBlockQuote = True }) + (blockToParagraphs blk) ps' <- blockToParagraphs $ BlockQuote blks return $ ps ++ ps' blockToParagraphs (BlockQuote blks) = @@ -474,25 +499,30 @@ blockToParagraphs (Header _ (ident, _, _) ils) = do return [Paragraph def{pPropSpaceBefore = Just 30} parElems] blockToParagraphs (BulletList blksLst) = do pProps <- asks envParaProps + incremental <- listShouldBeIncremental let lvl = pPropLevel pProps local (\env -> env{ envInList = True , envParaProps = pProps{ pPropLevel = lvl + 1 , pPropBullet = Just Bullet , pPropMarginLeft = Nothing , pPropIndent = Nothing + , pPropIncremental = incremental }}) $ concatMapM multiParBullet blksLst blockToParagraphs (OrderedList listAttr blksLst) = do pProps <- asks envParaProps + incremental <- listShouldBeIncremental let lvl = pPropLevel pProps local (\env -> env{ envInList = True , envParaProps = pProps{ pPropLevel = lvl + 1 , pPropBullet = Just (AutoNumbering listAttr) , pPropMarginLeft = Nothing , pPropIndent = Nothing + , pPropIncremental = incremental }}) $ concatMapM multiParBullet blksLst blockToParagraphs (DefinitionList entries) = do + incremental <- listShouldBeIncremental let go :: ([Inline], [[Block]]) -> Pres [Paragraph] go (ils, blksLst) = do term <-blockToParagraphs $ Para [Strong ils] @@ -500,8 +530,17 @@ blockToParagraphs (DefinitionList entries) = do -- blockquote. We can extend this further later. definition <- concatMapM (blockToParagraphs . BlockQuote) blksLst return $ term ++ definition - concatMapM go entries -blockToParagraphs (Div _ blks) = concatMapM blockToParagraphs blks + local (\env -> env {envParaProps = + (envParaProps env) {pPropIncremental = incremental}}) + $ concatMapM go entries +blockToParagraphs (Div (_, classes, _) blks) = let + hasIncremental = "incremental" `elem` classes + hasNonIncremental = "nonincremental" `elem` classes + incremental = if | hasIncremental -> Just InIncremental + | hasNonIncremental -> Just InNonIncremental + | otherwise -> Nothing + addIncremental env = env { envInIncrementalDiv = incremental } + in local addIncremental (concatMapM blockToParagraphs blks) blockToParagraphs blk = do addLogMessage $ BlockNotRendered blk return [] diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs index dd3846fef..6eb8c7f67 100644 --- a/test/Tests/Writers/Powerpoint.hs +++ b/test/Tests/Writers/Powerpoint.hs @@ -232,4 +232,12 @@ tests = groupPptxTests [ pptxTests "Inline formatting" 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" ] diff --git a/test/pptx/incremental-lists/with-flag/deleted-layouts.pptx b/test/pptx/incremental-lists/with-flag/deleted-layouts.pptx new file mode 100644 index 000000000..5a74826a4 Binary files /dev/null and b/test/pptx/incremental-lists/with-flag/deleted-layouts.pptx differ diff --git a/test/pptx/incremental-lists/with-flag/input.native b/test/pptx/incremental-lists/with-flag/input.native new file mode 100644 index 000000000..b690794dc --- /dev/null +++ b/test/pptx/incremental-lists/with-flag/input.native @@ -0,0 +1,139 @@ +[Header 1 ("slide-1-content",[],[]) [Str "Slide",Space,Str "1",Space,Str "(Content)"] +,BulletList + [[Plain [Str "These"]] + ,[Plain [Str "bullets"]] + ,[Plain [Str "should"]] + ,[Plain [Str "be"]] + ,[Plain [Str "incremental"]]] +,Header 1 ("slide-2-content",[],[]) [Str "Slide",Space,Str "2",Space,Str "(Content)"] +,BulletList + [[Para [Str "as"]] + ,[Para [Str "should"]] + ,[Para [Str "these"]]] +,Header 1 ("slide-3-content",[],[]) [Str "Slide",Space,Str "3",Space,Str "(Content)"] +,Para [Str "Even",Space,Str "with",Space,Str "some",Space,Str "text",Space,Str "first,",Space,Str "these",Space,Str "should:"] +,BulletList + [[Plain [Str "also"]] + ,[Plain [Str "be"]] + ,[Plain [Str "incremental"]]] +,Header 1 ("slide-4-content",[],[]) [Str "Slide",Space,Str "4",Space,Str "(Content)"] +,OrderedList (1,Decimal,Period) + [[Plain [Str "These"]] + ,[Plain [Str "are"]] + ,[Plain [Str "incremental"]]] +,Para [Str "But",Space,Str "this",Space,Str "text",Space,Str "isn\8217t"] +,BulletList + [[Plain [Str "But"]] + ,[Plain [Str "these"]] + ,[Plain [Str "are"]]] +,Header 1 ("slide-5-two-content",[],[]) [Str "Slide",Space,Str "5",Space,Str "(Two",Space,Str "Content)"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Str "Incremental",Space,Str "on",Space,Str "the",Space,Str "left:"] + ,BulletList + [[Plain [Str "one"]] + ,[Plain [Str "by"]] + ,[Plain [Str "one"]]] + ,Para [Str "With",Space,Str "something",Space,Str "below"]] + ,Div ("",["column"],[]) + [Para [Str "Incremental",Space,Str "on",Space,Str "the",Space,Str "right:"] + ,BulletList + [[Plain [Str "one"]] + ,[Plain [Str "by"]] + ,[Plain [Str "one"]]] + ,Para [Str "With",Space,Str "something",Space,Str "else",Space,Str "below"]]] +,Header 1 ("slide-6-two-content-right",[],[]) [Str "Slide",Space,Str "6",Space,Str "(Two",Space,Str "Content",Space,Str "Right)"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Image ("",[],[]) [Str "an",Space,Str "image"] ("lalune.jpg","fig:")]] + ,Div ("",["column"],[]) + [BulletList + [[Plain [Str "An"]] + ,[Plain [Str "Incremental"]] + ,[Plain [Str "List"]]]]] +,Header 1 ("slide-7-content-with-caption",[],[]) [Str "Slide",Space,Str "7",Space,Str "(Content",Space,Str "with",Space,Str "Caption)"] +,Para [Str "First,",Space,Str "we",Space,Str "have",Space,Str "some",Space,Str "incremental",Space,Str "bullets:"] +,BulletList + [[Plain [Str "one"]] + ,[Plain [Str "two"]] + ,[Plain [Str "three"]]] +,Para [Str "Then,",Space,Str "a",Space,Str "picture:"] +,Para [Image ("",[],[]) [Str "An",Space,Str "image"] ("./lalune.jpg","fig:")] +,Header 1 ("slide-8-comparison",[],[]) [Str "Slide",Space,Str "8",Space,Str "(Comparison)"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [BulletList + [[Plain [Str "one"]] + ,[Plain [Str "two"]] + ,[Plain [Str "three"]]] + ,Para [Image ("",[],[]) [Str "An",Space,Str "image"] ("./lalune.jpg","fig:")]] + ,Div ("",["column"],[]) + [OrderedList (1,Decimal,Period) + [[Plain [Str "one"]] + ,[Plain [Str "two"]] + ,[Plain [Str "three"]]] + ,Table ("",[],[]) (Caption Nothing + []) + [(AlignDefault,ColWidth 5.555555555555555e-2)] + (TableHead ("",[],[]) + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]]]]) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "2"]]]])] + (TableFoot ("",[],[]) + [])]] +,Header 1 ("slide-9-content",[],[]) [Str "Slide",Space,Str "9",Space,Str "(Content)"] +,Div ("",["nonincremental"],[]) + [BulletList + [[Plain [Str "these"]] + ,[Plain [Str "are"]] + ,[Plain [Str "not"]] + ,[Plain [Str "incremental"]]]] +,BulletList + [[Plain [Str "these"]] + ,[Plain [Str "are"]]] +,Header 1 ("slide-10-content",[],[]) [Str "Slide",Space,Str "10",Space,Str "(Content)"] +,Div ("",["incremental","nonincremental"],[]) + [BulletList + [[Plain [Str "these"]] + ,[Plain [Str "are"]] + ,[Plain [Str "incremental"]] + ,[Plain [Str "(the",Space,Str "incremental",Space,Str "class",Space,Str "wins)"]]]] +,Header 1 ("slide-11-content",[],[]) [Str "Slide",Space,Str "11",Space,Str "(Content)"] +,Para [Str "These",Space,Str "bullets",Space,Str "are",Space,Str "not",Space,Str "incremental:"] +,BlockQuote + [BulletList + [[Plain [Str "one"]] + ,[Plain [Str "two"]] + ,[Plain [Str "three"]]]] +,Para [Str "These",Space,Str "are:"] +,Div ("",["nonincremental"],[]) + [BlockQuote + [BulletList + [[Plain [Str "one"]] + ,[Plain [Str "two"]] + ,[Plain [Str "three"]]]]] +,Para [Str "These",Space,Str "are",Space,Str "not:"] +,BlockQuote + [Div ("",["nonincremental"],[]) + [BulletList + [[Plain [Str "one"]] + ,[Plain [Str "two"]] + ,[Plain [Str "three"]]]]] +,Header 1 ("slide-12-content",[],[]) [Str "Slide",Space,Str "12",Space,Str "(Content)"] +,Div ("",["nonincremental"],[]) + [Div ("",["incremental"],[]) + [BulletList + [[Plain [Str "these"]] + ,[Plain [Str "are"]] + ,[Plain [Str "incremental"]]]]] +,Div ("",["incremental"],[]) + [Div ("",["nonincremental"],[]) + [BulletList + [[Plain [Str "these"]] + ,[Plain [Str "are"]] + ,[Plain [Str "not"]]]]]] diff --git a/test/pptx/incremental-lists/with-flag/moved-layouts.pptx b/test/pptx/incremental-lists/with-flag/moved-layouts.pptx new file mode 100644 index 000000000..f20dd2906 Binary files /dev/null and b/test/pptx/incremental-lists/with-flag/moved-layouts.pptx differ diff --git a/test/pptx/incremental-lists/with-flag/output.pptx b/test/pptx/incremental-lists/with-flag/output.pptx new file mode 100644 index 000000000..d4f76f1e7 Binary files /dev/null and b/test/pptx/incremental-lists/with-flag/output.pptx differ diff --git a/test/pptx/incremental-lists/with-flag/templated.pptx b/test/pptx/incremental-lists/with-flag/templated.pptx new file mode 100644 index 000000000..f5ee2ff5f Binary files /dev/null and b/test/pptx/incremental-lists/with-flag/templated.pptx differ diff --git a/test/pptx/incremental-lists/without-flag/deleted-layouts.pptx b/test/pptx/incremental-lists/without-flag/deleted-layouts.pptx new file mode 100644 index 000000000..16bd85ffd Binary files /dev/null and b/test/pptx/incremental-lists/without-flag/deleted-layouts.pptx differ diff --git a/test/pptx/incremental-lists/without-flag/input.native b/test/pptx/incremental-lists/without-flag/input.native new file mode 100644 index 000000000..87a4aea7e --- /dev/null +++ b/test/pptx/incremental-lists/without-flag/input.native @@ -0,0 +1,137 @@ +[Header 1 ("slide-1-content",[],[]) [Str "Slide",Space,Str "1",Space,Str "(Content)"] +,Div ("",["incremental"],[]) + [BulletList + [[Plain [Str "These"]] + ,[Plain [Str "bullets"]] + ,[Plain [Str "should"]] + ,[Plain [Str "be"]] + ,[Plain [Str "incremental"]]]] +,Header 1 ("slide-2-content",[],[]) [Str "Slide",Space,Str "2",Space,Str "(Content)"] +,BulletList + [[Plain [Str "These"]] + ,[Plain [Str "are"]] + ,[Plain [Str "not"]]] +,Header 1 ("slide-3-content",[],[]) [Str "Slide",Space,Str "3",Space,Str "(Content)"] +,Para [Str "Even",Space,Str "with",Space,Str "some",Space,Str "text",Space,Str "first,",Space,Str "these",Space,Str "should:"] +,Div ("",["incremental"],[]) + [BulletList + [[Plain [Str "also"]] + ,[Plain [Str "be"]] + ,[Plain [Str "incremental"]]]] +,Header 1 ("slide-4-content",[],[]) [Str "Slide",Space,Str "4",Space,Str "(Content)"] +,Div ("",["incremental"],[]) + [OrderedList (1,Decimal,Period) + [[Plain [Str "These"]] + ,[Plain [Str "are"]] + ,[Plain [Str "incremental"]]]] +,Para [Str "But",Space,Str "this",Space,Str "text",Space,Str "isn\8217t"] +,Header 1 ("slide-5-two-content",[],[]) [Str "Slide",Space,Str "5",Space,Str "(Two",Space,Str "Content)"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Str "Incremental",Space,Str "on",Space,Str "the",Space,Str "left:"] + ,Div ("",["incremental"],[]) + [BulletList + [[Plain [Str "one"]] + ,[Plain [Str "by"]] + ,[Plain [Str "one"]]]] + ,Para [Str "With",Space,Str "something",Space,Str "below"]] + ,Div ("",["column"],[]) + [Para [Str "Incremental",Space,Str "on",Space,Str "the",Space,Str "right:"] + ,Div ("",["incremental"],[]) + [BulletList + [[Plain [Str "one"]] + ,[Plain [Str "by"]] + ,[Plain [Str "one"]]]] + ,BulletList + [[Plain [Str "already"]] + ,[Plain [Str "here"]] + ,[Plain [Str "though"]]]]] +,Header 1 ("slide-6-two-content-right",[],[]) [Str "Slide",Space,Str "6",Space,Str "(Two",Space,Str "Content",Space,Str "Right)"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Image ("",[],[]) [Str "an",Space,Str "image"] ("lalune.jpg","fig:")]] + ,Div ("",["column"],[]) + [Div ("",["incremental"],[]) + [BulletList + [[Plain [Str "An"]] + ,[Plain [Str "Incremental"]] + ,[Plain [Str "List"]]]]]] +,Header 1 ("slide-7-content-with-caption",[],[]) [Str "Slide",Space,Str "7",Space,Str "(Content",Space,Str "with",Space,Str "Caption)"] +,Para [Str "First,",Space,Str "we",Space,Str "have",Space,Str "some",Space,Str "incremental",Space,Str "bullets:"] +,Div ("",["incremental"],[]) + [BulletList + [[Plain [Str "one"]] + ,[Plain [Str "two"]] + ,[Plain [Str "three"]]]] +,Para [Str "Then,",Space,Str "a",Space,Str "picture:"] +,Para [Image ("",[],[]) [Str "An",Space,Str "image"] ("./lalune.jpg","fig:")] +,Header 1 ("slide-8-comparison",[],[]) [Str "Slide",Space,Str "8",Space,Str "(Comparison)"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Div ("",["incremental"],[]) + [BulletList + [[Plain [Str "one"]] + ,[Plain [Str "two"]] + ,[Plain [Str "three"]]]] + ,Para [Image ("",[],[]) [Str "An",Space,Str "image"] ("./lalune.jpg","fig:")]] + ,Div ("",["column"],[]) + [Div ("",["incremental"],[]) + [OrderedList (1,Decimal,Period) + [[Plain [Str "one"]] + ,[Plain [Str "two"]] + ,[Plain [Str "three"]]]] + ,Table ("",[],[]) (Caption Nothing + []) + [(AlignDefault,ColWidth 5.555555555555555e-2)] + (TableHead ("",[],[]) + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]]]]) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "2"]]]])] + (TableFoot ("",[],[]) + [])]] +,Header 1 ("slide-10-content",[],[]) [Str "Slide",Space,Str "10",Space,Str "(Content)"] +,Div ("",["incremental","nonincremental"],[]) + [BulletList + [[Plain [Str "these"]] + ,[Plain [Str "are"]] + ,[Plain [Str "incremental"]] + ,[Plain [Str "(the",Space,Str "incremental",Space,Str "class",Space,Str "wins)"]]]] +,Header 1 ("slide-11-content",[],[]) [Str "Slide",Space,Str "11",Space,Str "(Content)"] +,Para [Str "These",Space,Str "bullets",Space,Str "are",Space,Str "incremental:"] +,BlockQuote + [BulletList + [[Plain [Str "one"]] + ,[Plain [Str "two"]] + ,[Plain [Str "three"]]]] +,Para [Str "These",Space,Str "are",Space,Str "not:"] +,Div ("",["incremental"],[]) + [BlockQuote + [BulletList + [[Plain [Str "one"]] + ,[Plain [Str "two"]] + ,[Plain [Str "three"]]]]] +,Para [Str "These",Space,Str "are:"] +,BlockQuote + [Div ("",["incremental"],[]) + [BulletList + [[Plain [Str "one"]] + ,[Plain [Str "two"]] + ,[Plain [Str "three"]]]]] +,Header 1 ("slide-12-content",[],[]) [Str "Slide",Space,Str "12",Space,Str "(Content)"] +,Div ("",["nonincremental"],[]) + [Div ("",["incremental"],[]) + [BulletList + [[Plain [Str "these"]] + ,[Plain [Str "are"]] + ,[Plain [Str "incremental"]]]]] +,Div ("",["incremental"],[]) + [Div ("",["nonincremental"],[]) + [BulletList + [[Plain [Str "these"]] + ,[Plain [Str "are"]] + ,[Plain [Str "not"]]]]]] diff --git a/test/pptx/incremental-lists/without-flag/moved-layouts.pptx b/test/pptx/incremental-lists/without-flag/moved-layouts.pptx new file mode 100644 index 000000000..054fe918e Binary files /dev/null and b/test/pptx/incremental-lists/without-flag/moved-layouts.pptx differ diff --git a/test/pptx/incremental-lists/without-flag/output.pptx b/test/pptx/incremental-lists/without-flag/output.pptx new file mode 100644 index 000000000..1b326461d Binary files /dev/null and b/test/pptx/incremental-lists/without-flag/output.pptx differ diff --git a/test/pptx/incremental-lists/without-flag/templated.pptx b/test/pptx/incremental-lists/without-flag/templated.pptx new file mode 100644 index 000000000..dee6e9b06 Binary files /dev/null and b/test/pptx/incremental-lists/without-flag/templated.pptx differ -- cgit v1.2.3 From 7c22c0202e8ed706d33f301e65f0aa1a847b4ec4 Mon Sep 17 00:00:00 2001 From: Emily Bourke Date: Mon, 13 Sep 2021 18:16:19 +0100 Subject: pptx: Support specifying slide background images MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit In the reveal-js output, it’s possible to use reveal’s `data-background-image` class on a slide’s title to specify a background image for the slide. With this commit, it’s possible to use `background-image` in the same way for pptx output. Only the “stretch” mode is supported, and the background image is centred around the slide in the image’s larger axis, matching the observed default behaviour of PowerPoint. - Support `background-image` per slide. - Add tests. - Update manual. --- MANUAL.txt | 69 +++++++----- pandoc.cabal | 2 + src/Text/Pandoc/Writers/Powerpoint/Output.hs | 117 ++++++++++++++++----- src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | 29 +++-- test/Tests/Writers/Powerpoint.hs | 4 + test/pptx/background-image/deleted-layouts.pptx | Bin 0 -> 56282 bytes test/pptx/background-image/input.native | 17 +++ test/pptx/background-image/moved-layouts.pptx | Bin 0 -> 66987 bytes test/pptx/background-image/output.pptx | Bin 0 -> 53408 bytes test/pptx/background-image/templated.pptx | Bin 0 -> 66487 bytes 10 files changed, 178 insertions(+), 60 deletions(-) create mode 100644 test/pptx/background-image/deleted-layouts.pptx create mode 100644 test/pptx/background-image/input.native create mode 100644 test/pptx/background-image/moved-layouts.pptx create mode 100644 test/pptx/background-image/output.pptx create mode 100644 test/pptx/background-image/templated.pptx (limited to 'test/Tests/Writers') diff --git a/MANUAL.txt b/MANUAL.txt index 82fc21684..98a2f4299 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -6054,40 +6054,61 @@ the [Beamer User's Guide] may also be used: `allowdisplaybreaks`, `allowframebreaks`, `b`, `c`, `t`, `environment`, `label`, `plain`, `shrink`, `standout`, `noframenumbering`. -## Background in reveal.js and beamer +## Background in reveal.js, beamer, and pptx -Background images can be added to self-contained reveal.js slide shows and -to beamer slide shows. +Background images can be added to self-contained reveal.js slide shows, +beamer slide shows, and pptx slide shows. -For the same image on every slide, use the configuration -option `background-image` either in the YAML metadata block -or as a command-line variable. (There are no other options in -beamer and the rest of this section concerns reveal.js slide shows.) +### On all slides (beamer, reveal.js, pptx) -For reveal.js, you can instead use the reveal.js-native option -`parallaxBackgroundImage`. You can also set `parallaxBackgroundHorizontal` -and `parallaxBackgroundVertical` the same way and must also set -`parallaxBackgroundSize` to have your values take effect. +With beamer and reveal.js, the configuration option `background-image` can be +used either in the YAML metadata block or as a command-line variable to get the +same image on every slide. -To set an image for a particular reveal.js slide, add -`{data-background-image="/path/to/image"}` -to the first slide-level heading on the slide (which may even be empty). +For pptx, you can use a [reference doc](#option--reference-doc) in which +background images have been set on the [relevant +layouts](#powerpoint-layout-choice). + +#### `parallaxBackgroundImage` (reveal.js) + +For reveal.js, there is also the reveal.js-native option +`parallaxBackgroundImage`, which can be used instead of `background-image` to +produce a parallax scrolling background. You must also set +`parallaxBackgroundSize`, and can optionally set `parallaxBackgroundHorizontal` +and `parallaxBackgroundVertical` to configure the scrolling behaviour. See the +[reveal.js documentation](https://revealjs.com/backgrounds/#parallax-background) +for more details about the meaning of these options. In reveal.js's overview mode, the parallaxBackgroundImage will show up only on the first slide. -Other reveal.js background settings also work on individual slides, including -`data-background-size`, `data-background-repeat`, `data-background-color`, -`data-transition`, and `data-transition-speed`. +### On individual slides (reveal.js, pptx) + +To set an image for a particular reveal.js or pptx slide, add +`{background-image="/path/to/image"}` to the first slide-level heading on the +slide (which may even be empty). + +As the [HTML writers pass unknown attributes +through](#extension-link_attributes), other reveal.js background settings also +work on individual slides, including `background-size`, `background-repeat`, +`background-color`, `transition`, and `transition-speed`. (The `data-` prefix +will automatically be added.) + +Note: `data-background-image` is also supported in pptx for consistency with +reveal.js – if `background-image` isn’t found, `data-background-image` will be +checked. + +### On the title slide (reveal.js, pptx) -To add a background image to the automatically generated title slide, use the -`title-slide-attributes` variable in the YAML metadata block. It must contain -a map of attribute names and values. +To add a background image to the automatically generated title slide for +reveal.js, use the `title-slide-attributes` variable in the YAML metadata block. +It must contain a map of attribute names and values. (Note that the `data-` +prefix is required here, as it isn’t added automatically.) -See the [reveal.js documentation](https://revealjs.com/backgrounds/) for more -details. +For pptx, pass a [reference doc](#option--reference-doc) with the background +image set on the “Title Slide” layout. -For example in reveal.js: +### Example (reveal.js) ``` --- @@ -6102,7 +6123,7 @@ title-slide-attributes: Slide 1 has background_image.png as its background. -## {data-background-image="/path/to/special_image.jpg"} +## {background-image="/path/to/special_image.jpg"} Slide 2 has a special image for its background, even though the heading has no content. ``` diff --git a/pandoc.cabal b/pandoc.cabal index 6fcc384f9..0c8cf0d61 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -380,6 +380,8 @@ extra-source-files: test/rtf/*.native test/rtf/*.rtf test/pptx/*.pptx + test/pptx/background-image/input.native + test/pptx/background-image/*.pptx test/pptx/blanks/just-speaker-notes/input.native test/pptx/blanks/just-speaker-notes/*.pptx test/pptx/blanks/nbsp-in-body/input.native diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs index 5eadf1312..1431469d3 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs @@ -31,6 +31,7 @@ import qualified Data.CaseInsensitive as CI import Data.Default import Data.Foldable (toList) import Data.List.NonEmpty (nonEmpty, NonEmpty ((:|))) +import Data.Ratio ((%), Ratio) import Data.Text (Text) import qualified Data.Text as T import Data.Text.Read (decimal) @@ -439,9 +440,9 @@ makeSpeakerNotesMap :: Presentation -> M.Map Int Int makeSpeakerNotesMap (Presentation _ slides) = M.fromList $ mapMaybe f (slides `zip` [1..]) `zip` [1..] - where f (Slide _ _ notes, n) = if notes == mempty - then Nothing - else Just n + where f (Slide _ _ notes _, n) = if notes == mempty + then Nothing + else Just n presentationToArchive :: PandocMonad m => WriterOptions -> Meta -> Presentation -> m Archive @@ -1570,8 +1571,9 @@ metadataToElement layout titleElems subtitleElems authorsElems dateElems metadataToElement _ _ _ _ _ = return (Nothing, mknode "p:sp" [] ()) slideToElement :: PandocMonad m => Slide -> P m Element -slideToElement (Slide _ l@(ContentSlide hdrElems shapes) _ )= do +slideToElement (Slide _ l@(ContentSlide hdrElems shapes) _ backgroundImage) = do layout <- getLayout l + backgroundImageElement <- traverse backgroundImageToElement backgroundImage (shapeIds, spTree) <- local (\env -> if null hdrElems then env @@ -1585,9 +1587,10 @@ slideToElement (Slide _ l@(ContentSlide hdrElems shapes) _ )= do [ ("xmlns:a", "http://schemas.openxmlformats.org/drawingml/2006/main"), ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") - ] (mknode "p:cSld" [] [spTree] : animations) -slideToElement (Slide _ l@(TwoColumnSlide hdrElems shapesL shapesR) _) = do + ] (mknode "p:cSld" [] (toList backgroundImageElement <> [spTree]) : animations) +slideToElement (Slide _ l@(TwoColumnSlide hdrElems shapesL shapesR) _ backgroundImage) = do layout <- getLayout l + backgroundImageElement <- traverse backgroundImageToElement backgroundImage (shapeIds, spTree) <- local (\env -> if null hdrElems then env else env{envSlideHasHeader=True}) $ @@ -1601,9 +1604,10 @@ slideToElement (Slide _ l@(TwoColumnSlide hdrElems shapesL shapesR) _) = do [ ("xmlns:a", "http://schemas.openxmlformats.org/drawingml/2006/main"), ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") - ] (mknode "p:cSld" [] [spTree] : animations) -slideToElement (Slide _ l@(ComparisonSlide hdrElems shapesL shapesR) _) = do + ] (mknode "p:cSld" [] (toList backgroundImageElement <> [spTree]) : animations) +slideToElement (Slide _ l@(ComparisonSlide hdrElems shapesL shapesR) _ backgroundImage) = do layout <- getLayout l + backgroundImageElement <- traverse backgroundImageToElement backgroundImage (shapeIds, spTree) <- local (\env -> if null hdrElems then env else env{envSlideHasHeader=True}) $ @@ -1620,25 +1624,36 @@ slideToElement (Slide _ l@(ComparisonSlide hdrElems shapesL shapesR) _) = do [ ("xmlns:a", "http://schemas.openxmlformats.org/drawingml/2006/main"), ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") - ] (mknode "p:cSld" [] [spTree] : animations) -slideToElement (Slide _ l@(TitleSlide hdrElems) _) = do + ] (mknode "p:cSld" [] (toList backgroundImageElement <> [spTree]) : animations) +slideToElement (Slide _ l@(TitleSlide hdrElems) _ backgroundImage) = do layout <- getLayout l + backgroundImageElement <- traverse backgroundImageToElement backgroundImage (_, spTree) <- titleToElement layout hdrElems return $ mknode "p:sld" [ ("xmlns:a", "http://schemas.openxmlformats.org/drawingml/2006/main"), ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") - ] [mknode "p:cSld" [] [spTree]] -slideToElement (Slide _ l@(MetadataSlide titleElems subtitleElems authorElems dateElems) _) = do + ] [mknode "p:cSld" [] (toList backgroundImageElement <> [spTree])] +slideToElement (Slide + _ + l@(MetadataSlide titleElems subtitleElems authorElems dateElems) + _ + backgroundImage) = do layout <- getLayout l + backgroundImageElement <- traverse backgroundImageToElement backgroundImage (_, spTree) <- metadataToElement layout titleElems subtitleElems authorElems dateElems return $ mknode "p:sld" [ ("xmlns:a", "http://schemas.openxmlformats.org/drawingml/2006/main"), ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") - ] [mknode "p:cSld" [] [spTree]] -slideToElement (Slide _ l@(ContentWithCaptionSlide hdrElems captionShapes contentShapes) _) = do + ] [mknode "p:cSld" [] (toList backgroundImageElement <> [spTree])] +slideToElement (Slide + _ + l@(ContentWithCaptionSlide hdrElems captionShapes contentShapes) + _ + backgroundImage) = do layout <- getLayout l + backgroundImageElement <- traverse backgroundImageToElement backgroundImage (shapeIds, spTree) <- contentWithCaptionToElement layout hdrElems captionShapes contentShapes let animations = case shapeIds of Nothing -> [] @@ -1650,15 +1665,63 @@ slideToElement (Slide _ l@(ContentWithCaptionSlide hdrElems captionShapes conten [ ("xmlns:a", "http://schemas.openxmlformats.org/drawingml/2006/main"), ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") - ] (mknode "p:cSld" [] [spTree] : animations) -slideToElement (Slide _ BlankSlide _) = do + ] (mknode "p:cSld" [] (toList backgroundImageElement <> [spTree]) : animations) +slideToElement (Slide _ BlankSlide _ backgroundImage) = do layout <- getLayout BlankSlide + backgroundImageElement <- traverse backgroundImageToElement backgroundImage spTree <- blankToElement layout return $ mknode "p:sld" [ ("xmlns:a", "http://schemas.openxmlformats.org/drawingml/2006/main"), ("xmlns:r", "http://schemas.openxmlformats.org/officeDocument/2006/relationships"), ("xmlns:p", "http://schemas.openxmlformats.org/presentationml/2006/main") - ] [mknode "p:cSld" [] [spTree]] + ] [mknode "p:cSld" [] (toList backgroundImageElement <> [spTree])] + +backgroundImageToElement :: PandocMonad m => FilePath -> P m Element +backgroundImageToElement path = do + MediaInfo{mInfoLocalId, mInfoFilePath} <- registerMedia path [] + (imgBytes, _) <- P.fetchItem (T.pack mInfoFilePath) + opts <- asks envOpts + let imageDimensions = either (const Nothing) + (Just . sizeInPixels) + (imageSize opts imgBytes) + pageSize <- asks envPresentationSize + let fillRectAttributes = maybe [] (offsetAttributes pageSize) imageDimensions + let rId = "rId" <> T.pack (show mInfoLocalId) + return + $ mknode "p:bg" [] + $ mknode "p:bgPr" [] + [ mknode "a:blipFill" [("dpi", "0"), ("rotWithShape", "1")] + [ mknode "a:blip" [("r:embed", rId)] + $ mknode "a:lum" [] () + , mknode "a:srcRect" [] () + , mknode "a:stretch" [] + $ mknode "a:fillRect" fillRectAttributes () + ] + , mknode "a:effectsLst" [] () + ] + where + offsetAttributes :: (Integer, Integer) -> (Integer, Integer) -> [(Text, Text)] + offsetAttributes (pageWidth, pageHeight) (pictureWidth, pictureHeight) = let + widthRatio = pictureWidth % pageWidth + heightRatio = pictureHeight % pageHeight + getOffset :: Ratio Integer -> Text + getOffset proportion = let + percentageOffset = (proportion - 1) * (-100 % 2) + integerOffset = round percentageOffset * 1000 :: Integer + in T.pack (show integerOffset) + in case compare widthRatio heightRatio of + EQ -> [] + LT -> let + offset = getOffset ((pictureHeight % pageHeight) / widthRatio) + in [ ("t", offset) + , ("b", offset) + ] + GT -> let + offset = getOffset ((pictureWidth % pageWidth) / heightRatio) + in [ ("l", offset) + , ("r", offset) + ] + slideToIncrementalAnimations :: [(ShapeId, Shape)] -> @@ -1790,8 +1853,8 @@ speakerNotesSlideNumber pgNum fieldId = ] slideToSpeakerNotesElement :: PandocMonad m => Slide -> P m (Maybe Element) -slideToSpeakerNotesElement (Slide _ _ (SpeakerNotes [])) = return Nothing -slideToSpeakerNotesElement slide@(Slide _ _ (SpeakerNotes paras)) = do +slideToSpeakerNotesElement (Slide _ _ (SpeakerNotes []) _) = return Nothing +slideToSpeakerNotesElement slide@(Slide _ _ (SpeakerNotes paras) _) = do master <- getNotesMaster fieldId <- getSlideNumberFieldId master num <- slideNum slide @@ -2037,7 +2100,7 @@ slideToSpeakerNotesEntry slide = do _ -> return Nothing slideToSpeakerNotesRelElement :: PandocMonad m => Slide -> P m (Maybe Element) -slideToSpeakerNotesRelElement (Slide _ _ (SpeakerNotes [])) = return Nothing +slideToSpeakerNotesRelElement (Slide _ _ (SpeakerNotes []) _) = return Nothing slideToSpeakerNotesRelElement slide@Slide{} = do idNum <- slideNum slide return $ Just $ @@ -2124,13 +2187,13 @@ slideToSlideRelElement slide = do target <- flip fmap getSlideLayouts $ T.pack . ("../slideLayouts/" <>) . takeFileName . slPath . case slide of - (Slide _ MetadataSlide{} _) -> metadata - (Slide _ TitleSlide{} _) -> title - (Slide _ ContentSlide{} _) -> content - (Slide _ TwoColumnSlide{} _) -> twoColumn - (Slide _ ComparisonSlide{} _) -> comparison - (Slide _ ContentWithCaptionSlide{} _) -> contentWithCaption - (Slide _ BlankSlide _) -> blank + (Slide _ MetadataSlide{} _ _) -> metadata + (Slide _ TitleSlide{} _ _) -> title + (Slide _ ContentSlide{} _ _) -> content + (Slide _ TwoColumnSlide{} _ _) -> twoColumn + (Slide _ ComparisonSlide{} _ _) -> comparison + (Slide _ ContentWithCaptionSlide{} _ _) -> contentWithCaption + (Slide _ BlankSlide _ _) -> blank speakerNotesRels <- maybeToList <$> speakerNotesSlideRelElement slide diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs index a7660fc5e..fb4518bd7 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs @@ -63,7 +63,7 @@ import Text.Pandoc.Writers.Shared (lookupMetaInlines, lookupMetaBlocks , toLegacyTable) import qualified Data.Map as M import qualified Data.Set as S -import Data.Maybe (maybeToList, fromMaybe, listToMaybe) +import Data.Maybe (maybeToList, fromMaybe, listToMaybe, isNothing) import Text.Pandoc.Highlighting import qualified Data.Text as T import Control.Applicative ((<|>)) @@ -201,6 +201,7 @@ data DocProps = DocProps { dcTitle :: Maybe T.Text data Slide = Slide { slideId :: SlideId , slideLayout :: Layout , slideSpeakerNotes :: SpeakerNotes + , slideBackgroundImage :: Maybe FilePath } deriving (Show, Eq) newtype SlideId = SlideId T.Text @@ -223,7 +224,7 @@ data Layout = MetadataSlide [ParaElem] [ParaElem] [[ParaElem]] [ParaElem] | ComparisonSlide [ParaElem] ([Shape], [Shape]) ([Shape], [Shape]) -- heading left@(text, content) right@(text, content) | ContentWithCaptionSlide [ParaElem] [Shape] [Shape] - -- heading text content + -- heading text content | BlankSlide deriving (Show, Eq) @@ -725,6 +726,7 @@ bodyBlocksToSlide _ (blk : blks) spkNotes sldId (TwoColumnSlide [] shapesL shapesR) spkNotes + Nothing let mkComparison blksL1 blksL2 blksR1 blksR2 = do shapesL1 <- blocksToShapes blksL1 shapesL2 <- blocksToShapes blksL2 @@ -735,6 +737,7 @@ bodyBlocksToSlide _ (blk : blks) spkNotes sldId (ComparisonSlide [] (shapesL1, shapesL2) (shapesR1, shapesR2)) spkNotes + Nothing let (blksL1, blksL2) = break notText blksL (blksR1, blksR2) = break notText blksR if (any null [blksL1, blksL2]) && (any null [blksR1, blksR2]) @@ -744,7 +747,7 @@ bodyBlocksToSlide _ (blk : blks) spkNotes = do sldId <- asks envCurSlideId inNoteSlide <- asks envInNoteSlide let mkSlide s = - Slide sldId s spkNotes + Slide sldId s spkNotes Nothing if inNoteSlide then mkSlide . ContentSlide [] <$> forceFontSize noteSize (blocksToShapes (blk : blks)) @@ -767,14 +770,15 @@ bodyBlocksToSlide _ [] spkNotes = do sldId BlankSlide spkNotes + Nothing blocksToSlide' :: Int -> [Block] -> SpeakerNotes -> Pres Slide -blocksToSlide' lvl (Header n (ident, _, _) ils : blks) spkNotes +blocksToSlide' lvl (Header n (ident, _, attributes) ils : blks) spkNotes | n < lvl = do registerAnchorId ident sldId <- asks envCurSlideId hdr <- inlinesToParElems ils - return $ Slide sldId (TitleSlide hdr) spkNotes + return $ Slide sldId (TitleSlide hdr) spkNotes backgroundImage | n == lvl || lvl == 0 = do registerAnchorId ident hdr <- inlinesToParElems ils @@ -788,7 +792,10 @@ blocksToSlide' lvl (Header n (ident, _, _) ils : blks) spkNotes ContentWithCaptionSlide _ text content -> ContentWithCaptionSlide hdr text content BlankSlide -> if all inlineIsBlank ils then BlankSlide else ContentSlide hdr [] layout' -> layout' - return $ slide{slideLayout = layout} + return $ slide{slideLayout = layout, slideBackgroundImage = backgroundImage} + where + backgroundImage = T.unpack <$> (lookup "background-image" attributes + <|> lookup "data-background-image" attributes) blocksToSlide' lvl blks spkNotes = bodyBlocksToSlide lvl blks spkNotes blockToSpeakerNotes :: Block -> Pres SpeakerNotes @@ -869,12 +876,13 @@ getMetaSlide = do metadataSlideId (MetadataSlide title subtitle authors date) mempty + Nothing addSpeakerNotesToMetaSlide :: Slide -> [Block] -> Pres (Slide, [Block]) -addSpeakerNotesToMetaSlide (Slide sldId layout@MetadataSlide{} spkNotes) blks = +addSpeakerNotesToMetaSlide (Slide sldId layout@MetadataSlide{} spkNotes backgroundImage) blks = do let (ntsBlks, blks') = span isNotesDiv blks spkNotes' <- mconcat <$> mapM blockToSpeakerNotes ntsBlks - return (Slide sldId layout (spkNotes <> spkNotes'), blks') + return (Slide sldId layout (spkNotes <> spkNotes') backgroundImage, blks') addSpeakerNotesToMetaSlide sld blks = return (sld, blks) makeTOCSlide :: [Block] -> Pres Slide @@ -1010,7 +1018,10 @@ emptyLayout layout = case layout of emptySlide :: Slide -> Bool -emptySlide (Slide _ layout notes) = (notes == mempty) && emptyLayout layout +emptySlide (Slide _ layout notes backgroundImage) + = (notes == mempty) + && emptyLayout layout + && isNothing backgroundImage makesBlankSlide :: [Block] -> Bool makesBlankSlide = all blockIsBlank diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs index 6eb8c7f67..6e676dc37 100644 --- a/test/Tests/Writers/Powerpoint.hs +++ b/test/Tests/Writers/Powerpoint.hs @@ -240,4 +240,8 @@ tests = groupPptxTests [ pptxTests "Inline formatting" 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" ] diff --git a/test/pptx/background-image/deleted-layouts.pptx b/test/pptx/background-image/deleted-layouts.pptx new file mode 100644 index 000000000..05d4104b7 Binary files /dev/null and b/test/pptx/background-image/deleted-layouts.pptx differ diff --git a/test/pptx/background-image/input.native b/test/pptx/background-image/input.native new file mode 100644 index 000000000..22b089a95 --- /dev/null +++ b/test/pptx/background-image/input.native @@ -0,0 +1,17 @@ +[Header 1 ("section-header-with-background-image",[],[("background-image","movie.jpg")]) [Str "Section",Space,Str "Header",Space,Str "(with",Space,Str "background",Space,Str "image)"] +,Header 2 ("slide-1",[],[("background-image","lalune.jpg")]) [Str "Slide",Space,Str "1"] +,Para [Str "This",Space,Str "slide",Space,Str "has",Space,Str "a",Space,Str "moon",Space,Str "background."] +,Header 2 ("slide-2",[],[("background-image","movie.jpg")]) [Str "Slide",Space,Str "2"] +,Para [Str "This",Space,Str "slide",Space,Str "has",Space,Str "a",Space,Str "movie",Space,Str "background."] +,Header 2 ("slide-3",[],[("background-image","movie.jpg")]) [Str "Slide",Space,Str "3"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Str "Background",Space,Str "images",Space,Str "work",Space,Str "in",Space,Str "two-column",Space,Str "layout."]] + ,Div ("",["column"],[]) + [Para [Str "hello"]]] +,Header 2 ("slide-4",[],[("background-image","movie.jpg")]) [Str "Slide",Space,Str "4"] +,Para [Str "You",Space,Str "can",Space,Str "have",Space,Str "images",Space,Str "on",Space,Str "slides",Space,Str "that",Space,Str "have",Space,Str "background",Space,Str "images:"] +,Para [Image ("",[],[]) [Str "An",Space,Str "image"] ("lalune.jpg","fig:")] +,Header 2 ("section",[],[("background-image","lalune.jpg")]) [] +,Div ("",["notes"],[]) + [Para [Str "Blank",Space,Str "slides",Space,Str "can",Space,Str "have",Space,Str "background",Space,Str "images."]]] diff --git a/test/pptx/background-image/moved-layouts.pptx b/test/pptx/background-image/moved-layouts.pptx new file mode 100644 index 000000000..73b69e1d6 Binary files /dev/null and b/test/pptx/background-image/moved-layouts.pptx differ diff --git a/test/pptx/background-image/output.pptx b/test/pptx/background-image/output.pptx new file mode 100644 index 000000000..9738eefb8 Binary files /dev/null and b/test/pptx/background-image/output.pptx differ diff --git a/test/pptx/background-image/templated.pptx b/test/pptx/background-image/templated.pptx new file mode 100644 index 000000000..52d304957 Binary files /dev/null and b/test/pptx/background-image/templated.pptx differ -- cgit v1.2.3 From 50adea220d09e445572e94e225fa7a81b3b2bf89 Mon Sep 17 00:00:00 2001 From: Emily Bourke Date: Tue, 14 Sep 2021 17:07:46 +0100 Subject: pptx: Support footers in the reference doc MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit In PowerPoint, it’s possible to specify footers across all slides, containing a date (optionally automatically updated to today’s date), the slide number (optionally starting from a higher number than 1), and static text. There’s also an option to hide the footer on the title slide. Before this commit, none of that footer content was pulled through from the reference doc: this commit supports all the functionality listed above. There is one behaviour which may not be immediately obvious: if the reference doc specifies a fixed date (i.e. not automatically updating), and there’s a date specified in the metadata for the document, the footer date is replaced by the metadata date. - Include date, slide number, and static footer content from reference doc - Respect “slide number starts from” option - Respect “Don’t show on title slide” option - Add tests --- pandoc.cabal | 5 + src/Text/Pandoc/Writers/Powerpoint/Output.hs | 103 +++++- test/Tests/Writers/Powerpoint.hs | 397 +++++++++++---------- test/pptx/footer/basic/output.pptx | Bin 0 -> 52775 bytes test/pptx/footer/basic/reference.pptx | Bin 0 -> 49063 bytes test/pptx/footer/fixed-date/output.pptx | Bin 0 -> 51397 bytes test/pptx/footer/fixed-date/reference.pptx | Bin 0 -> 47996 bytes test/pptx/footer/higher-slide-number/output.pptx | Bin 0 -> 52790 bytes .../pptx/footer/higher-slide-number/reference.pptx | Bin 0 -> 49082 bytes test/pptx/footer/input.native | 66 ++++ test/pptx/footer/no-title-slide/output.pptx | Bin 0 -> 52362 bytes test/pptx/footer/no-title-slide/reference.pptx | Bin 0 -> 48423 bytes 12 files changed, 372 insertions(+), 199 deletions(-) create mode 100644 test/pptx/footer/basic/output.pptx create mode 100644 test/pptx/footer/basic/reference.pptx create mode 100644 test/pptx/footer/fixed-date/output.pptx create mode 100644 test/pptx/footer/fixed-date/reference.pptx create mode 100644 test/pptx/footer/higher-slide-number/output.pptx create mode 100644 test/pptx/footer/higher-slide-number/reference.pptx create mode 100644 test/pptx/footer/input.native create mode 100644 test/pptx/footer/no-title-slide/output.pptx create mode 100644 test/pptx/footer/no-title-slide/reference.pptx (limited to 'test/Tests/Writers') diff --git a/pandoc.cabal b/pandoc.cabal index 0c8cf0d61..4881fe3a4 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -414,6 +414,11 @@ extra-source-files: test/pptx/endnotes-toc/*.pptx test/pptx/endnotes/input.native test/pptx/endnotes/*.pptx + test/pptx/footer/input.native + test/pptx/footer/basic/*.pptx + test/pptx/footer/fixed-date/*.pptx + test/pptx/footer/higher-slide-number/*.pptx + test/pptx/footer/no-title-slide/*.pptx test/pptx/images/input.native test/pptx/images/*.pptx test/pptx/incremental-lists/with-flag/input.native diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs index 1431469d3..acfd446de 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs @@ -2,6 +2,7 @@ {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} +{-# LANGUAGE RankNTypes #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TupleSections #-} {- | @@ -159,7 +160,7 @@ data SlideLayoutsOf a = SlideLayouts , comparison :: a , contentWithCaption :: a , blank :: a - } deriving (Show, Functor, Foldable, Traversable) + } deriving (Show, Eq, Functor, Foldable, Traversable) data SlideLayout = SlideLayout { slElement :: Element @@ -197,12 +198,14 @@ data WriterState = WriterState { stLinkIds :: M.Map Int (M.Map Int LinkTarget) -- (FP, Local ID, Global ID, Maybe Mime) , stMediaIds :: M.Map Int [MediaInfo] , stMediaGlobalIds :: M.Map FilePath Int + , stFooterInfo :: Maybe FooterInfo } deriving (Show, Eq) instance Default WriterState where def = WriterState { stLinkIds = mempty , stMediaIds = mempty , stMediaGlobalIds = mempty + , stFooterInfo = Nothing } type P m = ReaderT WriterEnv (StateT WriterState m) @@ -316,8 +319,14 @@ presentationToArchiveP p@(Presentation docProps slides) = do else id let newArch' = foldr f newArch slideLayouts - -- Update the master to make sure it includes any layouts we've just added master <- getMaster + refArchive <- asks envRefArchive + distArchive <- asks envDistArchive + presentationElement <- parseXml refArchive distArchive "ppt/presentation.xml" + modify (\s -> s {stFooterInfo = + getFooterInfo slideLayouts master presentationElement}) + + -- Update the master to make sure it includes any layouts we've just added masterRels <- getMasterRels let (updatedMasterElem, updatedMasterRelElem) = updateMasterElems slideLayouts master masterRels updatedMasterEntry <- elemToEntry "ppt/slideMasters/slideMaster1.xml" updatedMasterElem @@ -432,6 +441,56 @@ updateMasterElems layouts master masterRels = (updatedMaster, updatedMasterRels) getIdAttribute (Elem e) = findAttr (QName "id" Nothing Nothing) e getIdAttribute _ = Nothing +data FooterInfo = FooterInfo + { fiDate :: SlideLayoutsOf (Maybe Element) + , fiFooter :: SlideLayoutsOf (Maybe Element) + , fiSlideNumber :: SlideLayoutsOf (Maybe Element) + , fiShowOnFirstSlide :: Bool + } deriving (Show, Eq) + +getFooterInfo :: SlideLayouts -> Element -> Element -> Maybe FooterInfo +getFooterInfo layouts master presentation = do + let ns = elemToNameSpaces master + hf <- findChild (elemName ns "p" "hf") master + let fiDate = getShape "dt" hf . slElement <$> layouts + fiFooter = getShape "ftr" hf . slElement <$> layouts + fiSlideNumber = getShape "sldNum" hf . slElement <$> layouts + fiShowOnFirstSlide = + fromMaybe True + (getBooleanAttribute "showSpecialPlsOnTitleSld" presentation) + pure FooterInfo{..} + where + getShape t hf layout = + if fromMaybe True (getBooleanAttribute t hf) + then do + let ns = elemToNameSpaces layout + cSld <- findChild (elemName ns "p" "cSld") layout + spTree <- findChild (elemName ns "p" "spTree") cSld + let containsPlaceholder sp = fromMaybe False $ do + nvSpPr <- findChild (elemName ns "p" "nvSpPr") sp + nvPr <- findChild (elemName ns "p" "nvPr") nvSpPr + ph <- findChild (elemName ns "p" "ph") nvPr + placeholderType <- findAttr (QName "type" Nothing Nothing) ph + pure (placeholderType == t) + listToMaybe (filterChildren containsPlaceholder spTree) + else Nothing + + getBooleanAttribute t e = + (`elem` ["1", "true"]) <$> + (findAttr (QName t Nothing Nothing) e) + +footerElements :: + PandocMonad m => + (forall a. SlideLayoutsOf a -> a) -> + P m [Content] +footerElements layout = do + footerInfo <- gets stFooterInfo + pure + $ Elem <$> + (toList (footerInfo >>= layout . fiDate) + <> toList (footerInfo >>= layout . fiFooter) + <> toList (footerInfo >>= layout . fiSlideNumber)) + makeSlideIdMap :: Presentation -> M.Map SlideId Int makeSlideIdMap (Presentation _ slides) = M.fromList $ map slideId slides `zip` [1..] @@ -1372,13 +1431,14 @@ contentToElement layout hdrShape shapes (shapeId, element) <- nonBodyTextToElement layout [PHType "title"] hdrShape let hdrShapeElements = [Elem element | not (null hdrShape)] contentHeaderId = if null hdrShape then Nothing else shapeId - content <- local + content' <- local (\env -> env {envPlaceholder = Placeholder ObjType 0}) (shapesToElements layout shapes) - let contentContentIds = mapMaybe fst content - contentElements = snd <$> content + let contentContentIds = mapMaybe fst content' + contentElements = snd <$> content' + footer <- footerElements content return ( Just ContentShapeIds{..} - , buildSpTree ns spTree (hdrShapeElements <> contentElements) + , buildSpTree ns spTree (hdrShapeElements <> contentElements <> footer) ) contentToElement _ _ _ = return (Nothing, mknode "p:sp" [] ()) @@ -1412,10 +1472,11 @@ twoColumnToElement layout hdrShape shapesL shapesR contentElementsR = snd <$> contentR -- let contentElementsL' = map (setIdx ns "1") contentElementsL -- contentElementsR' = map (setIdx ns "2") contentElementsR + footer <- footerElements twoColumn return $ (Just TwoColumnShapeIds{..}, ) $ buildSpTree ns spTree - $ hdrShapeElements <> contentElementsL <> contentElementsR + $ hdrShapeElements <> contentElementsL <> contentElementsR <> footer twoColumnToElement _ _ _ _ = return (Nothing, mknode "p:sp" [] ()) data ComparisonShapeIds = ComparisonShapeIds @@ -1456,6 +1517,7 @@ comparisonToElement layout hdrShape (shapesL1, shapesL2) (shapesR1, shapesR2) (shapesToElements layout shapesR2) let comparisonRightContentIds = mapMaybe fst contentR2 contentElementsR2 = snd <$> contentR2 + footer <- footerElements comparison return $ (Just ComparisonShapeIds{..}, ) $ buildSpTree ns spTree @@ -1464,7 +1526,7 @@ comparisonToElement layout hdrShape (shapesL1, shapesL2) (shapesR1, shapesR2) , contentElementsL2 , contentElementsR1 , contentElementsR2 - ] + ] <> footer comparisonToElement _ _ _ _= return (Nothing, mknode "p:sp" [] ()) data ContentWithCaptionShapeIds = ContentWithCaptionShapeIds @@ -1495,13 +1557,14 @@ contentWithCaptionToElement layout hdrShape textShapes contentShapes (shapesToElements layout contentShapes) let contentWithCaptionContentIds = mapMaybe fst content contentElements = snd <$> content + footer <- footerElements contentWithCaption return $ (Just ContentWithCaptionShapeIds{..}, ) $ buildSpTree ns spTree $ mconcat [ hdrShapeElements , textElements , contentElements - ] + ] <> footer contentWithCaptionToElement _ _ _ _ = return (Nothing, mknode "p:sp" [] ()) blankToElement :: @@ -1511,8 +1574,8 @@ blankToElement :: blankToElement layout | ns <- elemToNameSpaces layout , Just cSld <- findChild (elemName ns "p" "cSld") layout - , Just spTree <- findChild (elemName ns "p" "spTree") cSld = do - return $ buildSpTree ns spTree [] + , Just spTree <- findChild (elemName ns "p" "spTree") cSld = + buildSpTree ns spTree <$> footerElements blank blankToElement _ = return $ mknode "p:sp" [] () newtype TitleShapeIds = TitleShapeIds @@ -1531,7 +1594,10 @@ titleToElement layout titleElems (shapeId, element) <- nonBodyTextToElement layout [PHType "title", PHType "ctrTitle"] titleElems let titleShapeElements = [Elem element | not (null titleElems)] titleHeaderId = if null titleElems then Nothing else shapeId - return $ (Just TitleShapeIds{..}, ) $ buildSpTree ns spTree titleShapeElements + footer <- footerElements title + return + $ (Just TitleShapeIds{..}, ) + $ buildSpTree ns spTree (titleShapeElements <> footer) titleToElement _ _ = return (Nothing, mknode "p:sp" [] ()) data MetadataShapeIds = MetadataShapeIds @@ -1561,13 +1627,20 @@ metadataToElement layout titleElems subtitleElems authorsElems dateElems metadataTitleId = if null titleElems then Nothing else titleId subtitleShapeElements = [subtitleElement | not (null subtitleAndAuthorElems)] metadataSubtitleId = if null subtitleAndAuthorElems then Nothing else subtitleId - dateShapeElements = [dateElement | not (null dateElems)] + footerInfo <- gets stFooterInfo + footer <- (if maybe False fiShowOnFirstSlide footerInfo + then id + else const []) <$> footerElements metadata + let dateShapeElements = [dateElement + | not (null dateElems + || isJust (footerInfo >>= metadata . fiDate)) + ] metadataDateId = if null dateElems then Nothing else dateId return $ (Just MetadataShapeIds{..}, ) $ buildSpTree ns spTree - $ map Elem - $ titleShapeElements <> subtitleShapeElements <> dateShapeElements + $ map Elem (titleShapeElements <> subtitleShapeElements <> dateShapeElements) + <> footer metadataToElement _ _ _ _ _ = return (Nothing, mknode "p:sp" [] ()) slideToElement :: PandocMonad m => Slide -> P m Element diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs index 6e676dc37..b2df80e5f 100644 --- a/test/Tests/Writers/Powerpoint.hs +++ b/test/Tests/Writers/Powerpoint.hs @@ -61,187 +61,216 @@ groupPptxTests pairs = tests :: [TestTree] -tests = 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 "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" - , pptxTests ("Using slide level 0, if the first thing on " - <> "a slide is 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 ("Using slide level 0, if the first thing on " - <> "a slide is 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" - , pptxTests ("Using slide level 0, if the first thing on " - <> "a slide is a heading it's used as the " - <> "slide title (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 ("Using slide level 0, if the first thing on " - <> "a slide is a heading it's used as the " - <> "slide title (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" - , pptxTests ("comparison layout used when two columns " - <> "contain text plus non-text") - def - "pptx/comparison/both-columns/input.native" - "pptx/comparison/both-columns/output.pptx" - , pptxTests ("comparison layout used even when only one " - <> "column contains text plus non-text") - def - "pptx/comparison/one-column/input.native" - "pptx/comparison/one-column/output.pptx" - , pptxTests ("extra text in one column in comparison " - <> "layout gets overlaid") - def - "pptx/comparison/extra-text/input.native" - "pptx/comparison/extra-text/output.pptx" - , pptxTests ("extra image in one column in comparison " - <> "layout gets overlaid") - def - "pptx/comparison/extra-image/input.native" - "pptx/comparison/extra-image/output.pptx" - , pptxTests "comparison not used if the non-text comes first" - def - "pptx/comparison/non-text-first/input.native" - "pptx/comparison/non-text-first/output.pptx" - , pptxTests ("Heading, text and an image on the same " - <> "slide uses the Content with Caption " - <> "layout") - def - "pptx/content-with-caption/heading-text-image/input.native" - "pptx/content-with-caption/heading-text-image/output.pptx" - , pptxTests ("Text and an image on the same " - <> "slide uses the Content with Caption " - <> "layout") - def - "pptx/content-with-caption/text-image/input.native" - "pptx/content-with-caption/text-image/output.pptx" - , pptxTests ("If the image comes first, Content with " - <> "Caption is not used") - def - "pptx/content-with-caption/image-text/input.native" - "pptx/content-with-caption/image-text/output.pptx" - , pptxTests ("If a slide contains only speaker notes, the " - <> "Blank layout is used") - def - "pptx/blanks/just-speaker-notes/input.native" - "pptx/blanks/just-speaker-notes/output.pptx" - , pptxTests ("If a slide contains only an empty heading " - <> "with a body of only non-breaking spaces" - <> ", the Blank layout is used") - def - "pptx/blanks/nbsp-in-body/input.native" - "pptx/blanks/nbsp-in-body/output.pptx" - , pptxTests ("If a slide contains only a heading " - <> "containing only non-breaking spaces, " - <> "the Blank layout is used") - 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" - ] +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 "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" + , pptxTests ("Using slide level 0, if the first thing on " + <> "a slide is 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 ("Using slide level 0, if the first thing on " + <> "a slide is 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" + , pptxTests ("Using slide level 0, if the first thing on " + <> "a slide is a heading it's used as the " + <> "slide title (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 ("Using slide level 0, if the first thing on " + <> "a slide is a heading it's used as the " + <> "slide title (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" + , pptxTests ("comparison layout used when two columns " + <> "contain text plus non-text") + def + "pptx/comparison/both-columns/input.native" + "pptx/comparison/both-columns/output.pptx" + , pptxTests ("comparison layout used even when only one " + <> "column contains text plus non-text") + def + "pptx/comparison/one-column/input.native" + "pptx/comparison/one-column/output.pptx" + , pptxTests ("extra text in one column in comparison " + <> "layout gets overlaid") + def + "pptx/comparison/extra-text/input.native" + "pptx/comparison/extra-text/output.pptx" + , pptxTests ("extra image in one column in comparison " + <> "layout gets overlaid") + def + "pptx/comparison/extra-image/input.native" + "pptx/comparison/extra-image/output.pptx" + , pptxTests "comparison not used if the non-text comes first" + def + "pptx/comparison/non-text-first/input.native" + "pptx/comparison/non-text-first/output.pptx" + , pptxTests ("Heading, text and an image on the same " + <> "slide uses the Content with Caption " + <> "layout") + def + "pptx/content-with-caption/heading-text-image/input.native" + "pptx/content-with-caption/heading-text-image/output.pptx" + , pptxTests ("Text and an image on the same " + <> "slide uses the Content with Caption " + <> "layout") + def + "pptx/content-with-caption/text-image/input.native" + "pptx/content-with-caption/text-image/output.pptx" + , pptxTests ("If the image comes first, Content with " + <> "Caption is not used") + def + "pptx/content-with-caption/image-text/input.native" + "pptx/content-with-caption/image-text/output.pptx" + , pptxTests ("If a slide contains only speaker notes, the " + <> "Blank layout is used") + def + "pptx/blanks/just-speaker-notes/input.native" + "pptx/blanks/just-speaker-notes/output.pptx" + , pptxTests ("If a slide contains only an empty heading " + <> "with a body of only non-breaking spaces" + <> ", the Blank layout is used") + def + "pptx/blanks/nbsp-in-body/input.native" + "pptx/blanks/nbsp-in-body/output.pptx" + , pptxTests ("If a slide contains only a heading " + <> "containing only non-breaking spaces, " + <> "the Blank layout is used") + 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" + ] + in regularTests <> referenceSpecificTests diff --git a/test/pptx/footer/basic/output.pptx b/test/pptx/footer/basic/output.pptx new file mode 100644 index 000000000..db8814418 Binary files /dev/null and b/test/pptx/footer/basic/output.pptx differ diff --git a/test/pptx/footer/basic/reference.pptx b/test/pptx/footer/basic/reference.pptx new file mode 100644 index 000000000..61f926fa6 Binary files /dev/null and b/test/pptx/footer/basic/reference.pptx differ diff --git a/test/pptx/footer/fixed-date/output.pptx b/test/pptx/footer/fixed-date/output.pptx new file mode 100644 index 000000000..85854a744 Binary files /dev/null and b/test/pptx/footer/fixed-date/output.pptx differ diff --git a/test/pptx/footer/fixed-date/reference.pptx b/test/pptx/footer/fixed-date/reference.pptx new file mode 100644 index 000000000..78bd3ce0d Binary files /dev/null and b/test/pptx/footer/fixed-date/reference.pptx differ diff --git a/test/pptx/footer/higher-slide-number/output.pptx b/test/pptx/footer/higher-slide-number/output.pptx new file mode 100644 index 000000000..c5bc3d047 Binary files /dev/null and b/test/pptx/footer/higher-slide-number/output.pptx differ diff --git a/test/pptx/footer/higher-slide-number/reference.pptx b/test/pptx/footer/higher-slide-number/reference.pptx new file mode 100644 index 000000000..6ada45399 Binary files /dev/null and b/test/pptx/footer/higher-slide-number/reference.pptx differ diff --git a/test/pptx/footer/input.native b/test/pptx/footer/input.native new file mode 100644 index 000000000..2c0ae5c06 --- /dev/null +++ b/test/pptx/footer/input.native @@ -0,0 +1,66 @@ +Pandoc (Meta {unMeta = fromList [("author",MetaInlines [Str "Me"]),("date",MetaInlines [Str "14/09/1995"]),("title",MetaInlines [Str "Slides"])]}) +[Header 2 ("slide-1",[],[]) [Str "Slide",Space,Str "1"] +,Para [Str "Hello",Space,Str "there"] +,Header 1 ("layouts",[],[]) [Str "Layouts"] +,Header 2 ("slide-3",[],[]) [Str "Slide",Space,Str "3"] +,Para [Str "Does",Space,Str "it",Space,Str "work",Space,Str "on",Space,Str "other",Space,Str "layouts?"] +,Table ("",[],[]) (Caption Nothing + []) + [(AlignDefault,ColWidth 5.555555555555555e-2) + ,(AlignDefault,ColWidth 5.555555555555555e-2)] + (TableHead ("",[],[]) + []) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "2"]]]])] + (TableFoot ("",[],[]) + []) +,Header 2 ("slide-4",[],[]) [Str "Slide",Space,Str "4"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Str "hello",Space,Str "hello"]] + ,Div ("",["column"],[]) + [Para [Str "goood",Space,Str "bye"]]] +,Header 2 ("slide-5",[],[]) [Str "Slide",Space,Str "5"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Str "Hello",Space,Str "there"] + ,Table ("",[],[]) (Caption Nothing + []) + [(AlignDefault,ColWidth 5.555555555555555e-2) + ,(AlignDefault,ColWidth 5.555555555555555e-2)] + (TableHead ("",[],[]) + []) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "2"]]]])] + (TableFoot ("",[],[]) + [])] + ,Div ("",["column"],[]) + [Para [Str "oh",Space,Str "wait"] + ,Table ("",[],[]) (Caption Nothing + []) + [(AlignDefault,ColWidth 5.555555555555555e-2) + ,(AlignDefault,ColWidth 5.555555555555555e-2)] + (TableHead ("",[],[]) + []) + [(TableBody ("",[],[]) (RowHeadColumns 0) + [] + [Row ("",[],[]) + [Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "1"]] + ,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1) + [Plain [Str "2"]]]])] + (TableFoot ("",[],[]) + [])]] +,Header 2 ("section",[],[]) [] +,Div ("",["notes"],[]) + [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "blank",Space,Str "slide:",Space,Str "does",Space,Str "it",Space,Str "have",Space,Str "a",Space,Str "footer?"]]] diff --git a/test/pptx/footer/no-title-slide/output.pptx b/test/pptx/footer/no-title-slide/output.pptx new file mode 100644 index 000000000..d1475bf1f Binary files /dev/null and b/test/pptx/footer/no-title-slide/output.pptx differ diff --git a/test/pptx/footer/no-title-slide/reference.pptx b/test/pptx/footer/no-title-slide/reference.pptx new file mode 100644 index 000000000..ecd524a9b Binary files /dev/null and b/test/pptx/footer/no-title-slide/reference.pptx differ -- cgit v1.2.3 From 6ff04ac52de07ef1de7d9ccba0d74db5aa12dda8 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 2 Oct 2021 06:51:21 -0700 Subject: Fix compareXML helper in Tests.Writers.OOXML. Given how it is used, we were getting "mine" and "good" flipped in the test results. --- test/Tests/Writers/OOXML.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) (limited to 'test/Tests/Writers') diff --git a/test/Tests/Writers/OOXML.hs b/test/Tests/Writers/OOXML.hs index f2957f7a6..fea7fa70f 100644 --- a/test/Tests/Writers/OOXML.hs +++ b/test/Tests/Writers/OOXML.hs @@ -23,15 +23,15 @@ 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. -compareXML (Elem myElem) (Elem goodElem) +compareXML (Elem goodElem) (Elem myElem) | (QName "created" _ (Just "dcterms")) <- elName myElem , (QName "created" _ (Just "dcterms")) <- elName goodElem = Nothing -compareXML (Elem myElem) (Elem goodElem) +compareXML (Elem goodElem) (Elem myElem) | (QName "modified" _ (Just "dcterms")) <- elName myElem , (QName "modified" _ (Just "dcterms")) <- elName goodElem = Nothing -compareXML (Elem myElem) (Elem goodElem) = +compareXML (Elem goodElem) (Elem myElem) = (if elName myElem == elName goodElem then Nothing else Just @@ -46,16 +46,16 @@ compareXML (Elem myElem) (Elem goodElem) = , good = sort (elAttribs goodElem) }))) <|> asum (zipWith compareXML (elContent myElem) (elContent goodElem)) -compareXML (Text myCData) (Text goodCData) = +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 myStr) (CRef goodStr) = +compareXML (CRef goodStr) (CRef myStr) = if myStr == goodStr then Nothing else Just (CRefsDiffer (Comparison { mine = myStr, good = goodStr })) -compareXML m g = Just (OtherContentsDiffer (Comparison {mine = m, good = g})) +compareXML g m = Just (OtherContentsDiffer (Comparison {mine = m, good = g})) data XMLDifference = ElemNamesDiffer (Comparison QName) -- cgit v1.2.3 From 11baeb88505342c580cc3dd0263c4ba97e6ddb8a Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 2 Oct 2021 07:03:22 -0700 Subject: OOXML tests: use pretty-printed form to display diffs. Otherwise everything is on one line and the diff is uninformative. --- test/Tests/Writers/OOXML.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) (limited to 'test/Tests/Writers') diff --git a/test/Tests/Writers/OOXML.hs b/test/Tests/Writers/OOXML.hs index fea7fa70f..43543954c 100644 --- a/test/Tests/Writers/OOXML.hs +++ b/test/Tests/Writers/OOXML.hs @@ -68,10 +68,10 @@ data XMLDifference data Comparison a = Comparison { good :: a, mine :: a } deriving (Show) -displayDiff :: Content -> Content -> String +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 @@ -137,7 +137,7 @@ compareXMLFile' fp goldenArch testArch = do display difference = "Non-matching xml in " ++ fp ++ ":\n" ++ "* " ++ show difference ++ "\n" - ++ displayDiff testContent goldenContent + ++ displayDiff testXMLDoc goldenXMLDoc maybe (Right ()) (Left . display) (compareXML goldenContent testContent) -- cgit v1.2.3 From aa78765bf9d21b3a617a9eafba59dd59e362aa6b Mon Sep 17 00:00:00 2001 From: Emily Bourke Date: Thu, 7 Oct 2021 15:25:15 +0100 Subject: pptx: Remove excessive layout tests MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit When I added the tests for moved layouts and deleted layouts, I added them to all tests. However, this doesn’t really give a lot more info than having single tests, and the extra tests take up time and disk space. This commit removes the moved-layouts and deleted-layouts tests, in favour of a single test for each of those scenarios. --- test/Tests/Writers/Powerpoint.hs | 35 +++++++++------------ test/pptx/background-image/deleted-layouts.pptx | Bin 56230 -> 0 bytes test/pptx/background-image/moved-layouts.pptx | Bin 66932 -> 0 bytes .../blanks/just-speaker-notes/deleted-layouts.pptx | Bin 35147 -> 0 bytes .../blanks/just-speaker-notes/moved-layouts.pptx | Bin 45837 -> 0 bytes test/pptx/blanks/nbsp-in-body/deleted-layouts.pptx | Bin 32085 -> 0 bytes test/pptx/blanks/nbsp-in-body/moved-layouts.pptx | Bin 42772 -> 0 bytes .../blanks/nbsp-in-heading/deleted-layouts.pptx | Bin 32085 -> 0 bytes .../pptx/blanks/nbsp-in-heading/moved-layouts.pptx | Bin 42772 -> 0 bytes test/pptx/code-custom/deleted-layouts.pptx | Bin 32697 -> 0 bytes test/pptx/code-custom/moved-layouts.pptx | Bin 43385 -> 0 bytes test/pptx/code/deleted-layouts.pptx | Bin 32695 -> 0 bytes test/pptx/code/moved-layouts.pptx | Bin 43383 -> 0 bytes .../comparison/both-columns/deleted-layouts.pptx | Bin 47441 -> 0 bytes .../comparison/both-columns/moved-layouts.pptx | Bin 58159 -> 0 bytes .../comparison/extra-image/deleted-layouts.pptx | Bin 47470 -> 0 bytes .../pptx/comparison/extra-image/moved-layouts.pptx | Bin 58185 -> 0 bytes .../comparison/extra-text/deleted-layouts.pptx | Bin 47441 -> 0 bytes test/pptx/comparison/extra-text/moved-layouts.pptx | Bin 58159 -> 0 bytes .../comparison/non-text-first/deleted-layouts.pptx | Bin 47355 -> 0 bytes .../comparison/non-text-first/moved-layouts.pptx | Bin 58050 -> 0 bytes .../comparison/one-column/deleted-layouts.pptx | Bin 30780 -> 0 bytes test/pptx/comparison/one-column/moved-layouts.pptx | Bin 41499 -> 0 bytes .../heading-text-image/deleted-layouts.pptx | Bin 47189 -> 0 bytes .../heading-text-image/moved-layouts.pptx | Bin 57887 -> 0 bytes .../image-text/deleted-layouts.pptx | Bin 47891 -> 0 bytes .../image-text/moved-layouts.pptx | Bin 58578 -> 0 bytes .../text-image/deleted-layouts.pptx | Bin 47129 -> 0 bytes .../text-image/moved-layouts.pptx | Bin 57827 -> 0 bytes .../deleted-layouts.pptx | Bin 31483 -> 0 bytes .../moved-layouts.pptx | Bin 42171 -> 0 bytes test/pptx/document-properties/deleted-layouts.pptx | Bin 31886 -> 0 bytes test/pptx/document-properties/moved-layouts.pptx | Bin 42573 -> 0 bytes test/pptx/endnotes-toc/deleted-layouts.pptx | Bin 32280 -> 0 bytes test/pptx/endnotes-toc/moved-layouts.pptx | Bin 42967 -> 0 bytes test/pptx/endnotes/deleted-layouts.pptx | Bin 31458 -> 0 bytes test/pptx/endnotes/moved-layouts.pptx | Bin 42146 -> 0 bytes test/pptx/images/deleted-layouts.pptx | Bin 49113 -> 0 bytes test/pptx/images/moved-layouts.pptx | Bin 59801 -> 0 bytes .../with-flag/deleted-layouts.pptx | Bin 80042 -> 0 bytes .../incremental-lists/with-flag/moved-layouts.pptx | Bin 90782 -> 0 bytes .../without-flag/deleted-layouts.pptx | Bin 78282 -> 0 bytes .../without-flag/moved-layouts.pptx | Bin 89020 -> 0 bytes test/pptx/inline-formatting/deleted-layouts.pptx | Bin 30651 -> 0 bytes test/pptx/inline-formatting/moved-layouts.pptx | Bin 41339 -> 0 bytes test/pptx/layouts/deleted.pptx | Bin 0 -> 55694 bytes test/pptx/layouts/input.native | 23 ++++++++++++++ test/pptx/layouts/moved.pptx | Bin 0 -> 66430 bytes test/pptx/lists/deleted-layouts.pptx | Bin 31540 -> 0 bytes test/pptx/lists/moved-layouts.pptx | Bin 42230 -> 0 bytes test/pptx/raw-ooxml/deleted-layouts.pptx | Bin 31438 -> 0 bytes test/pptx/raw-ooxml/moved-layouts.pptx | Bin 42126 -> 0 bytes test/pptx/remove-empty-slides/deleted-layouts.pptx | Bin 47866 -> 0 bytes test/pptx/remove-empty-slides/moved-layouts.pptx | Bin 58553 -> 0 bytes .../deleted-layouts.pptx | Bin 32233 -> 0 bytes .../slide-breaks-slide-level-1/moved-layouts.pptx | Bin 42923 -> 0 bytes test/pptx/slide-breaks-toc/deleted-layouts.pptx | Bin 34006 -> 0 bytes test/pptx/slide-breaks-toc/moved-layouts.pptx | Bin 44696 -> 0 bytes test/pptx/slide-breaks/deleted-layouts.pptx | Bin 33056 -> 0 bytes test/pptx/slide-breaks/moved-layouts.pptx | Bin 43746 -> 0 bytes .../h1-h2-with-table/deleted-layouts.pptx | Bin 30786 -> 0 bytes .../h1-h2-with-table/moved-layouts.pptx | Bin 41479 -> 0 bytes .../h1-with-image/deleted-layouts.pptx | Bin 47114 -> 0 bytes .../slide-level-0/h1-with-image/moved-layouts.pptx | Bin 57800 -> 0 bytes .../h1-with-table/deleted-layouts.pptx | Bin 30693 -> 0 bytes .../slide-level-0/h1-with-table/moved-layouts.pptx | Bin 41381 -> 0 bytes .../h2-with-image/deleted-layouts.pptx | Bin 47114 -> 0 bytes .../slide-level-0/h2-with-image/moved-layouts.pptx | Bin 57800 -> 0 bytes .../deleted-layouts.pptx | Bin 34486 -> 0 bytes .../moved-layouts.pptx | Bin 45176 -> 0 bytes .../speaker-notes-afterheader/deleted-layouts.pptx | Bin 33507 -> 0 bytes .../speaker-notes-afterheader/moved-layouts.pptx | Bin 44195 -> 0 bytes .../speaker-notes-afterseps/deleted-layouts.pptx | Bin 54374 -> 0 bytes .../speaker-notes-afterseps/moved-layouts.pptx | Bin 65064 -> 0 bytes test/pptx/speaker-notes/deleted-layouts.pptx | Bin 38206 -> 0 bytes test/pptx/speaker-notes/moved-layouts.pptx | Bin 48899 -> 0 bytes test/pptx/start-numbering-at/deleted-layouts.pptx | Bin 31502 -> 0 bytes test/pptx/start-numbering-at/moved-layouts.pptx | Bin 42192 -> 0 bytes test/pptx/tables/deleted-layouts.pptx | Bin 32040 -> 0 bytes test/pptx/tables/moved-layouts.pptx | Bin 42729 -> 0 bytes test/pptx/two-column/all-text/deleted-layouts.pptx | Bin 30567 -> 0 bytes test/pptx/two-column/all-text/moved-layouts.pptx | Bin 41255 -> 0 bytes .../two-column/text-and-image/deleted-layouts.pptx | Bin 48381 -> 0 bytes .../two-column/text-and-image/moved-layouts.pptx | Bin 59075 -> 0 bytes 84 files changed, 38 insertions(+), 20 deletions(-) delete mode 100644 test/pptx/background-image/deleted-layouts.pptx delete mode 100644 test/pptx/background-image/moved-layouts.pptx delete mode 100644 test/pptx/blanks/just-speaker-notes/deleted-layouts.pptx delete mode 100644 test/pptx/blanks/just-speaker-notes/moved-layouts.pptx delete mode 100644 test/pptx/blanks/nbsp-in-body/deleted-layouts.pptx delete mode 100644 test/pptx/blanks/nbsp-in-body/moved-layouts.pptx delete mode 100644 test/pptx/blanks/nbsp-in-heading/deleted-layouts.pptx delete mode 100644 test/pptx/blanks/nbsp-in-heading/moved-layouts.pptx delete mode 100644 test/pptx/code-custom/deleted-layouts.pptx delete mode 100644 test/pptx/code-custom/moved-layouts.pptx delete mode 100644 test/pptx/code/deleted-layouts.pptx delete mode 100644 test/pptx/code/moved-layouts.pptx delete mode 100644 test/pptx/comparison/both-columns/deleted-layouts.pptx delete mode 100644 test/pptx/comparison/both-columns/moved-layouts.pptx delete mode 100644 test/pptx/comparison/extra-image/deleted-layouts.pptx delete mode 100644 test/pptx/comparison/extra-image/moved-layouts.pptx delete mode 100644 test/pptx/comparison/extra-text/deleted-layouts.pptx delete mode 100644 test/pptx/comparison/extra-text/moved-layouts.pptx delete mode 100644 test/pptx/comparison/non-text-first/deleted-layouts.pptx delete mode 100644 test/pptx/comparison/non-text-first/moved-layouts.pptx delete mode 100644 test/pptx/comparison/one-column/deleted-layouts.pptx delete mode 100644 test/pptx/comparison/one-column/moved-layouts.pptx delete mode 100644 test/pptx/content-with-caption/heading-text-image/deleted-layouts.pptx delete mode 100644 test/pptx/content-with-caption/heading-text-image/moved-layouts.pptx delete mode 100644 test/pptx/content-with-caption/image-text/deleted-layouts.pptx delete mode 100644 test/pptx/content-with-caption/image-text/moved-layouts.pptx delete mode 100644 test/pptx/content-with-caption/text-image/deleted-layouts.pptx delete mode 100644 test/pptx/content-with-caption/text-image/moved-layouts.pptx delete mode 100644 test/pptx/document-properties-short-desc/deleted-layouts.pptx delete mode 100644 test/pptx/document-properties-short-desc/moved-layouts.pptx delete mode 100644 test/pptx/document-properties/deleted-layouts.pptx delete mode 100644 test/pptx/document-properties/moved-layouts.pptx delete mode 100644 test/pptx/endnotes-toc/deleted-layouts.pptx delete mode 100644 test/pptx/endnotes-toc/moved-layouts.pptx delete mode 100644 test/pptx/endnotes/deleted-layouts.pptx delete mode 100644 test/pptx/endnotes/moved-layouts.pptx delete mode 100644 test/pptx/images/deleted-layouts.pptx delete mode 100644 test/pptx/images/moved-layouts.pptx delete mode 100644 test/pptx/incremental-lists/with-flag/deleted-layouts.pptx delete mode 100644 test/pptx/incremental-lists/with-flag/moved-layouts.pptx delete mode 100644 test/pptx/incremental-lists/without-flag/deleted-layouts.pptx delete mode 100644 test/pptx/incremental-lists/without-flag/moved-layouts.pptx delete mode 100644 test/pptx/inline-formatting/deleted-layouts.pptx delete mode 100644 test/pptx/inline-formatting/moved-layouts.pptx create mode 100644 test/pptx/layouts/deleted.pptx create mode 100644 test/pptx/layouts/input.native create mode 100644 test/pptx/layouts/moved.pptx delete mode 100644 test/pptx/lists/deleted-layouts.pptx delete mode 100644 test/pptx/lists/moved-layouts.pptx delete mode 100644 test/pptx/raw-ooxml/deleted-layouts.pptx delete mode 100644 test/pptx/raw-ooxml/moved-layouts.pptx delete mode 100644 test/pptx/remove-empty-slides/deleted-layouts.pptx delete mode 100644 test/pptx/remove-empty-slides/moved-layouts.pptx delete mode 100644 test/pptx/slide-breaks-slide-level-1/deleted-layouts.pptx delete mode 100644 test/pptx/slide-breaks-slide-level-1/moved-layouts.pptx delete mode 100644 test/pptx/slide-breaks-toc/deleted-layouts.pptx delete mode 100644 test/pptx/slide-breaks-toc/moved-layouts.pptx delete mode 100644 test/pptx/slide-breaks/deleted-layouts.pptx delete mode 100644 test/pptx/slide-breaks/moved-layouts.pptx delete mode 100644 test/pptx/slide-level-0/h1-h2-with-table/deleted-layouts.pptx delete mode 100644 test/pptx/slide-level-0/h1-h2-with-table/moved-layouts.pptx delete mode 100644 test/pptx/slide-level-0/h1-with-image/deleted-layouts.pptx delete mode 100644 test/pptx/slide-level-0/h1-with-image/moved-layouts.pptx delete mode 100644 test/pptx/slide-level-0/h1-with-table/deleted-layouts.pptx delete mode 100644 test/pptx/slide-level-0/h1-with-table/moved-layouts.pptx delete mode 100644 test/pptx/slide-level-0/h2-with-image/deleted-layouts.pptx delete mode 100644 test/pptx/slide-level-0/h2-with-image/moved-layouts.pptx delete mode 100644 test/pptx/speaker-notes-after-metadata/deleted-layouts.pptx delete mode 100644 test/pptx/speaker-notes-after-metadata/moved-layouts.pptx delete mode 100644 test/pptx/speaker-notes-afterheader/deleted-layouts.pptx delete mode 100644 test/pptx/speaker-notes-afterheader/moved-layouts.pptx delete mode 100644 test/pptx/speaker-notes-afterseps/deleted-layouts.pptx delete mode 100644 test/pptx/speaker-notes-afterseps/moved-layouts.pptx delete mode 100644 test/pptx/speaker-notes/deleted-layouts.pptx delete mode 100644 test/pptx/speaker-notes/moved-layouts.pptx delete mode 100644 test/pptx/start-numbering-at/deleted-layouts.pptx delete mode 100644 test/pptx/start-numbering-at/moved-layouts.pptx delete mode 100644 test/pptx/tables/deleted-layouts.pptx delete mode 100644 test/pptx/tables/moved-layouts.pptx delete mode 100644 test/pptx/two-column/all-text/deleted-layouts.pptx delete mode 100644 test/pptx/two-column/all-text/moved-layouts.pptx delete mode 100644 test/pptx/two-column/text-and-image/deleted-layouts.pptx delete mode 100644 test/pptx/two-column/text-and-image/moved-layouts.pptx (limited to 'test/Tests/Writers') diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs index b2df80e5f..84bdd7476 100644 --- a/test/Tests/Writers/Powerpoint.hs +++ b/test/Tests/Writers/Powerpoint.hs @@ -7,7 +7,6 @@ import System.FilePath import Text.DocTemplates (ToContext(toVal), Context(..)) import qualified Data.Map as M import Data.Text (pack) -import Data.List (unzip4) -- templating is important enough, and can break enough things, that -- we want to run all our tests with both default formatting and a @@ -17,11 +16,9 @@ modifyPptxName :: FilePath -> String -> FilePath modifyPptxName fp suffix = addExtension (takeDirectory fp ++ suffix) "pptx" -pptxTests :: String -> WriterOptions -> FilePath -> FilePath -> (TestTree, TestTree, TestTree, TestTree) +pptxTests :: String -> WriterOptions -> FilePath -> FilePath -> (TestTree, TestTree) pptxTests name opts native pptx = let referenceDoc = "pptx/reference-depth.pptx" - movedLayoutsReferenceDoc = "pptx/reference-moved-layouts.pptx" - deletedLayoutsReferenceDoc = "pptx/reference-deleted-layouts.pptx" in ( ooxmlTest writePowerpoint @@ -35,28 +32,14 @@ pptxTests name opts native pptx = opts{writerReferenceDoc=Just referenceDoc} native (modifyPptxName pptx "/templated") - , ooxmlTest - writePowerpoint - name - opts{writerReferenceDoc=Just movedLayoutsReferenceDoc} - native - (modifyPptxName pptx "/moved-layouts") - , ooxmlTest - writePowerpoint - name - opts{writerReferenceDoc=Just deletedLayoutsReferenceDoc} - native - (modifyPptxName pptx "/deleted-layouts") ) -groupPptxTests :: [(TestTree, TestTree, TestTree, TestTree)] -> [TestTree] +groupPptxTests :: [(TestTree, TestTree)] -> [TestTree] groupPptxTests pairs = - let (noRefs, refs, movedLayouts, deletedLayouts) = unzip4 pairs + let (noRefs, refs) = unzip pairs in [ testGroup "Default slide formatting" noRefs , testGroup "With `--reference-doc` pptx file" refs - , testGroup "With layouts in reference doc moved" movedLayouts - , testGroup "With layouts in reference doc deleted" deletedLayouts ] @@ -272,5 +255,17 @@ tests = let 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 diff --git a/test/pptx/background-image/deleted-layouts.pptx b/test/pptx/background-image/deleted-layouts.pptx deleted file mode 100644 index e46a58ad7..000000000 Binary files a/test/pptx/background-image/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/background-image/moved-layouts.pptx b/test/pptx/background-image/moved-layouts.pptx deleted file mode 100644 index 98fe33095..000000000 Binary files a/test/pptx/background-image/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/blanks/just-speaker-notes/deleted-layouts.pptx b/test/pptx/blanks/just-speaker-notes/deleted-layouts.pptx deleted file mode 100644 index f729c3ce6..000000000 Binary files a/test/pptx/blanks/just-speaker-notes/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/blanks/just-speaker-notes/moved-layouts.pptx b/test/pptx/blanks/just-speaker-notes/moved-layouts.pptx deleted file mode 100644 index dfae6a645..000000000 Binary files a/test/pptx/blanks/just-speaker-notes/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/blanks/nbsp-in-body/deleted-layouts.pptx b/test/pptx/blanks/nbsp-in-body/deleted-layouts.pptx deleted file mode 100644 index dcd88cb24..000000000 Binary files a/test/pptx/blanks/nbsp-in-body/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/blanks/nbsp-in-body/moved-layouts.pptx b/test/pptx/blanks/nbsp-in-body/moved-layouts.pptx deleted file mode 100644 index 0a69853fa..000000000 Binary files a/test/pptx/blanks/nbsp-in-body/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/blanks/nbsp-in-heading/deleted-layouts.pptx b/test/pptx/blanks/nbsp-in-heading/deleted-layouts.pptx deleted file mode 100644 index dcd88cb24..000000000 Binary files a/test/pptx/blanks/nbsp-in-heading/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/blanks/nbsp-in-heading/moved-layouts.pptx b/test/pptx/blanks/nbsp-in-heading/moved-layouts.pptx deleted file mode 100644 index 0a69853fa..000000000 Binary files a/test/pptx/blanks/nbsp-in-heading/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/code-custom/deleted-layouts.pptx b/test/pptx/code-custom/deleted-layouts.pptx deleted file mode 100644 index f8b1c789e..000000000 Binary files a/test/pptx/code-custom/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/code-custom/moved-layouts.pptx b/test/pptx/code-custom/moved-layouts.pptx deleted file mode 100644 index 810b46dd1..000000000 Binary files a/test/pptx/code-custom/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/code/deleted-layouts.pptx b/test/pptx/code/deleted-layouts.pptx deleted file mode 100644 index 3127e20e5..000000000 Binary files a/test/pptx/code/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/code/moved-layouts.pptx b/test/pptx/code/moved-layouts.pptx deleted file mode 100644 index 7a2e3b7ac..000000000 Binary files a/test/pptx/code/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/comparison/both-columns/deleted-layouts.pptx b/test/pptx/comparison/both-columns/deleted-layouts.pptx deleted file mode 100644 index 6d80e275f..000000000 Binary files a/test/pptx/comparison/both-columns/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/comparison/both-columns/moved-layouts.pptx b/test/pptx/comparison/both-columns/moved-layouts.pptx deleted file mode 100644 index 2840e0535..000000000 Binary files a/test/pptx/comparison/both-columns/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/comparison/extra-image/deleted-layouts.pptx b/test/pptx/comparison/extra-image/deleted-layouts.pptx deleted file mode 100644 index 771ad409a..000000000 Binary files a/test/pptx/comparison/extra-image/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/comparison/extra-image/moved-layouts.pptx b/test/pptx/comparison/extra-image/moved-layouts.pptx deleted file mode 100644 index 2418e98c1..000000000 Binary files a/test/pptx/comparison/extra-image/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/comparison/extra-text/deleted-layouts.pptx b/test/pptx/comparison/extra-text/deleted-layouts.pptx deleted file mode 100644 index c87b3f3ee..000000000 Binary files a/test/pptx/comparison/extra-text/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/comparison/extra-text/moved-layouts.pptx b/test/pptx/comparison/extra-text/moved-layouts.pptx deleted file mode 100644 index 2840e0535..000000000 Binary files a/test/pptx/comparison/extra-text/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/comparison/non-text-first/deleted-layouts.pptx b/test/pptx/comparison/non-text-first/deleted-layouts.pptx deleted file mode 100644 index 95b2e3a3c..000000000 Binary files a/test/pptx/comparison/non-text-first/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/comparison/non-text-first/moved-layouts.pptx b/test/pptx/comparison/non-text-first/moved-layouts.pptx deleted file mode 100644 index 5a60028d4..000000000 Binary files a/test/pptx/comparison/non-text-first/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/comparison/one-column/deleted-layouts.pptx b/test/pptx/comparison/one-column/deleted-layouts.pptx deleted file mode 100644 index 6a705c735..000000000 Binary files a/test/pptx/comparison/one-column/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/comparison/one-column/moved-layouts.pptx b/test/pptx/comparison/one-column/moved-layouts.pptx deleted file mode 100644 index f456151a5..000000000 Binary files a/test/pptx/comparison/one-column/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/content-with-caption/heading-text-image/deleted-layouts.pptx b/test/pptx/content-with-caption/heading-text-image/deleted-layouts.pptx deleted file mode 100644 index d01a8f9d8..000000000 Binary files a/test/pptx/content-with-caption/heading-text-image/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/content-with-caption/heading-text-image/moved-layouts.pptx b/test/pptx/content-with-caption/heading-text-image/moved-layouts.pptx deleted file mode 100644 index 69cb830a9..000000000 Binary files a/test/pptx/content-with-caption/heading-text-image/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/content-with-caption/image-text/deleted-layouts.pptx b/test/pptx/content-with-caption/image-text/deleted-layouts.pptx deleted file mode 100644 index e9aebd579..000000000 Binary files a/test/pptx/content-with-caption/image-text/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/content-with-caption/image-text/moved-layouts.pptx b/test/pptx/content-with-caption/image-text/moved-layouts.pptx deleted file mode 100644 index c27f1e1cf..000000000 Binary files a/test/pptx/content-with-caption/image-text/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/content-with-caption/text-image/deleted-layouts.pptx b/test/pptx/content-with-caption/text-image/deleted-layouts.pptx deleted file mode 100644 index f15e674c7..000000000 Binary files a/test/pptx/content-with-caption/text-image/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/content-with-caption/text-image/moved-layouts.pptx b/test/pptx/content-with-caption/text-image/moved-layouts.pptx deleted file mode 100644 index 39566cd7f..000000000 Binary files a/test/pptx/content-with-caption/text-image/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/document-properties-short-desc/deleted-layouts.pptx b/test/pptx/document-properties-short-desc/deleted-layouts.pptx deleted file mode 100644 index a6da0c338..000000000 Binary files a/test/pptx/document-properties-short-desc/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/document-properties-short-desc/moved-layouts.pptx b/test/pptx/document-properties-short-desc/moved-layouts.pptx deleted file mode 100644 index 4cff1d486..000000000 Binary files a/test/pptx/document-properties-short-desc/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/document-properties/deleted-layouts.pptx b/test/pptx/document-properties/deleted-layouts.pptx deleted file mode 100644 index a2a58af34..000000000 Binary files a/test/pptx/document-properties/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/document-properties/moved-layouts.pptx b/test/pptx/document-properties/moved-layouts.pptx deleted file mode 100644 index e24d904a2..000000000 Binary files a/test/pptx/document-properties/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/endnotes-toc/deleted-layouts.pptx b/test/pptx/endnotes-toc/deleted-layouts.pptx deleted file mode 100644 index 3e613e038..000000000 Binary files a/test/pptx/endnotes-toc/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/endnotes-toc/moved-layouts.pptx b/test/pptx/endnotes-toc/moved-layouts.pptx deleted file mode 100644 index e64cd9c77..000000000 Binary files a/test/pptx/endnotes-toc/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/endnotes/deleted-layouts.pptx b/test/pptx/endnotes/deleted-layouts.pptx deleted file mode 100644 index 1d7ccb928..000000000 Binary files a/test/pptx/endnotes/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/endnotes/moved-layouts.pptx b/test/pptx/endnotes/moved-layouts.pptx deleted file mode 100644 index 0f071207c..000000000 Binary files a/test/pptx/endnotes/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/images/deleted-layouts.pptx b/test/pptx/images/deleted-layouts.pptx deleted file mode 100644 index 3c3ed787f..000000000 Binary files a/test/pptx/images/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/images/moved-layouts.pptx b/test/pptx/images/moved-layouts.pptx deleted file mode 100644 index b22f3652a..000000000 Binary files a/test/pptx/images/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/incremental-lists/with-flag/deleted-layouts.pptx b/test/pptx/incremental-lists/with-flag/deleted-layouts.pptx deleted file mode 100644 index 3e92d4dab..000000000 Binary files a/test/pptx/incremental-lists/with-flag/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/incremental-lists/with-flag/moved-layouts.pptx b/test/pptx/incremental-lists/with-flag/moved-layouts.pptx deleted file mode 100644 index 050842865..000000000 Binary files a/test/pptx/incremental-lists/with-flag/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/incremental-lists/without-flag/deleted-layouts.pptx b/test/pptx/incremental-lists/without-flag/deleted-layouts.pptx deleted file mode 100644 index 4816c0b39..000000000 Binary files a/test/pptx/incremental-lists/without-flag/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/incremental-lists/without-flag/moved-layouts.pptx b/test/pptx/incremental-lists/without-flag/moved-layouts.pptx deleted file mode 100644 index 4f27db07b..000000000 Binary files a/test/pptx/incremental-lists/without-flag/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/inline-formatting/deleted-layouts.pptx b/test/pptx/inline-formatting/deleted-layouts.pptx deleted file mode 100644 index ac9fa4725..000000000 Binary files a/test/pptx/inline-formatting/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/inline-formatting/moved-layouts.pptx b/test/pptx/inline-formatting/moved-layouts.pptx deleted file mode 100644 index 49a2409d1..000000000 Binary files a/test/pptx/inline-formatting/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/layouts/deleted.pptx b/test/pptx/layouts/deleted.pptx new file mode 100644 index 000000000..f7116b2f4 Binary files /dev/null and b/test/pptx/layouts/deleted.pptx differ diff --git a/test/pptx/layouts/input.native b/test/pptx/layouts/input.native new file mode 100644 index 000000000..0cee2d14e --- /dev/null +++ b/test/pptx/layouts/input.native @@ -0,0 +1,23 @@ +Pandoc (Meta {unMeta = fromList [("title",MetaInlines [Str "Testing",Space,Str "Layouts"])]}) +[Header 2 ("slide-1",[],[]) [Str "Slide",Space,Str "1"] +,Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "title",Space,Str "and",Space,Str "content",Space,Str "slide"] +,Header 2 ("slide-2",[],[]) [Str "Slide",Space,Str "2"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Str "This"]] + ,Div ("",["column"],[]) + [Para [Str "\8230is",Space,Str "a",Space,Str "two-column",Space,Str "slide"]]] +,Header 2 ("slide-3",[],[]) [Str "Slide",Space,Str "3"] +,Para [Str "This",Space,Str "slide",Space,Str "is",Space,Str "a",Space,Str "Content",Space,Str "with",Space,Str "Caption",Space,Str "slide"] +,Para [Image ("",[],[]) [Str "Content"] ("lalune.jpg","fig:")] +,Header 2 ("slide-4",[],[]) [Str "Slide",Space,Str "4"] +,Div ("",["columns"],[]) + [Div ("",["column"],[]) + [Para [Str "This",Space,Str "slide",Space,Str "is",Space,Str "a",Space,Str "Comparison",Space,Str "slide:"] + ,Para [Image ("",[],[]) [Str "Content"] ("lalune.jpg","fig:")]] + ,Div ("",["column"],[]) + [Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "other",Space,Str "text"]]] +,Header 1 ("section-header",[],[]) [Str "Section",Space,Str "header"] +,Header 2 ("section",[],[]) [] +,Div ("",["notes"],[]) + [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "blank",Space,Str "slide"]]] diff --git a/test/pptx/layouts/moved.pptx b/test/pptx/layouts/moved.pptx new file mode 100644 index 000000000..e41465a86 Binary files /dev/null and b/test/pptx/layouts/moved.pptx differ diff --git a/test/pptx/lists/deleted-layouts.pptx b/test/pptx/lists/deleted-layouts.pptx deleted file mode 100644 index d064b7fd5..000000000 Binary files a/test/pptx/lists/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/lists/moved-layouts.pptx b/test/pptx/lists/moved-layouts.pptx deleted file mode 100644 index 8a9c9ec59..000000000 Binary files a/test/pptx/lists/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/raw-ooxml/deleted-layouts.pptx b/test/pptx/raw-ooxml/deleted-layouts.pptx deleted file mode 100644 index a7bd12281..000000000 Binary files a/test/pptx/raw-ooxml/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/raw-ooxml/moved-layouts.pptx b/test/pptx/raw-ooxml/moved-layouts.pptx deleted file mode 100644 index 614682671..000000000 Binary files a/test/pptx/raw-ooxml/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/remove-empty-slides/deleted-layouts.pptx b/test/pptx/remove-empty-slides/deleted-layouts.pptx deleted file mode 100644 index 488abc02a..000000000 Binary files a/test/pptx/remove-empty-slides/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/remove-empty-slides/moved-layouts.pptx b/test/pptx/remove-empty-slides/moved-layouts.pptx deleted file mode 100644 index 1e1cf1e44..000000000 Binary files a/test/pptx/remove-empty-slides/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-breaks-slide-level-1/deleted-layouts.pptx b/test/pptx/slide-breaks-slide-level-1/deleted-layouts.pptx deleted file mode 100644 index b6b004cd6..000000000 Binary files a/test/pptx/slide-breaks-slide-level-1/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-breaks-slide-level-1/moved-layouts.pptx b/test/pptx/slide-breaks-slide-level-1/moved-layouts.pptx deleted file mode 100644 index 229e4c32a..000000000 Binary files a/test/pptx/slide-breaks-slide-level-1/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-breaks-toc/deleted-layouts.pptx b/test/pptx/slide-breaks-toc/deleted-layouts.pptx deleted file mode 100644 index e3b3b2807..000000000 Binary files a/test/pptx/slide-breaks-toc/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-breaks-toc/moved-layouts.pptx b/test/pptx/slide-breaks-toc/moved-layouts.pptx deleted file mode 100644 index ecc942803..000000000 Binary files a/test/pptx/slide-breaks-toc/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-breaks/deleted-layouts.pptx b/test/pptx/slide-breaks/deleted-layouts.pptx deleted file mode 100644 index ada3453b0..000000000 Binary files a/test/pptx/slide-breaks/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-breaks/moved-layouts.pptx b/test/pptx/slide-breaks/moved-layouts.pptx deleted file mode 100644 index 0fe10f443..000000000 Binary files a/test/pptx/slide-breaks/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0/h1-h2-with-table/deleted-layouts.pptx b/test/pptx/slide-level-0/h1-h2-with-table/deleted-layouts.pptx deleted file mode 100644 index c315a7a7a..000000000 Binary files a/test/pptx/slide-level-0/h1-h2-with-table/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0/h1-h2-with-table/moved-layouts.pptx b/test/pptx/slide-level-0/h1-h2-with-table/moved-layouts.pptx deleted file mode 100644 index 81b49936d..000000000 Binary files a/test/pptx/slide-level-0/h1-h2-with-table/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0/h1-with-image/deleted-layouts.pptx b/test/pptx/slide-level-0/h1-with-image/deleted-layouts.pptx deleted file mode 100644 index 478dde788..000000000 Binary files a/test/pptx/slide-level-0/h1-with-image/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0/h1-with-image/moved-layouts.pptx b/test/pptx/slide-level-0/h1-with-image/moved-layouts.pptx deleted file mode 100644 index 63b411888..000000000 Binary files a/test/pptx/slide-level-0/h1-with-image/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0/h1-with-table/deleted-layouts.pptx b/test/pptx/slide-level-0/h1-with-table/deleted-layouts.pptx deleted file mode 100644 index 9d58c2c52..000000000 Binary files a/test/pptx/slide-level-0/h1-with-table/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0/h1-with-table/moved-layouts.pptx b/test/pptx/slide-level-0/h1-with-table/moved-layouts.pptx deleted file mode 100644 index 62424de73..000000000 Binary files a/test/pptx/slide-level-0/h1-with-table/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0/h2-with-image/deleted-layouts.pptx b/test/pptx/slide-level-0/h2-with-image/deleted-layouts.pptx deleted file mode 100644 index 478dde788..000000000 Binary files a/test/pptx/slide-level-0/h2-with-image/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/slide-level-0/h2-with-image/moved-layouts.pptx b/test/pptx/slide-level-0/h2-with-image/moved-layouts.pptx deleted file mode 100644 index 63b411888..000000000 Binary files a/test/pptx/slide-level-0/h2-with-image/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/speaker-notes-after-metadata/deleted-layouts.pptx b/test/pptx/speaker-notes-after-metadata/deleted-layouts.pptx deleted file mode 100644 index 07e21ef02..000000000 Binary files a/test/pptx/speaker-notes-after-metadata/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/speaker-notes-after-metadata/moved-layouts.pptx b/test/pptx/speaker-notes-after-metadata/moved-layouts.pptx deleted file mode 100644 index d6673aac0..000000000 Binary files a/test/pptx/speaker-notes-after-metadata/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/speaker-notes-afterheader/deleted-layouts.pptx b/test/pptx/speaker-notes-afterheader/deleted-layouts.pptx deleted file mode 100644 index 0ccdd72b7..000000000 Binary files a/test/pptx/speaker-notes-afterheader/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/speaker-notes-afterheader/moved-layouts.pptx b/test/pptx/speaker-notes-afterheader/moved-layouts.pptx deleted file mode 100644 index 81f0a56cb..000000000 Binary files a/test/pptx/speaker-notes-afterheader/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/speaker-notes-afterseps/deleted-layouts.pptx b/test/pptx/speaker-notes-afterseps/deleted-layouts.pptx deleted file mode 100644 index 33dedf2c3..000000000 Binary files a/test/pptx/speaker-notes-afterseps/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/speaker-notes-afterseps/moved-layouts.pptx b/test/pptx/speaker-notes-afterseps/moved-layouts.pptx deleted file mode 100644 index 28bcf3887..000000000 Binary files a/test/pptx/speaker-notes-afterseps/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/speaker-notes/deleted-layouts.pptx b/test/pptx/speaker-notes/deleted-layouts.pptx deleted file mode 100644 index 5f407086a..000000000 Binary files a/test/pptx/speaker-notes/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/speaker-notes/moved-layouts.pptx b/test/pptx/speaker-notes/moved-layouts.pptx deleted file mode 100644 index 83d5ed0af..000000000 Binary files a/test/pptx/speaker-notes/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/start-numbering-at/deleted-layouts.pptx b/test/pptx/start-numbering-at/deleted-layouts.pptx deleted file mode 100644 index d99fedfa6..000000000 Binary files a/test/pptx/start-numbering-at/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/start-numbering-at/moved-layouts.pptx b/test/pptx/start-numbering-at/moved-layouts.pptx deleted file mode 100644 index 98db3ec74..000000000 Binary files a/test/pptx/start-numbering-at/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/tables/deleted-layouts.pptx b/test/pptx/tables/deleted-layouts.pptx deleted file mode 100644 index 7ad714058..000000000 Binary files a/test/pptx/tables/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/tables/moved-layouts.pptx b/test/pptx/tables/moved-layouts.pptx deleted file mode 100644 index 9628717d7..000000000 Binary files a/test/pptx/tables/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/two-column/all-text/deleted-layouts.pptx b/test/pptx/two-column/all-text/deleted-layouts.pptx deleted file mode 100644 index a321128b5..000000000 Binary files a/test/pptx/two-column/all-text/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/two-column/all-text/moved-layouts.pptx b/test/pptx/two-column/all-text/moved-layouts.pptx deleted file mode 100644 index 90b1d9254..000000000 Binary files a/test/pptx/two-column/all-text/moved-layouts.pptx and /dev/null differ diff --git a/test/pptx/two-column/text-and-image/deleted-layouts.pptx b/test/pptx/two-column/text-and-image/deleted-layouts.pptx deleted file mode 100644 index 46274ffac..000000000 Binary files a/test/pptx/two-column/text-and-image/deleted-layouts.pptx and /dev/null differ diff --git a/test/pptx/two-column/text-and-image/moved-layouts.pptx b/test/pptx/two-column/text-and-image/moved-layouts.pptx deleted file mode 100644 index c25331e23..000000000 Binary files a/test/pptx/two-column/text-and-image/moved-layouts.pptx and /dev/null differ -- cgit v1.2.3 From a41c1fe0bbdf912f3585c7eb91b59340c35b9b77 Mon Sep 17 00:00:00 2001 From: Samuel Tardieu Date: Thu, 14 Oct 2021 16:16:25 +0200 Subject: asciidoc writer: translate numberLines attribute to linesnum switch AsciiDoctor allows to request line numbering on code blocks by using a switch on the `source` block, such as in: ``` [source%linesnum,haskell] ---- some Haskell code here ---- ``` --- src/Text/Pandoc/Writers/AsciiDoc.hs | 7 +++++-- test/Tests/Writers/AsciiDoc.hs | 16 ++++++++++++++++ 2 files changed, 21 insertions(+), 2 deletions(-) (limited to 'test/Tests/Writers') diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index bcef4a089..4d3906c5f 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -21,7 +21,7 @@ AsciiDoc: module Text.Pandoc.Writers.AsciiDoc (writeAsciiDoc, writeAsciiDoctor) where import Control.Monad.State.Strict import Data.Char (isPunctuation, isSpace) -import Data.List (intercalate, intersperse) +import Data.List (delete, intercalate, intersperse) import Data.List.NonEmpty (NonEmpty(..)) import Data.Maybe (fromMaybe, isJust) import qualified Data.Set as Set @@ -193,7 +193,10 @@ blockToAsciiDoc _ (CodeBlock (_,classes,_) str) = return $ flush ( then "...." $$ literal str $$ "...." else attrs $$ "----" $$ literal str $$ "----") <> blankline - where attrs = "[" <> literal (T.intercalate "," ("source" : classes)) <> "]" + where attrs = "[" <> literal (T.intercalate "," classes') <> "]" + classes' = if "numberLines" `elem` classes + then "source%linesnum" : delete "numberLines" classes + else "source" : classes blockToAsciiDoc opts (BlockQuote blocks) = do contents <- blockListToAsciiDoc opts blocks let isBlock (BlockQuote _) = True 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 -- cgit v1.2.3 From 8af15ab345bb0790cc3442722673d9da9f23a79c Mon Sep 17 00:00:00 2001 From: Emily Bourke Date: Fri, 17 Sep 2021 16:05:06 +0100 Subject: pptx: Fix list level numbering MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit In PowerPoint, the content of a top-level list is at the same level as the content of a top-level paragraph – the only difference is that a list style has been applied. At the moment, the pptx writer increments the paragraph level on each list, turning what should be top-level lists into second-level lists. This commit changes that logic, only incrementing the paragraph level on continuation paragraphs of lists. - Fixes https://github.com/jgm/pandoc/issues/4828 - Fixes https://github.com/jgm/pandoc/issues/4663 --- pandoc.cabal | 2 ++ src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | 31 +++++++++++---------- test/Tests/Writers/Powerpoint.hs | 4 +++ test/pptx/code-custom/output.pptx | Bin 29817 -> 29807 bytes test/pptx/code-custom/templated.pptx | Bin 42884 -> 42877 bytes test/pptx/code/output.pptx | Bin 29815 -> 29806 bytes test/pptx/code/templated.pptx | Bin 42882 -> 42876 bytes test/pptx/incremental-lists/with-flag/output.pptx | Bin 77169 -> 77136 bytes .../incremental-lists/with-flag/templated.pptx | Bin 90280 -> 90251 bytes .../incremental-lists/without-flag/output.pptx | Bin 75411 -> 75386 bytes .../incremental-lists/without-flag/templated.pptx | Bin 88518 -> 88495 bytes test/pptx/list-level/input.native | 20 +++++++++++++ test/pptx/list-level/output.pptx | Bin 0 -> 28635 bytes test/pptx/list-level/templated.pptx | Bin 0 -> 41701 bytes test/pptx/lists/output.pptx | Bin 28664 -> 28657 bytes test/pptx/lists/templated.pptx | Bin 41729 -> 41724 bytes test/pptx/pauses/without-incremental/output.pptx | Bin 0 -> 50083 bytes .../pptx/pauses/without-incremental/templated.pptx | Bin 0 -> 63157 bytes test/pptx/slide-breaks-toc/output.pptx | Bin 31129 -> 31123 bytes test/pptx/slide-breaks-toc/templated.pptx | Bin 44195 -> 44191 bytes test/pptx/speaker-notes-afterseps/output.pptx | Bin 51494 -> 51486 bytes test/pptx/speaker-notes-afterseps/templated.pptx | Bin 64558 -> 64552 bytes test/pptx/start-numbering-at/output.pptx | Bin 28626 -> 28620 bytes test/pptx/start-numbering-at/templated.pptx | Bin 41691 -> 41686 bytes 24 files changed, 43 insertions(+), 14 deletions(-) create mode 100644 test/pptx/list-level/input.native create mode 100644 test/pptx/list-level/output.pptx create mode 100644 test/pptx/list-level/templated.pptx create mode 100644 test/pptx/pauses/without-incremental/output.pptx create mode 100644 test/pptx/pauses/without-incremental/templated.pptx (limited to 'test/Tests/Writers') diff --git a/pandoc.cabal b/pandoc.cabal index 615feaccb..ac6cb8121 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -429,6 +429,8 @@ extra-source-files: test/pptx/inline-formatting/*.pptx test/pptx/lists/input.native test/pptx/lists/*.pptx + test/pptx/list-level/input.native + test/pptx/list-level/*.pptx test/pptx/raw-ooxml/input.native test/pptx/raw-ooxml/*.pptx test/pptx/remove-empty-slides/input.native diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs index fe34d24dc..2f94dcc17 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs @@ -500,27 +500,23 @@ blockToParagraphs (Header _ (ident, _, _) ils) = do blockToParagraphs (BulletList blksLst) = do pProps <- asks envParaProps incremental <- listShouldBeIncremental - let lvl = pPropLevel pProps local (\env -> env{ envInList = True - , envParaProps = pProps{ pPropLevel = lvl + 1 - , pPropBullet = Just Bullet + , envParaProps = pProps{ pPropBullet = Just Bullet , pPropMarginLeft = Nothing , pPropIndent = Nothing , pPropIncremental = incremental }}) $ - concatMapM multiParBullet blksLst + concatMapM multiParList blksLst blockToParagraphs (OrderedList listAttr blksLst) = do pProps <- asks envParaProps incremental <- listShouldBeIncremental - let lvl = pPropLevel pProps local (\env -> env{ envInList = True - , envParaProps = pProps{ pPropLevel = lvl + 1 - , pPropBullet = Just (AutoNumbering listAttr) + , envParaProps = pProps{ pPropBullet = Just (AutoNumbering listAttr) , pPropMarginLeft = Nothing , pPropIndent = Nothing , pPropIncremental = incremental }}) $ - concatMapM multiParBullet blksLst + concatMapM multiParList blksLst blockToParagraphs (DefinitionList entries) = do incremental <- listShouldBeIncremental let go :: ([Inline], [[Block]]) -> Pres [Paragraph] @@ -545,14 +541,21 @@ blockToParagraphs blk = do addLogMessage $ BlockNotRendered blk return [] --- Make sure the bullet env gets turned off after the first para. -multiParBullet :: [Block] -> Pres [Paragraph] -multiParBullet [] = return [] -multiParBullet (b:bs) = do +-- | Make sure the bullet env gets turned off after the first paragraph, and +-- indent any continuation paragraphs. +multiParList :: [Block] -> Pres [Paragraph] +multiParList [] = return [] +multiParList (b:bs) = do pProps <- asks envParaProps p <- blockToParagraphs b - ps <- local (\env -> env{envParaProps = pProps{pPropBullet = Nothing}}) $ - concatMapM blockToParagraphs bs + let level = pPropLevel pProps + ps <- local (\env -> env + { envParaProps = pProps + { pPropBullet = Nothing + , pPropLevel = level + 1 + } + }) + $ concatMapM blockToParagraphs bs return $ p ++ ps cellToParagraphs :: Alignment -> SimpleCell -> Pres [Paragraph] diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs index 84bdd7476..f3663efbb 100644 --- a/test/Tests/Writers/Powerpoint.hs +++ b/test/Tests/Writers/Powerpoint.hs @@ -66,6 +66,10 @@ tests = let 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" diff --git a/test/pptx/code-custom/output.pptx b/test/pptx/code-custom/output.pptx index ded8f1125..6c7a1a9ab 100644 Binary files a/test/pptx/code-custom/output.pptx and b/test/pptx/code-custom/output.pptx differ diff --git a/test/pptx/code-custom/templated.pptx b/test/pptx/code-custom/templated.pptx index 8bb0df1ff..116865c1f 100644 Binary files a/test/pptx/code-custom/templated.pptx and b/test/pptx/code-custom/templated.pptx differ diff --git a/test/pptx/code/output.pptx b/test/pptx/code/output.pptx index e700bc268..8fd00ff74 100644 Binary files a/test/pptx/code/output.pptx and b/test/pptx/code/output.pptx differ diff --git a/test/pptx/code/templated.pptx b/test/pptx/code/templated.pptx index 44f34cd64..0d7db048f 100644 Binary files a/test/pptx/code/templated.pptx and b/test/pptx/code/templated.pptx differ diff --git a/test/pptx/incremental-lists/with-flag/output.pptx b/test/pptx/incremental-lists/with-flag/output.pptx index 1ca1dbf17..82f5f926f 100644 Binary files a/test/pptx/incremental-lists/with-flag/output.pptx and b/test/pptx/incremental-lists/with-flag/output.pptx differ diff --git a/test/pptx/incremental-lists/with-flag/templated.pptx b/test/pptx/incremental-lists/with-flag/templated.pptx index 4ddf6bb75..e8482b25f 100644 Binary files a/test/pptx/incremental-lists/with-flag/templated.pptx and b/test/pptx/incremental-lists/with-flag/templated.pptx differ diff --git a/test/pptx/incremental-lists/without-flag/output.pptx b/test/pptx/incremental-lists/without-flag/output.pptx index 6f7261ba3..62e66e1fe 100644 Binary files a/test/pptx/incremental-lists/without-flag/output.pptx and b/test/pptx/incremental-lists/without-flag/output.pptx differ diff --git a/test/pptx/incremental-lists/without-flag/templated.pptx b/test/pptx/incremental-lists/without-flag/templated.pptx index ca5c9fdab..ac7be9564 100644 Binary files a/test/pptx/incremental-lists/without-flag/templated.pptx and b/test/pptx/incremental-lists/without-flag/templated.pptx differ diff --git a/test/pptx/list-level/input.native b/test/pptx/list-level/input.native new file mode 100644 index 000000000..e0b36b8e5 --- /dev/null +++ b/test/pptx/list-level/input.native @@ -0,0 +1,20 @@ +[Header 1 ("slide",[],[]) [Str "Slide"] +,BulletList + [[Para [Str "Top-level"] + ,Para [Str "With",Space,Str "continuation",Space,Str "paragraph"]] + ,[Para [Str "Then:"] + ,BulletList + [[Plain [Str "nested"]] + ,[Plain [Str "list"]] + ,[Plain [Str "items"]]]]] +,Header 1 ("slide-1",[],[]) [Str "Slide"] +,Para [Str "Paragraph."] +,OrderedList (1,Decimal,Period) + [[Para [Str "Top-level"] + ,Para [Str "Continuation"] + ,OrderedList (1,Decimal,Period) + [[Para [Str "Sub-list"] + ,Para [Str "With",Space,Str "Continuation"]] + ,[Para [Str "(still",Space,Str "sub-list)"]]]] + ,[Para [Str "(back",Space,Str "to",Space,Str "top-level)"]]] +,Para [Str "Paragraph."]] diff --git a/test/pptx/list-level/output.pptx b/test/pptx/list-level/output.pptx new file mode 100644 index 000000000..5e3506958 Binary files /dev/null and b/test/pptx/list-level/output.pptx differ diff --git a/test/pptx/list-level/templated.pptx b/test/pptx/list-level/templated.pptx new file mode 100644 index 000000000..8853a3082 Binary files /dev/null and b/test/pptx/list-level/templated.pptx differ diff --git a/test/pptx/lists/output.pptx b/test/pptx/lists/output.pptx index 94a424f42..e23f47218 100644 Binary files a/test/pptx/lists/output.pptx and b/test/pptx/lists/output.pptx differ diff --git a/test/pptx/lists/templated.pptx b/test/pptx/lists/templated.pptx index 52097489f..290b5b519 100644 Binary files a/test/pptx/lists/templated.pptx and b/test/pptx/lists/templated.pptx differ diff --git a/test/pptx/pauses/without-incremental/output.pptx b/test/pptx/pauses/without-incremental/output.pptx new file mode 100644 index 000000000..9085db330 Binary files /dev/null and b/test/pptx/pauses/without-incremental/output.pptx differ diff --git a/test/pptx/pauses/without-incremental/templated.pptx b/test/pptx/pauses/without-incremental/templated.pptx new file mode 100644 index 000000000..6662e2451 Binary files /dev/null and b/test/pptx/pauses/without-incremental/templated.pptx differ diff --git a/test/pptx/slide-breaks-toc/output.pptx b/test/pptx/slide-breaks-toc/output.pptx index 788cdf148..f2660ef93 100644 Binary files a/test/pptx/slide-breaks-toc/output.pptx and b/test/pptx/slide-breaks-toc/output.pptx differ diff --git a/test/pptx/slide-breaks-toc/templated.pptx b/test/pptx/slide-breaks-toc/templated.pptx index d11744079..0a2bdb857 100644 Binary files a/test/pptx/slide-breaks-toc/templated.pptx and b/test/pptx/slide-breaks-toc/templated.pptx differ diff --git a/test/pptx/speaker-notes-afterseps/output.pptx b/test/pptx/speaker-notes-afterseps/output.pptx index 99110d3ca..b54ba4465 100644 Binary files a/test/pptx/speaker-notes-afterseps/output.pptx and b/test/pptx/speaker-notes-afterseps/output.pptx differ diff --git a/test/pptx/speaker-notes-afterseps/templated.pptx b/test/pptx/speaker-notes-afterseps/templated.pptx index daf8e2175..3b272ab1b 100644 Binary files a/test/pptx/speaker-notes-afterseps/templated.pptx and b/test/pptx/speaker-notes-afterseps/templated.pptx differ diff --git a/test/pptx/start-numbering-at/output.pptx b/test/pptx/start-numbering-at/output.pptx index bc74ec599..ecfc6901a 100644 Binary files a/test/pptx/start-numbering-at/output.pptx and b/test/pptx/start-numbering-at/output.pptx differ diff --git a/test/pptx/start-numbering-at/templated.pptx b/test/pptx/start-numbering-at/templated.pptx index 4f191a06e..f3f46ef30 100644 Binary files a/test/pptx/start-numbering-at/templated.pptx and b/test/pptx/start-numbering-at/templated.pptx differ -- cgit v1.2.3 From 96a01451efd487d0f6a91a2785fd28be001a92bf Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Fri, 12 Nov 2021 13:07:25 +0100 Subject: JATS writer: ensure figures are wrapped with `

      ` in list items. This prevents the generation of invalid output. --- src/Text/Pandoc/Writers/JATS.hs | 1 + test/Tests/Writers/JATS.hs | 48 ++++++++++++++++++++++++++++------------- 2 files changed, 34 insertions(+), 15 deletions(-) (limited to 'test/Tests/Writers') diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs index d58da8bd2..799fe29fa 100644 --- a/src/Text/Pandoc/Writers/JATS.hs +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -551,6 +551,7 @@ inlineToJATS _ (Image (ident,_,kvs) _ (src, tit)) = do return $ selfClosingTag "inline-graphic" attr isParaOrList :: Block -> Bool +isParaOrList SimpleFigure{} = False -- implicit figures are not paragraphs isParaOrList Para{} = True isParaOrList Plain{} = True isParaOrList BulletList{} = True 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 = , "

      " ]) ] - , "bullet list" =: bulletList [ plain $ text "first" - , plain $ text "second" - , plain $ text "third" - ] - =?> "\n\ - \ \n\ - \

      first

      \n\ - \
      \n\ - \ \n\ - \

      second

      \n\ - \
      \n\ - \ \n\ - \

      third

      \n\ - \
      \n\ - \
      " + , testGroup "bullet list" + [ "plain items" =: bulletList [ plain $ text "first" + , plain $ text "second" + , plain $ text "third" + ] + =?> "\n\ + \ \n\ + \

      first

      \n\ + \
      \n\ + \ \n\ + \

      second

      \n\ + \
      \n\ + \ \n\ + \

      third

      \n\ + \
      \n\ + \
      " + + , "item with implicit figure" =: + bulletList [ simpleFigure (text "caption") "a.png" "" ] =?> + T.unlines + [ "" + , " " + , "

      " + , " " + , "

      caption

      " + , " + " xlink:href=\"a.png\" xlink:title=\"\" />" + , " " + , "

      " + , "
      " + , "
      " + ] + ] , testGroup "definition lists" [ "with internal link" =: definitionList [(link "#go" "" (str "testing"), [plain (text "hi there")])] =?> -- cgit v1.2.3 From a64ea1864743ed8d96acec04f2895dc638bc1df7 Mon Sep 17 00:00:00 2001 From: Albert Krewinkel Date: Fri, 10 Dec 2021 18:10:36 +0100 Subject: Powerpoint tests: shorten lines by grouping tests This makes the test output more pleasant to read in narrow terminal windows. --- test/Tests/Writers/Powerpoint.hs | 375 +++++++++++++++++++-------------------- 1 file changed, 186 insertions(+), 189 deletions(-) (limited to 'test/Tests/Writers') diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs index f3663efbb..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 @@ -42,198 +43,194 @@ 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 = 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" - , pptxTests ("Using slide level 0, if the first thing on " - <> "a slide is 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 ("Using slide level 0, if the first thing on " - <> "a slide is 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" - , pptxTests ("Using slide level 0, if the first thing on " - <> "a slide is a heading it's used as the " - <> "slide title (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 ("Using slide level 0, if the first thing on " - <> "a slide is a heading it's used as the " - <> "slide title (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" - , pptxTests ("comparison layout used when two columns " - <> "contain text plus non-text") - def - "pptx/comparison/both-columns/input.native" - "pptx/comparison/both-columns/output.pptx" - , pptxTests ("comparison layout used even when only one " - <> "column contains text plus non-text") - def - "pptx/comparison/one-column/input.native" - "pptx/comparison/one-column/output.pptx" - , pptxTests ("extra text in one column in comparison " - <> "layout gets overlaid") - def - "pptx/comparison/extra-text/input.native" - "pptx/comparison/extra-text/output.pptx" - , pptxTests ("extra image in one column in comparison " - <> "layout gets overlaid") - def - "pptx/comparison/extra-image/input.native" - "pptx/comparison/extra-image/output.pptx" - , pptxTests "comparison not used if the non-text comes first" - def - "pptx/comparison/non-text-first/input.native" - "pptx/comparison/non-text-first/output.pptx" - , pptxTests ("Heading, text and an image on the same " - <> "slide uses the Content with Caption " - <> "layout") - def - "pptx/content-with-caption/heading-text-image/input.native" - "pptx/content-with-caption/heading-text-image/output.pptx" - , pptxTests ("Text and an image on the same " - <> "slide uses the Content with Caption " - <> "layout") - def - "pptx/content-with-caption/text-image/input.native" - "pptx/content-with-caption/text-image/output.pptx" - , pptxTests ("If the image comes first, Content with " - <> "Caption is not used") - def - "pptx/content-with-caption/image-text/input.native" - "pptx/content-with-caption/image-text/output.pptx" - , pptxTests ("If a slide contains only speaker notes, the " - <> "Blank layout is used") - def - "pptx/blanks/just-speaker-notes/input.native" - "pptx/blanks/just-speaker-notes/output.pptx" - , pptxTests ("If a slide contains only an empty heading " - <> "with a body of only non-breaking spaces" - <> ", the Blank layout is used") - def - "pptx/blanks/nbsp-in-body/input.native" - "pptx/blanks/nbsp-in-body/output.pptx" - , pptxTests ("If a slide contains only a heading " - <> "containing only non-breaking spaces, " - <> "the Blank layout is used") - 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" - ] + 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 -- cgit v1.2.3 From 0610f16f7f684b320325b6c0b501725138d10a52 Mon Sep 17 00:00:00 2001 From: binaarinen <53334195+binaarinen@users.noreply.github.com> Date: Sun, 19 Dec 2021 21:10:41 +0100 Subject: Add a writer for Markua 0.10 (#7729) Markua is a markdown variant used by Leanpub. More information about Markua can be found at https://leanpub.com/markua/read. Adds a new exported function `writeMarkua` from T.P.Writers.Markdown. [API change] Closes #1871. Co-authored by Tim Wisotzki and Samuel Lemmenmeier. --- MANUAL.txt | 2 + data/templates/default.markua | 21 + pandoc.cabal | 2 + src/Text/Pandoc/App/FormatHeuristics.hs | 1 + src/Text/Pandoc/Extensions.hs | 2 + src/Text/Pandoc/Shared.hs | 5 + src/Text/Pandoc/Writers.hs | 2 + src/Text/Pandoc/Writers/Markdown.hs | 102 ++++- src/Text/Pandoc/Writers/Markdown/Inline.hs | 172 +++++-- src/Text/Pandoc/Writers/Markdown/Types.hs | 3 +- test/Tests/Old.hs | 1 + test/Tests/Writers/Markua.hs | 40 ++ test/tables.markua | 58 +++ test/test-pandoc.hs | 2 + test/writer.markua | 700 +++++++++++++++++++++++++++++ 15 files changed, 1043 insertions(+), 70 deletions(-) create mode 100644 data/templates/default.markua create mode 100644 test/Tests/Writers/Markua.hs create mode 100644 test/tables.markua create mode 100644 test/writer.markua (limited to 'test/Tests/Writers') diff --git a/MANUAL.txt b/MANUAL.txt index fe551bbce..2e6d53ca6 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -316,6 +316,7 @@ header when requesting a document from a URL: - `markdown_mmd` ([MultiMarkdown]) - `markdown_phpextra` ([PHP Markdown Extra]) - `markdown_strict` (original unextended [Markdown]) + - `markua` ([Markua]) - `mediawiki` ([MediaWiki markup]) - `ms` ([roff ms]) - `muse` ([Muse]), @@ -502,6 +503,7 @@ header when requesting a document from a URL: [CSL JSON]: https://citeproc-js.readthedocs.io/en/latest/csl-json/markup.html [BibTeX]: https://ctan.org/pkg/bibtex [BibLaTeX]: https://ctan.org/pkg/biblatex +[Markua]: https://leanpub.com/markua/read ## Reader options {.options} diff --git a/data/templates/default.markua b/data/templates/default.markua new file mode 100644 index 000000000..9f6ca96de --- /dev/null +++ b/data/templates/default.markua @@ -0,0 +1,21 @@ +$if(titleblock)$ +$titleblock$ + +$endif$ +$for(header-includes)$ +$header-includes$ + +$endfor$ +$for(include-before)$ +$include-before$ + +$endfor$ +$if(toc)$ +$table-of-contents$ + +$endif$ +$body$ +$for(include-after)$ + +$include-after$ +$endfor$ diff --git a/pandoc.cabal b/pandoc.cabal index b09b19144..3cad5bce7 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -90,6 +90,7 @@ data-files: data/templates/default.epub3 data/templates/article.jats_publishing data/templates/affiliations.jats + data/templates/default.markua -- translations data/translations/*.yaml -- source files for reference.docx @@ -825,6 +826,7 @@ test-suite test-pandoc Tests.Writers.Docx Tests.Writers.RST Tests.Writers.TEI + Tests.Writers.Markua Tests.Writers.Muse Tests.Writers.FB2 Tests.Writers.Powerpoint diff --git a/src/Text/Pandoc/App/FormatHeuristics.hs b/src/Text/Pandoc/App/FormatHeuristics.hs index a2acfc6d6..e5fe7ad81 100644 --- a/src/Text/Pandoc/App/FormatHeuristics.hs +++ b/src/Text/Pandoc/App/FormatHeuristics.hs @@ -54,6 +54,7 @@ formatFromFilePath x = ".lhs" -> Just "markdown+lhs" ".ltx" -> Just "latex" ".markdown" -> Just "markdown" + ".markua" -> Just "markua" ".mkdn" -> Just "markdown" ".mkd" -> Just "markdown" ".mdwn" -> Just "markdown" diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs index ce6a95458..33f615740 100644 --- a/src/Text/Pandoc/Extensions.hs +++ b/src/Text/Pandoc/Extensions.hs @@ -432,6 +432,8 @@ getDefaultExtensions "jats_archiving" = getDefaultExtensions "jats" getDefaultExtensions "jats_publishing" = getDefaultExtensions "jats" getDefaultExtensions "jats_articleauthoring" = getDefaultExtensions "jats" getDefaultExtensions "opml" = pandocExtensions -- affects notes +getDefaultExtensions "markua" = extensionsFromList + [] getDefaultExtensions _ = extensionsFromList [Ext_auto_identifiers] diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index eb0b4acbf..50abe6937 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -25,6 +25,7 @@ module Text.Pandoc.Shared ( ordNub, findM, -- * Text processing + inquotes, tshow, elemText, notElemText, @@ -186,6 +187,10 @@ findM p = foldr go (pure Nothing) -- Text processing -- +-- | Wrap double quotes around a Text +inquotes :: T.Text -> T.Text +inquotes txt = T.cons '\"' (T.snoc txt '\"') + tshow :: Show a => a -> T.Text tshow = T.pack . show diff --git a/src/Text/Pandoc/Writers.hs b/src/Text/Pandoc/Writers.hs index c348477c2..960b9074c 100644 --- a/src/Text/Pandoc/Writers.hs +++ b/src/Text/Pandoc/Writers.hs @@ -51,6 +51,7 @@ module Text.Pandoc.Writers , writeLaTeX , writeMan , writeMarkdown + , writeMarkua , writeMediaWiki , writeMs , writeMuse @@ -190,6 +191,7 @@ writers = [ ,("csljson" , TextWriter writeCslJson) ,("bibtex" , TextWriter writeBibTeX) ,("biblatex" , TextWriter writeBibLaTeX) + ,("markua" , TextWriter writeMarkua) ] -- | Retrieve writer, extensions based on formatSpec (format+extensions). diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 022dbc24f..bb68d9fee 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -18,6 +18,7 @@ Markdown: module Text.Pandoc.Writers.Markdown ( writeMarkdown, writeCommonMark, + writeMarkua, writePlain) where import Control.Monad.Reader import Control.Monad.State.Strict @@ -42,7 +43,10 @@ import Text.Pandoc.Templates (renderTemplate) import Text.DocTemplates (Val(..), Context(..), FromContext(..)) import Text.Pandoc.Walk import Text.Pandoc.Writers.HTML (writeHtml5String) -import Text.Pandoc.Writers.Markdown.Inline (inlineListToMarkdown, linkAttributes, attrsToMarkdown) +import Text.Pandoc.Writers.Markdown.Inline (inlineListToMarkdown, + linkAttributes, + attrsToMarkdown, + attrsToMarkua) import Text.Pandoc.Writers.Markdown.Types (MarkdownVariant(..), WriterState(..), WriterEnv(..), @@ -77,6 +81,26 @@ writeCommonMark opts document = enableExtension Ext_intraword_underscores $ writerExtensions opts } +-- | Convert Pandoc to Markua. +writeMarkua :: PandocMonad m => WriterOptions -> Pandoc -> m Text +writeMarkua opts document = + evalMD (pandocToMarkdown opts' document) def{ envVariant = Markua } def + where + opts' = opts{ writerExtensions = + enableExtension Ext_hard_line_breaks $ + enableExtension Ext_pipe_tables $ + -- required for fancy list enumerators + enableExtension Ext_fancy_lists $ + enableExtension Ext_startnum $ + enableExtension Ext_strikeout $ + enableExtension Ext_subscript $ + enableExtension Ext_superscript $ + enableExtension Ext_definition_lists $ + enableExtension Ext_smart $ + enableExtension Ext_footnotes + mempty } + + pandocTitleBlock :: Doc Text -> [Doc Text] -> Doc Text -> Doc Text pandocTitleBlock tit auths dat = hang 2 (text "% ") tit <> cr <> @@ -327,8 +351,15 @@ blockToMarkdown' opts (Div attrs ils) = do contents <- blockListToMarkdown opts ils variant <- asks envVariant return $ - case () of - _ | isEnabled Ext_fenced_divs opts && + case () of + _ | variant == Markua -> + case () of + () | "blurb" `elem` classes' -> prefixed "B> " contents <> blankline + | "aside" `elem` classes' -> prefixed "A> " contents <> blankline + -- | necessary to enable option to create a bibliography + | (take 3 (T.unpack id')) == "ref" -> contents <> blankline + | otherwise -> contents <> blankline + | isEnabled Ext_fenced_divs opts && attrs /= nullAttr -> let attrsToMd = if variant == Commonmark then attrsToMarkdown @@ -408,6 +439,7 @@ blockToMarkdown' opts b@(RawBlock f str) = do | f `elem` ["markdown", "markdown_github", "markdown_phpextra", "markdown_mmd", "markdown_strict"] -> return $ literal str <> literal "\n" + Markua -> renderEmpty _ | isEnabled Ext_raw_attribute opts -> rawAttribBlock | f `elem` ["html", "html5", "html4"] , isEnabled Ext_markdown_attribute opts @@ -419,17 +451,19 @@ blockToMarkdown' opts b@(RawBlock f str) = do , isEnabled Ext_raw_tex opts -> return $ literal str <> literal "\n" _ -> renderEmpty -blockToMarkdown' opts HorizontalRule = - return $ blankline <> literal (T.replicate (writerColumns opts) "-") <> blankline +blockToMarkdown' opts HorizontalRule = do + variant <- asks envVariant + let indicator = case variant of + Markua -> "* * *" + _ -> T.replicate (writerColumns opts) "-" + return $ blankline <> literal indicator <> blankline blockToMarkdown' opts (Header level attr inlines) = do - -- first, if we're putting references at the end of a section, we -- put them here. blkLevel <- asks envBlockLevel refs <- if writerReferenceLocation opts == EndOfSection && blkLevel == 1 then notesAndRefs opts else return empty - variant <- asks envVariant -- we calculate the id that would be used by auto_identifiers -- so we know whether to print an explicit identifier @@ -442,7 +476,8 @@ blockToMarkdown' opts (Header level attr inlines) = do && id' == autoId -> empty (id',_,_) | isEnabled Ext_mmd_header_identifiers opts -> space <> brackets (literal id') - _ | isEnabled Ext_header_attributes opts || + _ | variant == Markua -> attrsToMarkua attr + | isEnabled Ext_header_attributes opts || isEnabled Ext_attributes opts -> space <> attrsToMarkdown attr | otherwise -> empty @@ -476,6 +511,8 @@ blockToMarkdown' opts (Header level attr inlines) = do -- ghc interprets '#' characters in column 1 as linenum specifiers. _ | variant == PlainText || isEnabled Ext_literate_haskell opts -> contents <> blankline + _ | variant == Markua -> attr' <> cr <> literal (T.replicate level "#") + <> space <> contents <> blankline _ -> literal (T.replicate level "#") <> space <> contents <> attr' <> blankline return $ refs <> hdr @@ -492,9 +529,11 @@ blockToMarkdown' opts (CodeBlock attribs str) = do backticks <> attrs <> cr <> literal str <> cr <> backticks <> blankline | isEnabled Ext_fenced_code_blocks opts -> tildes <> attrs <> cr <> literal str <> cr <> tildes <> blankline - _ -> nest (writerTabStop opts) (literal str) <> blankline + _ | variant == Markua -> blankline <> attrsToMarkua attribs <> cr <> backticks <> cr <> + literal str <> cr <> backticks <> cr <> blankline + | otherwise -> nest (writerTabStop opts) (literal str) <> blankline where - endlineLen c = maybe 3 ((+1) . maximum) $ nonEmpty $ + endlineLen c = maybe 3 ((+1) . maximum) $ nonEmpty [T.length ln | ln <- map trim (T.lines str) , T.pack [c,c,c] `T.isPrefixOf` ln @@ -581,24 +620,29 @@ blockToMarkdown' opts t@(Table _ blkCapt specs thead tbody tfoot) = do return $ nst (tbl $$ caption'') $$ blankline blockToMarkdown' opts (BulletList items) = do contents <- inList $ mapM (bulletListItemToMarkdown opts) items - return $ (if isTightList items then vcat else vsep) contents <> blankline + return $ (if isTightList items then vcat else vsep) + contents <> blankline blockToMarkdown' opts (OrderedList (start,sty,delim) items) = do variant <- asks envVariant let start' = if variant == Commonmark || isEnabled Ext_startnum opts then start else 1 let sty' = if isEnabled Ext_fancy_lists opts then sty else DefaultStyle - let delim' = if isEnabled Ext_fancy_lists opts - then delim - else if variant == Commonmark && - (delim == OneParen || delim == TwoParens) - then OneParen -- commonmark only supports one paren - else DefaultDelim + let delim' | isEnabled Ext_fancy_lists opts = + case variant of + -- Markua supports 'fancy' enumerators, but no TwoParens + Markua -> if delim == TwoParens then OneParen else delim + _ -> delim + | variant == Commonmark && --commonmark only supports one paren + (delim == OneParen || delim == TwoParens) = OneParen + | otherwise = DefaultDelim let attribs = (start', sty', delim') let markers = orderedListMarkers attribs - let markers' = map (\m -> if T.length m < 3 - then m <> T.replicate (3 - T.length m) " " - else m) markers + let markers' = case variant of + Markua -> markers + _ -> map (\m -> if T.length m < 3 + then m <> T.replicate (3 - T.length m) " " + else m) markers contents <- inList $ zipWithM (orderedListItemToMarkdown opts) markers' items return $ (if isTightList items then vcat else vsep) contents <> blankline @@ -712,10 +756,13 @@ itemEndsWithTightList bs = -- | Convert bullet list item (list of blocks) to markdown. bulletListItemToMarkdown :: PandocMonad m => WriterOptions -> [Block] -> MD m (Doc Text) bulletListItemToMarkdown opts bs = do + variant <- asks envVariant let exts = writerExtensions opts contents <- blockListToMarkdown opts $ taskListItemToAscii exts bs let sps = T.replicate (writerTabStop opts - 2) " " - let start = literal $ "- " <> sps + let start = case variant of + Markua -> literal "* " + _ -> literal $ "- " <> sps -- remove trailing blank line if item ends with a tight list let contents' = if itemEndsWithTightList bs then chomp contents <> cr @@ -725,19 +772,22 @@ bulletListItemToMarkdown opts bs = do -- | Convert ordered list item (a list of blocks) to markdown. orderedListItemToMarkdown :: PandocMonad m => WriterOptions -- ^ options - -> Text -- ^ list item marker + -> Text -- ^ list item marker -> [Block] -- ^ list item (list of blocks) -> MD m (Doc Text) orderedListItemToMarkdown opts marker bs = do let exts = writerExtensions opts contents <- blockListToMarkdown opts $ taskListItemToAscii exts bs + variant <- asks envVariant let sps = case writerTabStop opts - T.length marker of n | n > 0 -> literal $ T.replicate n " " _ -> literal " " let ind = if isEnabled Ext_four_space_rule opts then writerTabStop opts else max (writerTabStop opts) (T.length marker + 1) - let start = literal marker <> sps + let start = case variant of + Markua -> literal marker <> " " + _ -> literal marker <> sps -- remove trailing blank line if item ends with a tight list let contents' = if itemEndsWithTightList bs then chomp contents <> cr @@ -756,7 +806,10 @@ definitionListItemToMarkdown opts (label, defs) = do then do let tabStop = writerTabStop opts variant <- asks envVariant - let leader = if variant == PlainText then " " else ": " + let leader = case variant of + PlainText -> " " + Markua -> ":" + _ -> ": " let sps = case writerTabStop opts - 3 of n | n > 0 -> literal $ T.replicate n " " _ -> literal " " @@ -827,6 +880,7 @@ blockListToMarkdown opts blocks = do isListBlock _ = False commentSep | variant == PlainText = Null + | variant == Markua = Null | isEnabled Ext_raw_html opts = RawBlock "html" "\n" | otherwise = RawBlock "markdown" " \n" mconcat <$> mapM (blockToMarkdown opts) (fixBlocks blocks) diff --git a/src/Text/Pandoc/Writers/Markdown/Inline.hs b/src/Text/Pandoc/Writers/Markdown/Inline.hs index d299d31b2..0bf70e80e 100644 --- a/src/Text/Pandoc/Writers/Markdown/Inline.hs +++ b/src/Text/Pandoc/Writers/Markdown/Inline.hs @@ -13,7 +13,8 @@ module Text.Pandoc.Writers.Markdown.Inline ( inlineListToMarkdown, linkAttributes, - attrsToMarkdown + attrsToMarkdown, + attrsToMarkua ) where import Control.Monad.Reader import Control.Monad.State.Strict @@ -95,6 +96,11 @@ escapeText opts = T.pack . go' . T.unpack , isAlphaNum x -> c : '_' : x : go xs _ -> c : go cs +-- Escape the escape character, as well as formatting pairs +escapeMarkuaString :: Text -> Text +escapeMarkuaString s = foldr (uncurry T.replace) s [("--","~-~-"), + ("**","~*~*"),("//","~/~/"),("^^","~^~^"),(",,","~,~,")] + attrsToMarkdown :: Attr -> Doc Text attrsToMarkdown attribs = braces $ hsep [attribId, attribClasses, attribKeys] where attribId = case attribs of @@ -116,9 +122,56 @@ attrsToMarkdown attribs = braces $ hsep [attribId, attribClasses, attribKeys] escAttrChar '\\' = literal "\\\\" escAttrChar c = literal $ T.singleton c +attrsToMarkua:: Attr -> Doc Text +attrsToMarkua attributes + | null list = empty + | otherwise = braces $ intercalateDocText list + where attrId = case attributes of + ("",_,_) -> [] + (i,_,_) -> [literal $ "id: " <> i] + -- all non explicit (key,value) attributes besides id are getting + -- a default class key to be Markua conform + attrClasses = case attributes of + (_,[],_) -> [] + (_,classes,_) -> map (escAttr . ("class: " <>)) + classes + attrKeyValues = case attributes of + (_,_,[]) -> [] + (_,_,keyvalues) -> map ((\(k,v) -> escAttr k + <> ": " <> escAttr v) . + preprocessKeyValues) keyvalues + escAttr = mconcat . map escAttrChar . T.unpack + escAttrChar '"' = literal "\"" + escAttrChar c = literal $ T.singleton c + + list = concat [attrId, attrClasses, attrKeyValues] + + -- if attribute key is alt, caption, title then content + -- gets wrapped inside quotes + -- attribute gets removed + preprocessKeyValues :: (Text, Text) -> (Text, Text) + preprocessKeyValues (key,value) + | key == "alt" || + key == "caption" || + key == "title" = (key, inquotes value) + | otherwise = (key,value) + intercalateDocText :: [Doc Text] -> Doc Text + intercalateDocText [] = empty + intercalateDocText [x] = x + intercalateDocText (x:xs) = x <> ", " <> (intercalateDocText xs) + +-- | Add a (key, value) pair to Pandoc attr type +addKeyValueToAttr :: Attr -> (Text,Text) -> Attr +addKeyValueToAttr (ident,classes,kvs) (key,value) + | not (T.null key) && not (T.null value) = (ident, + classes, + (key,value): kvs) + | otherwise = (ident,classes,kvs) + linkAttributes :: WriterOptions -> Attr -> Doc Text linkAttributes opts attr = - if (isEnabled Ext_link_attributes opts || isEnabled Ext_attributes opts) && attr /= nullAttr + if (isEnabled Ext_link_attributes opts || + isEnabled Ext_attributes opts) && attr /= nullAttr then attrsToMarkdown attr else empty @@ -283,6 +336,7 @@ inlineToMarkdown opts (Span attrs ils) = do _ -> id $ case variant of PlainText -> contents + Markua -> "`" <> contents <> "`" <> attrsToMarkua attrs _ | attrs == nullAttr -> contents | isEnabled Ext_bracketed_spans opts -> let attrs' = if attrs /= nullAttr @@ -396,60 +450,75 @@ inlineToMarkdown opts (Quoted DoubleQuote lst) = do then "“" <> contents <> "”" else "“" <> contents <> "”" inlineToMarkdown opts (Code attr str) = do + variant <- asks envVariant let tickGroups = filter (T.any (== '`')) $ T.group str let longest = maybe 0 maximum $ nonEmpty $ map T.length tickGroups let marker = T.replicate (longest + 1) "`" let spacer = if longest == 0 then "" else " " let attrsEnabled = isEnabled Ext_inline_code_attributes opts || isEnabled Ext_attributes opts - let attrs = if attrsEnabled && attr /= nullAttr - then attrsToMarkdown attr - else empty - variant <- asks envVariant + let attrs = case variant of + Markua -> attrsToMarkua attr + _ -> if attrsEnabled && attr /= nullAttr + then attrsToMarkdown attr + else empty case variant of PlainText -> return $ literal str _ -> return $ literal (marker <> spacer <> str <> spacer <> marker) <> attrs inlineToMarkdown opts (Str str) = do variant <- asks envVariant - let str' = (if writerPreferAscii opts - then toHtml5Entities - else id) . - (if isEnabled Ext_smart opts - then unsmartify opts - else id) . - (if variant == PlainText - then id - else escapeText opts) $ str + let str' = case variant of + Markua -> escapeMarkuaString str + _ -> (if writerPreferAscii opts + then toHtml5Entities + else id) . + (if isEnabled Ext_smart opts + then unsmartify opts + else id) . + (if variant == PlainText + then id + else escapeText opts) $ str return $ literal str' -inlineToMarkdown opts (Math InlineMath str) = - case writerHTMLMathMethod opts of - WebTeX url -> inlineToMarkdown opts - (Image nullAttr [Str str] (url <> urlEncode str, str)) - _ | isEnabled Ext_tex_math_dollars opts -> - return $ "$" <> literal str <> "$" - | isEnabled Ext_tex_math_single_backslash opts -> - return $ "\\(" <> literal str <> "\\)" - | isEnabled Ext_tex_math_double_backslash opts -> - return $ "\\\\(" <> literal str <> "\\\\)" - | otherwise -> do - variant <- asks envVariant - texMathToInlines InlineMath str >>= - inlineListToMarkdown opts . - (if variant == PlainText then makeMathPlainer else id) -inlineToMarkdown opts (Math DisplayMath str) = - case writerHTMLMathMethod opts of - WebTeX url -> (\x -> blankline <> x <> blankline) `fmap` - inlineToMarkdown opts (Image nullAttr [Str str] - (url <> urlEncode str, str)) - _ | isEnabled Ext_tex_math_dollars opts -> - return $ "$$" <> literal str <> "$$" - | isEnabled Ext_tex_math_single_backslash opts -> - return $ "\\[" <> literal str <> "\\]" - | isEnabled Ext_tex_math_double_backslash opts -> - return $ "\\\\[" <> literal str <> "\\\\]" - | otherwise -> (\x -> cr <> x <> cr) `fmap` - (texMathToInlines DisplayMath str >>= inlineListToMarkdown opts) +inlineToMarkdown opts (Math InlineMath str) = do + variant <- asks envVariant + case () of + _ | variant == Markua -> return $ "`" <> literal str <> "`" <> "$" + | otherwise -> case writerHTMLMathMethod opts of + WebTeX url -> inlineToMarkdown opts + (Image nullAttr [Str str] (url <> urlEncode str, str)) + _ | isEnabled Ext_tex_math_dollars opts -> + return $ "$" <> literal str <> "$" + | isEnabled Ext_tex_math_single_backslash opts -> + return $ "\\(" <> literal str <> "\\)" + | isEnabled Ext_tex_math_double_backslash opts -> + return $ "\\\\(" <> literal str <> "\\\\)" + | otherwise -> + texMathToInlines InlineMath str >>= + inlineListToMarkdown opts . + (if variant == PlainText then makeMathPlainer else id) + +inlineToMarkdown opts (Math DisplayMath str) = do + variant <- asks envVariant + case () of + _ | variant == Markua -> do + let attributes = attrsToMarkua (addKeyValueToAttr ("",[],[]) + ("format", "latex")) + return $ blankline <> attributes <> cr <> literal "```" <> cr + <> literal str <> cr <> literal "```" <> blankline + | otherwise -> case writerHTMLMathMethod opts of + WebTeX url -> (\x -> blankline <> x <> blankline) `fmap` + inlineToMarkdown opts (Image nullAttr [Str str] + (url <> urlEncode str, str)) + _ | isEnabled Ext_tex_math_dollars opts -> + return $ "$$" <> literal str <> "$$" + | isEnabled Ext_tex_math_single_backslash opts -> + return $ "\\[" <> literal str <> "\\]" + | isEnabled Ext_tex_math_double_backslash opts -> + return $ "\\\\[" <> literal str <> "\\\\]" + | otherwise -> (\x -> cr <> x <> cr) `fmap` + (texMathToInlines DisplayMath str >>= inlineListToMarkdown opts) + inlineToMarkdown opts il@(RawInline f str) = do let tickGroups = filter (T.any (== '`')) $ T.group str let numticks = 1 + maybe 0 maximum (nonEmpty (map T.length tickGroups)) @@ -469,6 +538,7 @@ inlineToMarkdown opts il@(RawInline f str) = do | f `elem` ["markdown", "markdown_github", "markdown_phpextra", "markdown_mmd", "markdown_strict"] -> return $ literal str + Markua -> renderEmpty _ | isEnabled Ext_raw_attribute opts -> rawAttribInline | f `elem` ["html", "html5", "html4"] , isEnabled Ext_raw_html opts @@ -563,6 +633,11 @@ inlineToMarkdown opts lnk@(Link attr@(ident,classes,kvs) txt (src, tit)) = do PlainText | useAuto -> return $ literal srcSuffix | otherwise -> return linktext + Markua + | T.null tit -> return $ result <> attrsToMarkua attr + | otherwise -> return $ result <> attrsToMarkua attributes + where result = "[" <> linktext <> "](" <> (literal src) <> ")" + attributes = addKeyValueToAttr attr ("title", tit) _ | useAuto -> return $ "<" <> literal srcSuffix <> ">" | useRefLinks -> let first = "[" <> linktext <> "]" @@ -594,9 +669,16 @@ inlineToMarkdown opts img@(Image attr alternate (source, tit)) then [Str ""] else alternate linkPart <- inlineToMarkdown opts (Link attr txt (source, tit)) + alt <- inlineListToMarkdown opts alternate + let attributes | variant == Markua = attrsToMarkua $ + addKeyValueToAttr (addKeyValueToAttr attr ("title", tit)) + ("alt", render (Just (writerColumns opts)) alt) + | otherwise = empty return $ case variant of - PlainText -> "[" <> linkPart <> "]" - _ -> "!" <> linkPart + PlainText -> "[" <> linkPart <> "]" + Markua -> cr <> attributes <> cr <> literal "![](" <> + literal source <> ")" <> cr + _ -> "!" <> linkPart inlineToMarkdown opts (Note contents) = do modify (\st -> st{ stNotes = contents : stNotes st }) st <- get diff --git a/src/Text/Pandoc/Writers/Markdown/Types.hs b/src/Text/Pandoc/Writers/Markdown/Types.hs index a1d0d14e4..060446811 100644 --- a/src/Text/Pandoc/Writers/Markdown/Types.hs +++ b/src/Text/Pandoc/Writers/Markdown/Types.hs @@ -45,7 +45,8 @@ data WriterEnv = WriterEnv { envInList :: Bool } data MarkdownVariant = - PlainText + Markua + | PlainText | Commonmark | Markdown deriving (Show, Eq) diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs index e03d94e85..450449946 100644 --- a/test/Tests/Old.hs +++ b/test/Tests/Old.hs @@ -228,6 +228,7 @@ tests pandocPath = , test' "reader" ["-f", "ipynb", "-t", "html"] "ipynb/rank.ipynb" "ipynb/rank.out.html" ] + , testGroup "markua" [ testGroup "writer" $ writerTests' "markua"] ] where test' = test pandocPath 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/tables.markua b/test/tables.markua new file mode 100644 index 000000000..b82264fd7 --- /dev/null +++ b/test/tables.markua @@ -0,0 +1,58 @@ +Simple table with caption: + +| Right | Left | Center | Default | +|------:|:-----|:------:|---------| +| 12 | 12 | 12 | 12 | +| 123 | 123 | 123 | 123 | +| 1 | 1 | 1 | 1 | + +Demonstration of simple table syntax. + +Simple table without caption: + +| Right | Left | Center | Default | +|------:|:-----|:------:|---------| +| 12 | 12 | 12 | 12 | +| 123 | 123 | 123 | 123 | +| 1 | 1 | 1 | 1 | + +Simple table indented two spaces: + +| Right | Left | Center | Default | +|------:|:-----|:------:|---------| +| 12 | 12 | 12 | 12 | +| 123 | 123 | 123 | 123 | +| 1 | 1 | 1 | 1 | + +Demonstration of simple table syntax. + +Multiline table with caption: + +| Centered Header | Left Aligned | Right Aligned | Default aligned | +|:---------------:|:-------------|--------------:|:------------------------------------------------------| +| First | row | 12.0 | Example of a row that spans multiple lines. | +| Second | row | 5.0 | Here’s another one. Note the blank line between rows. | + +Here’s the caption. It may span multiple lines. + +Multiline table without caption: + +| Centered Header | Left Aligned | Right Aligned | Default aligned | +|:---------------:|:-------------|--------------:|:------------------------------------------------------| +| First | row | 12.0 | Example of a row that spans multiple lines. | +| Second | row | 5.0 | Here’s another one. Note the blank line between rows. | + +Table without column headers: + +| | | | | +|----:|:----|:---:|----:| +| 12 | 12 | 12 | 12 | +| 123 | 123 | 123 | 123 | +| 1 | 1 | 1 | 1 | + +Multiline table without column headers: + +| | | | | +|:------:|:----|-----:|-------------------------------------------------------| +| First | row | 12.0 | Example of a row that spans multiple lines. | +| Second | row | 5.0 | Here’s another one. Note the blank line between rows. | diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs index 476762aac..fcb157fb7 100644 --- a/test/test-pandoc.hs +++ b/test/test-pandoc.hs @@ -50,6 +50,7 @@ import qualified Tests.Writers.Powerpoint import qualified Tests.Writers.RST import qualified Tests.Writers.AnnotatedTable import qualified Tests.Writers.TEI +import qualified Tests.Writers.Markua import Text.Pandoc.Shared (inDirectory) tests :: FilePath -> TestTree @@ -72,6 +73,7 @@ tests pandocPath = testGroup "pandoc tests" , testGroup "Docx" Tests.Writers.Docx.tests , testGroup "RST" Tests.Writers.RST.tests , testGroup "TEI" Tests.Writers.TEI.tests + , testGroup "markua" Tests.Writers.Markua.tests , testGroup "Muse" Tests.Writers.Muse.tests , testGroup "FB2" Tests.Writers.FB2.tests , testGroup "PowerPoint" Tests.Writers.Powerpoint.tests diff --git a/test/writer.markua b/test/writer.markua new file mode 100644 index 000000000..1c5b44cc2 --- /dev/null +++ b/test/writer.markua @@ -0,0 +1,700 @@ +This is a set of tests for pandoc. Most of them are adapted from John Gruber’s +markdown test suite. + +* * * + +{id: headers} +# Headers + +{id: level-2-with-an-embedded-link} +## Level 2 with an [embedded link](/url) + +{id: level-3-with-emphasis} +### Level 3 with *emphasis* + +{id: level-4} +#### Level 4 + +{id: level-5} +##### Level 5 + +{id: level-1} +# Level 1 + +{id: level-2-with-emphasis} +## Level 2 with *emphasis* + +{id: level-3} +### Level 3 + +with no blank line + +{id: level-2} +## Level 2 + +with no blank line + +* * * + +{id: paragraphs} +# Paragraphs + +Here’s a regular paragraph. + +In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. +Because a hard-wrapped line in the middle of a paragraph looked like a list +item. + +Here’s one with a bullet. * criminey. + +There should be a hard line break +here. + +* * * + +{id: block-quotes} +# Block Quotes + +E-mail style: + +> This is a block quote. It is pretty short. + +> Code in a block quote: +> +> ``` +> sub status { +> print "working"; +> } +> ``` +> +> A list: +> +> 1. item one +> 2. item two +> +> Nested block quotes: +> +> > nested +> +> > nested + +This should not be a block quote: 2 > 1. + +And a following paragraph. + +* * * + +{id: code-blocks} +# Code Blocks + +Code: + +``` +---- (should be four hyphens) + +sub status { + print "working"; +} + +this code block is indented by one tab +``` + +And: + +``` + this code block is indented by two tabs + +These should not be escaped: \$ \\ \> \[ \{ +``` + +* * * + +{id: lists} +# Lists + +{id: unordered} +## Unordered + +Asterisks tight: + +* asterisk 1 +* asterisk 2 +* asterisk 3 + +Asterisks loose: + +* asterisk 1 + +* asterisk 2 + +* asterisk 3 + +Pluses tight: + +* Plus 1 +* Plus 2 +* Plus 3 + +Pluses loose: + +* Plus 1 + +* Plus 2 + +* Plus 3 + +Minuses tight: + +* Minus 1 +* Minus 2 +* Minus 3 + +Minuses loose: + +* Minus 1 + +* Minus 2 + +* Minus 3 + +{id: ordered} +## Ordered + +Tight: + +1. First +2. Second +3. Third + +and: + +1. One +2. Two +3. Three + +Loose using tabs: + +1. First + +2. Second + +3. Third + +and using spaces: + +1. One + +2. Two + +3. Three + +Multiple paragraphs: + +1. Item 1, graf one. + + Item 1. graf two. The quick brown fox jumped over the lazy dog’s back. + +2. Item 2. + +3. Item 3. + +{id: nested} +## Nested + +* Tab + * Tab + * Tab + +Here’s another: + +1. First +2. Second: + * Fee + * Fie + * Foe +3. Third + +Same thing but with paragraphs: + +1. First + +2. Second: + + * Fee + * Fie + * Foe + +3. Third + +{id: tabs-and-spaces} +## Tabs and spaces + +* this is a list item indented with tabs + +* this is a list item indented with spaces + + * this is an example list item indented with tabs + + * this is an example list item indented with spaces + +{id: fancy-list-markers} +## Fancy list markers + +2) begins with 2 + +3) and now 3 + + with a continuation + + iv. sublist with roman numerals, starting with 4 + v. more items + A) a subsublist + B) a subsublist + +Nesting: + +A. Upper Alpha + I. Upper Roman. + 6) Decimal start with 6 + c) Lower alpha with paren + +Autonumbering: + +1. Autonumber. +2. More. + 1. Nested. + +Should not be a list item: + +M.A. 2007 + +B. Williams + +* * * + +{id: definition-lists} +# Definition Lists + +Tight using spaces: + +apple +: red fruit + +orange +: orange fruit + +banana +: yellow fruit + +Tight using tabs: + +apple +: red fruit + +orange +: orange fruit + +banana +: yellow fruit + +Loose: + +apple + +: red fruit + +orange + +: orange fruit + +banana + +: yellow fruit + +Multiple blocks with italics: + +*apple* + +: red fruit + + contains seeds, crisp, pleasant to taste + +*orange* + +: orange fruit + + ``` + { orange code block } + ``` + + > orange block quote + +Multiple definitions, tight: + +apple +: red fruit +: computer + +orange +: orange fruit +: bank + +Multiple definitions, loose: + +apple + +: red fruit + +: computer + +orange + +: orange fruit + +: bank + +Blank line after term, indented marker, alternate markers: + +apple + +: red fruit + +: computer + +orange + +: orange fruit + + 1. sublist + 2. sublist + +{id: html-blocks} +# HTML Blocks + +Simple block on one line: + +foo + +And nested without indentation: + +foo + +bar + +Interpreted markdown in a table: + +This is *emphasized* +And this is **strong** +Here’s a simple block: + +foo + +This should be a code block, though: + +``` +
      + foo +
      +``` + +As should this: + +``` +
      foo
      +``` + +Now, nested: + +foo + +This should just be an HTML comment: + +Multiline: + +Code block: + +``` + +``` + +Just plain comment, with trailing spaces on the line: + +Code: + +``` +
      +``` + +Hr’s: + +* * * + +{id: inline-markup} +# Inline Markup + +This is *emphasized*, and so *is this*. + +This is **strong**, and so **is this**. + +An *[emphasized link](/url)*. + +***This is strong and em.*** + +So is ***this*** word. + +***This is strong and em.*** + +So is ***this*** word. + +This is code: `>`, `$`, `\`, `\$`, ``. + +~~This is *strikeout*.~~ + +Superscripts: a^bc^d a^*hello*^ a^hello there^. + +Subscripts: H~2~O, H~23~O, H~many of them~O. + +These should not be superscripts or subscripts, because of the unescaped spaces: +a^b c^d, a~b c~d. + +* * * + +{id: smart-quotes-ellipses-dashes} +# Smart quotes, ellipses, dashes + +"Hello," said the spider. "'Shelob' is my name." + +'A', 'B', and 'C' are letters. + +'Oak,' 'elm,' and 'beech' are names of trees. So is 'pine.' + +'He said, "I want to go."' Were you alive in the 70’s? + +Here is some quoted '`code`' and a "[quoted +link](http://example.com/?foo=1&bar=2)". + +Some dashes: one—two — three—four — five. + +Dashes between numbers: 5–7, 255–66, 1987–1999. + +Ellipses…and…and…. + +* * * + +{id: latex} +# LaTeX + +* +* `2+2=4`$ +* `x \in y`$ +* `\alpha \wedge \omega`$ +* `223`$ +* `p`$-Tree +* Here’s some display math: + + {format: latex} + ``` + \frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h} + ``` +* Here’s one that has a line break in it: `\alpha + \omega \times x^2`$. + +These shouldn’t be math: + +* To get the famous equation, write `$e = mc^2$`. +* $22,000 is a *lot* of money. So is $34,000. (It worked if "lot" is + emphasized.) +* Shoes ($20) and socks ($5). +* Escaped `$`: $73 *this should be emphasized* 23$. + +Here’s a LaTeX table: + +* * * + +{id: special-characters} +# Special Characters + +Here is some unicode: + +* I hat: Î +* o umlaut: ö +* section: § +* set membership: ∈ +* copyright: © + +AT&T has an ampersand in their name. + +AT&T is another way to write it. + +This & that. + +4 < 5. + +6 > 5. + +Backslash: \ + +Backtick: ` + +Asterisk: * + +Underscore: _ + +Left brace: { + +Right brace: } + +Left bracket: [ + +Right bracket: ] + +Left paren: ( + +Right paren: ) + +Greater-than: > + +Hash: # + +Period: . + +Bang: ! + +Plus: + + +Minus: - + +* * * + +{id: links} +# Links + +{id: explicit} +## Explicit + +Just a [URL](/url/). + +[URL and title](/url/){title: "title"}. + +[URL and title](/url/){title: "title preceded by two spaces"}. + +[URL and title](/url/){title: "title preceded by a tab"}. + +[URL and title](/url/){title: "title with "quotes" in it"} + +[URL and title](/url/){title: "title with single quotes"} + +[with_underscore](/url/with_underscore) + +[Email link](mailto:nobody@nowhere.net) + +[Empty](). + +{id: reference} +## Reference + +Foo [bar](/url/). + +With [embedded [brackets]](/url/). + +[b](/url/) by itself should be a link. + +Indented [once](/url). + +Indented [twice](/url). + +Indented [thrice](/url). + +This should [not][] be a link. + +``` +[not]: /url +``` + +Foo [bar](/url/){title: "Title with "quotes" inside"}. + +Foo [biz](/url/){title: "Title with "quote" inside"}. + +{id: with-ampersands} +## With ampersands + +Here’s a [link with an ampersand in the URL](http://example.com/?foo=1&bar=2). + +Here’s a link with an amersand in the link text: +[AT&T](http://att.com/){title: "AT&T"}. + +Here’s an [inline link](/script?foo=1&bar=2). + +Here’s an [inline link in pointy braces](/script?foo=1&bar=2). + +{id: autolinks} +## Autolinks + +With an ampersand: +[http:~/~/example.com/?foo=1&bar=2](http://example.com/?foo=1&bar=2){class: uri} + +* In a list? +* [http:~/~/example.com/](http://example.com/){class: uri} +* It should. + +An e-mail address: [nobody@nowhere.net](mailto:nobody@nowhere.net){class: email} + +> Blockquoted: [http:~/~/example.com/](http://example.com/){class: uri} + +Auto-links should not occur here: `` + +``` +or here: +``` + +* * * + +{id: images} +# Images + +From "Voyage dans la Lune" by Georges Melies (1902): + +{alt: "lalune", title: "Voyage dans la Lune"} +![](lalune.jpg) + +Here is a movie +{alt: "movie"} +![](movie.jpg) +icon. + +* * * + +{id: footnotes} +# Footnotes + +Here is a footnote reference,[^1] and another.[^2] This should *not* be a +footnote reference, because it contains a space.[^my note] Here is an inline +note.[^3] + +> Notes can go in quotes.[^4] + +1. And in list items.[^5] + +This paragraph should not be part of the note, as it is not indented. + +[^1]: Here is the footnote. It can go anywhere after the footnote reference. It + need not be placed at the end of the document. + +[^2]: Here’s the long note. This one contains multiple blocks. + + Subsequent blocks are indented to show that they belong to the footnote (as + with list items). + + ``` + { } + ``` + + If you want, you can indent every line, but you can also be lazy and just + indent the first line of each block. + +[^3]: This is *easier* to type. Inline notes may contain + [links](http://google.com) and `]` verbatim characters, as well as + [bracketed text]. + +[^4]: In quote. + +[^5]: In list. -- cgit v1.2.3 From c4f6e6cb57e4fdda9ad59ff7220988810583ec60 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 21 Dec 2021 22:53:22 -0800 Subject: HTML writer: make line breaks more consistent. - With `--wrap=none`, we now output line breaks between block-level elements. Previously they were omitted entirely, so the whole document was on one line, unless there were literal line breaks in pre sections. This makes the HTML writer's behavior more consistent with that of other writers. - Put newline after `
      `. - Put newlines after block-level elements in footnote section. --- src/Text/Pandoc/Writers/HTML.hs | 119 ++++++++++++++++++++-------------------- test/Tests/Writers/HTML.hs | 73 +++++++++++++++++++----- test/command/853.md | 5 +- test/writer.html4 | 66 ++++++++++++++-------- test/writer.html5 | 66 ++++++++++++++-------- 5 files changed, 208 insertions(+), 121 deletions(-) (limited to 'test/Tests/Writers') diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 664aeffb6..8c5548196 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -132,10 +132,8 @@ needsVariationSelector '↔' = True needsVariationSelector _ = False -- | Hard linebreak. -nl :: WriterOptions -> Html -nl opts = if writerWrapText opts == WrapNone - then mempty - else preEscapedString "\n" +nl :: Html +nl = preEscapedString "\n" -- | Convert Pandoc document to Html 5 string. writeHtml5String :: PandocMonad m => WriterOptions -> Pandoc -> m Text @@ -284,7 +282,7 @@ pandocToHtml opts (Pandoc meta blocks) = do if null (stNotes st) then return mempty else do - notes <- footnoteSection opts EndOfDocument (stEmittedNotes st + 1) (reverse (stNotes st)) + notes <- footnoteSection EndOfDocument (stEmittedNotes st + 1) (reverse (stNotes st)) modify (\st' -> st'{ stNotes = mempty, stEmittedNotes = stEmittedNotes st' + length (stNotes st') }) return notes st <- get @@ -303,7 +301,7 @@ pandocToHtml opts (Pandoc meta blocks) = do KaTeX url -> do H.script ! A.src (toValue $ url <> "katex.min.js") $ mempty - nl opts + nl let katexFlushLeft = case lookupContext "classoption" metadata of Just clsops | "fleqn" `elem` (clsops :: [Doc Text]) -> "true" @@ -323,7 +321,7 @@ pandocToHtml opts (Pandoc meta blocks) = do , " });" , "}}});" ] - nl opts + nl H.link ! A.rel "stylesheet" ! A.href (toValue $ url <> "katex.min.css") @@ -459,15 +457,15 @@ toList listop opts items = do unordList :: PandocMonad m => WriterOptions -> [Html] -> StateT WriterState m Html -unordList opts = toList H.ul opts . toListItems opts +unordList opts = toList H.ul opts . toListItems ordList :: PandocMonad m => WriterOptions -> [Html] -> StateT WriterState m Html -ordList opts = toList H.ol opts . toListItems opts +ordList opts = toList H.ol opts . toListItems defList :: PandocMonad m => WriterOptions -> [Html] -> StateT WriterState m Html -defList opts items = toList H.dl opts (items ++ [nl opts]) +defList opts items = toList H.dl opts (items ++ [nl]) isTaskListItem :: [Block] -> Bool isTaskListItem (Plain (Str "☐":Space:_):_) = True @@ -489,7 +487,7 @@ listItemToHtml opts bls let checkbox = if checked then checkbox' ! A.checked "" else checkbox' - checkbox' = H.input ! A.type_ "checkbox" ! A.disabled "" >> nl opts + checkbox' = H.input ! A.type_ "checkbox" ! A.disabled "" >> nl isContents <- inlineListToHtml opts is bsContents <- blockListToHtml opts bs return $ constr (checkbox >> isContents) >> bsContents @@ -513,11 +511,13 @@ tableOfContents opts sects = do -- | Convert list of Note blocks to a footnote
      . -- Assumes notes are sorted. footnoteSection :: - PandocMonad m => WriterOptions -> ReferenceLocation -> Int -> [Html] -> StateT WriterState m Html -footnoteSection opts refLocation startCounter notes = do + PandocMonad m => ReferenceLocation -> Int -> [Html] -> StateT WriterState m Html +footnoteSection refLocation startCounter notes = do html5 <- gets stHtml5 slideVariant <- gets stSlideVariant - let hrtag = if refLocation /= EndOfBlock then (if html5 then H5.hr else H.hr) else mempty + let hrtag = if refLocation /= EndOfBlock + then (if html5 then H5.hr else H.hr) <> nl + else mempty let additionalClassName = case refLocation of EndOfBlock -> "footnotes-end-of-block" EndOfDocument -> "footnotes-end-of-document" @@ -538,17 +538,17 @@ footnoteSection opts refLocation startCounter notes = do if null notes then mempty else do - nl opts + nl container $ do - nl opts + nl hrtag - nl opts -- Keep the previous output exactly the same if we don't -- have multiple notes sections if startCounter == 1 - then H.ol $ mconcat notes >> nl opts - else H.ol ! A.start (fromString (show startCounter)) $ mconcat notes >> nl opts - nl opts + then H.ol $ mconcat notes >> nl + else H.ol ! A.start (fromString (show startCounter)) $ + mconcat notes >> nl + nl -- | Parse a mailto link; return Just (name, domain) or Nothing. parseMailto :: Text -> Maybe (Text, Text) @@ -715,8 +715,8 @@ figure opts attr@(_, _, attrList) txt (s,tit) = do img <- inlineToHtml opts (Image attr alt (s,tit)) capt <- if null txt then return mempty - else (nl opts <>) . tocapt <$> inlineListToHtml opts txt - let inner = mconcat [nl opts, img, capt, nl opts] + else (nl <>) . tocapt <$> inlineListToHtml opts txt + let inner = mconcat [nl, img, capt, nl] return $ if html5 then H5.figure inner else H.div ! A.class_ "figure" $ inner @@ -820,32 +820,32 @@ blockToHtmlInner opts (Div (ident, "section":dclasses, dkvs) if titleSlide then do t <- addAttrs opts attr $ - secttag $ nl opts <> header' <> nl opts <> titleContents <> nl opts + secttag $ nl <> header' <> nl <> titleContents <> nl -- ensure 2D nesting for revealjs, but only for one level; -- revealjs doesn't like more than one level of nesting return $ if slideVariant == RevealJsSlides && not inSection && not (null innerSecs) - then H5.section (nl opts <> t <> nl opts <> innerContents) - else t <> nl opts <> if null innerSecs + then H5.section (nl <> t <> nl <> innerContents) + else t <> nl <> if null innerSecs then mempty - else innerContents <> nl opts + else innerContents <> nl else if writerSectionDivs opts || slide || (hident /= ident && not (T.null hident || T.null ident)) || (hclasses /= dclasses) || (hkvs /= dkvs) then addAttrs opts attr $ secttag - $ nl opts <> header' <> nl opts <> + $ nl <> header' <> nl <> if null innerSecs then mempty - else innerContents <> nl opts + else innerContents <> nl else do let attr' = (ident, classes' \\ hclasses, dkvs \\ hkvs) t <- addAttrs opts attr' header' return $ t <> if null innerSecs then mempty - else nl opts <> innerContents + else nl <> innerContents blockToHtmlInner opts (Div attr@(ident, classes, kvs') bs) = do html5 <- gets stHtml5 slideVariant <- gets stSlideVariant @@ -883,7 +883,7 @@ blockToHtmlInner opts (Div attr@(ident, classes, kvs') bs) = do -- off widths! see #4028 mconcat <$> mapM (blockToHtml opts) bs' else blockListToHtml opts' bs' - let contents' = nl opts >> contents >> nl opts + let contents' = nl >> contents >> nl let (divtag, classes'') = if html5 && "section" `elem` classes' then (H5.section, filter (/= "section") classes') else (H.div, classes') @@ -964,10 +964,10 @@ blockToHtmlInner opts (BlockQuote blocks) = do (DefinitionList lst) _ -> do contents <- blockListToHtml opts blocks return $ H.blockquote - $ nl opts >> contents >> nl opts + $ nl >> contents >> nl else do contents <- blockListToHtml opts blocks - return $ H.blockquote $ nl opts >> contents >> nl opts + return $ H.blockquote $ nl >> contents >> nl blockToHtmlInner opts (Header level (ident,classes,kvs) lst) = do contents <- inlineListToHtml opts lst let secnum = fromMaybe mempty $ lookup "number" kvs @@ -1022,10 +1022,10 @@ blockToHtmlInner opts (OrderedList (startnum, numstyle, _) lst) = do blockToHtmlInner opts (DefinitionList lst) = do contents <- mapM (\(term, defs) -> do term' <- liftM H.dt $ inlineListToHtml opts term - defs' <- mapM (liftM (\x -> H.dd (x >> nl opts)) . + defs' <- mapM (liftM (\x -> H.dd (nl >> x >> nl)) . blockListToHtml opts) defs - return $ mconcat $ nl opts : term' : nl opts : - intersperse (nl opts) defs') lst + return $ mconcat $ nl : term' : nl : + intersperse (nl) defs') lst defList opts contents blockToHtmlInner opts (Table attr caption colspecs thead tbody tfoot) = tableToHtml opts (Ann.toTable attr caption colspecs thead tbody tfoot) @@ -1052,7 +1052,7 @@ blockToHtml opts block = do then do notes <- if null (stNotes st) then return mempty - else footnoteSection opts (writerReferenceLocation opts) (stEmittedNotes st + 1) (reverse (stNotes st)) + else footnoteSection (writerReferenceLocation opts) (stEmittedNotes st + 1) (reverse (stNotes st)) modify (\st' -> st'{ stNotes = mempty, stEmittedNotes = stEmittedNotes st' + length (stNotes st') }) return (doc <> notes) else return doc @@ -1071,10 +1071,10 @@ tableToHtml opts (Ann.Table attr caption colspecs thead tbodies tfoot) = do cs <- blockListToHtml opts longCapt return $ do H.caption cs - nl opts - coltags <- colSpecListToHtml opts colspecs + nl + coltags <- colSpecListToHtml colspecs head' <- tableHeadToHtml opts thead - bodies <- intersperse (nl opts) <$> mapM (tableBodyToHtml opts) tbodies + bodies <- intersperse (nl) <$> mapM (tableBodyToHtml opts) tbodies foot' <- tableFootToHtml opts tfoot let (ident,classes,kvs) = attr -- When widths of columns are < 100%, we need to set width for the whole @@ -1091,13 +1091,13 @@ tableToHtml opts (Ann.Table attr caption colspecs thead tbodies tfoot) = do <> "%;"):kvs) _ -> attr addAttrs opts attr' $ H.table $ do - nl opts + nl captionDoc coltags head' mconcat bodies foot' - nl opts + nl tableBodyToHtml :: PandocMonad m => WriterOptions @@ -1144,7 +1144,7 @@ tablePartToHtml opts tblpart attr rows = tablePartElement <- addAttrs opts attr $ tag' contents return $ do tablePartElement - nl opts + nl where isEmptyRow (Ann.HeaderRow _attr _rownum cells) = all isEmptyCell cells isEmptyCell (Ann.Cell _colspecs _colnum cell) = @@ -1185,14 +1185,13 @@ rowListToHtml :: PandocMonad m -> [TableRow] -> StateT WriterState m Html rowListToHtml opts rows = - (\x -> nl opts *> mconcat x) <$> + (\x -> nl *> mconcat x) <$> mapM (tableRowToHtml opts) rows colSpecListToHtml :: PandocMonad m - => WriterOptions - -> [ColSpec] + => [ColSpec] -> StateT WriterState m Html -colSpecListToHtml opts colspecs = do +colSpecListToHtml colspecs = do html5 <- gets stHtml5 let hasDefaultWidth (_, ColWidthDefault) = True hasDefaultWidth _ = False @@ -1206,16 +1205,16 @@ colSpecListToHtml opts colspecs = do ColWidth w -> if html5 then A.style (toValue $ "width: " <> percent w) else A.width (toValue $ percent w) - nl opts + nl return $ if all hasDefaultWidth colspecs then mempty else do H.colgroup $ do - nl opts + nl mapM_ (col . snd) colspecs - nl opts + nl tableRowToHtml :: PandocMonad m => WriterOptions @@ -1234,12 +1233,12 @@ tableRowToHtml opts (TableRow tblpart attr rownum rowhead rowbody) = do headcells <- mapM (cellToHtml opts HeaderCell) rowhead bodycells <- mapM (cellToHtml opts celltype) rowbody rowHtml <- addAttrs opts attr' $ H.tr $ do - nl opts + nl mconcat headcells mconcat bodycells return $ do rowHtml - nl opts + nl alignmentToString :: Alignment -> Maybe Text alignmentToString = \case @@ -1297,18 +1296,18 @@ tableCellToHtml opts ctype colAlign (Cell attr align rowspan colspan item) = do : otherAttribs return $ do tag' ! attribs $ contents - nl opts + nl -toListItems :: WriterOptions -> [Html] -> [Html] -toListItems opts items = map (toListItem opts) items ++ [nl opts] +toListItems :: [Html] -> [Html] +toListItems items = map toListItem items ++ [nl] -toListItem :: WriterOptions -> Html -> Html -toListItem opts item = nl opts *> H.li item +toListItem :: Html -> Html +toListItem item = nl *> H.li item blockListToHtml :: PandocMonad m => WriterOptions -> [Block] -> StateT WriterState m Html blockListToHtml opts lst = - mconcat . intersperse (nl opts) . filter nonempty + mconcat . intersperse (nl) . filter nonempty <$> mapM (blockToHtml opts) lst where nonempty (Empty _) = False nonempty _ = True @@ -1340,9 +1339,9 @@ inlineToHtml opts inline = do (Str str) -> return $ strToHtml str Space -> return $ strToHtml " " SoftBreak -> return $ case writerWrapText opts of - WrapNone -> preEscapedText " " + WrapNone -> " " WrapAuto -> " " - WrapPreserve -> preEscapedText "\n" + WrapPreserve -> nl LineBreak -> return $ do if html5 then H5.br else H.br strToHtml "\n" @@ -1607,7 +1606,7 @@ blockListToNote opts ref blocks = do _ | html5 -> noteItem ! customAttribute "role" "doc-endnote" _ -> noteItem - return $ nl opts >> noteItem' + return $ nl >> noteItem' inDiv :: PandocMonad m=> Text -> Html -> StateT WriterState m Html inDiv cls x = do diff --git a/test/Tests/Writers/HTML.hs b/test/Tests/Writers/HTML.hs index 50775b171..a81badae8 100644 --- a/test/Tests/Writers/HTML.hs +++ b/test/Tests/Writers/HTML.hs @@ -2,6 +2,7 @@ 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 @@ -68,7 +69,7 @@ tests = , testGroup "blocks" [ "definition list with empty
      " =: definitionList [(mempty, [para $ text "foo bar"])] - =?> "

      foo bar

      " + =?> "
      \n
      \n
      \n

      foo bar

      \n
      \n
      " , "heading with disallowed attributes" =: headerWith ("", [], [("invalid","1"), ("lang", "en")]) 1 "test" =?> @@ -108,37 +109,66 @@ tests = [ test (htmlWithOpts def{writerReferenceLocation=EndOfDocument}) "at the end of a document" $ noteTestDoc =?> - concat + T.unlines [ "

      Page title

      " , "

      First section

      " , "

      This is a footnote.1 And this is a link.

      " - , "

      A note inside a block quote.2

      A second paragraph.

      " + , "
      " + , "

      A note inside a block quote.2

      " + , "

      A second paragraph.

      " + , "
      " , "

      Second section

      " , "

      Some more text.

      " - , "

      1. Down here.↩︎

      2. The second note.↩︎

      " + , "
      " + , "
      " + , "
        " + , "
      1. Down here.↩︎

      2. " + , "
      3. The second note.↩︎

      4. " + , "
      " + , "
      " ] , test (htmlWithOpts def{writerReferenceLocation=EndOfBlock}) "at the end of a block" $ noteTestDoc =?> - concat + T.unlines [ "

      Page title

      " , "

      First section

      " , "

      This is a footnote.1 And this is a link.

      " - , "
      1. Down here.↩︎

      " - , "

      A note inside a block quote.2

      A second paragraph.

      " - , "
      1. The second note.↩︎

      " + , "
      " + , "
        " + , "
      1. Down here.↩︎

      2. " + , "
      " + , "
      " + , "
      " + , "

      A note inside a block quote.2

      " + , "

      A second paragraph.

      " + , "
      " + , "
      " + , "
        " + , "
      1. The second note.↩︎

      2. " + , "
      " + , "
      " , "

      Second section

      " , "

      Some more text.

      " ] , test (htmlWithOpts def{writerReferenceLocation=EndOfSection}) "at the end of a section" $ noteTestDoc =?> - concat + T.unlines [ "

      Page title

      " , "

      First section

      " , "

      This is a footnote.1 And this is a link.

      " - , "

      A note inside a block quote.2

      A second paragraph.

      " - , "

      1. Down here.↩︎

      2. The second note.↩︎

      " + , "
      " + , "

      A note inside a block quote.2

      " + , "

      A second paragraph.

      " + , "
      " + , "
      " + , "
      " + , "
        " + , "
      1. Down here.↩︎

      2. " + , "
      3. The second note.↩︎

      4. " + , "
      " + , "
      " , "

      Second section

      " , "

      Some more text.

      " ] @@ -147,15 +177,28 @@ tests = noteTestDoc =?> -- Footnotes are rendered _after_ their section (in this case after the level2 section -- that contains it). - concat + T.unlines [ "
      " , "

      Page title

      " , "
      " , "

      First section

      " - , "

      This is a footnote.1 And this is a link.

      A note inside a block quote.2

      A second paragraph.

      " + , "

      This is a footnote.1 And this is a link.

      " + , "
      " + , "

      A note inside a block quote.2

      " + , "

      A second paragraph.

      " + , "
      " + , "
      " + , "
      " + , "
      " + , "
        " + , "
      1. Down here.↩︎

      2. " + , "
      3. The second note.↩︎

      4. " + , "
      " + , "
      " + , "
      " + , "

      Second section

      " + , "

      Some more text.

      " , "
      " - , "

      1. Down here.↩︎

      2. The second note.↩︎

      " - , "

      Second section

      Some more text.

      " , "
      " ] ] diff --git a/test/command/853.md b/test/command/853.md index bcc3b4654..518c6593b 100644 --- a/test/command/853.md +++ b/test/command/853.md @@ -12,8 +12,9 @@ class="citation">[CIT2002].

      CIT2002
      -

      This is the citation. It's just like a footnote, except the label -is textual.

      +
      +

      This is the citation. It's just like a footnote, except the label is +textual.

      diff --git a/test/writer.html4 b/test/writer.html4 index e2adcf5bc..1e255fa70 100644 --- a/test/writer.html4 +++ b/test/writer.html4 @@ -376,47 +376,58 @@ back.

      Tight using spaces:

      apple
      -
      red fruit +
      +red fruit
      orange
      -
      orange fruit +
      +orange fruit
      banana
      -
      yellow fruit +
      +yellow fruit

      Tight using tabs:

      apple
      -
      red fruit +
      +red fruit
      orange
      -
      orange fruit +
      +orange fruit
      banana
      -
      yellow fruit +
      +yellow fruit

      Loose:

      apple
      -

      red fruit

      +
      +

      red fruit

      orange
      -

      orange fruit

      +
      +

      orange fruit

      banana
      -

      yellow fruit

      +
      +

      yellow fruit

      Multiple blocks with italics:

      apple
      -

      red fruit

      +
      +

      red fruit

      contains seeds, crisp, pleasant to taste

      orange
      -

      orange fruit

      +
      +

      orange fruit

      { orange code block }

      orange block quote

      @@ -426,38 +437,49 @@ back.

      Multiple definitions, tight:

      apple
      -
      red fruit +
      +red fruit
      -
      computer +
      +computer
      orange
      -
      orange fruit +
      +orange fruit
      -
      bank +
      +bank

      Multiple definitions, loose:

      apple
      -

      red fruit

      +
      +

      red fruit

      -

      computer

      +
      +

      computer

      orange
      -

      orange fruit

      +
      +

      orange fruit

      -

      bank

      +
      +

      bank

      Blank line after term, indented marker, alternate markers:

      apple
      -

      red fruit

      +
      +

      red fruit

      -

      computer

      +
      +

      computer

      orange
      -

      orange fruit

      +
      +

      orange fruit

      1. sublist
      2. sublist
      3. diff --git a/test/writer.html5 b/test/writer.html5 index cdfcf042f..d8e89b3e2 100644 --- a/test/writer.html5 +++ b/test/writer.html5 @@ -379,47 +379,58 @@ back.

        Tight using spaces:

        apple
        -
        red fruit +
        +red fruit
        orange
        -
        orange fruit +
        +orange fruit
        banana
        -
        yellow fruit +
        +yellow fruit

        Tight using tabs:

        apple
        -
        red fruit +
        +red fruit
        orange
        -
        orange fruit +
        +orange fruit
        banana
        -
        yellow fruit +
        +yellow fruit

        Loose:

        apple
        -

        red fruit

        +
        +

        red fruit

        orange
        -

        orange fruit

        +
        +

        orange fruit

        banana
        -

        yellow fruit

        +
        +

        yellow fruit

        Multiple blocks with italics:

        apple
        -

        red fruit

        +
        +

        red fruit

        contains seeds, crisp, pleasant to taste

        orange
        -

        orange fruit

        +
        +

        orange fruit

        { orange code block }

        orange block quote

        @@ -429,38 +440,49 @@ back.

        Multiple definitions, tight:

        apple
        -
        red fruit +
        +red fruit
        -
        computer +
        +computer
        orange
        -
        orange fruit +
        +orange fruit
        -
        bank +
        +bank

        Multiple definitions, loose:

        apple
        -

        red fruit

        +
        +

        red fruit

        -

        computer

        +
        +

        computer

        orange
        -

        orange fruit

        +
        +

        orange fruit

        -

        bank

        +
        +

        bank

        Blank line after term, indented marker, alternate markers:

        apple
        -

        red fruit

        +
        +

        red fruit

        -

        computer

        +
        +

        computer

        orange
        -

        orange fruit

        +
        +

        orange fruit

        1. sublist
        2. sublist
        3. -- cgit v1.2.3