From 07f3aa178be1dda44cd5477089d26c26b9460751 Mon Sep 17 00:00:00 2001
From: Jesse Rosenthal <jrosenthal@jhu.edu>
Date: Sun, 18 Feb 2018 15:58:06 -0500
Subject: Powerpoint writer: Ignore links and (end)notes in speaker notes.

MS PowerPoint does not offer a way to insert links into speaker notes
text, so we match that behavior, and make our lives easier.

As for (end)notes, there is no clear solution to the question of wat
that would *mean*. The default behavior would be to add it to the
endnote slide, but that would put speaker note content into the public
presentation. The best solution would be to put the content at the
bottom of the notes page, but that would take some doing, and can be
added to the speaker notes feature later.
---
 src/Text/Pandoc/Writers/Powerpoint/Output.hs       | 10 +++++++-
 src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | 30 +++++++++++++++-------
 2 files changed, 30 insertions(+), 10 deletions(-)

(limited to 'src')

diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
index 801e0485e..93d511dce 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
@@ -1202,9 +1202,17 @@ speakerNotesSlideImage =
   , mknode "p:spPr" [] ()
   ]
 
+-- we want to wipe links from the speaker notes in the
+-- paragraphs. Powerpoint doesn't allow you to input them, and it
+-- would provide extra complications.
+removeLinks :: Paragraph -> Paragraph
+removeLinks paragraph = paragraph{paraElems = map f (paraElems paragraph)}
+  where f (Run rProps s) = Run rProps{rLink=Nothing} s
+        f pe             = pe
+
 speakerNotesBody :: PandocMonad m => [Paragraph] -> P m Element
 speakerNotesBody paras = do
-  elements <- mapM paragraphToElement paras
+  elements <- mapM paragraphToElement $ map removeLinks paras
   let txBody = mknode "p:txBody" [] $
                [mknode "a:bodyPr" [] (), mknode "a:lstStyle" [] ()] ++ elements
   return $
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
index 2ba74f4ec..ac7c86945 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
@@ -87,6 +87,7 @@ data WriterEnv = WriterEnv { envMetadata :: Meta
                            , envInList :: Bool
                            , envInNoteSlide :: Bool
                            , envCurSlideId :: SlideId
+                           , envInSpeakerNotes :: Bool
                            }
                  deriving (Show)
 
@@ -100,6 +101,7 @@ instance Default WriterEnv where
                   , envInList = False
                   , envInNoteSlide = False
                   , envCurSlideId = SlideId "Default"
+                  , envInSpeakerNotes = False
                   }
 
 
@@ -354,15 +356,24 @@ inlineToParElems (Code _ str) =
   inlineToParElems $ Str str
 inlineToParElems (Math mathtype str) =
   return [MathElem mathtype (TeXString str)]
+-- We ignore notes if we're in a speaker notes div. Otherwise this
+-- would add an entry to the endnotes slide, which would put speaker
+-- notes in the public presentation. In the future, we can entertain a
+-- way of adding a speakernotes-specific note that would just add
+-- paragraphs to the bottom of the notes page.
 inlineToParElems (Note blks) = do
-  notes <- gets stNoteIds
-  let maxNoteId = case M.keys notes of
-        [] -> 0
-        lst -> maximum lst
-      curNoteId = maxNoteId + 1
-  modify $ \st -> st { stNoteIds = M.insert curNoteId blks notes }
-  local (\env -> env{envRunProps = (envRunProps env){rLink = Just $ InternalTarget endNotesSlideId}}) $
-    inlineToParElems $ Superscript [Str $ show curNoteId]
+  inSpNotes <- asks envInSpeakerNotes
+  if inSpNotes
+    then return []
+    else do
+    notes <- gets stNoteIds
+    let maxNoteId = case M.keys notes of
+          [] -> 0
+          lst -> maximum lst
+        curNoteId = maxNoteId + 1
+    modify $ \st -> st { stNoteIds = M.insert curNoteId blks notes }
+    local (\env -> env{envRunProps = (envRunProps env){rLink = Just $ InternalTarget endNotesSlideId}}) $
+      inlineToParElems $ Superscript [Str $ show curNoteId]
 inlineToParElems (Span _ ils) = concatMapM inlineToParElems ils
 inlineToParElems (RawInline _ _) = return []
 inlineToParElems _ = return []
@@ -464,7 +475,8 @@ blockToParagraphs (DefinitionList entries) = do
         definition <- concatMapM (blockToParagraphs . BlockQuote) blksLst
         return $ term ++ definition
   concatMapM go entries
-blockToParagraphs (Div (_, "notes" : [], _) blks) = do
+blockToParagraphs (Div (_, "notes" : [], _) blks) =
+  local (\env -> env{envInSpeakerNotes=True}) $ do
   sldId <- asks envCurSlideId
   spkNotesMap <- gets stSpeakerNotesMap
   paras <- concatMapM blockToParagraphs blks
-- 
cgit v1.2.3