diff options
-rw-r--r-- | pandoc.hs | 1 | ||||
-rw-r--r-- | src/Text/Pandoc/Options.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 1 | ||||
-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 |
6 files changed, 10 insertions, 18 deletions
@@ -306,7 +306,6 @@ convertWithOpts opts args = do writerHTMLMathMethod = mathMethod, writerIncremental = incremental, writerCiteMethod = citeMethod, - writerIgnoreNotes = False, writerNumberSections = numberSections, writerNumberOffset = numberFrom, writerSectionDivs = sectionDivs, diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index d81f4da88..cd10abeff 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -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 diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 18b4d3eac..f2a80fccf 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -56,6 +56,7 @@ module Text.Pandoc.Shared ( normalizeSpaces, extractSpaces, removeFormatting, + deNote, stringify, capitalize, compactify, 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 |