aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/HTML.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/HTML.hs')
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs374
1 files changed, 220 insertions, 154 deletions
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 6f91d1965..8c5548196 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -28,7 +28,6 @@ module Text.Pandoc.Writers.HTML (
writeRevealJs,
tagWithAttributes
) where
-import Control.Monad.Identity (runIdentity)
import Control.Monad.State.Strict
import Data.Char (ord)
import Data.List (intercalate, intersperse, partition, delete, (\\), foldl')
@@ -38,10 +37,9 @@ import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
-import Network.HTTP (urlEncode)
import Network.URI (URI (..), parseURIReference)
import Numeric (showHex)
-import Text.DocLayout (render, literal)
+import Text.DocLayout (render, literal, Doc)
import Text.Blaze.Internal (MarkupM (Empty), customLeaf, customParent)
import Text.DocTemplates (FromContext (lookupContext), Context (..))
import Text.Blaze.Html hiding (contents)
@@ -52,11 +50,12 @@ import Text.Pandoc.ImageSize
import Text.Pandoc.Options
import Text.Pandoc.Shared
import Text.Pandoc.Slides
-import Text.Pandoc.Templates (Template, compileTemplate, renderTemplate)
+import Text.Pandoc.Templates (renderTemplate)
import Text.Pandoc.Walk
import Text.Pandoc.Writers.Math
import Text.Pandoc.Writers.Shared
import qualified Text.Pandoc.Writers.AnnotatedTable as Ann
+import Text.Pandoc.Network.HTTP (urlEncode)
import Text.Pandoc.XML (escapeStringForXML, fromEntities, toEntities,
html5Attributes, html4Attributes, rdfaAttributes)
import qualified Text.Blaze.XHtml5 as H5
@@ -71,13 +70,16 @@ import Text.Pandoc.Class.PandocPure (runPure)
import Text.Pandoc.Error
import Text.Pandoc.Logging
import Text.Pandoc.MIME (mediaCategory)
+import Text.Pandoc.Writers.Blaze (layoutMarkup)
import Text.TeXMath
import Text.XML.Light (elChildren, unode, unqual)
import qualified Text.XML.Light as XML
import Text.XML.Light.Output
+import Data.String (fromString)
data WriterState = WriterState
{ stNotes :: [Html] -- ^ List of notes
+ , stEmittedNotes :: Int -- ^ How many notes we've already pushed out to the HTML
, stMath :: Bool -- ^ Math is used in document
, stQuotes :: Bool -- ^ <q> tag is used
, stHighlighting :: Bool -- ^ Syntax highlighting is used
@@ -89,10 +91,11 @@ data WriterState = WriterState
, stCodeBlockNum :: Int -- ^ Number of code block
, stCsl :: Bool -- ^ Has CSL references
, stCslEntrySpacing :: Maybe Int -- ^ CSL entry spacing
+ , stBlockLevel :: Int -- ^ Current block depth, excluding section divs
}
defaultWriterState :: WriterState
-defaultWriterState = WriterState {stNotes= [], stMath = False, stQuotes = False,
+defaultWriterState = WriterState {stNotes= [], stEmittedNotes = 0, stMath = False, stQuotes = False,
stHighlighting = False,
stHtml5 = False,
stEPUBVersion = Nothing,
@@ -101,7 +104,8 @@ defaultWriterState = WriterState {stNotes= [], stMath = False, stQuotes = False,
stInSection = False,
stCodeBlockNum = 0,
stCsl = False,
- stCslEntrySpacing = Nothing}
+ stCslEntrySpacing = Nothing,
+ stBlockLevel = 0}
-- Helpers to render HTML with the appropriate function.
@@ -128,10 +132,8 @@ needsVariationSelector '↔' = True
needsVariationSelector _ = False
-- | Hard linebreak.
-nl :: WriterOptions -> Html
-nl opts = if writerWrapText opts == WrapNone
- then mempty
- else preEscapedString "\n"
+nl :: Html
+nl = preEscapedString "\n"
-- | Convert Pandoc document to Html 5 string.
writeHtml5String :: PandocMonad m => WriterOptions -> Pandoc -> m Text
@@ -157,7 +159,8 @@ writeHtmlStringForEPUB :: PandocMonad m
-> m Text
writeHtmlStringForEPUB version o = writeHtmlString'
defaultWriterState{ stHtml5 = version == EPUB3,
- stEPUBVersion = Just version } o
+ stEPUBVersion = Just version }
+ o{ writerWrapText = WrapNone }
-- | Convert Pandoc document to Reveal JS HTML slide show.
writeRevealJs :: PandocMonad m
@@ -204,20 +207,23 @@ writeHtmlString' :: PandocMonad m
=> WriterState -> WriterOptions -> Pandoc -> m Text
writeHtmlString' st opts d = do
(body, context) <- evalStateT (pandocToHtml opts d) st
- let defaultTemplate = fmap (const tocTemplate) (getField "table-of-contents" context :: Maybe Text)
- let template = msum [ writerTemplate opts
- , defaultTemplate ]
+ let colwidth = case writerWrapText opts of
+ WrapAuto -> Just (writerColumns opts)
+ _ -> Nothing
(if writerPreferAscii opts
then toEntities
else id) <$>
- case template of
- Nothing -> return $ renderHtml' body
+ case writerTemplate opts of
+ Nothing -> return $
+ case colwidth of
+ Nothing -> renderHtml' body -- optimization, skip layout
+ Just cols -> render (Just cols) $ layoutMarkup body
Just tpl -> do
-- warn if empty lang
when (isNothing (getField "lang" context :: Maybe Text)) $
report NoLangSpecified
-- check for empty pagetitle
- context' <-
+ (context' :: Context Text) <-
case getField "pagetitle" context of
Just (s :: Text) | not (T.null s) -> return context
_ -> do
@@ -228,9 +234,9 @@ writeHtmlString' st opts d = do
Just [] -> "Untitled"
Just (x:_) -> takeBaseName $ T.unpack x
report $ NoTitleElement fallback
- return $ resetField "pagetitle" fallback context
- return $ render Nothing $ renderTemplate tpl
- (defField "body" (renderHtml' body) context')
+ return $ resetField "pagetitle" (literal fallback) context
+ return $ render colwidth $ renderTemplate tpl
+ (defField "body" (layoutMarkup body) context')
writeHtml' :: PandocMonad m => WriterState -> WriterOptions -> Pandoc -> m Html
writeHtml' st opts d =
@@ -243,13 +249,6 @@ writeHtml' st opts d =
(body, _) <- evalStateT (pandocToHtml opts d) st
return body
-wantTOC :: Meta -> Maybe Bool
-wantTOC = fmap (== MetaBool True) . lookupMeta "tableOfContents"
-
-tocTemplate :: Template Text
-tocTemplate = either error id . runIdentity . compileTemplate "" $
- "<div class=\"toc\"><h1></h1>$table-of-contents$</div>$body$"
-
-- result is (title, authors, date, toc, body, new variables)
pandocToHtml :: PandocMonad m
=> WriterOptions
@@ -259,13 +258,13 @@ pandocToHtml opts (Pandoc meta blocks) = do
let slideLevel = fromMaybe (getSlideLevel blocks) $ writerSlideLevel opts
modify $ \st -> st{ stSlideLevel = slideLevel }
metadata <- metaToContext opts
- (fmap (literal . renderHtml') . blockListToHtml opts)
- (fmap (literal . renderHtml') . inlineListToHtml opts)
+ (fmap layoutMarkup . blockListToHtml opts)
+ (fmap layoutMarkup . inlineListToHtml opts)
meta
let stringifyHTML = escapeStringForXML . stringify
- let authsMeta = map stringifyHTML $ docAuthors meta
+ let authsMeta = map (literal . stringifyHTML) $ docAuthors meta
let dateMeta = stringifyHTML $ docDate meta
- let descriptionMeta = escapeStringForXML $
+ let descriptionMeta = literal $ escapeStringForXML $
lookupMetaString "description" meta
slideVariant <- gets stSlideVariant
let sects = adjustNumbers opts $
@@ -273,15 +272,22 @@ pandocToHtml opts (Pandoc meta blocks) = do
if slideVariant == NoSlides
then blocks
else prepSlides slideLevel blocks
- let withTOC = fromMaybe (writerTableOfContents opts) (wantTOC meta)
- toc <- if withTOC && slideVariant /= S5Slides
- then fmap renderHtml' <$> tableOfContents opts sects
+ toc <- if writerTableOfContents opts && slideVariant /= S5Slides
+ then fmap layoutMarkup <$> tableOfContents opts sects
else return Nothing
blocks' <- blockListToHtml opts sects
+ notes <- do
+ -- make the st private just to be safe, since we modify it right afterwards
+ st <- get
+ if null (stNotes st)
+ then return mempty
+ else do
+ notes <- footnoteSection EndOfDocument (stEmittedNotes st + 1) (reverse (stNotes st))
+ modify (\st' -> st'{ stNotes = mempty, stEmittedNotes = stEmittedNotes st' + length (stNotes st') })
+ return notes
st <- get
- notes <- footnoteSection opts (reverse (stNotes st))
let thebody = blocks' >> notes
- let math = case writerHTMLMathMethod opts of
+ let math = layoutMarkup $ case writerHTMLMathMethod opts of
MathJax url
| slideVariant /= RevealJsSlides ->
-- mathjax is handled via a special plugin in revealjs
@@ -295,10 +301,10 @@ pandocToHtml opts (Pandoc meta blocks) = do
KaTeX url -> do
H.script !
A.src (toValue $ url <> "katex.min.js") $ mempty
- nl opts
+ nl
let katexFlushLeft =
case lookupContext "classoption" metadata of
- Just clsops | "fleqn" `elem` (clsops :: [Text]) -> "true"
+ Just clsops | "fleqn" `elem` (clsops :: [Doc Text]) -> "true"
_ -> "false"
H.script $ text $ T.unlines [
"document.addEventListener(\"DOMContentLoaded\", function () {"
@@ -315,7 +321,7 @@ pandocToHtml opts (Pandoc meta blocks) = do
, " });"
, "}}});"
]
- nl opts
+ nl
H.link ! A.rel "stylesheet" !
A.href (toValue $ url <> "katex.min.css")
@@ -324,15 +330,16 @@ pandocToHtml opts (Pandoc meta blocks) = do
Just s | not (stHtml5 st) ->
H.script ! A.type_ "text/javascript"
$ preEscapedString
- ("/*<![CDATA[*/\n" ++ T.unpack s ++
+ ("/*<![CDATA[*/\n" <> T.unpack s <>
"/*]]>*/\n")
| otherwise -> mempty
Nothing -> mempty
let mCss :: Maybe [Text] = lookupContext "css" metadata
- let context = (if stHighlighting st
+ let context :: Context Text
+ context = (if stHighlighting st
then case writerHighlightStyle opts of
Just sty -> defField "highlighting-css"
- (T.pack $ styleToCss sty)
+ (literal $ T.pack $ styleToCss sty)
Nothing -> id
else id) .
(if stCsl st
@@ -342,15 +349,15 @@ pandocToHtml opts (Pandoc meta blocks) = do
Just 0 -> id
Just n ->
defField "csl-entry-spacing"
- (tshow n <> "em"))
+ (literal $ tshow n <> "em"))
else id) .
(if stMath st
- then defField "math" (renderHtml' math)
+ then defField "math" math
else id) .
(case writerHTMLMathMethod opts of
MathJax u -> defField "mathjax" True .
defField "mathjaxurl"
- (T.takeWhile (/='?') u)
+ (literal $ T.takeWhile (/='?') u)
_ -> defField "mathjax" False) .
(case writerHTMLMathMethod opts of
PlainMath -> defField "displaymath-css" True
@@ -361,13 +368,14 @@ pandocToHtml opts (Pandoc meta blocks) = do
-- template can't distinguish False/undefined
defField "controls" True .
defField "controlsTutorial" True .
- defField "controlsLayout" ("bottom-right" :: Text) .
- defField "controlsBackArrows" ("faded" :: Text) .
+ defField "controlsLayout"
+ ("bottom-right" :: Doc Text) .
+ defField "controlsBackArrows" ("faded" :: Doc Text) .
defField "progress" True .
defField "slideNumber" False .
- defField "showSlideNumber" ("all" :: Text) .
+ defField "showSlideNumber" ("all" :: Doc Text) .
defField "hashOneBasedIndex" False .
- defField "hash" False .
+ defField "hash" True .
defField "respondToHashChanges" True .
defField "history" False .
defField "keyboard" True .
@@ -377,7 +385,7 @@ pandocToHtml opts (Pandoc meta blocks) = do
defField "touch" True .
defField "loop" False .
defField "rtl" False .
- defField "navigationMode" ("default" :: Text) .
+ defField "navigationMode" ("default" :: Doc Text) .
defField "shuffle" False .
defField "fragments" True .
defField "fragmentInURL" True .
@@ -385,22 +393,22 @@ pandocToHtml opts (Pandoc meta blocks) = do
defField "help" True .
defField "pause" True .
defField "showNotes" False .
- defField "autoPlayMedia" ("null" :: Text) .
- defField "preloadIframes" ("null" :: Text) .
- defField "autoSlide" ("0" :: Text) .
+ defField "autoPlayMedia" ("null" :: Doc Text) .
+ defField "preloadIframes" ("null" :: Doc Text) .
+ defField "autoSlide" ("0" :: Doc Text) .
defField "autoSlideStoppable" True .
- defField "autoSlideMethod" ("null" :: Text) .
- defField "defaultTiming" ("null" :: Text) .
+ defField "autoSlideMethod" ("null" :: Doc Text) .
+ defField "defaultTiming" ("null" :: Doc Text) .
defField "mouseWheel" False .
- defField "display" ("block" :: Text) .
+ defField "display" ("block" :: Doc Text) .
defField "hideInactiveCursor" True .
- defField "hideCursorTime" ("5000" :: Text) .
+ defField "hideCursorTime" ("5000" :: Doc Text) .
defField "previewLinks" False .
- defField "transition" ("slide" :: Text) .
- defField "transitionSpeed" ("default" :: Text) .
- defField "backgroundTransition" ("fade" :: Text) .
- defField "viewDistance" ("3" :: Text) .
- defField "mobileViewDistance" ("2" :: Text)
+ defField "transition" ("slide" :: Doc Text) .
+ defField "transitionSpeed" ("default" :: Doc Text) .
+ defField "backgroundTransition" ("fade" :: Doc Text) .
+ defField "viewDistance" ("3" :: Doc Text) .
+ defField "mobileViewDistance" ("2" :: Doc Text)
else id) .
defField "document-css" (isNothing mCss && slideVariant == NoSlides) .
defField "quotes" (stQuotes st) .
@@ -410,18 +418,18 @@ pandocToHtml opts (Pandoc meta blocks) = do
maybe id (defField "toc") toc .
maybe id (defField "table-of-contents") toc .
defField "author-meta" authsMeta .
- maybe id (defField "date-meta")
+ maybe id (defField "date-meta" . literal)
(normalizeDate dateMeta) .
defField "description-meta" descriptionMeta .
defField "pagetitle"
- (stringifyHTML . docTitle $ meta) .
- defField "idprefix" (writerIdentifierPrefix opts) .
+ (literal . stringifyHTML . docTitle $ meta) .
+ defField "idprefix" (literal $ writerIdentifierPrefix opts) .
-- these should maybe be set in pandoc.hs
defField "slidy-url"
- ("https://www.w3.org/Talks/Tools/Slidy2" :: Text) .
- defField "slideous-url" ("slideous" :: Text) .
- defField "revealjs-url" ("https://unpkg.com/reveal.js@^4/" :: Text) $
- defField "s5-url" ("s5/default" :: Text) .
+ ("https://www.w3.org/Talks/Tools/Slidy2" :: Doc Text) .
+ defField "slideous-url" ("slideous" :: Doc Text) .
+ defField "revealjs-url" ("https://unpkg.com/reveal.js@^4/" :: Doc Text) $
+ defField "s5-url" ("s5/default" :: Doc Text) .
defField "html5" (stHtml5 st) $
metadata
return (thebody, context)
@@ -449,15 +457,15 @@ toList listop opts items = do
unordList :: PandocMonad m
=> WriterOptions -> [Html] -> StateT WriterState m Html
-unordList opts = toList H.ul opts . toListItems opts
+unordList opts = toList H.ul opts . toListItems
ordList :: PandocMonad m
=> WriterOptions -> [Html] -> StateT WriterState m Html
-ordList opts = toList H.ol opts . toListItems opts
+ordList opts = toList H.ol opts . toListItems
defList :: PandocMonad m
=> WriterOptions -> [Html] -> StateT WriterState m Html
-defList opts items = toList H.dl opts (items ++ [nl opts])
+defList opts items = toList H.dl opts (items ++ [nl])
isTaskListItem :: [Block] -> Bool
isTaskListItem (Plain (Str "☐":Space:_):_) = True
@@ -479,7 +487,7 @@ listItemToHtml opts bls
let checkbox = if checked
then checkbox' ! A.checked ""
else checkbox'
- checkbox' = H.input ! A.type_ "checkbox" ! A.disabled "" >> nl opts
+ checkbox' = H.input ! A.type_ "checkbox" ! A.disabled "" >> nl
isContents <- inlineListToHtml opts is
bsContents <- blockListToHtml opts bs
return $ constr (checkbox >> isContents) >> bsContents
@@ -502,28 +510,45 @@ tableOfContents opts sects = do
-- | Convert list of Note blocks to a footnote <div>.
-- Assumes notes are sorted.
-footnoteSection :: PandocMonad m
- => WriterOptions -> [Html] -> StateT WriterState m Html
-footnoteSection opts notes = do
+footnoteSection ::
+ PandocMonad m => ReferenceLocation -> Int -> [Html] -> StateT WriterState m Html
+footnoteSection refLocation startCounter notes = do
html5 <- gets stHtml5
slideVariant <- gets stSlideVariant
- let hrtag = if html5 then H5.hr else H.hr
+ let hrtag = if refLocation /= EndOfBlock
+ then (if html5 then H5.hr else H.hr) <> nl
+ else mempty
+ let additionalClassName = case refLocation of
+ EndOfBlock -> "footnotes-end-of-block"
+ EndOfDocument -> "footnotes-end-of-document"
+ EndOfSection -> "footnotes-end-of-section"
+ let className = "footnotes " <> additionalClassName
epubVersion <- gets stEPUBVersion
let container x
| html5
, epubVersion == Just EPUB3
- = H5.section ! A.class_ "footnotes"
+ = H5.section ! A.class_ className
! customAttribute "epub:type" "footnotes" $ x
- | html5 = H5.section ! A.class_ "footnotes"
+ | html5 = H5.section ! A.class_ className
! customAttribute "role" "doc-endnotes"
$ x
| slideVariant /= NoSlides = H.div ! A.class_ "footnotes slide" $ x
- | otherwise = H.div ! A.class_ "footnotes" $ x
+ | otherwise = H.div ! A.class_ className $ x
return $
if null notes
then mempty
- else nl opts >> container (nl opts >> hrtag >> nl opts >>
- H.ol (mconcat notes >> nl opts) >> nl opts)
+ else do
+ nl
+ container $ do
+ nl
+ hrtag
+ -- Keep the previous output exactly the same if we don't
+ -- have multiple notes sections
+ if startCounter == 1
+ then H.ol $ mconcat notes >> nl
+ else H.ol ! A.start (fromString (show startCounter)) $
+ mconcat notes >> nl
+ nl
-- | Parse a mailto link; return Just (name, domain) or Nothing.
parseMailto :: Text -> Maybe (Text, Text)
@@ -618,6 +643,7 @@ toAttrs kvs = do
return (keys, attrs)
else return (Set.insert k keys, addAttr html5 mbEpubVersion k v attrs)
addAttr html5 mbEpubVersion x y
+ | T.null x = id -- see #7546
| html5
= if x `Set.member` (html5Attributes <> rdfaAttributes)
|| T.any (== ':') x -- e.g. epub: namespace
@@ -689,12 +715,11 @@ figure opts attr@(_, _, attrList) txt (s,tit) = do
img <- inlineToHtml opts (Image attr alt (s,tit))
capt <- if null txt
then return mempty
- else tocapt `fmap` inlineListToHtml opts txt
+ else (nl <>) . tocapt <$> inlineListToHtml opts txt
+ let inner = mconcat [nl, img, capt, nl]
return $ if html5
- then H5.figure $ mconcat
- [nl opts, img, capt, nl opts]
- else H.div ! A.class_ "figure" $ mconcat
- [nl opts, img, nl opts, capt, nl opts]
+ then H5.figure inner
+ else H.div ! A.class_ "figure" $ inner
adjustNumbers :: WriterOptions -> [Block] -> [Block]
@@ -714,11 +739,10 @@ adjustNumbers opts doc =
fixnum x = x
showSecNum = T.intercalate "." . map tshow
--- | Convert Pandoc block element to HTML.
-blockToHtml :: PandocMonad m => WriterOptions -> Block -> StateT WriterState m Html
-blockToHtml _ Null = return mempty
-blockToHtml opts (Plain lst) = inlineListToHtml opts lst
-blockToHtml opts (Para [Image attr@(_,classes,_) txt (src,tit)])
+blockToHtmlInner :: PandocMonad m => WriterOptions -> Block -> StateT WriterState m Html
+blockToHtmlInner _ Null = return mempty
+blockToHtmlInner opts (Plain lst) = inlineListToHtml opts lst
+blockToHtmlInner opts (Para [Image attr@(_,classes,_) txt (src,tit)])
| "stretch" `elem` classes = do
slideVariant <- gets stSlideVariant
case slideVariant of
@@ -728,20 +752,20 @@ blockToHtml opts (Para [Image attr@(_,classes,_) txt (src,tit)])
inlineToHtml opts (Image attr txt (src, tit))
_ -> figure opts attr txt (src, tit)
-- title beginning with fig: indicates that the image is a figure
-blockToHtml opts (Para [Image attr txt (s,T.stripPrefix "fig:" -> Just tit)]) =
- figure opts attr txt (s,tit)
-blockToHtml opts (Para lst) = do
+blockToHtmlInner opts (SimpleFigure attr caption (src, title)) =
+ figure opts attr caption (src, title)
+blockToHtmlInner opts (Para lst) = do
contents <- inlineListToHtml opts lst
case contents of
Empty _ | not (isEnabled Ext_empty_paragraphs opts) -> return mempty
_ -> return $ H.p contents
-blockToHtml opts (LineBlock lns) =
+blockToHtmlInner opts (LineBlock lns) =
if writerWrapText opts == WrapNone
then blockToHtml opts $ linesToPara lns
else do
htmlLines <- inlineListToHtml opts $ intercalate [LineBreak] lns
return $ H.div ! A.class_ "line-block" $ htmlLines
-blockToHtml opts (Div (ident, "section":dclasses, dkvs)
+blockToHtmlInner opts (Div (ident, "section":dclasses, dkvs)
(Header level
hattr@(hident,hclasses,hkvs) ils : xs)) = do
slideVariant <- gets stSlideVariant
@@ -796,33 +820,33 @@ blockToHtml opts (Div (ident, "section":dclasses, dkvs)
if titleSlide
then do
t <- addAttrs opts attr $
- secttag $ nl opts <> header' <> nl opts <> titleContents <> nl opts
+ secttag $ nl <> header' <> nl <> titleContents <> nl
-- ensure 2D nesting for revealjs, but only for one level;
-- revealjs doesn't like more than one level of nesting
return $
if slideVariant == RevealJsSlides && not inSection &&
not (null innerSecs)
- then H5.section (nl opts <> t <> nl opts <> innerContents)
- else t <> nl opts <> if null innerSecs
+ then H5.section (nl <> t <> nl <> innerContents)
+ else t <> nl <> if null innerSecs
then mempty
- else innerContents <> nl opts
+ else innerContents <> nl
else if writerSectionDivs opts || slide ||
(hident /= ident && not (T.null hident || T.null ident)) ||
(hclasses /= dclasses) || (hkvs /= dkvs)
then addAttrs opts attr
$ secttag
- $ nl opts <> header' <> nl opts <>
+ $ nl <> header' <> nl <>
if null innerSecs
then mempty
- else innerContents <> nl opts
+ else innerContents <> nl
else do
let attr' = (ident, classes' \\ hclasses, dkvs \\ hkvs)
t <- addAttrs opts attr' header'
return $ t <>
if null innerSecs
then mempty
- else nl opts <> innerContents
-blockToHtml opts (Div attr@(ident, classes, kvs') bs) = do
+ else nl <> innerContents
+blockToHtmlInner opts (Div attr@(ident, classes, kvs') bs) = do
html5 <- gets stHtml5
slideVariant <- gets stSlideVariant
let isCslBibBody = ident == "refs" || "csl-bib-body" `elem` classes
@@ -859,7 +883,7 @@ blockToHtml opts (Div attr@(ident, classes, kvs') bs) = do
-- off widths! see #4028
mconcat <$> mapM (blockToHtml opts) bs'
else blockListToHtml opts' bs'
- let contents' = nl opts >> contents >> nl opts
+ let contents' = nl >> contents >> nl
let (divtag, classes'') = if html5 && "section" `elem` classes'
then (H5.section, filter (/= "section") classes')
else (H.div, classes')
@@ -876,7 +900,7 @@ blockToHtml opts (Div attr@(ident, classes, kvs') bs) = do
_ -> return mempty
else addAttrs opts (ident, classes'', kvs) $
divtag contents'
-blockToHtml opts (RawBlock f str) = do
+blockToHtmlInner opts (RawBlock f str) = do
ishtml <- isRawHtml f
if ishtml
then return $ preEscapedText str
@@ -887,10 +911,10 @@ blockToHtml opts (RawBlock f str) = do
else do
report $ BlockNotRendered (RawBlock f str)
return mempty
-blockToHtml _ HorizontalRule = do
+blockToHtmlInner _ HorizontalRule = do
html5 <- gets stHtml5
return $ if html5 then H5.hr else H.hr
-blockToHtml opts (CodeBlock (id',classes,keyvals) rawCode) = do
+blockToHtmlInner opts (CodeBlock (id',classes,keyvals) rawCode) = do
id'' <- if T.null id'
then do
modify $ \st -> st{ stCodeBlockNum = stCodeBlockNum st + 1 }
@@ -922,7 +946,7 @@ blockToHtml opts (CodeBlock (id',classes,keyvals) rawCode) = do
-- we set writerIdentifierPrefix to "" since id'' already
-- includes it:
addAttrs opts{writerIdentifierPrefix = ""} (id'',[],keyvals) h
-blockToHtml opts (BlockQuote blocks) = do
+blockToHtmlInner opts (BlockQuote blocks) = do
-- in S5, treat list in blockquote specially
-- if default is incremental, make it nonincremental;
-- otherwise incremental
@@ -940,11 +964,11 @@ blockToHtml opts (BlockQuote blocks) = do
(DefinitionList lst)
_ -> do contents <- blockListToHtml opts blocks
return $ H.blockquote
- $ nl opts >> contents >> nl opts
+ $ nl >> contents >> nl
else do
contents <- blockListToHtml opts blocks
- return $ H.blockquote $ nl opts >> contents >> nl opts
-blockToHtml opts (Header level (ident,classes,kvs) lst) = do
+ return $ H.blockquote $ nl >> contents >> nl
+blockToHtmlInner opts (Header level (ident,classes,kvs) lst) = do
contents <- inlineListToHtml opts lst
let secnum = fromMaybe mempty $ lookup "number" kvs
let contents' = if writerNumberSections opts && not (T.null secnum)
@@ -967,12 +991,12 @@ blockToHtml opts (Header level (ident,classes,kvs) lst) = do
5 -> H.h5 contents'
6 -> H.h6 contents'
_ -> H.p ! A.class_ "heading" $ contents'
-blockToHtml opts (BulletList lst) = do
+blockToHtmlInner opts (BulletList lst) = do
contents <- mapM (listItemToHtml opts) lst
let isTaskList = not (null lst) && all isTaskListItem lst
(if isTaskList then (! A.class_ "task-list") else id) <$>
unordList opts contents
-blockToHtml opts (OrderedList (startnum, numstyle, _) lst) = do
+blockToHtmlInner opts (OrderedList (startnum, numstyle, _) lst) = do
contents <- mapM (listItemToHtml opts) lst
html5 <- gets stHtml5
let numstyle' = case numstyle of
@@ -995,17 +1019,47 @@ blockToHtml opts (OrderedList (startnum, numstyle, _) lst) = do
else [])
l <- ordList opts contents
return $ foldl' (!) l attribs
-blockToHtml opts (DefinitionList lst) = do
+blockToHtmlInner opts (DefinitionList lst) = do
contents <- mapM (\(term, defs) ->
do term' <- liftM H.dt $ inlineListToHtml opts term
- defs' <- mapM (liftM (\x -> H.dd (x >> nl opts)) .
+ defs' <- mapM (liftM (\x -> H.dd (nl >> x >> nl)) .
blockListToHtml opts) defs
- return $ mconcat $ nl opts : term' : nl opts :
- intersperse (nl opts) defs') lst
+ return $ mconcat $ nl : term' : nl :
+ intersperse (nl) defs') lst
defList opts contents
-blockToHtml opts (Table attr caption colspecs thead tbody tfoot) =
+blockToHtmlInner opts (Table attr caption colspecs thead tbody tfoot) =
tableToHtml opts (Ann.toTable attr caption colspecs thead tbody tfoot)
+-- | Convert Pandoc block element to HTML. All the legwork is done by
+-- 'blockToHtmlInner', this just takes care of emitting the notes after
+-- the block if necessary.
+blockToHtml :: PandocMonad m => WriterOptions -> Block -> StateT WriterState m Html
+blockToHtml opts block = do
+ -- Ignore inserted section divs -- they are not blocks as they came from
+ -- the document itself (at least not when coming from markdown)
+ let isSection = case block of
+ Div (_, classes, _) _ | "section" `elem` classes -> True
+ _ -> False
+ let increaseLevel = not isSection
+ when increaseLevel $
+ modify (\st -> st{ stBlockLevel = stBlockLevel st + 1 })
+ doc <- blockToHtmlInner opts block
+ st <- get
+ let emitNotes =
+ (writerReferenceLocation opts == EndOfBlock && stBlockLevel st == 1) ||
+ (writerReferenceLocation opts == EndOfSection && isSection)
+ res <- if emitNotes
+ then do
+ notes <- if null (stNotes st)
+ then return mempty
+ else footnoteSection (writerReferenceLocation opts) (stEmittedNotes st + 1) (reverse (stNotes st))
+ modify (\st' -> st'{ stNotes = mempty, stEmittedNotes = stEmittedNotes st' + length (stNotes st') })
+ return (doc <> notes)
+ else return doc
+ when increaseLevel $
+ modify (\st' -> st'{ stBlockLevel = stBlockLevel st' - 1 })
+ return res
+
tableToHtml :: PandocMonad m
=> WriterOptions
-> Ann.Table
@@ -1017,10 +1071,10 @@ tableToHtml opts (Ann.Table attr caption colspecs thead tbodies tfoot) = do
cs <- blockListToHtml opts longCapt
return $ do
H.caption cs
- nl opts
- coltags <- colSpecListToHtml opts colspecs
+ nl
+ coltags <- colSpecListToHtml colspecs
head' <- tableHeadToHtml opts thead
- bodies <- intersperse (nl opts) <$> mapM (tableBodyToHtml opts) tbodies
+ bodies <- intersperse (nl) <$> mapM (tableBodyToHtml opts) tbodies
foot' <- tableFootToHtml opts tfoot
let (ident,classes,kvs) = attr
-- When widths of columns are < 100%, we need to set width for the whole
@@ -1037,13 +1091,13 @@ tableToHtml opts (Ann.Table attr caption colspecs thead tbodies tfoot) = do
<> "%;"):kvs)
_ -> attr
addAttrs opts attr' $ H.table $ do
- nl opts
+ nl
captionDoc
coltags
head'
mconcat bodies
foot'
- nl opts
+ nl
tableBodyToHtml :: PandocMonad m
=> WriterOptions
@@ -1090,7 +1144,7 @@ tablePartToHtml opts tblpart attr rows =
tablePartElement <- addAttrs opts attr $ tag' contents
return $ do
tablePartElement
- nl opts
+ nl
where
isEmptyRow (Ann.HeaderRow _attr _rownum cells) = all isEmptyCell cells
isEmptyCell (Ann.Cell _colspecs _colnum cell) =
@@ -1131,14 +1185,13 @@ rowListToHtml :: PandocMonad m
-> [TableRow]
-> StateT WriterState m Html
rowListToHtml opts rows =
- (\x -> nl opts *> mconcat x) <$>
+ (\x -> nl *> mconcat x) <$>
mapM (tableRowToHtml opts) rows
colSpecListToHtml :: PandocMonad m
- => WriterOptions
- -> [ColSpec]
+ => [ColSpec]
-> StateT WriterState m Html
-colSpecListToHtml opts colspecs = do
+colSpecListToHtml colspecs = do
html5 <- gets stHtml5
let hasDefaultWidth (_, ColWidthDefault) = True
hasDefaultWidth _ = False
@@ -1152,16 +1205,16 @@ colSpecListToHtml opts colspecs = do
ColWidth w -> if html5
then A.style (toValue $ "width: " <> percent w)
else A.width (toValue $ percent w)
- nl opts
+ nl
return $
if all hasDefaultWidth colspecs
then mempty
else do
H.colgroup $ do
- nl opts
+ nl
mapM_ (col . snd) colspecs
- nl opts
+ nl
tableRowToHtml :: PandocMonad m
=> WriterOptions
@@ -1180,12 +1233,12 @@ tableRowToHtml opts (TableRow tblpart attr rownum rowhead rowbody) = do
headcells <- mapM (cellToHtml opts HeaderCell) rowhead
bodycells <- mapM (cellToHtml opts celltype) rowbody
rowHtml <- addAttrs opts attr' $ H.tr $ do
- nl opts
+ nl
mconcat headcells
mconcat bodycells
return $ do
rowHtml
- nl opts
+ nl
alignmentToString :: Alignment -> Maybe Text
alignmentToString = \case
@@ -1243,18 +1296,18 @@ tableCellToHtml opts ctype colAlign (Cell attr align rowspan colspan item) = do
: otherAttribs
return $ do
tag' ! attribs $ contents
- nl opts
+ nl
-toListItems :: WriterOptions -> [Html] -> [Html]
-toListItems opts items = map (toListItem opts) items ++ [nl opts]
+toListItems :: [Html] -> [Html]
+toListItems items = map toListItem items ++ [nl]
-toListItem :: WriterOptions -> Html -> Html
-toListItem opts item = nl opts *> H.li item
+toListItem :: Html -> Html
+toListItem item = nl *> H.li item
blockListToHtml :: PandocMonad m
=> WriterOptions -> [Block] -> StateT WriterState m Html
blockListToHtml opts lst =
- mconcat . intersperse (nl opts) . filter nonempty
+ mconcat . intersperse (nl) . filter nonempty
<$> mapM (blockToHtml opts) lst
where nonempty (Empty _) = False
nonempty _ = True
@@ -1286,9 +1339,9 @@ inlineToHtml opts inline = do
(Str str) -> return $ strToHtml str
Space -> return $ strToHtml " "
SoftBreak -> return $ case writerWrapText opts of
- WrapNone -> preEscapedText " "
- WrapAuto -> preEscapedText " "
- WrapPreserve -> preEscapedText "\n"
+ WrapNone -> " "
+ WrapAuto -> " "
+ WrapPreserve -> nl
LineBreak -> return $ do
if html5 then H5.br else H.br
strToHtml "\n"
@@ -1389,7 +1442,7 @@ inlineToHtml opts inline = do
InlineMath -> "\\textstyle "
DisplayMath -> "\\displaystyle "
return $ imtag ! A.style "vertical-align:middle"
- ! A.src (toValue $ url <> T.pack (urlEncode (T.unpack $ s <> str)))
+ ! A.src (toValue . (url <>) . urlEncode $ s <> str)
! A.alt (toValue str)
! A.title (toValue str)
! A.class_ mathClass
@@ -1424,13 +1477,17 @@ inlineToHtml opts inline = do
ishtml <- isRawHtml f
if ishtml
then return $ preEscapedText str
- else if (f == Format "latex" || f == Format "tex") &&
- allowsMathEnvironments (writerHTMLMathMethod opts) &&
- isMathEnvironment str
- then inlineToHtml opts $ Math DisplayMath str
- else do
- report $ InlineNotRendered inline
- return mempty
+ else do
+ let istex = f == Format "latex" || f == Format "tex"
+ let mm = writerHTMLMathMethod opts
+ case istex of
+ True
+ | allowsMathEnvironments mm && isMathEnvironment str
+ -> inlineToHtml opts $ Math DisplayMath str
+ | allowsRef mm && isRef str
+ -> inlineToHtml opts $ Math InlineMath str
+ _ -> do report $ InlineNotRendered inline
+ return mempty
(Link attr txt (s,_)) | "mailto:" `T.isPrefixOf` s -> do
linkText <- inlineListToHtml opts txt
obfuscateLink opts attr linkText s
@@ -1480,7 +1537,8 @@ inlineToHtml opts inline = do
-- note: null title included, as in Markdown.pl
(Note contents) -> do
notes <- gets stNotes
- let number = length notes + 1
+ emittedNotes <- gets stEmittedNotes
+ let number = emittedNotes + length notes + 1
let ref = tshow number
htmlContents <- blockListToNote opts ref contents
epubVersion <- gets stEPUBVersion
@@ -1548,7 +1606,7 @@ blockListToNote opts ref blocks = do
_ | html5 -> noteItem !
customAttribute "role" "doc-endnote"
_ -> noteItem
- return $ nl opts >> noteItem'
+ return $ nl >> noteItem'
inDiv :: PandocMonad m=> Text -> Html -> StateT WriterState m Html
inDiv cls x = do
@@ -1557,6 +1615,9 @@ inDiv cls x = do
(if html5 then H5.div else H.div)
x ! A.class_ (toValue cls)
+isRef :: Text -> Bool
+isRef t = "\\ref{" `T.isPrefixOf` t || "\\eqref{" `T.isPrefixOf` t
+
isMathEnvironment :: Text -> Bool
isMathEnvironment s = "\\begin{" `T.isPrefixOf` s &&
envName `elem` mathmlenvs
@@ -1591,10 +1652,15 @@ isMathEnvironment s = "\\begin{" `T.isPrefixOf` s &&
allowsMathEnvironments :: HTMLMathMethod -> Bool
allowsMathEnvironments (MathJax _) = True
+allowsMathEnvironments (KaTeX _) = True
allowsMathEnvironments MathML = True
allowsMathEnvironments (WebTeX _) = True
allowsMathEnvironments _ = False
+allowsRef :: HTMLMathMethod -> Bool
+allowsRef (MathJax _) = True
+allowsRef _ = False
+
-- | List of intrinsic event attributes allowed on all elements in HTML4.
intrinsicEventsHTML4 :: [Text]
intrinsicEventsHTML4 =