diff options
author | Emily Bourke <undergroundquizscene@protonmail.com> | 2021-09-07 13:38:47 +0100 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2021-09-15 09:13:05 -0700 |
commit | 0fb6474a55427b52bf9aebd179f7b26f30c7dbaf (patch) | |
tree | 805afab753da87814146374b3305fc2f60f5024a /src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | |
parent | a3162d341b2937113514b5f515cbc86141fbfcf2 (diff) | |
download | pandoc-0fb6474a55427b52bf9aebd179f7b26f30c7dbaf.tar.gz |
pptx: Add support for incremental lists
- Support -i option
- Support incremental/noincremental divs
- Support older block quote syntax
- Add tests
One thing not clear from the manual is what should happen when the input
uses a combination of these things. For example, what should the
following produce?
```md
::: {.incremental .nonincremental}
- are
- these
- incremental?
:::
::: incremental
::::: nonincremental
- or
- these?
:::::
:::
::: nonincremental
> - how
> - about
> - these?
:::
```
In this commit I’ve taken the following approach, matching the observed
behaviour for beamer and reveal.js output:
- if a div with both classes, incremental wins
- the innermost incremental/nonincremental div is the one which takes
effect
- a block quote containing a list as its first element inverts whether
the list is incremental, whether or not the quote is inside an
incremental/non-incremental div
I’ve added some tests to verify this behaviour.
This commit closes issue #5689
(https://github.com/jgm/pandoc/issues/5689).
Diffstat (limited to 'src/Text/Pandoc/Writers/Powerpoint/Presentation.hs')
-rw-r--r-- | src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | 51 |
1 files changed, 45 insertions, 6 deletions
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs index 015e2cbdd..a7660fc5e 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs @@ -1,8 +1,9 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE ViewPatterns #-} -{-# LANGUAGE GeneralizedNewtypeDeriving #-} -{-# LANGUAGE LambdaCase #-} {- | Module : Text.Pandoc.Writers.Powerpoint.Presentation Copyright : Copyright (C) 2017-2020 Jesse Rosenthal @@ -80,6 +81,8 @@ data WriterEnv = WriterEnv { envMetadata :: Meta , envInNoteSlide :: Bool , envCurSlideId :: SlideId , envInSpeakerNotes :: Bool + , envInIncrementalDiv :: Maybe InIncrementalDiv + , envInListInBlockQuote :: Bool } deriving (Show) @@ -94,6 +97,8 @@ instance Default WriterEnv where , envInNoteSlide = False , envCurSlideId = SlideId "Default" , envInSpeakerNotes = False + , envInIncrementalDiv = Nothing + , envInListInBlockQuote = False } @@ -114,6 +119,23 @@ instance Default WriterState where , stSpeakerNotes = mempty } +data InIncrementalDiv + = InIncremental + -- ^ The current content is contained within an "incremental" div. + | InNonIncremental + -- ^ The current content is contained within a "nonincremental" div. + deriving (Show) + +listShouldBeIncremental :: Pres Bool +listShouldBeIncremental = do + incrementalOption <- asks (writerIncremental . envOpts) + inIncrementalDiv <- asks envInIncrementalDiv + inBlockQuote <- asks envInListInBlockQuote + let toBoolean = (\case InIncremental -> True + InNonIncremental -> False) + maybeInvert = if inBlockQuote then not else id + pure (maybeInvert (maybe incrementalOption toBoolean inIncrementalDiv)) + metadataSlideId :: SlideId metadataSlideId = SlideId "Metadata" @@ -227,7 +249,7 @@ data Graphic = Tbl TableProps [TableCell] [[TableCell]] data Paragraph = Paragraph { paraProps :: ParaProps - , paraElems :: [ParaElem] + , paraElems :: [ParaElem] } deriving (Show, Eq) data BulletType = Bullet @@ -244,6 +266,7 @@ data ParaProps = ParaProps { pPropMarginLeft :: Maybe Pixels , pPropAlign :: Maybe Algnment , pPropSpaceBefore :: Maybe Pixels , pPropIndent :: Maybe Pixels + , pPropIncremental :: Bool } deriving (Show, Eq) instance Default ParaProps where @@ -254,6 +277,7 @@ instance Default ParaProps where , pPropAlign = Nothing , pPropSpaceBefore = Nothing , pPropIndent = Just 0 + , pPropIncremental = False } newtype TeXString = TeXString {unTeXString :: T.Text} @@ -449,7 +473,8 @@ blockToParagraphs (CodeBlock attr str) = do -- (BlockQuote List) as a list to maintain compatibility with other -- formats. blockToParagraphs (BlockQuote (blk : blks)) | isListType blk = do - ps <- blockToParagraphs blk + ps <- local (\env -> env { envInListInBlockQuote = True }) + (blockToParagraphs blk) ps' <- blockToParagraphs $ BlockQuote blks return $ ps ++ ps' blockToParagraphs (BlockQuote blks) = @@ -474,25 +499,30 @@ blockToParagraphs (Header _ (ident, _, _) ils) = do return [Paragraph def{pPropSpaceBefore = Just 30} parElems] blockToParagraphs (BulletList blksLst) = do pProps <- asks envParaProps + incremental <- listShouldBeIncremental let lvl = pPropLevel pProps local (\env -> env{ envInList = True , envParaProps = pProps{ pPropLevel = lvl + 1 , pPropBullet = Just Bullet , pPropMarginLeft = Nothing , pPropIndent = Nothing + , pPropIncremental = incremental }}) $ concatMapM multiParBullet blksLst blockToParagraphs (OrderedList listAttr blksLst) = do pProps <- asks envParaProps + incremental <- listShouldBeIncremental let lvl = pPropLevel pProps local (\env -> env{ envInList = True , envParaProps = pProps{ pPropLevel = lvl + 1 , pPropBullet = Just (AutoNumbering listAttr) , pPropMarginLeft = Nothing , pPropIndent = Nothing + , pPropIncremental = incremental }}) $ concatMapM multiParBullet blksLst blockToParagraphs (DefinitionList entries) = do + incremental <- listShouldBeIncremental let go :: ([Inline], [[Block]]) -> Pres [Paragraph] go (ils, blksLst) = do term <-blockToParagraphs $ Para [Strong ils] @@ -500,8 +530,17 @@ blockToParagraphs (DefinitionList entries) = do -- blockquote. We can extend this further later. definition <- concatMapM (blockToParagraphs . BlockQuote) blksLst return $ term ++ definition - concatMapM go entries -blockToParagraphs (Div _ blks) = concatMapM blockToParagraphs blks + local (\env -> env {envParaProps = + (envParaProps env) {pPropIncremental = incremental}}) + $ concatMapM go entries +blockToParagraphs (Div (_, classes, _) blks) = let + hasIncremental = "incremental" `elem` classes + hasNonIncremental = "nonincremental" `elem` classes + incremental = if | hasIncremental -> Just InIncremental + | hasNonIncremental -> Just InNonIncremental + | otherwise -> Nothing + addIncremental env = env { envInIncrementalDiv = incremental } + in local addIncremental (concatMapM blockToParagraphs blks) blockToParagraphs blk = do addLogMessage $ BlockNotRendered blk return [] |