diff options
author | John MacFarlane <jgm@berkeley.edu> | 2019-10-10 08:59:37 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2019-10-10 09:15:40 -0700 |
commit | 68b09a6d81b24b928b1629ecb3061a51a5ce2352 (patch) | |
tree | 0c8d43810efdc45c62d3a312a95ee29118a2d085 /src | |
parent | 2b1361e7381d45c47c4a53becab5b895b26f1dae (diff) | |
download | pandoc-68b09a6d81b24b928b1629ecb3061a51a5ce2352.tar.gz |
Make some writers sensitive to 'unlisted' class on headings.
If this is present on a heading with the 'unnumbered' class,
the heading won't appear in the TOC. This class has no
effect if 'unnumbered' is not also specified.
This affects HTML-based writers (including slide shows
and epub), LateX (including beamer), RTF, and PowerPoint.
Other writers do not yet support `unlisted`.
Closes #1762.
Diffstat (limited to 'src')
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 10 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Shared.hs | 7 |
2 files changed, 10 insertions, 7 deletions
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 81a3082cb..e73819df0 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -748,7 +748,7 @@ blockToLaTeX HorizontalRule = "\\begin{center}\\rule{0.5\\linewidth}{\\linethickness}\\end{center}" blockToLaTeX (Header level (id',classes,_) lst) = do modify $ \s -> s{stInHeading = True} - hdr <- sectionHeader ("unnumbered" `elem` classes) id' level lst + hdr <- sectionHeader classes id' level lst modify $ \s -> s{stInHeading = False} return hdr blockToLaTeX (Table caption aligns widths heads rows) = do @@ -949,12 +949,14 @@ defListItemToLaTeX (term, defs) = do -- | Craft the section header, inserting the secton reference, if supplied. sectionHeader :: PandocMonad m - => Bool -- True for unnumbered + => [String] -- classes -> [Char] -> Int -> [Inline] -> LW m (Doc Text) -sectionHeader unnumbered ident level lst = do +sectionHeader classes ident level lst = do + let unnumbered = "unnumbered" `elem` classes + let unlisted = "unlisted" `elem` classes txt <- inlineListToLaTeX lst plain <- stringToLaTeX TextString $ concatMap stringify lst let removeInvalidInline (Note _) = [] @@ -1013,7 +1015,7 @@ sectionHeader unnumbered ident level lst = do return $ if level' > 5 then txt else prefix $$ stuffing' - $$ if unnumbered + $$ if unnumbered && not unlisted then "\\addcontentsline{toc}" <> braces (text sectionType) <> braces txtNoNotes diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs index c294eeebb..f7af26a99 100644 --- a/src/Text/Pandoc/Writers/Shared.hs +++ b/src/Text/Pandoc/Writers/Shared.hs @@ -40,7 +40,7 @@ where import Prelude import Safe (lastMay) import qualified Data.ByteString.Lazy as BL -import Data.Maybe (fromMaybe) +import Data.Maybe (fromMaybe, isNothing) import Control.Monad (zipWithM) import Data.Aeson (ToJSON (..), encode) import Data.Char (chr, ord, isSpace) @@ -394,8 +394,9 @@ toTableOfContents opts bs = -- | Converts an Element to a list item for a table of contents, sectionToListItem :: WriterOptions -> Block -> [Block] sectionToListItem opts (Div (ident,_,_) - (Header lev (_,_,kvs) ils : subsecs)) = - Plain headerLink : [BulletList listContents | not (null listContents) + (Header lev (_,classes,kvs) ils : subsecs)) + | not (isNothing (lookup "number" kvs) && "unlisted" `elem` classes) + = Plain headerLink : [BulletList listContents | not (null listContents) , lev < writerTOCDepth opts] where num = fromMaybe "" $ lookup "number" kvs |