Removed writerIgnoreNotes.
Instead, just temporarily remove notes when generating TOC lists in HTML and Markdown (as we already did in LaTeX). Also export deNote from Text.Pandoc.Shared. API change in Shared and Options.WriterOptions.
This commit is contained in:
parent
2d04922cd0
commit
4007d6a897
6 changed files with 10 additions and 18 deletions
|
@ -306,7 +306,6 @@ convertWithOpts opts args = do
|
|||
writerHTMLMathMethod = mathMethod,
|
||||
writerIncremental = incremental,
|
||||
writerCiteMethod = citeMethod,
|
||||
writerIgnoreNotes = False,
|
||||
writerNumberSections = numberSections,
|
||||
writerNumberOffset = numberFrom,
|
||||
writerSectionDivs = sectionDivs,
|
||||
|
|
|
@ -151,7 +151,6 @@ data WriterOptions = WriterOptions
|
|||
, writerSlideVariant :: HTMLSlideVariant -- ^ Are we writing S5, Slidy or Slideous?
|
||||
, writerIncremental :: Bool -- ^ True if lists should be incremental
|
||||
, writerHTMLMathMethod :: HTMLMathMethod -- ^ How to print math in HTML
|
||||
, writerIgnoreNotes :: Bool -- ^ Ignore footnotes (used in making toc)
|
||||
, writerNumberSections :: Bool -- ^ Number sections in LaTeX
|
||||
, writerNumberOffset :: [Int] -- ^ Starting number for section, subsection, ...
|
||||
, writerSectionDivs :: Bool -- ^ Put sections in div tags in HTML
|
||||
|
@ -197,7 +196,6 @@ instance Default WriterOptions where
|
|||
, writerSlideVariant = NoSlides
|
||||
, writerIncremental = False
|
||||
, writerHTMLMathMethod = PlainMath
|
||||
, writerIgnoreNotes = False
|
||||
, writerNumberSections = False
|
||||
, writerNumberOffset = [0,0,0,0,0,0]
|
||||
, writerSectionDivs = False
|
||||
|
|
|
@ -56,6 +56,7 @@ module Text.Pandoc.Shared (
|
|||
normalizeSpaces,
|
||||
extractSpaces,
|
||||
removeFormatting,
|
||||
deNote,
|
||||
stringify,
|
||||
capitalize,
|
||||
compactify,
|
||||
|
|
|
@ -30,6 +30,7 @@ Conversion of 'Pandoc' documents to HTML.
|
|||
-}
|
||||
module Text.Pandoc.Writers.HTML ( writeHtml , writeHtmlString ) where
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Walk
|
||||
import Data.Monoid ((<>))
|
||||
import Text.Pandoc.Shared
|
||||
import Text.Pandoc.Writers.Shared
|
||||
|
@ -228,8 +229,7 @@ defList opts items = toList H.dl opts (items ++ [nl opts])
|
|||
tableOfContents :: PandocMonad m => WriterOptions -> [Element] -> StateT WriterState m (Maybe Html)
|
||||
tableOfContents _ [] = return Nothing
|
||||
tableOfContents opts sects = do
|
||||
let opts' = opts { writerIgnoreNotes = True }
|
||||
contents <- mapM (elementToListItem opts') sects
|
||||
contents <- mapM (elementToListItem opts) sects
|
||||
let tocList = catMaybes contents
|
||||
return $ if null tocList
|
||||
then Nothing
|
||||
|
@ -253,7 +253,7 @@ elementToListItem opts (Sec lev num (id',classes,_) headerText subsecs)
|
|||
then (H.span ! A.class_ "toc-section-number"
|
||||
$ toHtml $ showSecNum num') >> preEscapedString " "
|
||||
else mempty
|
||||
txt <- liftM (sectnum >>) $ inlineListToHtml opts headerText
|
||||
txt <- liftM (sectnum >>) $ inlineListToHtml opts $ walk deNote headerText
|
||||
subHeads <- mapM (elementToListItem opts) subsecs >>= return . catMaybes
|
||||
let subList = if null subHeads
|
||||
then mempty
|
||||
|
@ -852,9 +852,7 @@ inlineToHtml opts inline =
|
|||
imgAttrsToHtml opts attr
|
||||
return $ foldl (!) H5.embed attributes
|
||||
-- note: null title included, as in Markdown.pl
|
||||
(Note contents)
|
||||
| writerIgnoreNotes opts -> return mempty
|
||||
| otherwise -> do
|
||||
(Note contents) -> do
|
||||
notes <- gets stNotes
|
||||
let number = (length notes) + 1
|
||||
let ref = show number
|
||||
|
|
|
@ -1318,10 +1318,6 @@ commonFromBcp47 x = fromIso $ head x
|
|||
fromIso "vi" = "vietnamese"
|
||||
fromIso _ = ""
|
||||
|
||||
deNote :: Inline -> Inline
|
||||
deNote (Note _) = RawInline (Format "latex") ""
|
||||
deNote x = x
|
||||
|
||||
pDocumentOptions :: P.Parsec String () [String]
|
||||
pDocumentOptions = do
|
||||
P.char '['
|
||||
|
|
|
@ -288,9 +288,8 @@ escapeString opts = escapeStringUsing markdownEscapes
|
|||
-- | Construct table of contents from list of header blocks.
|
||||
tableOfContents :: PandocMonad m => WriterOptions -> [Block] -> m Doc
|
||||
tableOfContents opts headers =
|
||||
let opts' = opts { writerIgnoreNotes = True }
|
||||
contents = BulletList $ map (elementToListItem opts) $ hierarchicalize headers
|
||||
in evalMD (blockToMarkdown opts' contents) def def
|
||||
let contents = BulletList $ map (elementToListItem opts) $ hierarchicalize headers
|
||||
in evalMD (blockToMarkdown opts contents) def def
|
||||
|
||||
-- | Converts an Element to a list item for a table of contents,
|
||||
elementToListItem :: WriterOptions -> Element -> [Block]
|
||||
|
@ -299,8 +298,9 @@ elementToListItem opts (Sec lev _nums (ident,_,_) headerText subsecs)
|
|||
[ BulletList (map (elementToListItem opts) subsecs) |
|
||||
not (null subsecs) && lev < writerTOCDepth opts ]
|
||||
where headerLink = if null ident
|
||||
then headerText
|
||||
else [Link nullAttr headerText ('#':ident, "")]
|
||||
then walk deNote headerText
|
||||
else [Link nullAttr (walk deNote headerText)
|
||||
('#':ident, "")]
|
||||
elementToListItem _ (Blk _) = []
|
||||
|
||||
attrsToMarkdown :: Attr -> Doc
|
||||
|
|
Loading…
Reference in a new issue