aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2024-05-19 10:47:46 -0700
committerJohn MacFarlane <[email protected]>2024-05-19 13:09:21 -0700
commitdb559e100c02ca1f95953f3eeeca005fdc01b595 (patch)
tree3eaad4d8b4449deaa54b29c3eed1f8da870e1a95
parente8f44a854310a134249d89e8e6cfa5245afbc84e (diff)
Allow OpenXML templates to be used with `docx`.
The `--reference-doc` option allows customization of styles in docx output, but it does not allow one to adjust the content of the output (e.g., changing the order in which metadata, the table of contents, and the body of the document are displayed), or adding boilerplate text before or after the document body. For these changes, one can now use `--template` with an OpenXML template. (See the default `openxml` template for a sample.) This patch also allows `--include-before-body` and `--include-after-body` to be used with `docx` output. The included files must be OpenXML fragments suitable for inclusion in the document body. Closes #8338 (`--include-before-body`, `--include-after-body`). Closes #9069 (a custom template can be used to omit the title page). Closes #7256. Closes #2928.
-rw-r--r--MANUAL.txt12
-rw-r--r--data/templates/default.openxml69
-rw-r--r--pandoc.cabal1
-rw-r--r--src/Text/Pandoc/Templates.hs2
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs117
-rw-r--r--src/Text/Pandoc/Writers/Docx/OpenXML.hs60
-rw-r--r--test/docx/golden/block_quotes.docxbin10646 -> 10658 bytes
-rw-r--r--test/docx/golden/codeblock.docxbin10461 -> 10475 bytes
-rw-r--r--test/docx/golden/comments.docxbin10794 -> 10805 bytes
-rw-r--r--test/docx/golden/custom_style_no_reference.docxbin10564 -> 10577 bytes
-rw-r--r--test/docx/golden/custom_style_preserve.docxbin11192 -> 11204 bytes
-rw-r--r--test/docx/golden/custom_style_reference.docxbin12519 -> 12427 bytes
-rw-r--r--test/docx/golden/definition_list.docxbin10460 -> 10475 bytes
-rw-r--r--test/docx/golden/document-properties-short-desc.docxbin10467 -> 10436 bytes
-rw-r--r--test/docx/golden/document-properties.docxbin10953 -> 10925 bytes
-rw-r--r--test/docx/golden/headers.docxbin10600 -> 10615 bytes
-rw-r--r--test/docx/golden/image.docxbin27342 -> 27355 bytes
-rw-r--r--test/docx/golden/inline_code.docxbin10400 -> 10414 bytes
-rw-r--r--test/docx/golden/inline_formatting.docxbin10581 -> 10593 bytes
-rw-r--r--test/docx/golden/inline_images.docxbin27340 -> 27351 bytes
-rw-r--r--test/docx/golden/link_in_notes.docxbin10622 -> 10636 bytes
-rw-r--r--test/docx/golden/links.docxbin10793 -> 10805 bytes
-rw-r--r--test/docx/golden/lists.docxbin10992 -> 11006 bytes
-rw-r--r--test/docx/golden/lists_continuing.docxbin10656 -> 10668 bytes
-rw-r--r--test/docx/golden/lists_div_bullets.docxbin10640 -> 10652 bytes
-rw-r--r--test/docx/golden/lists_multiple_initial.docxbin10874 -> 10886 bytes
-rw-r--r--test/docx/golden/lists_restarting.docxbin10654 -> 10666 bytes
-rw-r--r--test/docx/golden/nested_anchors_in_header.docxbin10793 -> 10807 bytes
-rw-r--r--test/docx/golden/notes.docxbin10569 -> 10584 bytes
-rw-r--r--test/docx/golden/raw-blocks.docxbin10501 -> 10513 bytes
-rw-r--r--test/docx/golden/raw-bookmarks.docxbin10635 -> 10647 bytes
-rw-r--r--test/docx/golden/table_one_row.docxbin10484 -> 10497 bytes
-rw-r--r--test/docx/golden/table_with_list_cell.docxbin10933 -> 10947 bytes
-rw-r--r--test/docx/golden/tables-default-widths.docxbin10829 -> 10848 bytes
-rw-r--r--test/docx/golden/tables.docxbin10843 -> 10862 bytes
-rw-r--r--test/docx/golden/tables_separated_with_rawblock.docxbin10482 -> 10493 bytes
-rw-r--r--test/docx/golden/track_changes_deletion.docxbin10444 -> 10458 bytes
-rw-r--r--test/docx/golden/track_changes_insertion.docxbin10427 -> 10440 bytes
-rw-r--r--test/docx/golden/track_changes_move.docxbin10461 -> 10471 bytes
-rw-r--r--test/docx/golden/track_changes_scrubbed_metadata.docxbin10570 -> 10584 bytes
-rw-r--r--test/docx/golden/unicode.docxbin10386 -> 10398 bytes
-rw-r--r--test/docx/golden/verbatim_subsuper.docxbin10433 -> 10445 bytes
42 files changed, 170 insertions, 91 deletions
diff --git a/MANUAL.txt b/MANUAL.txt
index 5865ea720..c309e0638 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -928,7 +928,11 @@ header when requesting a document from a URL:
`\begin{document}` command in LaTeX). This can be used to include
navigation bars or banners in HTML documents. This option can be
used repeatedly to include multiple files. They will be included in
- the order specified. Implies `--standalone`.
+ the order specified. Implies `--standalone`. Note that if the
+ output format is `odt`, this file must be in OpenDocument XML format
+ suitable for insertion into the body of the document, and if
+ the output is `docx`, this file must be in appropriate
+ OpenXML format.
`-A` *FILE*, `--include-after-body=`*FILE*|*URL*
@@ -936,7 +940,11 @@ header when requesting a document from a URL:
body (before the `</body>` tag in HTML, or the
`\end{document}` command in LaTeX). This option can be used
repeatedly to include multiple files. They will be included in the
- order specified. Implies `--standalone`.
+ order specified. Implies `--standalone`. Note that if the
+ output format is `odt`, this file must be in OpenDocument XML format
+ suitable for insertion into the body of the document, and if
+ the output is `docx`, this file must be in appropriate
+ OpenXML format.
`--resource-path=`*SEARCHPATH*
diff --git a/data/templates/default.openxml b/data/templates/default.openxml
new file mode 100644
index 000000000..b002e3496
--- /dev/null
+++ b/data/templates/default.openxml
@@ -0,0 +1,69 @@
+<?xml version="1.0" encoding="UTF-8"?>
+<w:document xmlns:w="http://schemas.openxmlformats.org/wordprocessingml/2006/main" xmlns:m="http://schemas.openxmlformats.org/officeDocument/2006/math" xmlns:r="http://schemas.openxmlformats.org/officeDocument/2006/relationships" xmlns:o="urn:schemas-microsoft-com:office:office" xmlns:v="urn:schemas-microsoft-com:vml" xmlns:w10="urn:schemas-microsoft-com:office:word" xmlns:a="http://schemas.openxmlformats.org/drawingml/2006/main" xmlns:pic="http://schemas.openxmlformats.org/drawingml/2006/picture" xmlns:wp="http://schemas.openxmlformats.org/drawingml/2006/wordprocessingDrawing">
+<w:body>
+$if(title)$
+ <w:p>
+ <w:pPr>
+ <w:pStyle w:val="Title" />
+ </w:pPr>
+ $title$
+ </w:p>
+$endif$
+$if(subtitle)$
+ <w:p>
+ <w:pPr>
+ <w:pStyle w:val="Subtitle" />
+ </w:pPr>
+ $subtitle$
+ </w:p>
+$endif$
+$for(author)$
+ <w:p>
+ <w:pPr>
+ <w:pStyle w:val="Author" />
+ </w:pPr>
+ $author$
+ </w:p>
+$endfor$
+$if(date)$
+ <w:p>
+ <w:pPr>
+ <w:pStyle w:val="Date" />
+ </w:pPr>
+ $date$
+ </w:p>
+$endif$
+$if(abstract)$
+ <w:p>
+ <w:pPr>
+ <w:pStyle w:val="AbstractTitle" />
+ </w:pPr>
+ $if(abstract-title)$
+ $abstract-title$
+ $else$
+ <w:r>
+ <w:t xml:space="preserve">Abstract
+ </w:t>
+ </w:r>
+ $endif$
+ </w:p>
+ $abstract$
+$endif$
+$for(include-before)$
+ $include-before$
+$endfor$
+$if(toc)$
+ $toc$
+$endif$
+ $body$
+$for(include-after)$
+ $include-after$
+$endfor$
+$-- sectpr will be set to the last sectpr in a reference.docx, if present
+$if(sectpr)$
+ $sectpr$
+$else$
+ <w:sectPr />
+$endif$
+ </w:body>
+</w:document>
diff --git a/pandoc.cabal b/pandoc.cabal
index 8a52cfbcc..7a55b96a2 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -64,6 +64,7 @@ data-files:
data/templates/default.jats_publishing
data/templates/default.tei
data/templates/default.opendocument
+ data/templates/default.openxml
data/templates/default.icml
data/templates/default.opml
data/templates/default.latex
diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs
index 5834b7def..122a33c66 100644
--- a/src/Text/Pandoc/Templates.hs
+++ b/src/Text/Pandoc/Templates.hs
@@ -102,12 +102,12 @@ getDefaultTemplate format = do
"native" -> return ""
"csljson" -> return ""
"json" -> return ""
- "docx" -> return ""
"fb2" -> return ""
"pptx" -> return ""
"ipynb" -> return ""
"asciidoctor" -> getDefaultTemplate "asciidoc"
"asciidoc_legacy" -> getDefaultTemplate "asciidoc"
+ "docx" -> getDefaultTemplate "openxml"
"odt" -> getDefaultTemplate "opendocument"
"html" -> getDefaultTemplate "html5"
"docbook" -> getDefaultTemplate "docbook5"
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index f5410c707..ca1ada4c9 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -47,6 +47,7 @@ import Text.Pandoc.Class (PandocMonad, toLang)
import qualified Text.Pandoc.Class.PandocMonad as P
import Text.Pandoc.Data (readDataFile, readDefaultDataFile)
import Data.Time
+import qualified Text.Pandoc.UTF8 as UTF8
import Text.Pandoc.Definition
import Text.Pandoc.Error
import Text.Pandoc.MIME (getMimeTypeDef)
@@ -192,10 +193,64 @@ writeDocx opts doc = do
, envPrintWidth = maybe 420 (`quot` 20) pgContentWidth
}
+ parsedRels <- parseXml refArchive distArchive "word/_rels/document.xml.rels"
+ let isHeaderNode e = findAttr (QName "Type" Nothing Nothing) e == Just "http://schemas.openxmlformats.org/officeDocument/2006/relationships/header"
+ let isFooterNode e = findAttr (QName "Type" Nothing Nothing) e == Just "http://schemas.openxmlformats.org/officeDocument/2006/relationships/footer"
+ let headers = filterElements isHeaderNode parsedRels
+ let footers = filterElements isFooterNode parsedRels
+ -- word/_rels/document.xml.rels
+ let toBaseRel (url', id', target') = mknode "Relationship"
+ [("Type",url')
+ ,("Id",id')
+ ,("Target",target')] ()
+ let baserels' = map toBaseRel
+ [("http://schemas.openxmlformats.org/officeDocument/2006/relationships/numbering",
+ "rId1",
+ "numbering.xml")
+ ,("http://schemas.openxmlformats.org/officeDocument/2006/relationships/styles",
+ "rId2",
+ "styles.xml")
+ ,("http://schemas.openxmlformats.org/officeDocument/2006/relationships/settings",
+ "rId3",
+ "settings.xml")
+ ,("http://schemas.openxmlformats.org/officeDocument/2006/relationships/webSettings",
+ "rId4",
+ "webSettings.xml")
+ ,("http://schemas.openxmlformats.org/officeDocument/2006/relationships/fontTable",
+ "rId5",
+ "fontTable.xml")
+ ,("http://schemas.openxmlformats.org/officeDocument/2006/relationships/theme",
+ "rId6",
+ "theme/theme1.xml")
+ ,("http://schemas.openxmlformats.org/officeDocument/2006/relationships/footnotes",
+ "rId7",
+ "footnotes.xml")
+ ,("http://schemas.openxmlformats.org/officeDocument/2006/relationships/comments",
+ "rId8",
+ "comments.xml")
+ ]
+
+ let idMap = renumIdMap (length baserels' + 1) (headers ++ footers)
+
+ -- adjust contents to add sectPr from reference.docx
+ let sectpr = case mbsectpr of
+ Just sectpr' -> let cs = renumIds
+ (\q -> qName q == "id" && qPrefix q == Just "r")
+ idMap
+ (elChildren sectpr')
+ in Just . ppElement $
+ add_attrs (elAttribs sectpr') $ mknode "w:sectPr" [] cs
+ Nothing -> Nothing
+
((contents, footnotes, comments), st) <- runStateT
(runReaderT
- (writeOpenXML opts{writerWrapText = WrapNone} doc')
+ (writeOpenXML opts{ writerWrapText = WrapNone
+ , writerVariables =
+ (maybe id (setField "sectpr") sectpr)
+ (writerVariables opts)
+ }
+ doc')
env)
initialSt
let epochtime = floor $ utcTimeToPOSIXSeconds utctime
@@ -217,13 +272,7 @@ writeDocx opts doc = do
,("xmlns:wp","http://schemas.openxmlformats.org/drawingml/2006/wordprocessingDrawing")]
- parsedRels <- parseXml refArchive distArchive "word/_rels/document.xml.rels"
- let isHeaderNode e = findAttr (QName "Type" Nothing Nothing) e == Just "http://schemas.openxmlformats.org/officeDocument/2006/relationships/header"
- let isFooterNode e = findAttr (QName "Type" Nothing Nothing) e == Just "http://schemas.openxmlformats.org/officeDocument/2006/relationships/footer"
- let headers = filterElements isHeaderNode parsedRels
- let footers = filterElements isFooterNode parsedRels
-
- -- we create [Content_Types].xml and word/_rels/document.xml.rels
+ -- we create [Content_Types].xml and word/_rels/document.xml.rels
-- from scratch rather than reading from reference.docx,
-- because Word sometimes changes these files when a reference.docx is modified,
-- e.g. deleting the reference to footnotes.xml or removing default entries
@@ -284,39 +333,7 @@ writeDocx opts doc = do
let contentTypesEntry = toEntry "[Content_Types].xml" epochtime
$ renderXml contentTypesDoc
- -- word/_rels/document.xml.rels
- let toBaseRel (url', id', target') = mknode "Relationship"
- [("Type",url')
- ,("Id",id')
- ,("Target",target')] ()
- let baserels' = map toBaseRel
- [("http://schemas.openxmlformats.org/officeDocument/2006/relationships/numbering",
- "rId1",
- "numbering.xml")
- ,("http://schemas.openxmlformats.org/officeDocument/2006/relationships/styles",
- "rId2",
- "styles.xml")
- ,("http://schemas.openxmlformats.org/officeDocument/2006/relationships/settings",
- "rId3",
- "settings.xml")
- ,("http://schemas.openxmlformats.org/officeDocument/2006/relationships/webSettings",
- "rId4",
- "webSettings.xml")
- ,("http://schemas.openxmlformats.org/officeDocument/2006/relationships/fontTable",
- "rId5",
- "fontTable.xml")
- ,("http://schemas.openxmlformats.org/officeDocument/2006/relationships/theme",
- "rId6",
- "theme/theme1.xml")
- ,("http://schemas.openxmlformats.org/officeDocument/2006/relationships/footnotes",
- "rId7",
- "footnotes.xml")
- ,("http://schemas.openxmlformats.org/officeDocument/2006/relationships/comments",
- "rId8",
- "comments.xml")
- ]
- let idMap = renumIdMap (length baserels' + 1) (headers ++ footers)
let renumHeaders = renumIds (\q -> qName q == "Id") idMap headers
let renumFooters = renumIds (\q -> qName q == "Id") idMap footers
let baserels = baserels' ++ renumHeaders ++ renumFooters
@@ -328,27 +345,11 @@ writeDocx opts doc = do
let relEntry = toEntry "word/_rels/document.xml.rels" epochtime
$ renderXml reldoc
-
- -- adjust contents to add sectPr from reference.docx
- let sectpr = case mbsectpr of
- Just sectpr' -> let cs = renumIds
- (\q -> qName q == "id" && qPrefix q == Just "r")
- idMap
- (elChildren sectpr')
- in
- add_attrs (elAttribs sectpr') $ mknode "w:sectPr" [] cs
- Nothing -> mknode "w:sectPr" [] ()
-
-- let sectpr = fromMaybe (mknode "w:sectPr" [] ()) mbsectpr'
- let contents' = contents ++ [Elem sectpr]
- let docContents = mknode "w:document" stdAttributes
- $ mknode "w:body" [] contents'
-
-
+ let contents' = BL.fromStrict $ UTF8.fromText contents
-- word/document.xml
- let contentEntry = toEntry "word/document.xml" epochtime
- $ renderXml docContents
+ let contentEntry = toEntry "word/document.xml" epochtime contents'
-- footnotes
let notes = mknode "w:footnotes" stdAttributes footnotes
diff --git a/src/Text/Pandoc/Writers/Docx/OpenXML.hs b/src/Text/Pandoc/Writers/Docx/OpenXML.hs
index f1f5fbb27..8ac095d77 100644
--- a/src/Text/Pandoc/Writers/Docx/OpenXML.hs
+++ b/src/Text/Pandoc/Writers/Docx/OpenXML.hs
@@ -36,6 +36,7 @@ import Data.Text (Text)
import qualified Data.Text.Lazy as TL
import Data.Digest.Pure.SHA (sha1, showDigest)
import Skylighting
+import Text.DocLayout (hcat, vcat, literal, render)
import Text.Pandoc.Class (PandocMonad, report, getMediaBag)
import Text.Pandoc.Translations (Term(Abstract), translateTerm)
import Text.Pandoc.MediaBag (lookupMedia, MediaItem(..))
@@ -45,6 +46,7 @@ import Text.Pandoc.UTF8 (fromTextLazy)
import Text.Pandoc.Definition
import Text.Pandoc.Generic
import Text.Pandoc.Highlighting (highlight)
+import Text.Pandoc.Templates (compileDefaultTemplate, renderTemplate)
import Text.Pandoc.ImageSize
import Text.Pandoc.Logging
import Text.Pandoc.MIME (extensionFromMimeType, getMimeType)
@@ -167,43 +169,29 @@ makeTOC opts = do
])
]] -- w:sdt
--- | Convert Pandoc document to two lists of
--- OpenXML elements (the main document and footnotes).
-writeOpenXML :: (PandocMonad m)
+-- | Convert Pandoc document to rendered document contents plus two lists of
+-- OpenXML elements (footnotes and comments).
+writeOpenXML :: PandocMonad m
=> WriterOptions -> Pandoc
- -> WS m ([Content], [Element], [Element])
+ -> WS m (Text, [Element], [Element])
writeOpenXML opts (Pandoc meta blocks) = do
- let tit = docTitle meta
- let auths = docAuthors meta
- let dat = docDate meta
- let abstract' = lookupMetaBlocks "abstract" meta
- let subtitle' = lookupMetaInlines "subtitle" meta
+ setupTranslations meta
let includeTOC = writerTableOfContents opts || lookupMetaBool "toc" meta
- title <- withParaPropM (pStyleM "Title") $ blocksToOpenXML opts [Para tit | not (null tit)]
- subtitle <- withParaPropM (pStyleM "Subtitle") $ blocksToOpenXML opts [Para subtitle' | not (null subtitle')]
- authors <- withParaPropM (pStyleM "Author") $ blocksToOpenXML opts $
- map Para auths
- date <- withParaPropM (pStyleM "Date") $ blocksToOpenXML opts [Para dat | not (null dat)]
- abstract <- if null abstract'
- then return []
- else do
- abstractTitle <- case lookupMeta "abstract-title" meta of
- Just (MetaBlocks bs) -> pure $ stringify bs
- Just (MetaInlines ils) -> pure $ stringify ils
- Just (MetaString s) -> pure s
- _ -> translateTerm Abstract
- abstractTit <- withParaPropM (pStyleM "AbstractTitle") $
- blocksToOpenXML opts
- [Para [Str abstractTitle]]
- abstractContents <- withParaPropM (pStyleM "Abstract") $
- blocksToOpenXML opts abstract'
- return $ abstractTit <> abstractContents
+ abstractTitle <- case lookupMeta "abstract-title" meta of
+ Just (MetaBlocks bs) -> pure $ stringify bs
+ Just (MetaInlines ils) -> pure $ stringify ils
+ Just (MetaString s) -> pure s
+ _ -> translateTerm Abstract
+ abstract <- case lookupMetaBlocks "abstract" meta of
+ [] -> return []
+ xs -> withParaPropM (pStyleM "Abstract") $ blocksToOpenXML opts xs
let convertSpace (Str x : Space : Str y : xs) = Str (x <> " " <> y) : xs
convertSpace (Str x : Str y : xs) = Str (x <> y) : xs
convertSpace xs = xs
let blocks' = bottomUp convertSpace blocks
doc' <- setFirstPara >> blocksToOpenXML opts blocks'
+ let body = vcat $ map (literal . showContent) doc'
notes' <- gets (reverse . stFootnotes)
comments <- gets (reverse . stComments)
let toComment (kvs, ils) = do
@@ -226,8 +214,20 @@ writeOpenXML opts (Pandoc meta blocks) = do
toc <- if includeTOC
then makeTOC opts
else return []
- let meta' = title ++ subtitle ++ authors ++ date ++ abstract ++ map Elem toc
- return (meta' ++ doc', notes', comments')
+ metadata <- metaToContext opts
+ (fmap (vcat . map (literal . showContent)) . blocksToOpenXML opts)
+ (fmap (hcat . map (literal . showContent)) . inlinesToOpenXML opts)
+ meta
+ let context = defField "body" body
+ . defField "toc"
+ (vcat (map (literal . showElement) toc))
+ . defField "abstract"
+ (vcat (map (literal . showContent) abstract))
+ . defField "abstract-title" abstractTitle
+ $ metadata
+ tpl <- maybe (lift $ compileDefaultTemplate "openxml") pure $ writerTemplate opts
+ let rendered = render Nothing $ renderTemplate tpl context
+ return (rendered, notes', comments')
-- | Convert a list of Pandoc blocks to OpenXML.
blocksToOpenXML :: (PandocMonad m) => WriterOptions -> [Block] -> WS m [Content]
diff --git a/test/docx/golden/block_quotes.docx b/test/docx/golden/block_quotes.docx
index 747d63c02..133d9b554 100644
--- a/test/docx/golden/block_quotes.docx
+++ b/test/docx/golden/block_quotes.docx
Binary files differ
diff --git a/test/docx/golden/codeblock.docx b/test/docx/golden/codeblock.docx
index 4d5c21c62..a24fa5857 100644
--- a/test/docx/golden/codeblock.docx
+++ b/test/docx/golden/codeblock.docx
Binary files differ
diff --git a/test/docx/golden/comments.docx b/test/docx/golden/comments.docx
index 8d400155e..3e417beff 100644
--- a/test/docx/golden/comments.docx
+++ b/test/docx/golden/comments.docx
Binary files differ
diff --git a/test/docx/golden/custom_style_no_reference.docx b/test/docx/golden/custom_style_no_reference.docx
index b3b638b7a..a2535e61e 100644
--- a/test/docx/golden/custom_style_no_reference.docx
+++ b/test/docx/golden/custom_style_no_reference.docx
Binary files differ
diff --git a/test/docx/golden/custom_style_preserve.docx b/test/docx/golden/custom_style_preserve.docx
index aa0c320a5..82f0ba521 100644
--- a/test/docx/golden/custom_style_preserve.docx
+++ b/test/docx/golden/custom_style_preserve.docx
Binary files differ
diff --git a/test/docx/golden/custom_style_reference.docx b/test/docx/golden/custom_style_reference.docx
index 6037ef752..ccc07d9e7 100644
--- a/test/docx/golden/custom_style_reference.docx
+++ b/test/docx/golden/custom_style_reference.docx
Binary files differ
diff --git a/test/docx/golden/definition_list.docx b/test/docx/golden/definition_list.docx
index 826915b9f..03e4173f9 100644
--- a/test/docx/golden/definition_list.docx
+++ b/test/docx/golden/definition_list.docx
Binary files differ
diff --git a/test/docx/golden/document-properties-short-desc.docx b/test/docx/golden/document-properties-short-desc.docx
index 393979956..e39131431 100644
--- a/test/docx/golden/document-properties-short-desc.docx
+++ 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
index 1743cac62..58a488989 100644
--- a/test/docx/golden/document-properties.docx
+++ b/test/docx/golden/document-properties.docx
Binary files differ
diff --git a/test/docx/golden/headers.docx b/test/docx/golden/headers.docx
index 20cde33f2..f3860214b 100644
--- a/test/docx/golden/headers.docx
+++ b/test/docx/golden/headers.docx
Binary files differ
diff --git a/test/docx/golden/image.docx b/test/docx/golden/image.docx
index 44ffc0c8b..f4b967d17 100644
--- a/test/docx/golden/image.docx
+++ b/test/docx/golden/image.docx
Binary files differ
diff --git a/test/docx/golden/inline_code.docx b/test/docx/golden/inline_code.docx
index 3288b6c8e..c2abe7a93 100644
--- a/test/docx/golden/inline_code.docx
+++ b/test/docx/golden/inline_code.docx
Binary files differ
diff --git a/test/docx/golden/inline_formatting.docx b/test/docx/golden/inline_formatting.docx
index 6d7687338..f1049877d 100644
--- a/test/docx/golden/inline_formatting.docx
+++ b/test/docx/golden/inline_formatting.docx
Binary files differ
diff --git a/test/docx/golden/inline_images.docx b/test/docx/golden/inline_images.docx
index 15a305ad6..324855f96 100644
--- a/test/docx/golden/inline_images.docx
+++ b/test/docx/golden/inline_images.docx
Binary files differ
diff --git a/test/docx/golden/link_in_notes.docx b/test/docx/golden/link_in_notes.docx
index 4c8dd0888..4935a8053 100644
--- a/test/docx/golden/link_in_notes.docx
+++ b/test/docx/golden/link_in_notes.docx
Binary files differ
diff --git a/test/docx/golden/links.docx b/test/docx/golden/links.docx
index 1f04c3aff..796968f8a 100644
--- a/test/docx/golden/links.docx
+++ b/test/docx/golden/links.docx
Binary files differ
diff --git a/test/docx/golden/lists.docx b/test/docx/golden/lists.docx
index d78d0cbd8..4f021efc9 100644
--- a/test/docx/golden/lists.docx
+++ b/test/docx/golden/lists.docx
Binary files differ
diff --git a/test/docx/golden/lists_continuing.docx b/test/docx/golden/lists_continuing.docx
index 136e1e45b..c93ece92f 100644
--- a/test/docx/golden/lists_continuing.docx
+++ b/test/docx/golden/lists_continuing.docx
Binary files differ
diff --git a/test/docx/golden/lists_div_bullets.docx b/test/docx/golden/lists_div_bullets.docx
index b77d6bab3..52a29568d 100644
--- a/test/docx/golden/lists_div_bullets.docx
+++ b/test/docx/golden/lists_div_bullets.docx
Binary files differ
diff --git a/test/docx/golden/lists_multiple_initial.docx b/test/docx/golden/lists_multiple_initial.docx
index 1675b64ec..2a7559a52 100644
--- a/test/docx/golden/lists_multiple_initial.docx
+++ b/test/docx/golden/lists_multiple_initial.docx
Binary files differ
diff --git a/test/docx/golden/lists_restarting.docx b/test/docx/golden/lists_restarting.docx
index 262e0cc99..f9af2b83b 100644
--- a/test/docx/golden/lists_restarting.docx
+++ b/test/docx/golden/lists_restarting.docx
Binary files differ
diff --git a/test/docx/golden/nested_anchors_in_header.docx b/test/docx/golden/nested_anchors_in_header.docx
index ccf6eafac..dbe3f6d51 100644
--- a/test/docx/golden/nested_anchors_in_header.docx
+++ b/test/docx/golden/nested_anchors_in_header.docx
Binary files differ
diff --git a/test/docx/golden/notes.docx b/test/docx/golden/notes.docx
index 3469f096a..14a833d21 100644
--- a/test/docx/golden/notes.docx
+++ b/test/docx/golden/notes.docx
Binary files differ
diff --git a/test/docx/golden/raw-blocks.docx b/test/docx/golden/raw-blocks.docx
index a2fc9faf5..0fb1f40b9 100644
--- a/test/docx/golden/raw-blocks.docx
+++ b/test/docx/golden/raw-blocks.docx
Binary files differ
diff --git a/test/docx/golden/raw-bookmarks.docx b/test/docx/golden/raw-bookmarks.docx
index 7257f0e9d..b94285947 100644
--- a/test/docx/golden/raw-bookmarks.docx
+++ b/test/docx/golden/raw-bookmarks.docx
Binary files differ
diff --git a/test/docx/golden/table_one_row.docx b/test/docx/golden/table_one_row.docx
index b2740e391..b73a997cc 100644
--- a/test/docx/golden/table_one_row.docx
+++ b/test/docx/golden/table_one_row.docx
Binary files differ
diff --git a/test/docx/golden/table_with_list_cell.docx b/test/docx/golden/table_with_list_cell.docx
index 5edc06e9d..79ceaf8fe 100644
--- a/test/docx/golden/table_with_list_cell.docx
+++ b/test/docx/golden/table_with_list_cell.docx
Binary files differ
diff --git a/test/docx/golden/tables-default-widths.docx b/test/docx/golden/tables-default-widths.docx
index e78ede9d2..6473bfaff 100644
--- a/test/docx/golden/tables-default-widths.docx
+++ b/test/docx/golden/tables-default-widths.docx
Binary files differ
diff --git a/test/docx/golden/tables.docx b/test/docx/golden/tables.docx
index a4320ce3e..34b50579a 100644
--- a/test/docx/golden/tables.docx
+++ b/test/docx/golden/tables.docx
Binary files differ
diff --git a/test/docx/golden/tables_separated_with_rawblock.docx b/test/docx/golden/tables_separated_with_rawblock.docx
index 73ad45670..4c7ca4459 100644
--- a/test/docx/golden/tables_separated_with_rawblock.docx
+++ b/test/docx/golden/tables_separated_with_rawblock.docx
Binary files differ
diff --git a/test/docx/golden/track_changes_deletion.docx b/test/docx/golden/track_changes_deletion.docx
index 38362564a..90fdf2464 100644
--- a/test/docx/golden/track_changes_deletion.docx
+++ b/test/docx/golden/track_changes_deletion.docx
Binary files differ
diff --git a/test/docx/golden/track_changes_insertion.docx b/test/docx/golden/track_changes_insertion.docx
index 998adc6b9..70d17b05c 100644
--- a/test/docx/golden/track_changes_insertion.docx
+++ b/test/docx/golden/track_changes_insertion.docx
Binary files differ
diff --git a/test/docx/golden/track_changes_move.docx b/test/docx/golden/track_changes_move.docx
index 05d0f66fc..3111b17f7 100644
--- a/test/docx/golden/track_changes_move.docx
+++ b/test/docx/golden/track_changes_move.docx
Binary files differ
diff --git a/test/docx/golden/track_changes_scrubbed_metadata.docx b/test/docx/golden/track_changes_scrubbed_metadata.docx
index 97d3c6731..ae0190ef0 100644
--- a/test/docx/golden/track_changes_scrubbed_metadata.docx
+++ b/test/docx/golden/track_changes_scrubbed_metadata.docx
Binary files differ
diff --git a/test/docx/golden/unicode.docx b/test/docx/golden/unicode.docx
index 49d72f256..f6bebcebe 100644
--- a/test/docx/golden/unicode.docx
+++ b/test/docx/golden/unicode.docx
Binary files differ
diff --git a/test/docx/golden/verbatim_subsuper.docx b/test/docx/golden/verbatim_subsuper.docx
index effac9ce1..f8d1471c7 100644
--- a/test/docx/golden/verbatim_subsuper.docx
+++ b/test/docx/golden/verbatim_subsuper.docx
Binary files differ