aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--MANUAL.txt5
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs10
-rw-r--r--src/Text/Pandoc/Writers/Shared.hs7
-rw-r--r--test/command/1762.md18
4 files changed, 33 insertions, 7 deletions
diff --git a/MANUAL.txt b/MANUAL.txt
index b4e15319f..f7373b4c4 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -2712,6 +2712,11 @@ is just the same as
# 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` ####
Pandoc behaves as if reference links have been defined for each heading.
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
diff --git a/test/command/1762.md b/test/command/1762.md
new file mode 100644
index 000000000..c0c34dc24
--- /dev/null
+++ b/test/command/1762.md
@@ -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}}
+```