aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2020-12-04 09:47:56 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2020-12-04 09:47:56 -0800
commit171d3db3848a8ca79480688748d0ffff67ed2039 (patch)
tree6c98c625c1f3a59bd5c83ec35031cc9229651293 /src/Text
parent7199d68ba078148ff76a38f2c483da73edd62747 (diff)
downloadpandoc-171d3db3848a8ca79480688748d0ffff67ed2039.tar.gz
HTML writer: Fix handling of nested csl- display spans.
Previously inner Spans used to represent CSL display attributes were not rendered as div tags. See #6921.
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs32
1 files changed, 12 insertions, 20 deletions
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index c92131d5a..76f17f77a 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -695,12 +695,12 @@ blockToHtml opts (Div (ident, "section":dclasses, dkvs)
let fragmentClass = case slideVariant of
RevealJsSlides -> "fragment"
_ -> "incremental"
- let inDiv zs = RawBlock (Format "html") ("<div class=\""
+ let inDiv' zs = RawBlock (Format "html") ("<div class=\""
<> fragmentClass <> "\">") :
(zs ++ [RawBlock (Format "html") "</div>"])
let breakOnPauses zs = case splitBy isPause zs of
[] -> []
- y:ys -> y ++ concatMap inDiv ys
+ y:ys -> y ++ concatMap inDiv' ys
let (titleBlocks, innerSecs) =
if titleSlide
-- title slides have no content of their own
@@ -783,9 +783,7 @@ blockToHtml opts (Div attr@(ident, classes, kvs') bs) = do
-- a newline between the column divs, which throws
-- off widths! see #4028
mconcat <$> mapM (blockToHtml opts) bs
- else if isCslBibEntry
- then mconcat <$> mapM (cslEntryToHtml opts') bs
- else blockListToHtml opts' bs
+ else blockListToHtml opts' bs
let contents' = nl opts >> contents >> nl opts
let (divtag, classes'') = if html5 && "section" `elem` classes'
then (H5.section, filter (/= "section") classes')
@@ -1213,6 +1211,10 @@ inlineToHtml opts inline = do
LineBreak -> return $ do
if html5 then H5.br else H.br
strToHtml "\n"
+ (Span ("",[cls],[]) ils)
+ | cls == "csl-block" || cls == "csl-left-margin" ||
+ cls == "csl-right-inline" || cls == "csl-indent"
+ -> inlineListToHtml opts ils >>= inDiv cls
(Span (id',classes,kvs) ils) ->
let spanLikeTag = case classes of
@@ -1462,22 +1464,12 @@ blockListToNote opts ref blocks = do
_ -> noteItem
return $ nl opts >> noteItem'
-cslEntryToHtml :: PandocMonad m
- => WriterOptions
- -> Block
- -> StateT WriterState m Html
-cslEntryToHtml opts (Para xs) = do
+inDiv :: PandocMonad m=> Text -> Html -> StateT WriterState m Html
+inDiv cls x = do
html5 <- gets stHtml5
- let inDiv :: Text -> Html -> Html
- inDiv cls x = (if html5 then H5.div else H.div)
- x ! A.class_ (toValue cls)
- let go (Span ("",[cls],[]) ils)
- | cls == "csl-block" || cls == "csl-left-margin" ||
- cls == "csl-right-inline" || cls == "csl-indent"
- = inDiv cls <$> inlineListToHtml opts ils
- go il = inlineToHtml opts il
- mconcat <$> mapM go xs
-cslEntryToHtml opts x = blockToHtml opts x
+ return $
+ (if html5 then H5.div else H.div)
+ x ! A.class_ (toValue cls)
isMathEnvironment :: Text -> Bool
isMathEnvironment s = "\\begin{" `T.isPrefixOf` s &&