Improve writing metadata for docx, pptx and odt (#5252)

* docx writer: support custom properties.  Solves the writer part of #3024.
  Also supports additional core properties:  `subject`, `lang`, `category`,
  `description`.

* odt writer: improve standard properties, including the following core properties:
  `generator` (Pandoc/VERSION), `description`, `subject`, `keywords`,
  `initial-creator` (from authors), `creation-date` (actual creation date).
  Also fix date.

* pptx writer: support custom properties.  Also supports additional core
  properties: `subject`, `category`, `description`.

* Includes golden tests.

* MANUAL: document metadata support for docx, odt, pptx writers
This commit is contained in:
Agustín Martín Barbero 2019-01-26 16:14:35 -08:00 committed by John MacFarlane
parent ff0aaa549d
commit 9894d05fe3
45 changed files with 165 additions and 24 deletions

View file

@ -1355,7 +1355,7 @@ directory (see `--data-dir`, above). *Exceptions:*
(or the `default.context` template, if you use `-t context`, (or the `default.context` template, if you use `-t context`,
or the `default.ms` template, if you use `-t ms`, or the or the `default.ms` template, if you use `-t ms`, or the
`default.html` template, if you use `-t html`). `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). `--reference-doc` to customize the output).
Templates contain *variables*, which allow for the inclusion of 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, 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 pandoc will look for the key in the document's metadata which can be set
using either [YAML metadata blocks][Extension: `yaml_metadata_block`] using either [YAML metadata blocks][Extension: `yaml_metadata_block`]
or with the `--metadata` option. or with the `-M/--metadata` option.
Metadata variables Metadata variables
------------------ ------------------
@ -1381,14 +1381,48 @@ Metadata variables
... ...
`subtitle` `subtitle`
: document subtitle, included in HTML, EPUB, LaTeX, ConTeXt, and Word docx : document subtitle, included in HTML, EPUB, LaTeX, ConTeXt, and docx
documents
`abstract` `abstract`
: document summary, included in LaTeX, ConTeXt, AsciiDoc, and Word docx : document summary, included in LaTeX, ConTeXt, AsciiDoc, and docx
documents
`keywords` `keywords`
: list of keywords to be included in HTML, PDF, and AsciiDoc metadata; : list of keywords to be included in HTML, PDF, ODT, pptx, docx
repeat as for `author`, above 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 Language variables
------------------ ------------------

View file

@ -496,7 +496,17 @@ writeDocx opts doc@(Pandoc meta _) = do
Just (MetaList xs) -> map stringify xs Just (MetaList xs) -> map stringify xs
_ -> [] _ -> []
-- docProps/core.xml
let docPropsPath = "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" let docProps = mknode "cp:coreProperties"
[("xmlns:cp","http://schemas.openxmlformats.org/package/2006/metadata/core-properties") [("xmlns:cp","http://schemas.openxmlformats.org/package/2006/metadata/core-properties")
,("xmlns:dc","http://purl.org/dc/elements/1.1/") ,("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")] ,("xmlns:xsi","http://www.w3.org/2001/XMLSchema-instance")]
$ mknode "dc:title" [] (stringify $ docTitle meta) $ mknode "dc:title" [] (stringify $ docTitle meta)
: mknode "dc:creator" [] (intercalate "; " (map stringify $ docAuthors 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 : (\x -> [ mknode "dcterms:created" [("xsi:type","dcterms:W3CDTF")] x
, mknode "dcterms:modified" [("xsi:type","dcterms:W3CDTF")] x , mknode "dcterms:modified" [("xsi:type","dcterms:W3CDTF")] x
]) (formatTime defaultTimeLocale "%FT%XZ" utctime) ]) (formatTime defaultTimeLocale "%FT%XZ" utctime)
let docPropsEntry = toEntry docPropsPath epochtime $ renderXml docProps let docPropsEntry = toEntry docPropsPath epochtime $ renderXml docProps
-- docProps/custom.xml
let customProperties :: [(String, String)] 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" let mkCustomProp (k, v) pid = mknode "property"
[("fmtid","{D5CDD505-2E9C-101B-9397-08002B2CF9AE}") [("fmtid","{D5CDD505-2E9C-101B-9397-08002B2CF9AE}")
,("pid", show pid) ,("pid", show pid)

View file

@ -40,6 +40,7 @@ import Data.List (isPrefixOf, intercalate)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import qualified Data.Map as Map import qualified Data.Map as Map
import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy as TL
import Data.Time
import System.FilePath (takeDirectory, takeExtension, (<.>)) import System.FilePath (takeDirectory, takeExtension, (<.>))
import Text.Pandoc.BCP47 (Lang (..), getLang, renderLang) import Text.Pandoc.BCP47 (Lang (..), getLang, renderLang)
import Text.Pandoc.Class (PandocMonad, report, toLang) import Text.Pandoc.Class (PandocMonad, report, toLang)
@ -50,8 +51,9 @@ import Text.Pandoc.Logging
import Text.Pandoc.MIME (extensionFromMimeType, getMimeType) import Text.Pandoc.MIME (extensionFromMimeType, getMimeType)
import Text.Pandoc.Options (WrapOption (..), WriterOptions (..)) import Text.Pandoc.Options (WrapOption (..), WriterOptions (..))
import Text.Pandoc.Pretty import Text.Pandoc.Pretty
import Text.Pandoc.Shared (stringify, normalizeDate) import Text.Pandoc.Shared (stringify, pandocVersion)
import Text.Pandoc.Writers.Shared (lookupMetaString, fixDisplayMath) import Text.Pandoc.Writers.Shared (lookupMetaString, lookupMetaBlocks,
fixDisplayMath)
import Text.Pandoc.UTF8 (fromStringLazy, fromTextLazy, toStringLazy) import Text.Pandoc.UTF8 (fromStringLazy, fromTextLazy, toStringLazy)
import Text.Pandoc.Walk import Text.Pandoc.Walk
import Text.Pandoc.Writers.OpenDocument (writeOpenDocument) import Text.Pandoc.Writers.OpenDocument (writeOpenDocument)
@ -83,6 +85,7 @@ pandocToODT :: PandocMonad m
pandocToODT opts doc@(Pandoc meta _) = do pandocToODT opts doc@(Pandoc meta _) = do
let title = docTitle meta let title = docTitle meta
let authors = docAuthors meta let authors = docAuthors meta
utctime <- P.getCurrentTime
lang <- toLang (getLang opts meta) lang <- toLang (getLang opts meta)
refArchive <- refArchive <-
case writerReferenceDoc opts of case writerReferenceDoc opts of
@ -125,9 +128,14 @@ pandocToODT opts doc@(Pandoc meta _) = do
) )
) )
let archive' = addEntryToArchive manifestEntry archive let archive' = addEntryToArchive manifestEntry archive
-- create meta.xml
let userDefinedMetaFields = [k | k <- Map.keys (unMeta meta) 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 escapedText = text . escapeStringForXML
let keywords = case lookupMeta "keywords" meta of
Just (MetaList xs) -> map stringify xs
_ -> []
let userDefinedMeta = let userDefinedMeta =
map (\k -> inTags False "meta:user-defined" map (\k -> inTags False "meta:user-defined"
[ ("meta:name", escapeStringForXML k) [ ("meta:name", escapeStringForXML k)
@ -146,19 +154,29 @@ pandocToODT opts doc@(Pandoc meta _) = do
,("xmlns:ooo","http://openoffice.org/2004/office") ,("xmlns:ooo","http://openoffice.org/2004/office")
,("xmlns:grddl","http://www.w3.org/2003/g/data-view#") ,("xmlns:grddl","http://www.w3.org/2003/g/data-view#")
,("office:version","1.2")] ( inTags True "office:meta" [] $ ,("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 case lang of
Just l -> metaTag "dc:language" (renderLang l) Just l -> metaTag "dc:language" (renderLang l)
Nothing -> empty 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)) (intercalate "; " (map stringify authors))
$$ $$
maybe mempty
(metaTag "dc:date")
(normalizeDate (lookupMetaString "date" meta))
$$
vcat userDefinedMeta vcat userDefinedMeta
) )
) )

View file

@ -58,7 +58,7 @@ import Text.Pandoc.MIME
import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Lazy as BL
import Text.Pandoc.Writers.OOXML import Text.Pandoc.Writers.OOXML
import qualified Data.Map as M 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 Text.Pandoc.ImageSize
import Control.Applicative ((<|>)) import Control.Applicative ((<|>))
import System.FilePath.Glob import System.FilePath.Glob
@ -252,6 +252,8 @@ presentationToArchiveP p@(Presentation docProps slides) = do
newArch' <- foldM copyFileToArchive emptyArchive filePaths newArch' <- foldM copyFileToArchive emptyArchive filePaths
-- we make a docProps/core.xml entry out of the presentation docprops -- we make a docProps/core.xml entry out of the presentation docprops
docPropsEntry <- docPropsToEntry 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 -- we make this ourself in case there's something unexpected in the
-- one in the reference doc. -- one in the reference doc.
relsEntry <- topLevelRelsEntry relsEntry <- topLevelRelsEntry
@ -274,7 +276,8 @@ presentationToArchiveP p@(Presentation docProps slides) = do
spkNotesEntries ++ spkNotesEntries ++
spkNotesRelEntries ++ spkNotesRelEntries ++
mediaEntries ++ mediaEntries ++
[contentTypesEntry, docPropsEntry, relsEntry, presEntry, presRelsEntry] [contentTypesEntry, docPropsEntry, docCustomPropsEntry, relsEntry,
presEntry, presRelsEntry]
makeSlideIdMap :: Presentation -> M.Map SlideId Int makeSlideIdMap :: Presentation -> M.Map SlideId Int
makeSlideIdMap (Presentation _ slides) = makeSlideIdMap (Presentation _ slides) =
@ -1425,6 +1428,10 @@ topLevelRels =
, relType = "http://schemas.openxmlformats.org/package/2006/relationships/metadata/extended-properties" , relType = "http://schemas.openxmlformats.org/package/2006/relationships/metadata/extended-properties"
, relTarget = "docProps/app.xml" , 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 topLevelRelsEntry :: PandocMonad m => P m Entry
@ -1657,7 +1664,7 @@ docPropsElement :: PandocMonad m => DocProps -> P m Element
docPropsElement docProps = do docPropsElement docProps = do
utctime <- asks envUTCTime utctime <- asks envUTCTime
let keywords = case dcKeywords docProps of let keywords = case dcKeywords docProps of
Just xs -> intercalate "," xs Just xs -> intercalate ", " xs
Nothing -> "" Nothing -> ""
return $ return $
mknode "cp:coreProperties" mknode "cp:coreProperties"
@ -1669,7 +1676,13 @@ docPropsElement docProps = do
$ (mknode "dc:title" [] $ fromMaybe "" $ dcTitle docProps) $ (mknode "dc:title" [] $ fromMaybe "" $ dcTitle docProps)
: (mknode "dc:creator" [] $ fromMaybe "" $ dcCreator docProps) : (mknode "dc:creator" [] $ fromMaybe "" $ dcCreator docProps)
: (mknode "cp:keywords" [] keywords) : (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 , mknode "dcterms:modified" [("xsi:type","dcterms:W3CDTF")] x
]) (formatTime defaultTimeLocale "%FT%XZ" utctime) ]) (formatTime defaultTimeLocale "%FT%XZ" utctime)
@ -1677,6 +1690,21 @@ docPropsToEntry :: PandocMonad m => DocProps -> P m Entry
docPropsToEntry docProps = docPropsElement docProps >>= docPropsToEntry docProps = docPropsElement docProps >>=
elemToEntry "docProps/core.xml" 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 :: DefaultContentType -> Element
defaultContentTypeToElem dct = defaultContentTypeToElem dct =
@ -1765,6 +1793,7 @@ presentationToContentTypes p@(Presentation _ slides) = do
inheritedOverrides = mapMaybe pathToOverride filePaths inheritedOverrides = mapMaybe pathToOverride filePaths
docPropsOverride = mapMaybe pathToOverride ["docProps/core.xml"] docPropsOverride = mapMaybe pathToOverride ["docProps/core.xml"]
docCustomPropsOverride = mapMaybe pathToOverride ["docProps/custom.xml"]
presOverride = mapMaybe pathToOverride ["ppt/presentation.xml"] presOverride = mapMaybe pathToOverride ["ppt/presentation.xml"]
relativePaths <- mapM slideToFilePath slides relativePaths <- mapM slideToFilePath slides
let slideOverrides = mapMaybe let slideOverrides = mapMaybe
@ -1773,7 +1802,8 @@ presentationToContentTypes p@(Presentation _ slides) = do
speakerNotesOverrides <- (mapMaybe pathToOverride) <$> getSpeakerNotesFilePaths speakerNotesOverrides <- (mapMaybe pathToOverride) <$> getSpeakerNotesFilePaths
return $ ContentTypes return $ ContentTypes
(defaults ++ mediaDefaults) (defaults ++ mediaDefaults)
(inheritedOverrides ++ docPropsOverride ++ presOverride ++ slideOverrides ++ speakerNotesOverrides) (inheritedOverrides ++ docPropsOverride ++ docCustomPropsOverride ++
presOverride ++ slideOverrides ++ speakerNotesOverrides)
presML :: String presML :: String
presML = "application/vnd.openxmlformats-officedocument.presentationml" presML = "application/vnd.openxmlformats-officedocument.presentationml"
@ -1788,6 +1818,7 @@ getContentType fp
| fp == "ppt/viewProps.xml" = Just $ presML ++ ".viewProps+xml" | fp == "ppt/viewProps.xml" = Just $ presML ++ ".viewProps+xml"
| fp == "ppt/tableStyles.xml" = Just $ presML ++ ".tableStyles+xml" | fp == "ppt/tableStyles.xml" = Just $ presML ++ ".tableStyles+xml"
| fp == "docProps/core.xml" = Just $ "application/vnd.openxmlformats-package.core-properties+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" | fp == "docProps/app.xml" = Just $ noPresML ++ ".extended-properties+xml"
| "ppt" : "slideMasters" : f : [] <- splitDirectories fp | "ppt" : "slideMasters" : f : [] <- splitDirectories fp
, (_, ".xml") <- splitExtension f = , (_, ".xml") <- splitExtension f =

View file

@ -72,7 +72,8 @@ import Text.Pandoc.Logging
import Text.Pandoc.Walk import Text.Pandoc.Walk
import Data.Time (UTCTime) import Data.Time (UTCTime)
import qualified Text.Pandoc.Shared as Shared -- so we don't overlap "Element" 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.Map as M
import qualified Data.Set as S import qualified Data.Set as S
import Data.Maybe (maybeToList, fromMaybe) import Data.Maybe (maybeToList, fromMaybe)
@ -180,7 +181,10 @@ data DocProps = DocProps { dcTitle :: Maybe String
, dcSubject :: Maybe String , dcSubject :: Maybe String
, dcCreator :: Maybe String , dcCreator :: Maybe String
, dcKeywords :: Maybe [String] , dcKeywords :: Maybe [String]
, dcDescription :: Maybe String
, cpCategory :: Maybe String
, dcCreated :: Maybe UTCTime , dcCreated :: Maybe UTCTime
, customProperties :: Maybe [(String, String)]
} deriving (Show, Eq) } deriving (Show, Eq)
@ -930,13 +934,26 @@ metaToDocProps meta =
authors = case map Shared.stringify $ docAuthors meta of authors = case map Shared.stringify $ docAuthors meta of
[] -> Nothing [] -> 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 in
DocProps{ dcTitle = Shared.stringify <$> lookupMeta "title" meta DocProps{ dcTitle = Shared.stringify <$> lookupMeta "title" meta
, dcSubject = Shared.stringify <$> lookupMeta "subject" meta , dcSubject = Shared.stringify <$> lookupMeta "subject" meta
, dcCreator = authors , dcCreator = authors
, dcKeywords = keywords , dcKeywords = keywords
, dcDescription = description
, cpCategory = Shared.stringify <$> lookupMeta "category" meta
, dcCreated = Nothing , dcCreated = Nothing
, customProperties = customProperties'
} }
documentToPresentation :: WriterOptions documentToPresentation :: WriterOptions

View file

@ -156,4 +156,14 @@ tests = [ testGroup "inlines"
"docx/custom_style.native" "docx/custom_style.native"
"docx/golden/custom_style_reference.docx" "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"
]
] ]

View file

@ -99,4 +99,12 @@ tests = groupPptxTests [ pptxTests "Inline formatting"
def def
"pptx/raw_ooxml.native" "pptx/raw_ooxml.native"
"pptx/raw_ooxml.pptx" "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"
] ]

View file

@ -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"]]

View file

@ -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"]]

Binary file not shown.

Binary file not shown.

View file

@ -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"]]

Binary file not shown.

View file

@ -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"]]

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.