diff options
author | Emily Bourke <undergroundquizscene@protonmail.com> | 2021-08-18 10:13:54 +0100 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2021-08-18 10:10:55 -0700 |
commit | 5616d00d09d3a940364befd380dde328c6ac1a08 (patch) | |
tree | 85261b682bf5669c4d47fbded1bb206489f45948 /src/Text/Pandoc | |
parent | fd99fe4d7ee5459d32505ef14f4453839cfcefab (diff) | |
download | pandoc-5616d00d09d3a940364befd380dde328c6ac1a08.tar.gz |
pptx: Include image title in description
The image title (i.e. `![alt text](link "title")`) was previously
ignored when writing to pptx. This commit includes it in PowerPoint's
description of the image, along with the link (which was already
included).
Fixes 7352.
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r-- | src/Text/Pandoc/Writers/Powerpoint/Output.hs | 13 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | 18 |
2 files changed, 19 insertions, 12 deletions
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs index e0eb72161..0e6a67861 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs @@ -872,9 +872,10 @@ makePicElements :: PandocMonad m => Element -> PicProps -> MediaInfo + -> Text -> [ParaElem] -> P m [Element] -makePicElements layout picProps mInfo alt = do +makePicElements layout picProps mInfo titleText alt = do opts <- asks envOpts (pageWidth, pageHeight) <- asks envPresentationSize -- hasHeader <- asks envSlideHasHeader @@ -907,7 +908,11 @@ makePicElements layout picProps mInfo alt = do ,("noChangeAspect","1")] () -- cNvPr will contain the link information so we do that separately, -- and register the link if necessary. - let cNvPrAttr = [("descr", T.pack $ mInfoFilePath mInfo), + let description = (if T.null titleText + then "" + else titleText <> "\n\n") + <> T.pack (mInfoFilePath mInfo) + let cNvPrAttr = [("descr", description), ("id","0"), ("name","Picture 1")] cNvPr <- case picPropLink picProps of @@ -1106,11 +1111,11 @@ shapeToElement layout (TextBox paras) shapeToElement _ _ = return $ mknode "p:sp" [] () shapeToElements :: PandocMonad m => Element -> Shape -> P m [Content] -shapeToElements layout (Pic picProps fp alt) = do +shapeToElements layout (Pic picProps fp titleText alt) = do mInfo <- registerMedia fp alt case mInfoExt mInfo of Just _ -> map Elem <$> - makePicElements layout picProps mInfo alt + makePicElements layout picProps mInfo titleText alt Nothing -> shapeToElements layout $ TextBox [Paragraph def alt] shapeToElements layout (GraphicFrame tbls cptn) = map Elem <$> graphicFrameToElements layout tbls cptn diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs index 9246a93e9..0400783e3 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs @@ -197,7 +197,8 @@ data Layout = MetadataSlide [ParaElem] [ParaElem] [[ParaElem]] [ParaElem] -- heading left right deriving (Show, Eq) -data Shape = Pic PicProps FilePath [ParaElem] +data Shape = Pic PicProps FilePath T.Text [ParaElem] + -- title alt-text | GraphicFrame [Graphic] [ParaElem] | TextBox [Paragraph] | RawOOXMLShape T.Text @@ -525,21 +526,22 @@ rowToParagraphs algns tblCells = do mapM (uncurry cellToParagraphs) pairs withAttr :: Attr -> Shape -> Shape -withAttr attr (Pic picPr url caption) = +withAttr attr (Pic picPr url title caption) = let picPr' = picPr { picWidth = dimension Width attr , picHeight = dimension Height attr } in - Pic picPr' url caption + Pic picPr' url title caption withAttr _ sp = sp blockToShape :: Block -> Pres Shape blockToShape (Plain ils) = blockToShape (Para ils) -blockToShape (Para (il:_)) | Image attr ils (url, _) <- il = - withAttr attr . Pic def (T.unpack url) <$> inlinesToParElems ils +blockToShape (Para (il:_)) | Image attr ils (url, title) <- il = + withAttr attr . Pic def (T.unpack url) title <$> inlinesToParElems ils blockToShape (Para (il:_)) | Link _ (il':_) target <- il - , Image attr ils (url, _) <- il' = - withAttr attr . Pic def{picPropLink = Just $ ExternalTarget target} (T.unpack url) + , Image attr ils (url, title) <- il' = + withAttr attr . + Pic def{picPropLink = Just $ ExternalTarget target} (T.unpack url) title <$> inlinesToParElems ils blockToShape (Table _ blkCapt specs thead tbody tfoot) = do let (caption, algn, _, hdrCells, rows) = toLegacyTable blkCapt specs thead tbody tfoot @@ -805,7 +807,7 @@ applyToParagraph f para = do return $ para {paraElems = paraElems'} applyToShape :: Monad m => (ParaElem -> m ParaElem) -> Shape -> m Shape -applyToShape f (Pic pPr fp pes) = Pic pPr fp <$> mapM f pes +applyToShape f (Pic pPr fp title pes) = Pic pPr fp title <$> mapM f pes applyToShape f (GraphicFrame gfx pes) = GraphicFrame gfx <$> mapM f pes applyToShape f (TextBox paras) = TextBox <$> mapM (applyToParagraph f) paras applyToShape _ (RawOOXMLShape str) = return $ RawOOXMLShape str |