aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Writers/Powerpoint/Output.hs13
-rw-r--r--src/Text/Pandoc/Writers/Powerpoint/Presentation.hs18
-rw-r--r--test/pptx/images.pptxbin44579 -> 44596 bytes
-rw-r--r--test/pptx/images_deleted_layouts.pptxbin47424 -> 47437 bytes
-rw-r--r--test/pptx/images_moved_layouts.pptxbin58213 -> 58160 bytes
-rw-r--r--test/pptx/images_templated.pptxbin57729 -> 57660 bytes
-rw-r--r--test/pptx/speaker_notes_afterseps.pptxbin51548 -> 51557 bytes
-rw-r--r--test/pptx/speaker_notes_afterseps_deleted_layouts.pptxbin54390 -> 54396 bytes
-rw-r--r--test/pptx/speaker_notes_afterseps_moved_layouts.pptxbin65181 -> 65121 bytes
-rw-r--r--test/pptx/speaker_notes_afterseps_templated.pptxbin64695 -> 64619 bytes
10 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
diff --git a/test/pptx/images.pptx b/test/pptx/images.pptx
index 670a825de..89325e577 100644
--- a/test/pptx/images.pptx
+++ b/test/pptx/images.pptx
Binary files differ
diff --git a/test/pptx/images_deleted_layouts.pptx b/test/pptx/images_deleted_layouts.pptx
index 7a38ea625..053928863 100644
--- a/test/pptx/images_deleted_layouts.pptx
+++ b/test/pptx/images_deleted_layouts.pptx
Binary files differ
diff --git a/test/pptx/images_moved_layouts.pptx b/test/pptx/images_moved_layouts.pptx
index 08d1c27e0..7951a09f6 100644
--- a/test/pptx/images_moved_layouts.pptx
+++ b/test/pptx/images_moved_layouts.pptx
Binary files differ
diff --git a/test/pptx/images_templated.pptx b/test/pptx/images_templated.pptx
index 48ebf66d6..7c0ed9a17 100644
--- a/test/pptx/images_templated.pptx
+++ b/test/pptx/images_templated.pptx
Binary files differ
diff --git a/test/pptx/speaker_notes_afterseps.pptx b/test/pptx/speaker_notes_afterseps.pptx
index 13f564bf0..9542fe8b5 100644
--- a/test/pptx/speaker_notes_afterseps.pptx
+++ b/test/pptx/speaker_notes_afterseps.pptx
Binary files differ
diff --git a/test/pptx/speaker_notes_afterseps_deleted_layouts.pptx b/test/pptx/speaker_notes_afterseps_deleted_layouts.pptx
index 1e7f4968d..9fec1c279 100644
--- a/test/pptx/speaker_notes_afterseps_deleted_layouts.pptx
+++ b/test/pptx/speaker_notes_afterseps_deleted_layouts.pptx
Binary files differ
diff --git a/test/pptx/speaker_notes_afterseps_moved_layouts.pptx b/test/pptx/speaker_notes_afterseps_moved_layouts.pptx
index e092ae444..de697cbd8 100644
--- a/test/pptx/speaker_notes_afterseps_moved_layouts.pptx
+++ b/test/pptx/speaker_notes_afterseps_moved_layouts.pptx
Binary files differ
diff --git a/test/pptx/speaker_notes_afterseps_templated.pptx b/test/pptx/speaker_notes_afterseps_templated.pptx
index 9c22eaf38..5a3d15d57 100644
--- a/test/pptx/speaker_notes_afterseps_templated.pptx
+++ b/test/pptx/speaker_notes_afterseps_templated.pptx
Binary files differ