diff options
| author | John MacFarlane <[email protected]> | 2025-04-05 13:35:55 -0700 |
|---|---|---|
| committer | John MacFarlane <[email protected]> | 2025-04-05 13:48:46 -0700 |
| commit | af57648e58d2babe17dbc30935a1b1f8c888f083 (patch) | |
| tree | af3c1514683a4ca3c1578111ca61731c7b92871c | |
| parent | f8f7c29fb81468a7b559e9590089152cee5d0b04 (diff) | |
Docx writer: preserve Relationships for images from reference docx.
This should allow one to include an image in a reference.docx and
reference it in an openxml template.
Closes #10759.
39 files changed, 31 insertions, 29 deletions
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 7fb539289..596bb6944 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -3,9 +3,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE FlexibleContexts #-} -{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE TypeApplications #-} {- | Module : Text.Pandoc.Writers.Docx Copyright : Copyright (C) 2012-2024 John MacFarlane @@ -176,12 +174,6 @@ writeDocx opts doc = do [] -> stTocTitle defaultWriterState ls -> ls - let initialSt = defaultWriterState { - stStyleMaps = styleMaps - , stTocTitle = tocTitle - , stCurId = 20 - } - let isRTLmeta = case lookupMeta "dir" meta of Just (MetaString "rtl") -> True Just (MetaInlines [Str "rtl"]) -> True @@ -194,44 +186,58 @@ writeDocx opts doc = do , envPrintWidth = maybe 420 (`quot` 20) pgContentWidth } - parsedRels <- parseXml refArchive distArchive "word/_rels/document.xml.rels" + let isImageNode e = findAttr (QName "Type" Nothing Nothing) e == Just "http://schemas.openxmlformats.org/officeDocument/2006/relationships/image" 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 + parsedRels <- filterElements + (\e -> isImageNode e || isHeaderNode e || isFooterNode e) + <$> parseXml refArchive distArchive "word/_rels/document.xml.rels" + let getRelId e = + case findAttr (QName "Id" Nothing Nothing) e of + Just ident -> T.stripPrefix "rId" ident >>= safeRead + Nothing -> Nothing + let relIds = mapMaybe getRelId parsedRels + let maxRelId = if null relIds then 0 else maximum relIds + + let headers = filter isHeaderNode parsedRels + let footers = filter isFooterNode parsedRels -- word/_rels/document.xml.rels - let toBaseRel (url', id', target') = mknode "Relationship" - [("Type",url') - ,("Id",id') - ,("Target",target')] () - let baserels' = map toBaseRel + let addBaseRel (url', target') (maxId, rels) = + case [e | e <- rels + , findAttr (QName "Target" Nothing Nothing) e == + Just target'] of + [] -> (maxId + 1, mknode "Relationship" + [("Type",url') + ,("Id","rId" <> tshow (maxId + 1)) + ,("Target",target')] () : rels) + _ -> (maxId, rels) + + let (newMaxRelId, baserels) = foldr addBaseRel (maxRelId, parsedRels) [("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 initialSt = defaultWriterState { + stStyleMaps = styleMaps + , stTocTitle = tocTitle + , stCurId = newMaxRelId + 1 + } + + let idMap = renumIdMap (length baserels + 1) (headers ++ footers) -- adjust contents to add sectPr from reference.docx let sectpr = case mbsectpr of @@ -331,10 +337,6 @@ writeDocx opts doc = do let contentTypesEntry = toEntry "[Content_Types].xml" epochtime $ renderXml contentTypesDoc - - let renumHeaders = renumIds (\q -> qName q == "Id") idMap headers - let renumFooters = renumIds (\q -> qName q == "Id") idMap footers - let baserels = baserels' ++ renumHeaders ++ renumFooters let toImgRel (ident,path,_,_) = mknode "Relationship" [("Type","http://schemas.openxmlformats.org/officeDocument/2006/relationships/image"),("Id",T.pack ident),("Target",T.pack path)] () let imgrels = map toImgRel imgs let toLinkRel (src,ident) = mknode "Relationship" [("Type","http://schemas.openxmlformats.org/officeDocument/2006/relationships/hyperlink"),("Id",ident),("Target",src),("TargetMode","External") ] () diff --git a/test/docx/golden/block_quotes.docx b/test/docx/golden/block_quotes.docx Binary files differindex 214a57a5b..ba308cb04 100644 --- a/test/docx/golden/block_quotes.docx +++ b/test/docx/golden/block_quotes.docx diff --git a/test/docx/golden/codeblock.docx b/test/docx/golden/codeblock.docx Binary files differindex 9aa1dd858..160f02c87 100644 --- a/test/docx/golden/codeblock.docx +++ b/test/docx/golden/codeblock.docx diff --git a/test/docx/golden/comments.docx b/test/docx/golden/comments.docx Binary files differindex 41eb630ea..a3d09e933 100644 --- a/test/docx/golden/comments.docx +++ b/test/docx/golden/comments.docx diff --git a/test/docx/golden/custom_style_no_reference.docx b/test/docx/golden/custom_style_no_reference.docx Binary files differindex ff7b8c477..740a3f33b 100644 --- a/test/docx/golden/custom_style_no_reference.docx +++ b/test/docx/golden/custom_style_no_reference.docx diff --git a/test/docx/golden/custom_style_preserve.docx b/test/docx/golden/custom_style_preserve.docx Binary files differindex 8afe51ecd..d23633d94 100644 --- a/test/docx/golden/custom_style_preserve.docx +++ b/test/docx/golden/custom_style_preserve.docx diff --git a/test/docx/golden/custom_style_reference.docx b/test/docx/golden/custom_style_reference.docx Binary files differindex e4dd93f47..5c6270704 100644 --- a/test/docx/golden/custom_style_reference.docx +++ b/test/docx/golden/custom_style_reference.docx diff --git a/test/docx/golden/definition_list.docx b/test/docx/golden/definition_list.docx Binary files differindex cf152c5f2..fcf451174 100644 --- a/test/docx/golden/definition_list.docx +++ b/test/docx/golden/definition_list.docx diff --git a/test/docx/golden/document-properties-short-desc.docx b/test/docx/golden/document-properties-short-desc.docx Binary files differindex 8af10827a..85790580d 100644 --- a/test/docx/golden/document-properties-short-desc.docx +++ b/test/docx/golden/document-properties-short-desc.docx diff --git a/test/docx/golden/document-properties.docx b/test/docx/golden/document-properties.docx Binary files differindex 6d151023f..a72127699 100644 --- a/test/docx/golden/document-properties.docx +++ b/test/docx/golden/document-properties.docx diff --git a/test/docx/golden/headers.docx b/test/docx/golden/headers.docx Binary files differindex c6bec6ca4..1d3595da8 100644 --- a/test/docx/golden/headers.docx +++ b/test/docx/golden/headers.docx diff --git a/test/docx/golden/image.docx b/test/docx/golden/image.docx Binary files differindex ab841908c..4f2c7fa05 100644 --- a/test/docx/golden/image.docx +++ b/test/docx/golden/image.docx diff --git a/test/docx/golden/inline_code.docx b/test/docx/golden/inline_code.docx Binary files differindex f8dd88987..44b0345d9 100644 --- a/test/docx/golden/inline_code.docx +++ b/test/docx/golden/inline_code.docx diff --git a/test/docx/golden/inline_formatting.docx b/test/docx/golden/inline_formatting.docx Binary files differindex 9e83fa0e3..4675ae918 100644 --- a/test/docx/golden/inline_formatting.docx +++ b/test/docx/golden/inline_formatting.docx diff --git a/test/docx/golden/inline_images.docx b/test/docx/golden/inline_images.docx Binary files differindex b76cf6417..b091b3b38 100644 --- a/test/docx/golden/inline_images.docx +++ b/test/docx/golden/inline_images.docx diff --git a/test/docx/golden/link_in_notes.docx b/test/docx/golden/link_in_notes.docx Binary files differindex fc8326472..88b8e500e 100644 --- a/test/docx/golden/link_in_notes.docx +++ b/test/docx/golden/link_in_notes.docx diff --git a/test/docx/golden/links.docx b/test/docx/golden/links.docx Binary files differindex 5b1fce508..b1c755329 100644 --- a/test/docx/golden/links.docx +++ b/test/docx/golden/links.docx diff --git a/test/docx/golden/lists.docx b/test/docx/golden/lists.docx Binary files differindex 99ccd88a7..d5ae963fe 100644 --- a/test/docx/golden/lists.docx +++ b/test/docx/golden/lists.docx diff --git a/test/docx/golden/lists_9994.docx b/test/docx/golden/lists_9994.docx Binary files differindex a43d1869b..bf1d640ef 100644 --- a/test/docx/golden/lists_9994.docx +++ b/test/docx/golden/lists_9994.docx diff --git a/test/docx/golden/lists_continuing.docx b/test/docx/golden/lists_continuing.docx Binary files differindex f9409df00..2049af474 100644 --- a/test/docx/golden/lists_continuing.docx +++ b/test/docx/golden/lists_continuing.docx diff --git a/test/docx/golden/lists_div_bullets.docx b/test/docx/golden/lists_div_bullets.docx Binary files differindex ee504f3c1..66d6c7c95 100644 --- a/test/docx/golden/lists_div_bullets.docx +++ b/test/docx/golden/lists_div_bullets.docx diff --git a/test/docx/golden/lists_multiple_initial.docx b/test/docx/golden/lists_multiple_initial.docx Binary files differindex 593fe03b5..7cc22667a 100644 --- a/test/docx/golden/lists_multiple_initial.docx +++ b/test/docx/golden/lists_multiple_initial.docx diff --git a/test/docx/golden/lists_restarting.docx b/test/docx/golden/lists_restarting.docx Binary files differindex 5cbe7b24e..bf4bd4b1b 100644 --- a/test/docx/golden/lists_restarting.docx +++ b/test/docx/golden/lists_restarting.docx diff --git a/test/docx/golden/nested_anchors_in_header.docx b/test/docx/golden/nested_anchors_in_header.docx Binary files differindex a97cd445b..45b0410a6 100644 --- a/test/docx/golden/nested_anchors_in_header.docx +++ b/test/docx/golden/nested_anchors_in_header.docx diff --git a/test/docx/golden/notes.docx b/test/docx/golden/notes.docx Binary files differindex 2562cceb3..a120d87bf 100644 --- a/test/docx/golden/notes.docx +++ b/test/docx/golden/notes.docx diff --git a/test/docx/golden/raw-blocks.docx b/test/docx/golden/raw-blocks.docx Binary files differindex 145801c0e..de5186b5d 100644 --- a/test/docx/golden/raw-blocks.docx +++ b/test/docx/golden/raw-blocks.docx diff --git a/test/docx/golden/raw-bookmarks.docx b/test/docx/golden/raw-bookmarks.docx Binary files differindex 6e774aa15..cae7b2a71 100644 --- a/test/docx/golden/raw-bookmarks.docx +++ b/test/docx/golden/raw-bookmarks.docx diff --git a/test/docx/golden/table_one_row.docx b/test/docx/golden/table_one_row.docx Binary files differindex abbe767a5..d989f2562 100644 --- a/test/docx/golden/table_one_row.docx +++ b/test/docx/golden/table_one_row.docx diff --git a/test/docx/golden/table_with_list_cell.docx b/test/docx/golden/table_with_list_cell.docx Binary files differindex 8477a7cf1..f623dffdf 100644 --- a/test/docx/golden/table_with_list_cell.docx +++ b/test/docx/golden/table_with_list_cell.docx diff --git a/test/docx/golden/tables-default-widths.docx b/test/docx/golden/tables-default-widths.docx Binary files differindex 790d8cd63..b82616bd9 100644 --- a/test/docx/golden/tables-default-widths.docx +++ b/test/docx/golden/tables-default-widths.docx diff --git a/test/docx/golden/tables.docx b/test/docx/golden/tables.docx Binary files differindex 1b80a7904..4272568db 100644 --- a/test/docx/golden/tables.docx +++ b/test/docx/golden/tables.docx diff --git a/test/docx/golden/tables_separated_with_rawblock.docx b/test/docx/golden/tables_separated_with_rawblock.docx Binary files differindex fd8c68c06..ab99fd05b 100644 --- a/test/docx/golden/tables_separated_with_rawblock.docx +++ b/test/docx/golden/tables_separated_with_rawblock.docx diff --git a/test/docx/golden/task_list.docx b/test/docx/golden/task_list.docx Binary files differindex 2ca6c7d77..dfebd5873 100644 --- a/test/docx/golden/task_list.docx +++ b/test/docx/golden/task_list.docx diff --git a/test/docx/golden/track_changes_deletion.docx b/test/docx/golden/track_changes_deletion.docx Binary files differindex f3fd20137..1ed6c0b1a 100644 --- a/test/docx/golden/track_changes_deletion.docx +++ b/test/docx/golden/track_changes_deletion.docx diff --git a/test/docx/golden/track_changes_insertion.docx b/test/docx/golden/track_changes_insertion.docx Binary files differindex a791641a0..7e53ff9d1 100644 --- a/test/docx/golden/track_changes_insertion.docx +++ b/test/docx/golden/track_changes_insertion.docx diff --git a/test/docx/golden/track_changes_move.docx b/test/docx/golden/track_changes_move.docx Binary files differindex fb25a5bbb..9c099afc7 100644 --- a/test/docx/golden/track_changes_move.docx +++ b/test/docx/golden/track_changes_move.docx diff --git a/test/docx/golden/track_changes_scrubbed_metadata.docx b/test/docx/golden/track_changes_scrubbed_metadata.docx Binary files differindex 6305c0d59..7a0fd6c78 100644 --- a/test/docx/golden/track_changes_scrubbed_metadata.docx +++ b/test/docx/golden/track_changes_scrubbed_metadata.docx diff --git a/test/docx/golden/unicode.docx b/test/docx/golden/unicode.docx Binary files differindex ccd92baa4..396a7d7ca 100644 --- a/test/docx/golden/unicode.docx +++ b/test/docx/golden/unicode.docx diff --git a/test/docx/golden/verbatim_subsuper.docx b/test/docx/golden/verbatim_subsuper.docx Binary files differindex 55323f885..85bed4c01 100644 --- a/test/docx/golden/verbatim_subsuper.docx +++ b/test/docx/golden/verbatim_subsuper.docx |
