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.
This commit is contained in:
John MacFarlane 2019-10-10 08:59:37 -07:00
parent 2b1361e738
commit 68b09a6d81
4 changed files with 33 additions and 7 deletions

View file

@ -2712,6 +2712,11 @@ is just the same as
# My heading {.unnumbered} # My heading {.unnumbered}
If the `unlisted` class is present in addition to `unnumbered`,
the heading will not be included in a table of contents.
(Currently this feature is only implemented for certain
formats: those based on LaTeX and HTML, PowerPoint, and RTF.)
#### Extension: `implicit_header_references` #### #### Extension: `implicit_header_references` ####
Pandoc behaves as if reference links have been defined for each heading. Pandoc behaves as if reference links have been defined for each heading.

View file

@ -748,7 +748,7 @@ blockToLaTeX HorizontalRule =
"\\begin{center}\\rule{0.5\\linewidth}{\\linethickness}\\end{center}" "\\begin{center}\\rule{0.5\\linewidth}{\\linethickness}\\end{center}"
blockToLaTeX (Header level (id',classes,_) lst) = do blockToLaTeX (Header level (id',classes,_) lst) = do
modify $ \s -> s{stInHeading = True} modify $ \s -> s{stInHeading = True}
hdr <- sectionHeader ("unnumbered" `elem` classes) id' level lst hdr <- sectionHeader classes id' level lst
modify $ \s -> s{stInHeading = False} modify $ \s -> s{stInHeading = False}
return hdr return hdr
blockToLaTeX (Table caption aligns widths heads rows) = do 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. -- | Craft the section header, inserting the secton reference, if supplied.
sectionHeader :: PandocMonad m sectionHeader :: PandocMonad m
=> Bool -- True for unnumbered => [String] -- classes
-> [Char] -> [Char]
-> Int -> Int
-> [Inline] -> [Inline]
-> LW m (Doc Text) -> 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 txt <- inlineListToLaTeX lst
plain <- stringToLaTeX TextString $ concatMap stringify lst plain <- stringToLaTeX TextString $ concatMap stringify lst
let removeInvalidInline (Note _) = [] let removeInvalidInline (Note _) = []
@ -1013,7 +1015,7 @@ sectionHeader unnumbered ident level lst = do
return $ if level' > 5 return $ if level' > 5
then txt then txt
else prefix $$ stuffing' else prefix $$ stuffing'
$$ if unnumbered $$ if unnumbered && not unlisted
then "\\addcontentsline{toc}" <> then "\\addcontentsline{toc}" <>
braces (text sectionType) <> braces (text sectionType) <>
braces txtNoNotes braces txtNoNotes

View file

@ -40,7 +40,7 @@ where
import Prelude import Prelude
import Safe (lastMay) import Safe (lastMay)
import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Lazy as BL
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe, isNothing)
import Control.Monad (zipWithM) import Control.Monad (zipWithM)
import Data.Aeson (ToJSON (..), encode) import Data.Aeson (ToJSON (..), encode)
import Data.Char (chr, ord, isSpace) 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, -- | Converts an Element to a list item for a table of contents,
sectionToListItem :: WriterOptions -> Block -> [Block] sectionToListItem :: WriterOptions -> Block -> [Block]
sectionToListItem opts (Div (ident,_,_) sectionToListItem opts (Div (ident,_,_)
(Header lev (_,_,kvs) ils : subsecs)) = (Header lev (_,classes,kvs) ils : subsecs))
Plain headerLink : [BulletList listContents | not (null listContents) | not (isNothing (lookup "number" kvs) && "unlisted" `elem` classes)
= Plain headerLink : [BulletList listContents | not (null listContents)
, lev < writerTOCDepth opts] , lev < writerTOCDepth opts]
where where
num = fromMaybe "" $ lookup "number" kvs num = fromMaybe "" $ lookup "number" kvs

18
test/command/1762.md Normal file
View file

@ -0,0 +1,18 @@
```
% pandoc -t latex
# One {.unlisted}
# Two {.unnumbered}
# Three {.unlisted .unnumbered}
^D
\hypertarget{one}{%
\section{One}\label{one}}
\hypertarget{two}{%
\section*{Two}\label{two}}
\addcontentsline{toc}{section}{Two}
\hypertarget{three}{%
\section*{Three}\label{three}}
```