aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--MANUAL.txt46
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs19
-rw-r--r--src/Text/Pandoc/Writers/ODT.hs36
-rw-r--r--src/Text/Pandoc/Writers/Powerpoint/Output.hs41
-rw-r--r--src/Text/Pandoc/Writers/Powerpoint/Presentation.hs21
-rw-r--r--test/Tests/Writers/Docx.hs10
-rw-r--r--test/Tests/Writers/Powerpoint.hs8
-rw-r--r--test/docx/document-properties-short-desc.native2
-rw-r--r--test/docx/document-properties.native2
-rw-r--r--test/docx/golden/document-properties-short-desc.docxbin0 -> 9902 bytes
-rw-r--r--test/docx/golden/document-properties.docxbin0 -> 10388 bytes
-rw-r--r--test/pptx/document-properties-short-desc.native2
-rw-r--r--test/pptx/document-properties-short-desc.pptxbin0 -> 27002 bytes
-rw-r--r--test/pptx/document-properties-short-desc_templated.pptxbin0 -> 394321 bytes
-rw-r--r--test/pptx/document-properties.native2
-rw-r--r--test/pptx/document-properties.pptxbin0 -> 27408 bytes
-rw-r--r--test/pptx/document-properties_templated.pptxbin0 -> 394725 bytes
-rw-r--r--test/pptx/endnotes.pptxbin26678 -> 26959 bytes
-rw-r--r--test/pptx/endnotes_templated.pptxbin394004 -> 394284 bytes
-rw-r--r--test/pptx/endnotes_toc.pptxbin27602 -> 27883 bytes
-rw-r--r--test/pptx/endnotes_toc_templated.pptxbin394927 -> 395207 bytes
-rw-r--r--test/pptx/images.pptxbin44338 -> 44618 bytes
-rw-r--r--test/pptx/images_templated.pptxbin411658 -> 411938 bytes
-rw-r--r--test/pptx/inline_formatting.pptxbin25842 -> 26123 bytes
-rw-r--r--test/pptx/inline_formatting_templated.pptxbin393163 -> 393444 bytes
-rw-r--r--test/pptx/lists.pptxbin26765 -> 27046 bytes
-rw-r--r--test/pptx/lists_templated.pptxbin394091 -> 394371 bytes
-rw-r--r--test/pptx/raw_ooxml.pptxbin26656 -> 26937 bytes
-rw-r--r--test/pptx/raw_ooxml_templated.pptxbin393982 -> 394263 bytes
-rw-r--r--test/pptx/remove_empty_slides.pptxbin43784 -> 44064 bytes
-rw-r--r--test/pptx/remove_empty_slides_templated.pptxbin411101 -> 411382 bytes
-rw-r--r--test/pptx/slide_breaks.pptxbin28290 -> 28571 bytes
-rw-r--r--test/pptx/slide_breaks_slide_level_1.pptxbin27461 -> 27742 bytes
-rw-r--r--test/pptx/slide_breaks_slide_level_1_templated.pptxbin394786 -> 395066 bytes
-rw-r--r--test/pptx/slide_breaks_templated.pptxbin395617 -> 395896 bytes
-rw-r--r--test/pptx/slide_breaks_toc.pptxbin29248 -> 29530 bytes
-rw-r--r--test/pptx/slide_breaks_toc_templated.pptxbin396575 -> 396855 bytes
-rw-r--r--test/pptx/speaker_notes.pptxbin35156 -> 35435 bytes
-rw-r--r--test/pptx/speaker_notes_afterseps.pptxbin51322 -> 51604 bytes
-rw-r--r--test/pptx/speaker_notes_afterseps_templated.pptxbin418642 -> 418927 bytes
-rw-r--r--test/pptx/speaker_notes_templated.pptxbin402475 -> 402759 bytes
-rw-r--r--test/pptx/tables.pptxbin27282 -> 27563 bytes
-rw-r--r--test/pptx/tables_templated.pptxbin394610 -> 394890 bytes
-rw-r--r--test/pptx/two_column.pptxbin25785 -> 26066 bytes
-rw-r--r--test/pptx/two_column_templated.pptxbin393106 -> 393387 bytes
45 files changed, 165 insertions, 24 deletions
diff --git a/MANUAL.txt b/MANUAL.txt
index 061a52e8c..7714d62b1 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -1355,7 +1355,7 @@ directory (see `--data-dir`, above). *Exceptions:*
(or the `default.context` template, if you use `-t context`,
or the `default.ms` template, if you use `-t ms`, or the
`default.html` template, if you use `-t html`).
-- `docx` has no template (however, you can use
+- `docx` and `pptx` have no template (however, you can use
`--reference-doc` to customize the output).
Templates contain *variables*, which allow for the inclusion of
@@ -1363,7 +1363,7 @@ arbitrary information at any point in the file. They may be set at the
command line using the `-V/--variable` option. If a variable is not set,
pandoc will look for the key in the document's metadata – which can be set
using either [YAML metadata blocks][Extension: `yaml_metadata_block`]
-or with the `--metadata` option.
+or with the `-M/--metadata` option.
Metadata variables
------------------
@@ -1381,14 +1381,48 @@ Metadata variables
...
`subtitle`
-: document subtitle, included in HTML, EPUB, LaTeX, ConTeXt, and Word docx
+: document subtitle, included in HTML, EPUB, LaTeX, ConTeXt, and docx
+ documents
`abstract`
-: document summary, included in LaTeX, ConTeXt, AsciiDoc, and Word docx
+: document summary, included in LaTeX, ConTeXt, AsciiDoc, and docx
+ documents
`keywords`
-: list of keywords to be included in HTML, PDF, and AsciiDoc metadata;
- repeat as for `author`, above
+: list of keywords to be included in HTML, PDF, ODT, pptx, docx
+ and AsciiDoc metadata; repeat as for `author`, above
+
+`subject`
+: document subject, included in ODT, docx and pptx metadata
+
+`description`
+: document description, included in ODT, docx and pptx metadata. Some
+ applications show this as `Comments` metadata.
+
+`category`
+: document category, included in docx and pptx metadata
+
+Additionally,
+any root-level string metadata, not included in ODT, docx
+or pptx metadata is added as a *custom property*.
+The following YAML metadata block for instance:
+
+ ---
+ title: 'This is the title'
+ subtitle: "This is the subtitle"
+ author:
+ - Author One
+ - Author Two
+ description: |
+ This is a long
+ description.
+
+ It consists of two paragraphs
+ ...
+
+will include `title`, `author` and `description` as standard document
+properties and `subtitle` as a custom property when converting to docx,
+ODT or pptx.
Language variables
------------------
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 4f642871a..cee339ac7 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -496,7 +496,17 @@ writeDocx opts doc@(Pandoc meta _) = do
Just (MetaList xs) -> map stringify xs
_ -> []
+ -- docProps/core.xml
let docPropsPath = "docProps/core.xml"
+ let extraCoreProps = ["subject","lang","category","description"]
+ let extraCorePropsMap = M.fromList $ zip extraCoreProps
+ ["dc:subject","dc:language","cp:category","dc:description"]
+ let lookupMetaString' :: String -> Meta -> String
+ lookupMetaString' key' meta' =
+ case key' of
+ "description" -> intercalate "_x000d_\n" (map stringify $ lookupMetaBlocks "description" meta')
+ _ -> lookupMetaString key' meta'
+
let docProps = mknode "cp:coreProperties"
[("xmlns:cp","http://schemas.openxmlformats.org/package/2006/metadata/core-properties")
,("xmlns:dc","http://purl.org/dc/elements/1.1/")
@@ -505,14 +515,19 @@ writeDocx opts doc@(Pandoc meta _) = do
,("xmlns:xsi","http://www.w3.org/2001/XMLSchema-instance")]
$ mknode "dc:title" [] (stringify $ docTitle meta)
: mknode "dc:creator" [] (intercalate "; " (map stringify $ docAuthors meta))
- : mknode "cp:keywords" [] (intercalate ", " keywords)
+ : [ mknode (M.findWithDefault "" k extraCorePropsMap) [] (lookupMetaString' k meta)
+ | k <- M.keys (unMeta meta), k `elem` extraCoreProps]
+ ++ mknode "cp:keywords" [] (intercalate ", " keywords)
: (\x -> [ mknode "dcterms:created" [("xsi:type","dcterms:W3CDTF")] x
, mknode "dcterms:modified" [("xsi:type","dcterms:W3CDTF")] x
]) (formatTime defaultTimeLocale "%FT%XZ" utctime)
let docPropsEntry = toEntry docPropsPath epochtime $ renderXml docProps
+ -- docProps/custom.xml
let customProperties :: [(String, String)]
- customProperties = [] -- FIXME
+ customProperties = [(k, lookupMetaString k meta) | k <- M.keys (unMeta meta)
+ , k `notElem` (["title", "author", "keywords"]
+ ++ extraCoreProps)]
let mkCustomProp (k, v) pid = mknode "property"
[("fmtid","{D5CDD505-2E9C-101B-9397-08002B2CF9AE}")
,("pid", show pid)
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index a03575134..481e88da2 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -40,6 +40,7 @@ import Data.List (isPrefixOf, intercalate)
import Data.Maybe (fromMaybe)
import qualified Data.Map as Map
import qualified Data.Text.Lazy as TL
+import Data.Time
import System.FilePath (takeDirectory, takeExtension, (<.>))
import Text.Pandoc.BCP47 (Lang (..), getLang, renderLang)
import Text.Pandoc.Class (PandocMonad, report, toLang)
@@ -50,8 +51,9 @@ import Text.Pandoc.Logging
import Text.Pandoc.MIME (extensionFromMimeType, getMimeType)
import Text.Pandoc.Options (WrapOption (..), WriterOptions (..))
import Text.Pandoc.Pretty
-import Text.Pandoc.Shared (stringify, normalizeDate)
-import Text.Pandoc.Writers.Shared (lookupMetaString, fixDisplayMath)
+import Text.Pandoc.Shared (stringify, pandocVersion)
+import Text.Pandoc.Writers.Shared (lookupMetaString, lookupMetaBlocks,
+ fixDisplayMath)
import Text.Pandoc.UTF8 (fromStringLazy, fromTextLazy, toStringLazy)
import Text.Pandoc.Walk
import Text.Pandoc.Writers.OpenDocument (writeOpenDocument)
@@ -83,6 +85,7 @@ pandocToODT :: PandocMonad m
pandocToODT opts doc@(Pandoc meta _) = do
let title = docTitle meta
let authors = docAuthors meta
+ utctime <- P.getCurrentTime
lang <- toLang (getLang opts meta)
refArchive <-
case writerReferenceDoc opts of
@@ -125,9 +128,14 @@ pandocToODT opts doc@(Pandoc meta _) = do
)
)
let archive' = addEntryToArchive manifestEntry archive
+ -- create meta.xml
let userDefinedMetaFields = [k | k <- Map.keys (unMeta meta)
- , k `notElem` ["title", "lang", "author", "date"]]
+ , k `notElem` ["title", "lang", "author"
+ , "description", "subject", "keywords"]]
let escapedText = text . escapeStringForXML
+ let keywords = case lookupMeta "keywords" meta of
+ Just (MetaList xs) -> map stringify xs
+ _ -> []
let userDefinedMeta =
map (\k -> inTags False "meta:user-defined"
[ ("meta:name", escapeStringForXML k)
@@ -146,19 +154,29 @@ pandocToODT opts doc@(Pandoc meta _) = do
,("xmlns:ooo","http://openoffice.org/2004/office")
,("xmlns:grddl","http://www.w3.org/2003/g/data-view#")
,("office:version","1.2")] ( inTags True "office:meta" [] $
- ( metaTag "dc:title" (stringify title)
+ ( metaTag "meta:generator" ("Pandoc/" ++ pandocVersion)
+ $$
+ metaTag "dc:title" (stringify title)
+ $$
+ metaTag "dc:description"
+ (intercalate "\n" (map stringify $
+ lookupMetaBlocks "description" meta))
+ $$
+ metaTag "dc:subject" (lookupMetaString "subject" meta)
+ $$
+ metaTag "meta:keyword" (intercalate ", " keywords)
$$
case lang of
Just l -> metaTag "dc:language" (renderLang l)
Nothing -> empty
$$
- metaTag "dc:creator"
+ (\d a -> metaTag "meta:initial-creator" a
+ $$ metaTag "dc:creator" a
+ $$ metaTag "meta:creation-date" d
+ $$ metaTag "dc:date" d
+ ) (formatTime defaultTimeLocale "%FT%XZ" utctime)
(intercalate "; " (map stringify authors))
$$
- maybe mempty
- (metaTag "dc:date")
- (normalizeDate (lookupMetaString "date" meta))
- $$
vcat userDefinedMeta
)
)
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
index 3e6652686..7ab50b8c4 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
@@ -58,7 +58,7 @@ import Text.Pandoc.MIME
import qualified Data.ByteString.Lazy as BL
import Text.Pandoc.Writers.OOXML
import qualified Data.Map as M
-import Data.Maybe (mapMaybe, listToMaybe, fromMaybe, maybeToList, catMaybes)
+import Data.Maybe (mapMaybe, listToMaybe, fromMaybe, maybeToList, catMaybes, isNothing)
import Text.Pandoc.ImageSize
import Control.Applicative ((<|>))
import System.FilePath.Glob
@@ -252,6 +252,8 @@ presentationToArchiveP p@(Presentation docProps slides) = do
newArch' <- foldM copyFileToArchive emptyArchive filePaths
-- we make a docProps/core.xml entry out of the presentation docprops
docPropsEntry <- docPropsToEntry docProps
+ -- we make a docProps/custom.xml entry out of the custom properties
+ docCustomPropsEntry <- docCustomPropsToEntry docProps
-- we make this ourself in case there's something unexpected in the
-- one in the reference doc.
relsEntry <- topLevelRelsEntry
@@ -274,7 +276,8 @@ presentationToArchiveP p@(Presentation docProps slides) = do
spkNotesEntries ++
spkNotesRelEntries ++
mediaEntries ++
- [contentTypesEntry, docPropsEntry, relsEntry, presEntry, presRelsEntry]
+ [contentTypesEntry, docPropsEntry, docCustomPropsEntry, relsEntry,
+ presEntry, presRelsEntry]
makeSlideIdMap :: Presentation -> M.Map SlideId Int
makeSlideIdMap (Presentation _ slides) =
@@ -1425,6 +1428,10 @@ topLevelRels =
, relType = "http://schemas.openxmlformats.org/package/2006/relationships/metadata/extended-properties"
, relTarget = "docProps/app.xml"
}
+ , Relationship { relId = 4
+ , relType = "http://schemas.openxmlformats.org/officeDocument/2006/relationships/custom-properties"
+ , relTarget = "docProps/custom.xml"
+ }
]
topLevelRelsEntry :: PandocMonad m => P m Entry
@@ -1657,7 +1664,7 @@ docPropsElement :: PandocMonad m => DocProps -> P m Element
docPropsElement docProps = do
utctime <- asks envUTCTime
let keywords = case dcKeywords docProps of
- Just xs -> intercalate "," xs
+ Just xs -> intercalate ", " xs
Nothing -> ""
return $
mknode "cp:coreProperties"
@@ -1669,7 +1676,13 @@ docPropsElement docProps = do
$ (mknode "dc:title" [] $ fromMaybe "" $ dcTitle docProps)
: (mknode "dc:creator" [] $ fromMaybe "" $ dcCreator docProps)
: (mknode "cp:keywords" [] keywords)
- : (\x -> [ mknode "dcterms:created" [("xsi:type","dcterms:W3CDTF")] x
+ : (if isNothing (dcSubject docProps) then [] else
+ [mknode "dc:subject" [] $ fromMaybe "" $ dcSubject docProps])
+ ++ (if isNothing (dcDescription docProps) then [] else
+ [mknode "dc:description" [] $ fromMaybe "" $ dcDescription docProps])
+ ++ (if isNothing (cpCategory docProps) then [] else
+ [mknode "cp:category" [] $ fromMaybe "" $ cpCategory docProps])
+ ++ (\x -> [ mknode "dcterms:created" [("xsi:type","dcterms:W3CDTF")] x
, mknode "dcterms:modified" [("xsi:type","dcterms:W3CDTF")] x
]) (formatTime defaultTimeLocale "%FT%XZ" utctime)
@@ -1677,6 +1690,21 @@ docPropsToEntry :: PandocMonad m => DocProps -> P m Entry
docPropsToEntry docProps = docPropsElement docProps >>=
elemToEntry "docProps/core.xml"
+-- adapted from the Docx writer
+docCustomPropsElement :: PandocMonad m => DocProps -> P m Element
+docCustomPropsElement docProps = do
+ let mkCustomProp (k, v) pid = mknode "property"
+ [("fmtid","{D5CDD505-2E9C-101B-9397-08002B2CF9AE}")
+ ,("pid", show pid)
+ ,("name", k)] $ mknode "vt:lpwstr" [] v
+ return $ mknode "Properties"
+ [("xmlns","http://schemas.openxmlformats.org/officeDocument/2006/custom-properties")
+ ,("xmlns:vt","http://schemas.openxmlformats.org/officeDocument/2006/docPropsVTypes")
+ ] $ zipWith mkCustomProp (fromMaybe [] $ customProperties docProps) [(2 :: Int)..]
+
+docCustomPropsToEntry :: PandocMonad m => DocProps -> P m Entry
+docCustomPropsToEntry docProps = docCustomPropsElement docProps >>=
+ elemToEntry "docProps/custom.xml"
defaultContentTypeToElem :: DefaultContentType -> Element
defaultContentTypeToElem dct =
@@ -1765,6 +1793,7 @@ presentationToContentTypes p@(Presentation _ slides) = do
inheritedOverrides = mapMaybe pathToOverride filePaths
docPropsOverride = mapMaybe pathToOverride ["docProps/core.xml"]
+ docCustomPropsOverride = mapMaybe pathToOverride ["docProps/custom.xml"]
presOverride = mapMaybe pathToOverride ["ppt/presentation.xml"]
relativePaths <- mapM slideToFilePath slides
let slideOverrides = mapMaybe
@@ -1773,7 +1802,8 @@ presentationToContentTypes p@(Presentation _ slides) = do
speakerNotesOverrides <- (mapMaybe pathToOverride) <$> getSpeakerNotesFilePaths
return $ ContentTypes
(defaults ++ mediaDefaults)
- (inheritedOverrides ++ docPropsOverride ++ presOverride ++ slideOverrides ++ speakerNotesOverrides)
+ (inheritedOverrides ++ docPropsOverride ++ docCustomPropsOverride ++
+ presOverride ++ slideOverrides ++ speakerNotesOverrides)
presML :: String
presML = "application/vnd.openxmlformats-officedocument.presentationml"
@@ -1788,6 +1818,7 @@ getContentType fp
| fp == "ppt/viewProps.xml" = Just $ presML ++ ".viewProps+xml"
| fp == "ppt/tableStyles.xml" = Just $ presML ++ ".tableStyles+xml"
| fp == "docProps/core.xml" = Just $ "application/vnd.openxmlformats-package.core-properties+xml"
+ | fp == "docProps/custom.xml" = Just $ "application/vnd.openxmlformats-officedocument.custom-properties+xml"
| fp == "docProps/app.xml" = Just $ noPresML ++ ".extended-properties+xml"
| "ppt" : "slideMasters" : f : [] <- splitDirectories fp
, (_, ".xml") <- splitExtension f =
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
index 7897f2b11..fee1a0f6e 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
@@ -72,7 +72,8 @@ import Text.Pandoc.Logging
import Text.Pandoc.Walk
import Data.Time (UTCTime)
import qualified Text.Pandoc.Shared as Shared -- so we don't overlap "Element"
-import Text.Pandoc.Writers.Shared (lookupMetaInlines, toTableOfContents)
+import Text.Pandoc.Writers.Shared (lookupMetaInlines, lookupMetaBlocks
+ , lookupMetaString, toTableOfContents)
import qualified Data.Map as M
import qualified Data.Set as S
import Data.Maybe (maybeToList, fromMaybe)
@@ -180,7 +181,10 @@ data DocProps = DocProps { dcTitle :: Maybe String
, dcSubject :: Maybe String
, dcCreator :: Maybe String
, dcKeywords :: Maybe [String]
+ , dcDescription :: Maybe String
+ , cpCategory :: Maybe String
, dcCreated :: Maybe UTCTime
+ , customProperties :: Maybe [(String, String)]
} deriving (Show, Eq)
@@ -930,13 +934,26 @@ metaToDocProps meta =
authors = case map Shared.stringify $ docAuthors meta of
[] -> Nothing
- ss -> Just $ intercalate ";" ss
+ ss -> Just $ intercalate "; " ss
+
+ description = case map Shared.stringify $ lookupMetaBlocks "description" meta of
+ [] -> Nothing
+ ss -> Just $ intercalate "_x000d_\n" ss
+
+ customProperties' = case [(k, lookupMetaString k meta) | k <- M.keys (unMeta meta)
+ , k `notElem` (["title", "author", "keywords", "description"
+ , "subject","lang","category"])] of
+ [] -> Nothing
+ ss -> Just ss
in
DocProps{ dcTitle = Shared.stringify <$> lookupMeta "title" meta
, dcSubject = Shared.stringify <$> lookupMeta "subject" meta
, dcCreator = authors
, dcKeywords = keywords
+ , dcDescription = description
+ , cpCategory = Shared.stringify <$> lookupMeta "category" meta
, dcCreated = Nothing
+ , customProperties = customProperties'
}
documentToPresentation :: WriterOptions
diff --git a/test/Tests/Writers/Docx.hs b/test/Tests/Writers/Docx.hs
index d17984d63..c958ddf7d 100644
--- a/test/Tests/Writers/Docx.hs
+++ b/test/Tests/Writers/Docx.hs
@@ -156,4 +156,14 @@ tests = [ testGroup "inlines"
"docx/custom_style.native"
"docx/golden/custom_style_reference.docx"
]
+ , testGroup "metadata"
+ [ docxTest "document properties (core, custom)"
+ def
+ "docx/document-properties.native"
+ "docx/golden/document-properties.docx"
+ , docxTest "document properties (short description)"
+ def
+ "docx/document-properties-short-desc.native"
+ "docx/golden/document-properties-short-desc.docx"
+ ]
]
diff --git a/test/Tests/Writers/Powerpoint.hs b/test/Tests/Writers/Powerpoint.hs
index f3016cdb6..9c5409310 100644
--- a/test/Tests/Writers/Powerpoint.hs
+++ b/test/Tests/Writers/Powerpoint.hs
@@ -99,4 +99,12 @@ tests = groupPptxTests [ pptxTests "Inline formatting"
def
"pptx/raw_ooxml.native"
"pptx/raw_ooxml.pptx"
+ , pptxTests "metadata, custom properties"
+ def
+ "pptx/document-properties.native"
+ "pptx/document-properties.pptx"
+ , pptxTests "metadata, short description"
+ def
+ "pptx/document-properties-short-desc.native"
+ "pptx/document-properties-short-desc.pptx"
]
diff --git a/test/docx/document-properties-short-desc.native b/test/docx/document-properties-short-desc.native
new file mode 100644
index 000000000..fe3193dc1
--- /dev/null
+++ b/test/docx/document-properties-short-desc.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") "<i>",Str "description",RawInline (Format "html") "</i>",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/docx/document-properties.native b/test/docx/document-properties.native
new file mode 100644
index 000000000..59ca53f4d
--- /dev/null
+++ b/test/docx/document-properties.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") "<i>",Str "asdf",RawInline (Format "html") "</i>"]),("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") "<i>",Str "line",RawInline (Format "html") "</i>",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/docx/golden/document-properties-short-desc.docx b/test/docx/golden/document-properties-short-desc.docx
new file mode 100644
index 000000000..ae2813b90
--- /dev/null
+++ b/test/docx/golden/document-properties-short-desc.docx
Binary files differ
diff --git a/test/docx/golden/document-properties.docx b/test/docx/golden/document-properties.docx
new file mode 100644
index 000000000..5db470cd1
--- /dev/null
+++ b/test/docx/golden/document-properties.docx
Binary files differ
diff --git a/test/pptx/document-properties-short-desc.native b/test/pptx/document-properties-short-desc.native
new file mode 100644
index 000000000..fe3193dc1
--- /dev/null
+++ b/test/pptx/document-properties-short-desc.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") "<i>",Str "description",RawInline (Format "html") "</i>",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
new file mode 100644
index 000000000..7f5ef2704
--- /dev/null
+++ b/test/pptx/document-properties-short-desc.pptx
Binary files 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..527b65004
--- /dev/null
+++ b/test/pptx/document-properties-short-desc_templated.pptx
Binary files differ
diff --git a/test/pptx/document-properties.native b/test/pptx/document-properties.native
new file mode 100644
index 000000000..59ca53f4d
--- /dev/null
+++ b/test/pptx/document-properties.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") "<i>",Str "asdf",RawInline (Format "html") "</i>"]),("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") "<i>",Str "line",RawInline (Format "html") "</i>",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
new file mode 100644
index 000000000..b35ff771e
--- /dev/null
+++ b/test/pptx/document-properties.pptx
Binary files differ
diff --git a/test/pptx/document-properties_templated.pptx b/test/pptx/document-properties_templated.pptx
new file mode 100644
index 000000000..89a048592
--- /dev/null
+++ b/test/pptx/document-properties_templated.pptx
Binary files differ
diff --git a/test/pptx/endnotes.pptx b/test/pptx/endnotes.pptx
index f9bb17937..49209b21c 100644
--- a/test/pptx/endnotes.pptx
+++ b/test/pptx/endnotes.pptx
Binary files differ
diff --git a/test/pptx/endnotes_templated.pptx b/test/pptx/endnotes_templated.pptx
index 4e99c22e1..5972d61cf 100644
--- a/test/pptx/endnotes_templated.pptx
+++ b/test/pptx/endnotes_templated.pptx
Binary files differ
diff --git a/test/pptx/endnotes_toc.pptx b/test/pptx/endnotes_toc.pptx
index ec09e6f9d..5429f5e9a 100644
--- a/test/pptx/endnotes_toc.pptx
+++ b/test/pptx/endnotes_toc.pptx
Binary files differ
diff --git a/test/pptx/endnotes_toc_templated.pptx b/test/pptx/endnotes_toc_templated.pptx
index e6896a7d5..30b9a8326 100644
--- a/test/pptx/endnotes_toc_templated.pptx
+++ b/test/pptx/endnotes_toc_templated.pptx
Binary files differ
diff --git a/test/pptx/images.pptx b/test/pptx/images.pptx
index c9798422f..46d6747aa 100644
--- a/test/pptx/images.pptx
+++ b/test/pptx/images.pptx
Binary files differ
diff --git a/test/pptx/images_templated.pptx b/test/pptx/images_templated.pptx
index d9c93731c..cecd4d60f 100644
--- a/test/pptx/images_templated.pptx
+++ b/test/pptx/images_templated.pptx
Binary files differ
diff --git a/test/pptx/inline_formatting.pptx b/test/pptx/inline_formatting.pptx
index 3a69400ff..0598d6344 100644
--- a/test/pptx/inline_formatting.pptx
+++ b/test/pptx/inline_formatting.pptx
Binary files differ
diff --git a/test/pptx/inline_formatting_templated.pptx b/test/pptx/inline_formatting_templated.pptx
index ca44d82e6..32efe34bd 100644
--- a/test/pptx/inline_formatting_templated.pptx
+++ b/test/pptx/inline_formatting_templated.pptx
Binary files differ
diff --git a/test/pptx/lists.pptx b/test/pptx/lists.pptx
index c28e840f1..807b634db 100644
--- a/test/pptx/lists.pptx
+++ b/test/pptx/lists.pptx
Binary files differ
diff --git a/test/pptx/lists_templated.pptx b/test/pptx/lists_templated.pptx
index 74505454e..176afd554 100644
--- a/test/pptx/lists_templated.pptx
+++ b/test/pptx/lists_templated.pptx
Binary files differ
diff --git a/test/pptx/raw_ooxml.pptx b/test/pptx/raw_ooxml.pptx
index e71fb2f01..eb6bf6c36 100644
--- a/test/pptx/raw_ooxml.pptx
+++ b/test/pptx/raw_ooxml.pptx
Binary files differ
diff --git a/test/pptx/raw_ooxml_templated.pptx b/test/pptx/raw_ooxml_templated.pptx
index c0e72ca10..808b83b70 100644
--- a/test/pptx/raw_ooxml_templated.pptx
+++ b/test/pptx/raw_ooxml_templated.pptx
Binary files differ
diff --git a/test/pptx/remove_empty_slides.pptx b/test/pptx/remove_empty_slides.pptx
index 3b4843aa6..edda16a06 100644
--- a/test/pptx/remove_empty_slides.pptx
+++ b/test/pptx/remove_empty_slides.pptx
Binary files differ
diff --git a/test/pptx/remove_empty_slides_templated.pptx b/test/pptx/remove_empty_slides_templated.pptx
index 1efe33212..d5e026da0 100644
--- a/test/pptx/remove_empty_slides_templated.pptx
+++ b/test/pptx/remove_empty_slides_templated.pptx
Binary files differ
diff --git a/test/pptx/slide_breaks.pptx b/test/pptx/slide_breaks.pptx
index dabb58117..5e0a89129 100644
--- a/test/pptx/slide_breaks.pptx
+++ b/test/pptx/slide_breaks.pptx
Binary files differ
diff --git a/test/pptx/slide_breaks_slide_level_1.pptx b/test/pptx/slide_breaks_slide_level_1.pptx
index 65a44737d..566ac57ea 100644
--- a/test/pptx/slide_breaks_slide_level_1.pptx
+++ b/test/pptx/slide_breaks_slide_level_1.pptx
Binary files differ
diff --git a/test/pptx/slide_breaks_slide_level_1_templated.pptx b/test/pptx/slide_breaks_slide_level_1_templated.pptx
index 9770a5da0..5b971a6cc 100644
--- a/test/pptx/slide_breaks_slide_level_1_templated.pptx
+++ b/test/pptx/slide_breaks_slide_level_1_templated.pptx
Binary files differ
diff --git a/test/pptx/slide_breaks_templated.pptx b/test/pptx/slide_breaks_templated.pptx
index 25d199d3b..434af5bcb 100644
--- a/test/pptx/slide_breaks_templated.pptx
+++ b/test/pptx/slide_breaks_templated.pptx
Binary files differ
diff --git a/test/pptx/slide_breaks_toc.pptx b/test/pptx/slide_breaks_toc.pptx
index b51e94fbd..3f4fe1500 100644
--- a/test/pptx/slide_breaks_toc.pptx
+++ b/test/pptx/slide_breaks_toc.pptx
Binary files differ
diff --git a/test/pptx/slide_breaks_toc_templated.pptx b/test/pptx/slide_breaks_toc_templated.pptx
index 3d65242bb..7cb134f1b 100644
--- a/test/pptx/slide_breaks_toc_templated.pptx
+++ b/test/pptx/slide_breaks_toc_templated.pptx
Binary files differ
diff --git a/test/pptx/speaker_notes.pptx b/test/pptx/speaker_notes.pptx
index a9fad5ae4..51a156883 100644
--- a/test/pptx/speaker_notes.pptx
+++ b/test/pptx/speaker_notes.pptx
Binary files differ
diff --git a/test/pptx/speaker_notes_afterseps.pptx b/test/pptx/speaker_notes_afterseps.pptx
index a7ba1c0d4..8dbebdd96 100644
--- a/test/pptx/speaker_notes_afterseps.pptx
+++ b/test/pptx/speaker_notes_afterseps.pptx
Binary files differ
diff --git a/test/pptx/speaker_notes_afterseps_templated.pptx b/test/pptx/speaker_notes_afterseps_templated.pptx
index 73a142d1c..e90fb5672 100644
--- a/test/pptx/speaker_notes_afterseps_templated.pptx
+++ b/test/pptx/speaker_notes_afterseps_templated.pptx
Binary files differ
diff --git a/test/pptx/speaker_notes_templated.pptx b/test/pptx/speaker_notes_templated.pptx
index 9ae8ea1db..4fe6f284e 100644
--- a/test/pptx/speaker_notes_templated.pptx
+++ b/test/pptx/speaker_notes_templated.pptx
Binary files differ
diff --git a/test/pptx/tables.pptx b/test/pptx/tables.pptx
index c3e215a30..3b393393a 100644
--- a/test/pptx/tables.pptx
+++ b/test/pptx/tables.pptx
Binary files differ
diff --git a/test/pptx/tables_templated.pptx b/test/pptx/tables_templated.pptx
index 53de9b886..349792dc1 100644
--- a/test/pptx/tables_templated.pptx
+++ b/test/pptx/tables_templated.pptx
Binary files differ
diff --git a/test/pptx/two_column.pptx b/test/pptx/two_column.pptx
index 68b390bb7..343700084 100644
--- a/test/pptx/two_column.pptx
+++ b/test/pptx/two_column.pptx
Binary files differ
diff --git a/test/pptx/two_column_templated.pptx b/test/pptx/two_column_templated.pptx
index f74be1956..03eb598af 100644
--- a/test/pptx/two_column_templated.pptx
+++ b/test/pptx/two_column_templated.pptx
Binary files differ