Ensure we have unique ids for wp:docPr and pic:cNvPr elements.
This will, I hope, fix #7527 and #7503.
This commit is contained in:
parent
af9d464cee
commit
e4d7a6177f
3 changed files with 11 additions and 9 deletions
|
@ -175,6 +175,7 @@ writeDocx opts doc = do
|
||||||
let initialSt = defaultWriterState {
|
let initialSt = defaultWriterState {
|
||||||
stStyleMaps = styleMaps
|
stStyleMaps = styleMaps
|
||||||
, stTocTitle = tocTitle
|
, stTocTitle = tocTitle
|
||||||
|
, stCurId = 20
|
||||||
}
|
}
|
||||||
|
|
||||||
let isRTLmeta = case lookupMeta "dir" meta of
|
let isRTLmeta = case lookupMeta "dir" meta of
|
||||||
|
@ -783,8 +784,6 @@ rStyleM styleName = do
|
||||||
return $ mknode "w:rStyle" [("w:val", fromStyleId sty')] ()
|
return $ mknode "w:rStyle" [("w:val", fromStyleId sty')] ()
|
||||||
|
|
||||||
getUniqueId :: (PandocMonad m) => WS m Text
|
getUniqueId :: (PandocMonad m) => WS m Text
|
||||||
-- the + 20 is to ensure that there are no clashes with the rIds
|
|
||||||
-- already in word/document.xml.rel
|
|
||||||
getUniqueId = do
|
getUniqueId = do
|
||||||
n <- gets stCurId
|
n <- gets stCurId
|
||||||
modify $ \st -> st{stCurId = n + 1}
|
modify $ \st -> st{stCurId = n + 1}
|
||||||
|
@ -1234,7 +1233,9 @@ inlineToOpenXML' opts (Image attr@(imgident, _, _) alt (src, title)) = do
|
||||||
imgs <- gets stImages
|
imgs <- gets stImages
|
||||||
let
|
let
|
||||||
stImage = M.lookup (T.unpack src) imgs
|
stImage = M.lookup (T.unpack src) imgs
|
||||||
generateImgElt (ident, _, _, img) =
|
generateImgElt (ident, _, _, img) = do
|
||||||
|
docprid <- getUniqueId
|
||||||
|
nvpicprid <- getUniqueId
|
||||||
let
|
let
|
||||||
(xpt,ypt) = desiredSizeInPoints opts attr
|
(xpt,ypt) = desiredSizeInPoints opts attr
|
||||||
(either (const def) id (imageSize opts img))
|
(either (const def) id (imageSize opts img))
|
||||||
|
@ -1246,7 +1247,9 @@ inlineToOpenXML' opts (Image attr@(imgident, _, _) alt (src, title)) = do
|
||||||
,("noChangeAspect","1")] ()
|
,("noChangeAspect","1")] ()
|
||||||
nvPicPr = mknode "pic:nvPicPr" []
|
nvPicPr = mknode "pic:nvPicPr" []
|
||||||
[ mknode "pic:cNvPr"
|
[ mknode "pic:cNvPr"
|
||||||
[("descr",src),("id","0"),("name","Picture")] ()
|
[("descr",src)
|
||||||
|
,("id", nvpicprid)
|
||||||
|
,("name","Picture")] ()
|
||||||
, cNvPicPr ]
|
, cNvPicPr ]
|
||||||
blipFill = mknode "pic:blipFill" []
|
blipFill = mknode "pic:blipFill" []
|
||||||
[ mknode "a:blip" [("r:embed",T.pack ident)] ()
|
[ mknode "a:blip" [("r:embed",T.pack ident)] ()
|
||||||
|
@ -1283,16 +1286,15 @@ inlineToOpenXML' opts (Image attr@(imgident, _, _) alt (src, title)) = do
|
||||||
, mknode "wp:docPr"
|
, mknode "wp:docPr"
|
||||||
[ ("descr", stringify alt)
|
[ ("descr", stringify alt)
|
||||||
, ("title", title)
|
, ("title", title)
|
||||||
, ("id","1")
|
, ("id", docprid)
|
||||||
, ("name","Picture")
|
, ("name","Picture")
|
||||||
] ()
|
] ()
|
||||||
, graphic
|
, graphic
|
||||||
]
|
]
|
||||||
in
|
return [Elem imgElt]
|
||||||
imgElt
|
|
||||||
|
|
||||||
wrapBookmark imgident =<< case stImage of
|
wrapBookmark imgident =<< case stImage of
|
||||||
Just imgData -> return [Elem $ generateImgElt imgData]
|
Just imgData -> generateImgElt imgData
|
||||||
Nothing -> ( do --try
|
Nothing -> ( do --try
|
||||||
(img, mt) <- P.fetchItem src
|
(img, mt) <- P.fetchItem src
|
||||||
ident <- ("rId" <>) <$> getUniqueId
|
ident <- ("rId" <>) <$> getUniqueId
|
||||||
|
@ -1321,7 +1323,7 @@ inlineToOpenXML' opts (Image attr@(imgident, _, _) alt (src, title)) = do
|
||||||
else do
|
else do
|
||||||
-- insert mime type to use in constructing [Content_Types].xml
|
-- insert mime type to use in constructing [Content_Types].xml
|
||||||
modify $ \st -> st { stImages = M.insert (T.unpack src) imgData $ stImages st }
|
modify $ \st -> st { stImages = M.insert (T.unpack src) imgData $ stImages st }
|
||||||
return [Elem $ generateImgElt imgData]
|
generateImgElt imgData
|
||||||
)
|
)
|
||||||
`catchError` ( \e -> do
|
`catchError` ( \e -> do
|
||||||
report $ CouldNotFetchResource src $ T.pack (show e)
|
report $ CouldNotFetchResource src $ T.pack (show e)
|
||||||
|
|
Binary file not shown.
Binary file not shown.
Loading…
Add table
Reference in a new issue