aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--MANUAL.txt19
-rw-r--r--src/Text/Pandoc/Writers/Powerpoint/Output.hs225
-rw-r--r--test/Tests/Writers/Powerpoint.hs31
-rw-r--r--test/pptx/code-custom_deleted_layouts.pptxbin0 -> 31033 bytes
-rw-r--r--test/pptx/code-custom_moved_layouts.pptxbin0 -> 41822 bytes
-rw-r--r--test/pptx/code_deleted_layouts.pptxbin0 -> 31032 bytes
-rw-r--r--test/pptx/code_moved_layouts.pptxbin0 -> 41826 bytes
-rw-r--r--test/pptx/document-properties-short-desc_deleted_layouts.pptxbin0 -> 29806 bytes
-rw-r--r--test/pptx/document-properties-short-desc_moved_layouts.pptxbin0 -> 40600 bytes
-rw-r--r--test/pptx/document-properties_deleted_layouts.pptxbin0 -> 30210 bytes
-rw-r--r--test/pptx/document-properties_moved_layouts.pptxbin0 -> 41004 bytes
-rw-r--r--test/pptx/endnotes_deleted_layouts.pptxbin0 -> 29774 bytes
-rw-r--r--test/pptx/endnotes_moved_layouts.pptxbin0 -> 40566 bytes
-rw-r--r--test/pptx/endnotes_toc_deleted_layouts.pptxbin0 -> 30596 bytes
-rw-r--r--test/pptx/endnotes_toc_moved_layouts.pptxbin0 -> 41384 bytes
-rw-r--r--test/pptx/images_deleted_layouts.pptxbin0 -> 47424 bytes
-rw-r--r--test/pptx/images_moved_layouts.pptxbin0 -> 58213 bytes
-rw-r--r--test/pptx/inline_formatting_deleted_layouts.pptxbin0 -> 28966 bytes
-rw-r--r--test/pptx/inline_formatting_moved_layouts.pptxbin0 -> 39758 bytes
-rw-r--r--test/pptx/lists_deleted_layouts.pptxbin0 -> 29861 bytes
-rw-r--r--test/pptx/lists_moved_layouts.pptxbin0 -> 40653 bytes
-rw-r--r--test/pptx/raw_ooxml_deleted_layouts.pptxbin0 -> 29754 bytes
-rw-r--r--test/pptx/raw_ooxml_moved_layouts.pptxbin0 -> 40546 bytes
-rw-r--r--test/pptx/reference_deleted_layouts.pptxbin0 -> 18160 bytes
-rw-r--r--test/pptx/reference_moved_layouts.pptxbin0 -> 44237 bytes
-rw-r--r--test/pptx/remove_empty_slides_deleted_layouts.pptxbin0 -> 46867 bytes
-rw-r--r--test/pptx/remove_empty_slides_moved_layouts.pptxbin0 -> 57656 bytes
-rw-r--r--test/pptx/slide_breaks_deleted_layouts.pptxbin0 -> 31378 bytes
-rw-r--r--test/pptx/slide_breaks_moved_layouts.pptxbin0 -> 42171 bytes
-rw-r--r--test/pptx/slide_breaks_slide_level_1_deleted_layouts.pptxbin0 -> 30554 bytes
-rw-r--r--test/pptx/slide_breaks_slide_level_1_moved_layouts.pptxbin0 -> 41343 bytes
-rw-r--r--test/pptx/slide_breaks_toc_deleted_layouts.pptxbin0 -> 32328 bytes
-rw-r--r--test/pptx/slide_breaks_toc_moved_layouts.pptxbin0 -> 43118 bytes
-rw-r--r--test/pptx/speaker_notes_after_metadata_deleted_layouts.pptxbin0 -> 34473 bytes
-rw-r--r--test/pptx/speaker_notes_after_metadata_moved_layouts.pptxbin0 -> 45269 bytes
-rw-r--r--test/pptx/speaker_notes_afterheader_deleted_layouts.pptxbin0 -> 33500 bytes
-rw-r--r--test/pptx/speaker_notes_afterheader_moved_layouts.pptxbin0 -> 44297 bytes
-rw-r--r--test/pptx/speaker_notes_afterseps_deleted_layouts.pptxbin0 -> 54390 bytes
-rw-r--r--test/pptx/speaker_notes_afterseps_moved_layouts.pptxbin0 -> 65181 bytes
-rw-r--r--test/pptx/speaker_notes_deleted_layouts.pptxbin0 -> 38203 bytes
-rw-r--r--test/pptx/speaker_notes_moved_layouts.pptxbin0 -> 49002 bytes
-rw-r--r--test/pptx/start_numbering_at_deleted_layouts.pptxbin0 -> 29837 bytes
-rw-r--r--test/pptx/start_numbering_at_moved_layouts.pptxbin0 -> 40630 bytes
-rw-r--r--test/pptx/tables_deleted_layouts.pptxbin0 -> 30381 bytes
-rw-r--r--test/pptx/tables_moved_layouts.pptxbin0 -> 41174 bytes
-rw-r--r--test/pptx/two_column_deleted_layouts.pptxbin0 -> 28883 bytes
-rw-r--r--test/pptx/two_column_moved_layouts.pptxbin0 -> 39676 bytes
47 files changed, 242 insertions, 33 deletions
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
--- /dev/null
+++ b/test/pptx/code-custom_deleted_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/code-custom_moved_layouts.pptx
Binary files differ
diff --git a/test/pptx/code_deleted_layouts.pptx b/test/pptx/code_deleted_layouts.pptx
new file mode 100644
index 000000000..0f503f553
--- /dev/null
+++ b/test/pptx/code_deleted_layouts.pptx
Binary files differ
diff --git a/test/pptx/code_moved_layouts.pptx b/test/pptx/code_moved_layouts.pptx
new file mode 100644
index 000000000..4d66b1310
--- /dev/null
+++ b/test/pptx/code_moved_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/document-properties-short-desc_deleted_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/document-properties-short-desc_moved_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/document-properties_deleted_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/document-properties_moved_layouts.pptx
Binary files differ
diff --git a/test/pptx/endnotes_deleted_layouts.pptx b/test/pptx/endnotes_deleted_layouts.pptx
new file mode 100644
index 000000000..5c69a6310
--- /dev/null
+++ b/test/pptx/endnotes_deleted_layouts.pptx
Binary files differ
diff --git a/test/pptx/endnotes_moved_layouts.pptx b/test/pptx/endnotes_moved_layouts.pptx
new file mode 100644
index 000000000..0d4c491b9
--- /dev/null
+++ b/test/pptx/endnotes_moved_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/endnotes_toc_deleted_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/endnotes_toc_moved_layouts.pptx
Binary files differ
diff --git a/test/pptx/images_deleted_layouts.pptx b/test/pptx/images_deleted_layouts.pptx
new file mode 100644
index 000000000..7a38ea625
--- /dev/null
+++ b/test/pptx/images_deleted_layouts.pptx
Binary files differ
diff --git a/test/pptx/images_moved_layouts.pptx b/test/pptx/images_moved_layouts.pptx
new file mode 100644
index 000000000..08d1c27e0
--- /dev/null
+++ b/test/pptx/images_moved_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/inline_formatting_deleted_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/inline_formatting_moved_layouts.pptx
Binary files differ
diff --git a/test/pptx/lists_deleted_layouts.pptx b/test/pptx/lists_deleted_layouts.pptx
new file mode 100644
index 000000000..6512e44bb
--- /dev/null
+++ b/test/pptx/lists_deleted_layouts.pptx
Binary files differ
diff --git a/test/pptx/lists_moved_layouts.pptx b/test/pptx/lists_moved_layouts.pptx
new file mode 100644
index 000000000..2947c3211
--- /dev/null
+++ b/test/pptx/lists_moved_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/raw_ooxml_deleted_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/raw_ooxml_moved_layouts.pptx
Binary files differ
diff --git a/test/pptx/reference_deleted_layouts.pptx b/test/pptx/reference_deleted_layouts.pptx
new file mode 100644
index 000000000..a9a74ecd5
--- /dev/null
+++ b/test/pptx/reference_deleted_layouts.pptx
Binary files differ
diff --git a/test/pptx/reference_moved_layouts.pptx b/test/pptx/reference_moved_layouts.pptx
new file mode 100644
index 000000000..72c4f3fd7
--- /dev/null
+++ b/test/pptx/reference_moved_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/remove_empty_slides_deleted_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/remove_empty_slides_moved_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/slide_breaks_deleted_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/slide_breaks_moved_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/slide_breaks_slide_level_1_deleted_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/slide_breaks_slide_level_1_moved_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/slide_breaks_toc_deleted_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/slide_breaks_toc_moved_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/speaker_notes_after_metadata_deleted_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/speaker_notes_after_metadata_moved_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/speaker_notes_afterheader_deleted_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/speaker_notes_afterheader_moved_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/speaker_notes_afterseps_deleted_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/speaker_notes_afterseps_moved_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/speaker_notes_deleted_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/speaker_notes_moved_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/start_numbering_at_deleted_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/start_numbering_at_moved_layouts.pptx
Binary files differ
diff --git a/test/pptx/tables_deleted_layouts.pptx b/test/pptx/tables_deleted_layouts.pptx
new file mode 100644
index 000000000..a52222551
--- /dev/null
+++ b/test/pptx/tables_deleted_layouts.pptx
Binary files differ
diff --git a/test/pptx/tables_moved_layouts.pptx b/test/pptx/tables_moved_layouts.pptx
new file mode 100644
index 000000000..56608a039
--- /dev/null
+++ b/test/pptx/tables_moved_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/two_column_deleted_layouts.pptx
Binary files 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
--- /dev/null
+++ b/test/pptx/two_column_moved_layouts.pptx
Binary files differ