diff options
author | John MacFarlane <jgm@berkeley.edu> | 2017-01-15 22:34:14 +0100 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2017-01-25 17:07:42 +0100 |
commit | 4007d6a89749ff6576e65bb08631ff14a6d0ee20 (patch) | |
tree | a351b2840bae3e6c7e0cf63033c8be0789a7b1ee /src/Text/Pandoc/Writers | |
parent | 2d04922cd0f2213f371db41729f4348f968c8b30 (diff) | |
download | pandoc-4007d6a89749ff6576e65bb08631ff14a6d0ee20.tar.gz |
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.
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 10 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 10 |
3 files changed, 9 insertions, 15 deletions
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 40658eaa8..a63047866 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -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 diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index d9a31751e..655ea7dac 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -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 '[' diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 9ef968fc6..8ae550fe1 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -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 |