aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
diff options
context:
space:
mode:
authorJesse Rosenthal <jrosenthal@jhu.edu>2018-03-23 13:58:22 -0400
committerJesse Rosenthal <jrosenthal@jhu.edu>2018-03-23 13:58:22 -0400
commit3b7611a7c7edda01c2ae4224e873c602c7f3aefd (patch)
treed625d9225ffb820986fd8551264642fcbba8d1cb /src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
parent59f3997069131abaf9f206604971cc980d69071a (diff)
downloadpandoc-3b7611a7c7edda01c2ae4224e873c602c7f3aefd.tar.gz
Powerpoint writer: change notes state to a simpler per-slide value
We used to keep a map of the slideId-to-notes for each slide. Since we now extract them at the slide level, this is overcomplicated, and we can just extract them before converting a slide and then clear the state after.
Diffstat (limited to 'src/Text/Pandoc/Writers/Powerpoint/Presentation.hs')
-rw-r--r--src/Text/Pandoc/Writers/Powerpoint/Presentation.hs25
1 files changed, 7 insertions, 18 deletions
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
index bf26840f7..331e76e33 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
@@ -113,7 +113,7 @@ data WriterState = WriterState { stNoteIds :: M.Map Int [Block]
, stAnchorMap :: M.Map String SlideId
, stSlideIdSet :: S.Set SlideId
, stLog :: [LogMessage]
- , stSpeakerNotesMap :: M.Map SlideId [[Paragraph]]
+ , stSpeakerNotes :: SpeakerNotes
} deriving (Show, Eq)
instance Default WriterState where
@@ -122,7 +122,7 @@ instance Default WriterState where
-- we reserve this s
, stSlideIdSet = reservedSlideIds
, stLog = []
- , stSpeakerNotesMap = mempty
+ , stSpeakerNotes = mempty
}
metadataSlideId :: SlideId
@@ -196,7 +196,7 @@ newtype SlideId = SlideId String
-- designed mainly for one textbox, so we'll just put in the contents
-- of that textbox, to avoid other shapes that won't work as well.
newtype SpeakerNotes = SpeakerNotes {fromSpeakerNotes :: [Paragraph]}
- deriving (Show, Eq, Monoid)
+ deriving (Show, Eq, Monoid, Semigroup)
data Layout = MetadataSlide { metadataSlideTitle :: [ParaElem]
, metadataSlideSubtitle :: [ParaElem]
@@ -565,13 +565,8 @@ isNotesDiv _ = False
handleNotes :: Block -> Pres ()
handleNotes (Div (_, ["notes"], _) blks) =
local (\env -> env{envInSpeakerNotes=True}) $ do
- sldId <- asks envCurSlideId
- spkNotesMap <- gets stSpeakerNotesMap
- paras <- concatMapM blockToParagraphs blks
- let spkNotesMap' = case M.lookup sldId spkNotesMap of
- Just lst -> M.insert sldId (paras : lst) spkNotesMap
- Nothing -> M.insert sldId [paras] spkNotesMap
- modify $ \st -> st{stSpeakerNotesMap = spkNotesMap'}
+ spNotes <- SpeakerNotes <$> concatMapM blockToParagraphs blks
+ modify $ \st -> st{stSpeakerNotes = (stSpeakerNotes st) <> spNotes}
handleNotes _ = return ()
handleAndFilterNotes :: [Block] -> Pres [Block]
@@ -632,13 +627,6 @@ splitBlocks' cur acc (blk : blks) = splitBlocks' (cur ++ [blk]) acc blks
splitBlocks :: [Block] -> Pres [[Block]]
splitBlocks = splitBlocks' [] []
-getSpeakerNotes :: Pres SpeakerNotes
-getSpeakerNotes = do
- sldId <- asks envCurSlideId
- spkNtsMap <- gets stSpeakerNotesMap
- let paras = fromMaybe [] (M.lookup sldId spkNtsMap)
- return $ SpeakerNotes $ concat $ reverse paras
-
blocksToSlide' :: Int -> [Block] -> Pres Slide
blocksToSlide' lvl (Header n (ident, _, _) ils : blks)
| n < lvl = do
@@ -710,9 +698,10 @@ blocksToSlide' _ [] = do
blocksToSlide :: [Block] -> Pres Slide
blocksToSlide blks = do
slideLevel <- asks envSlideLevel
+ modify $ \st -> st{stSpeakerNotes = mempty}
blks' <- walkM handleAndFilterNotes blks
sld <- blocksToSlide' slideLevel blks'
- spkNotes <- getSpeakerNotes
+ spkNotes <- gets stSpeakerNotes
return $ sld{slideSpeakerNotes = spkNotes}
makeNoteEntry :: Int -> [Block] -> [Block]