From 407de98b5e3971c84c7e89de5f2a9d317b4d4557 Mon Sep 17 00:00:00 2001 From: mt_caret Date: Wed, 4 Aug 2021 05:53:05 +0800 Subject: Stop using the HTTP package. (#7456) We only depend on the urlEncode function in the package, which is also provided by http-types. The HTTP package also depends on the network package, which has difficulty building on ghcjs. Add internal module Text.Pandoc.Network.HTTP, exporting `urlEncode`. --- src/Text/Pandoc/Writers/HTML.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers/HTML.hs') diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 7eb8dfe12..89fc110ef 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -37,7 +37,6 @@ 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) @@ -56,6 +55,7 @@ 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 @@ -1377,7 +1377,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 -- cgit v1.2.3 From 99a4d1d0b06bb68e4d7a10acd642d439842004d1 Mon Sep 17 00:00:00 2001 From: Francesco Mazzoli Date: Fri, 10 Sep 2021 18:30:05 +0200 Subject: Support `--reference-location` for HTML output (#7461) The HTML writer now supports `EndOfBlock`, `EndOfSection`, and `EndOfDocument` for reference locations. EPUB and HTML slide show formats are also affected by this change. This works similarly to the markdown writer, but with special care taken to skipping section divs with what regards to the block level. The change also takes care to not modify the output if `EndOfDocument` is used. --- MANUAL.txt | 2 +- man/pandoc.1 | 2 +- src/Text/Pandoc/Writers/HTML.hs | 121 +++++++++++++++++++++++++++++----------- test/Tests/Writers/HTML.hs | 75 ++++++++++++++++++++++++- test/command/4235.md | 2 +- test/command/7006.md | 2 +- test/writer.html4 | 2 +- test/writer.html5 | 2 +- 8 files changed, 169 insertions(+), 39 deletions(-) (limited to 'src/Text/Pandoc/Writers/HTML.hs') diff --git a/MANUAL.txt b/MANUAL.txt index afdd66ddd..57b9f3b2c 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -972,7 +972,7 @@ header when requesting a document from a URL: : Specify whether footnotes (and references, if `reference-links` is set) are placed at the end of the current (top-level) block, the current section, or the document. The default is - `document`. Currently only affects the markdown writer. + `document`. Currently only affects the markdown and HTML writers. `--markdown-headings=setext`|`atx` diff --git a/man/pandoc.1 b/man/pandoc.1 index a0092b385..e901f60b3 100644 --- a/man/pandoc.1 +++ b/man/pandoc.1 @@ -995,7 +995,7 @@ Specify whether footnotes (and references, if \f[C]reference-links\f[R] is set) are placed at the end of the current (top-level) block, the current section, or the document. The default is \f[C]document\f[R]. -Currently only affects the markdown writer. +Currently only affects the markdown and HTML writers. .TP \f[B]\f[CB]--markdown-headings=setext\f[B]\f[R]|\f[B]\f[CB]atx\f[B]\f[R] Specify whether to use ATX-style (\f[C]#\f[R]-prefixed) or Setext-style diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 89fc110ef..c96d4622a 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -74,9 +74,11 @@ 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 -- ^ tag is used , stHighlighting :: Bool -- ^ Syntax highlighting is used @@ -88,10 +90,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, @@ -100,7 +103,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. @@ -266,8 +270,16 @@ pandocToHtml opts (Pandoc meta blocks) = do then fmap renderHtml' <$> 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 opts 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 MathJax url @@ -490,28 +502,43 @@ tableOfContents opts sects = do -- | Convert list of Note blocks to a footnote
. -- Assumes notes are sorted. -footnoteSection :: PandocMonad m - => WriterOptions -> [Html] -> StateT WriterState m Html -footnoteSection opts notes = do +footnoteSection :: + PandocMonad m => WriterOptions -> ReferenceLocation -> Int -> [Html] -> StateT WriterState m Html +footnoteSection opts 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) 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 opts + container $ do + nl opts + hrtag + nl opts + -- Keep the previous output exactly the same if we don't + -- have multiple notes sections + if startCounter == 1 + then H.ol $ mconcat notes >> nl opts + else H.ol ! A.start (fromString (show startCounter)) $ mconcat notes >> nl opts + nl opts -- | Parse a mailto link; return Just (name, domain) or Nothing. parseMailto :: Text -> Maybe (Text, Text) @@ -702,11 +729,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 @@ -716,20 +742,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)]) = +blockToHtmlInner opts (Para [Image attr txt (s,T.stripPrefix "fig:" -> Just tit)]) = figure opts attr txt (s,tit) -blockToHtml opts (Para lst) = do +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 @@ -810,7 +836,7 @@ blockToHtml opts (Div (ident, "section":dclasses, dkvs) if null innerSecs then mempty else nl opts <> innerContents -blockToHtml opts (Div attr@(ident, classes, kvs') bs) = do +blockToHtmlInner opts (Div attr@(ident, classes, kvs') bs) = do html5 <- gets stHtml5 slideVariant <- gets stSlideVariant let isCslBibBody = ident == "refs" || "csl-bib-body" `elem` classes @@ -864,7 +890,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 @@ -875,10 +901,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 } @@ -910,7 +936,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 @@ -932,7 +958,7 @@ blockToHtml opts (BlockQuote blocks) = do else do contents <- blockListToHtml opts blocks return $ H.blockquote $ nl opts >> contents >> nl opts -blockToHtml opts (Header level (ident,classes,kvs) lst) = do +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) @@ -955,12 +981,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 @@ -983,7 +1009,7 @@ 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)) . @@ -991,9 +1017,39 @@ blockToHtml opts (DefinitionList lst) = do return $ mconcat $ nl opts : term' : nl opts : intersperse (nl opts) 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 opts (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 @@ -1468,7 +1524,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 diff --git a/test/Tests/Writers/HTML.hs b/test/Tests/Writers/HTML.hs index 404f6da98..50775b171 100644 --- a/test/Tests/Writers/HTML.hs +++ b/test/Tests/Writers/HTML.hs @@ -8,8 +8,11 @@ import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder +htmlWithOpts :: (ToPandoc a) => WriterOptions -> a -> String +htmlWithOpts opts = unpack . purely (writeHtml4String opts{ writerWrapText = WrapNone }) . toPandoc + html :: (ToPandoc a) => a -> String -html = unpack . purely (writeHtml4String def{ writerWrapText = WrapNone }) . toPandoc +html = htmlWithOpts def htmlQTags :: (ToPandoc a) => a -> String htmlQTags = unpack @@ -33,6 +36,21 @@ infix 4 =: => String -> (a, String) -> TestTree (=:) = test html +noteTestDoc :: Blocks +noteTestDoc = + header 1 "Page title" <> + header 2 "First section" <> + para ("This is a footnote." <> + note (para "Down here.") <> + " And this is a " <> + link "https://www.google.com" "" "link" <> + ".") <> + blockQuote (para ("A note inside a block quote." <> + note (para "The second note.")) <> + para "A second paragraph.") <> + header 2 "Second section" <> + para "Some more text." + tests :: [TestTree] tests = [ testGroup "inline code" @@ -86,6 +104,61 @@ tests = =?> ("" ++ ">>=") ] + , testGroup "footnotes" + [ test (htmlWithOpts def{writerReferenceLocation=EndOfDocument}) + "at the end of a document" $ + noteTestDoc =?> + concat + [ "

Page title

" + , "

First section

" + , "

This is a footnote.1 And this is a link.

" + , "

A note inside a block quote.2

A second paragraph.

" + , "

Second section

" + , "

Some more text.

" + , "

  1. Down here.↩︎

  2. The second note.↩︎

" + ] + , test (htmlWithOpts def{writerReferenceLocation=EndOfBlock}) + "at the end of a block" $ + noteTestDoc =?> + concat + [ "

Page title

" + , "

First section

" + , "

This is a footnote.1 And this is a link.

" + , "
  1. Down here.↩︎

" + , "

A note inside a block quote.2

A second paragraph.

" + , "
  1. The second note.↩︎

" + , "

Second section

" + , "

Some more text.

" + ] + , test (htmlWithOpts def{writerReferenceLocation=EndOfSection}) + "at the end of a section" $ + noteTestDoc =?> + concat + [ "

Page title

" + , "

First section

" + , "

This is a footnote.1 And this is a link.

" + , "

A note inside a block quote.2

A second paragraph.

" + , "

  1. Down here.↩︎

  2. The second note.↩︎

" + , "

Second section

" + , "

Some more text.

" + ] + , test (htmlWithOpts def{writerReferenceLocation=EndOfSection, writerSectionDivs=True}) + "at the end of a section, with section divs" $ + noteTestDoc =?> + -- Footnotes are rendered _after_ their section (in this case after the level2 section + -- that contains it). + concat + [ "
" + , "

Page title

" + , "
" + , "

First section

" + , "

This is a footnote.1 And this is a link.

A note inside a block quote.2

A second paragraph.

" + , "
" + , "

  1. Down here.↩︎

  2. The second note.↩︎

" + , "

Second section

Some more text.

" + , "
" + ] + ] ] where tQ :: (ToString a, ToPandoc a) diff --git a/test/command/4235.md b/test/command/4235.md index 8bbf43ff9..4f2644dd6 100644 --- a/test/command/4235.md +++ b/test/command/4235.md @@ -3,7 +3,7 @@ This.^[Has a footnote.] ^D

This.1

-
+

  1. Has a footnote.↩︎

  2. diff --git a/test/command/7006.md b/test/command/7006.md index e7951fb1a..7e2215cdf 100644 --- a/test/command/7006.md +++ b/test/command/7006.md @@ -7,7 +7,7 @@ Test.[^fn] ![Caption.](/image.jpg) ^D

    Test.1

    -
    +

    1. Foo:

      diff --git a/test/writer.html4 b/test/writer.html4 index 215a1efb9..257d86ddb 100644 --- a/test/writer.html4 +++ b/test/writer.html4 @@ -665,7 +665,7 @@ Blah
    2. And in list items.5

    This paragraph should not be part of the note, as it is not indented.

    -
    +

    1. Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.↩︎

    2. diff --git a/test/writer.html5 b/test/writer.html5 index 387df4058..0141bf9fe 100644 --- a/test/writer.html5 +++ b/test/writer.html5 @@ -667,7 +667,7 @@ Blah
    3. And in list items.5

    This paragraph should not be part of the note, as it is not indented.

    -
    +

    1. Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.↩︎

    2. -- cgit v1.2.3 From d2449ad92642a5ba380979192029600a4f3e4424 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 16 Sep 2021 19:27:34 -0700 Subject: HTML writer: set "hash" to True by default (for reveal.js). Closes #7574. See #6968 where the motivation for setting "hash" to True is explained. --- src/Text/Pandoc/Writers/HTML.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src/Text/Pandoc/Writers/HTML.hs') diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index c96d4622a..3592bd2d4 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -367,7 +367,7 @@ pandocToHtml opts (Pandoc meta blocks) = do defField "slideNumber" False . defField "showSlideNumber" ("all" :: Text) . defField "hashOneBasedIndex" False . - defField "hash" False . + defField "hash" True . defField "respondToHashChanges" True . defField "history" False . defField "keyboard" True . -- cgit v1.2.3 From 7ab2f4a61d43928f597cad4916d25a94a5bde0e8 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 22 Sep 2021 22:18:38 -0700 Subject: HTML writer: pass through inline math environments with KaTeX. --- src/Text/Pandoc/Writers/HTML.hs | 1 + 1 file changed, 1 insertion(+) (limited to 'src/Text/Pandoc/Writers/HTML.hs') diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 3592bd2d4..03d182f5e 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -1636,6 +1636,7 @@ isMathEnvironment s = "\\begin{" `T.isPrefixOf` s && allowsMathEnvironments :: HTMLMathMethod -> Bool allowsMathEnvironments (MathJax _) = True +allowsMathEnvironments (KaTeX _) = True allowsMathEnvironments MathML = True allowsMathEnvironments (WebTeX _) = True allowsMathEnvironments _ = False -- cgit v1.2.3 From 0afb48cd384ea1663f88bda32d0d149dc9a6f6c5 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 22 Sep 2021 22:33:00 -0700 Subject: HTML writer: pass through `\ref` and `\eqref`... if MathJax is used. Closes #7587. --- src/Text/Pandoc/Writers/HTML.hs | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) (limited to 'src/Text/Pandoc/Writers/HTML.hs') diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 03d182f5e..f883bd6d8 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -1469,8 +1469,9 @@ inlineToHtml opts inline = do if ishtml then return $ preEscapedText str else if (f == Format "latex" || f == Format "tex") && - allowsMathEnvironments (writerHTMLMathMethod opts) && - isMathEnvironment str + ((allowsMathEnvironments (writerHTMLMathMethod opts) && + isMathEnvironment str) || + (allowsRef (writerHTMLMathMethod opts) && isRef str)) then inlineToHtml opts $ Math DisplayMath str else do report $ InlineNotRendered inline @@ -1602,6 +1603,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 @@ -1641,6 +1645,10 @@ 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 = -- cgit v1.2.3 From f0a6eb913d7ace9de720539efb8984ea00ac82db Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 23 Sep 2021 08:49:52 -0700 Subject: HTML writer: render `\ref` and `\eqref` as inline math... not display. See #7589. --- src/Text/Pandoc/Writers/HTML.hs | 19 +++++++++++-------- 1 file changed, 11 insertions(+), 8 deletions(-) (limited to 'src/Text/Pandoc/Writers/HTML.hs') diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index f883bd6d8..8fc81ed24 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -1468,14 +1468,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) || - (allowsRef (writerHTMLMathMethod opts) && isRef 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 -- cgit v1.2.3 From fb0d6c7cb63a791fa72becf21ed493282e65ea91 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Fri, 1 Oct 2021 15:42:00 -0700 Subject: Depend on pandoc-types 1.23, remove Null constructor on Block. --- pandoc.cabal | 4 ++-- src/Text/Pandoc/Lua/Marshaling/AST.hs | 2 -- src/Text/Pandoc/Shared.hs | 1 - src/Text/Pandoc/Writers/AsciiDoc.hs | 1 - src/Text/Pandoc/Writers/ConTeXt.hs | 1 - src/Text/Pandoc/Writers/Custom.hs | 2 -- src/Text/Pandoc/Writers/Docbook.hs | 1 - src/Text/Pandoc/Writers/Docx.hs | 1 - src/Text/Pandoc/Writers/DokuWiki.hs | 2 -- src/Text/Pandoc/Writers/FB2.hs | 1 - src/Text/Pandoc/Writers/HTML.hs | 1 - src/Text/Pandoc/Writers/Haddock.hs | 1 - src/Text/Pandoc/Writers/ICML.hs | 1 - src/Text/Pandoc/Writers/JATS.hs | 1 - src/Text/Pandoc/Writers/Jira.hs | 1 - src/Text/Pandoc/Writers/LaTeX.hs | 1 - src/Text/Pandoc/Writers/Man.hs | 1 - src/Text/Pandoc/Writers/Markdown.hs | 3 +-- src/Text/Pandoc/Writers/MediaWiki.hs | 2 -- src/Text/Pandoc/Writers/Ms.hs | 1 - src/Text/Pandoc/Writers/Muse.hs | 1 - src/Text/Pandoc/Writers/OpenDocument.hs | 1 - src/Text/Pandoc/Writers/Org.hs | 1 - src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | 1 - src/Text/Pandoc/Writers/RST.hs | 1 - src/Text/Pandoc/Writers/RTF.hs | 1 - src/Text/Pandoc/Writers/TEI.hs | 1 - src/Text/Pandoc/Writers/Texinfo.hs | 2 -- src/Text/Pandoc/Writers/Textile.hs | 2 -- src/Text/Pandoc/Writers/XWiki.hs | 2 -- src/Text/Pandoc/Writers/ZimWiki.hs | 2 -- stack.yaml | 9 +++++++-- 32 files changed, 10 insertions(+), 43 deletions(-) (limited to 'src/Text/Pandoc/Writers/HTML.hs') diff --git a/pandoc.cabal b/pandoc.cabal index f317c3302..a55dbcc22 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -561,7 +561,7 @@ library mtl >= 2.2 && < 2.3, network >= 2.6, network-uri >= 2.6 && < 2.8, - pandoc-types >= 1.22 && < 1.23, + pandoc-types >= 1.23 && < 1.24, parsec >= 3.1 && < 3.2, process >= 1.2.3 && < 1.7, random >= 1 && < 1.3, @@ -848,7 +848,7 @@ test-suite test-pandoc filepath >= 1.1 && < 1.5, hslua >= 1.1 && < 1.4, mtl >= 2.2 && < 2.3, - pandoc-types >= 1.22 && < 1.23, + pandoc-types >= 1.23 && < 1.24, process >= 1.2.3 && < 1.7, tasty >= 0.11 && < 1.5, tasty-golden >= 2.3 && < 2.4, diff --git a/src/Text/Pandoc/Lua/Marshaling/AST.hs b/src/Text/Pandoc/Lua/Marshaling/AST.hs index 8e12d232c..a1ad2cda3 100644 --- a/src/Text/Pandoc/Lua/Marshaling/AST.hs +++ b/src/Text/Pandoc/Lua/Marshaling/AST.hs @@ -165,7 +165,6 @@ pushBlock = \case LineBlock blcks -> pushViaConstructor "LineBlock" blcks OrderedList lstAttr list -> pushViaConstructor "OrderedList" list (LuaListAttributes lstAttr) - Null -> pushViaConstructor "Null" Para blcks -> pushViaConstructor "Para" blcks Plain blcks -> pushViaConstructor "Plain" blcks RawBlock f cs -> pushViaConstructor "RawBlock" f cs @@ -189,7 +188,6 @@ peekBlock idx = defineHowTo "get Block value" $! do "OrderedList" -> (\(LuaListAttributes lstAttr, lst) -> OrderedList lstAttr lst) <$!> elementContent - "Null" -> return Null "Para" -> Para <$!> elementContent "Plain" -> Plain <$!> elementContent "RawBlock" -> uncurry RawBlock <$!> elementContent diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 920edca7b..7bb830d0e 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -948,7 +948,6 @@ blockToInlines (Table _ _ _ (TableHead _ hbd) bodies (TableFoot _ fbd)) = unTableBody (TableBody _ _ hd bd) = hd <> bd unTableBodies = concatMap unTableBody blockToInlines (Div _ blks) = blocksToInlines' blks -blockToInlines Null = mempty blocksToInlinesWithSep :: Inlines -> [Block] -> Inlines blocksToInlinesWithSep sep = diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index bcef4a089..f0973178e 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -140,7 +140,6 @@ blockToAsciiDoc :: PandocMonad m => WriterOptions -- ^ Options -> Block -- ^ Block element -> ADW m (Doc Text) -blockToAsciiDoc _ Null = return empty blockToAsciiDoc opts (Div (id',"section":_,_) (Header level (_,cls,kvs) ils : xs)) = do hdr <- blockToAsciiDoc opts (Header level (id',cls,kvs) ils) diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 3cafcefba..0150f7dff 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -154,7 +154,6 @@ toLabel z = T.concatMap go z -- | Convert Pandoc block element to ConTeXt. blockToConTeXt :: PandocMonad m => Block -> WM m (Doc Text) -blockToConTeXt Null = return empty blockToConTeXt (Div attr@(_,"section":_,_) (Header level _ title' : xs)) = do header' <- sectionHeader attr level title' diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs index 1e9f37d2f..d207f5093 100644 --- a/src/Text/Pandoc/Writers/Custom.hs +++ b/src/Text/Pandoc/Writers/Custom.hs @@ -116,8 +116,6 @@ docToCustom opts (Pandoc (Meta metamap) blocks) = do blockToCustom :: Block -- ^ Block element -> Lua String -blockToCustom Null = return "" - blockToCustom (Plain inlines) = Lua.callFunc "Plain" (Stringify inlines) blockToCustom (Para [Image attr txt (src,tit)]) = diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 33a6f5f0c..3cb68c311 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -165,7 +165,6 @@ imageToDocbook _ attr src = selfClosingTag "imagedata" $ -- | Convert a Pandoc block element to Docbook. blockToDocbook :: PandocMonad m => WriterOptions -> Block -> DB m (Doc Text) -blockToDocbook _ Null = return empty -- Add ids to paragraphs in divs with ids - this is needed for -- pandoc-citeproc to get link anchors in bibliographies: blockToDocbook opts (Div (id',"section":_,_) (Header lvl (_,_,attrs) ils : xs)) = do diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 686a2f662..a3949792d 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -800,7 +800,6 @@ blockToOpenXML :: (PandocMonad m) => WriterOptions -> Block -> WS m [Content] blockToOpenXML opts blk = withDirection $ blockToOpenXML' opts blk blockToOpenXML' :: (PandocMonad m) => WriterOptions -> Block -> WS m [Content] -blockToOpenXML' _ Null = return [] blockToOpenXML' opts (Div (ident,_classes,kvs) bs) = do stylemod <- case lookup dynamicStyleKey kvs of Just (fromString . T.unpack -> sty) -> do diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 602c70ebe..5fe64717a 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -98,8 +98,6 @@ blockToDokuWiki :: PandocMonad m -> Block -- ^ Block element -> DokuWiki m Text -blockToDokuWiki _ Null = return "" - blockToDokuWiki opts (Div _attrs bs) = do contents <- blockListToDokuWiki opts bs return $ contents <> "\n" diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index 6bad37404..f393f031f 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -358,7 +358,6 @@ blockToXml (Table _ blkCapt specs thead tbody tfoot) = do align_str AlignCenter = "center" align_str AlignRight = "right" align_str AlignDefault = "left" -blockToXml Null = return [] -- Replace plain text with paragraphs and add line break after paragraphs. -- It is used to convert plain text from tight list items to paragraphs. diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 8fc81ed24..5992c994f 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -730,7 +730,6 @@ adjustNumbers opts doc = showSecNum = T.intercalate "." . map tshow 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 diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 75e14714b..9a61c339a 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -90,7 +90,6 @@ blockToHaddock :: PandocMonad m => WriterOptions -- ^ Options -> Block -- ^ Block element -> StateT WriterState m (Doc Text) -blockToHaddock _ Null = return empty blockToHaddock opts (Div _ ils) = do contents <- blockListToHaddock opts ils return $ contents <> blankline diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index c254fbc58..8da931406 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -381,7 +381,6 @@ blockToICML opts style (Table _ blkCapt specs thead tbody tfoot) = blockToICML opts style (Div (_ident, _, kvs) lst) = let dynamicStyle = maybeToList $ lookup dynamicStyleKey kvs in blocksToICML opts (dynamicStyle <> style) lst -blockToICML _ _ Null = return empty -- | Convert a list of lists of blocks to ICML list items. listItemsToICML :: PandocMonad m => WriterOptions -> Text -> Style -> Maybe ListAttributes -> [[Block]] -> WS m (Doc Text) diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs index 9db8723d1..f20178bd1 100644 --- a/src/Text/Pandoc/Writers/JATS.hs +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -251,7 +251,6 @@ codeAttr opts (ident,classes,kvs) = (lang, attr) -- | Convert a Pandoc block element to JATS. blockToJATS :: PandocMonad m => WriterOptions -> Block -> JATS m (Doc Text) -blockToJATS _ Null = return empty blockToJATS opts (Div (id',"section":_,kvs) (Header _lvl _ ils : xs)) = do let idAttr = [ ("id", writerIdentifierPrefix opts <> escapeNCName id') | not (T.null id')] diff --git a/src/Text/Pandoc/Writers/Jira.hs b/src/Text/Pandoc/Writers/Jira.hs index 1351814e9..709064270 100644 --- a/src/Text/Pandoc/Writers/Jira.hs +++ b/src/Text/Pandoc/Writers/Jira.hs @@ -103,7 +103,6 @@ toJiraBlocks blocks = do Para xs -> singleton . Jira.Para <$> toJiraInlines xs Plain xs -> singleton . Jira.Para <$> toJiraInlines xs RawBlock fmt cs -> rawBlockToJira fmt cs - Null -> return mempty Table _ blkCapt specs thead tbody tfoot -> singleton <$> do let (_, _, _, hd, body) = toLegacyTable blkCapt specs thead tbody tfoot headerRow <- if all null hd diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 8c45c8db5..144c3d579 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -253,7 +253,6 @@ isListBlock _ = False blockToLaTeX :: PandocMonad m => Block -- ^ Block to convert -> LW m (Doc Text) -blockToLaTeX Null = return empty blockToLaTeX (Div attr@(identifier,"block":dclasses,_) (Header _ _ ils : bs)) = do let blockname diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 87b2d8d21..45516ea06 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -106,7 +106,6 @@ blockToMan :: PandocMonad m => WriterOptions -- ^ Options -> Block -- ^ Block element -> StateT WriterState m (Doc Text) -blockToMan _ Null = return empty blockToMan opts (Div _ bs) = blockListToMan opts bs blockToMan opts (Plain inlines) = liftM vcat $ mapM (inlineListToMan opts) $ splitSentences inlines diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index fda2bbcef..49fb873a9 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -313,7 +313,6 @@ blockToMarkdown' :: PandocMonad m => WriterOptions -- ^ Options -> Block -- ^ Block element -> MD m (Doc Text) -blockToMarkdown' _ Null = return empty blockToMarkdown' opts (Div attrs ils) = do contents <- blockListToMarkdown opts ils variant <- asks envVariant @@ -812,7 +811,7 @@ blockListToMarkdown opts blocks = do isListBlock (DefinitionList _) = True isListBlock _ = False commentSep - | variant == PlainText = Null + | variant == PlainText = RawBlock "html" "\n" | isEnabled Ext_raw_html opts = RawBlock "html" "\n" | otherwise = RawBlock "markdown" " \n" mconcat <$> mapM (blockToMarkdown opts) (fixBlocks blocks) diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 5029be69f..899e40418 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -81,8 +81,6 @@ blockToMediaWiki :: PandocMonad m => Block -- ^ Block element -> MediaWikiWriter m Text -blockToMediaWiki Null = return "" - blockToMediaWiki (Div attrs bs) = do contents <- blockListToMediaWiki bs return $ render Nothing (tagWithAttrs "div" attrs) <> "\n\n" <> diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs index 97c23f24d..055324448 100644 --- a/src/Text/Pandoc/Writers/Ms.hs +++ b/src/Text/Pandoc/Writers/Ms.hs @@ -110,7 +110,6 @@ blockToMs :: PandocMonad m => WriterOptions -- ^ Options -> Block -- ^ Block element -> MS m (Doc Text) -blockToMs _ Null = return empty blockToMs opts (Div (ident,cls,kvs) bs) = do let anchor = if T.null ident then empty diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index d5100f43f..329522a48 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -275,7 +275,6 @@ blockToMuse (Table _ blkCapt specs thead tbody tfoot) = (length aligns :| length widths : map length (headers:rows)) isSimple = onlySimpleTableCells (headers : rows) && all (== 0) widths blockToMuse (Div _ bs) = flatBlockListToMuse bs -blockToMuse Null = return empty -- | Return Muse representation of notes collected so far. currentNotesToMuse :: PandocMonad m diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 5f3224c2f..27473775b 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -398,7 +398,6 @@ blockToOpenDocument o = \case b@(RawBlock f s) -> if f == Format "opendocument" then return $ text $ T.unpack s else empty <$ report (BlockNotRendered b) - Null -> return empty where defList b = do setInDefinitionList True r <- vcat <$> mapM (deflistItemToOpenDocument o) b diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index f4a22695c..aae6fe0ef 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -102,7 +102,6 @@ isRawFormat f = blockToOrg :: PandocMonad m => Block -- ^ Block element -> Org m (Doc Text) -blockToOrg Null = return empty blockToOrg (Div attr bs) = divToOrg attr bs blockToOrg (Plain inlines) = inlineListToOrg inlines -- title beginning with fig: indicates that the image is a figure diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs index 327774cd8..e3d31d099 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs @@ -1041,7 +1041,6 @@ blockIsBlank HorizontalRule -> True Table{} -> False Div _ bls -> all blockIsBlank bls - Null -> True textIsBlank :: T.Text -> Bool textIsBlank = T.all isSpace diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 8b2002851..88e185897 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -197,7 +197,6 @@ bordered contents c = blockToRST :: PandocMonad m => Block -- ^ Block element -> RST m (Doc Text) -blockToRST Null = return empty blockToRST (Div ("",["title"],[]) _) = return empty -- this is generated by the rst reader and can safely be -- omitted when we're generating rst diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 063371ebc..7e3e770ba 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -229,7 +229,6 @@ blockToRTF :: PandocMonad m -> Alignment -- ^ alignment -> Block -- ^ block to convert -> m Text -blockToRTF _ _ Null = return "" blockToRTF indent alignment (Div _ bs) = blocksToRTF indent alignment bs blockToRTF indent alignment (Plain lst) = diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index 18015259d..e8682018b 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -97,7 +97,6 @@ imageToTEI opts attr src = return $ selfClosingTag "graphic" $ -- | Convert a Pandoc block element to TEI. blockToTEI :: PandocMonad m => WriterOptions -> Block -> m (Doc Text) -blockToTEI _ Null = return empty blockToTEI opts (Div attr@(_,"section":_,_) (Header lvl _ ils : xs)) = do -- TEI doesn't allow sections with no content, so insert some if needed diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index 6a33b4283..f817900e5 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -115,8 +115,6 @@ blockToTexinfo :: PandocMonad m => Block -- ^ Block to convert -> TI m (Doc Text) -blockToTexinfo Null = return empty - blockToTexinfo (Div _ bs) = blockListToTexinfo bs blockToTexinfo (Plain lst) = diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index 03d030477..b1a4ed4a0 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -100,8 +100,6 @@ blockToTextile :: PandocMonad m -> Block -- ^ Block element -> TW m Text -blockToTextile _ Null = return "" - blockToTextile opts (Div attr bs) = do let startTag = render Nothing $ tagWithAttrs "div" attr let endTag = "
    " diff --git a/src/Text/Pandoc/Writers/XWiki.hs b/src/Text/Pandoc/Writers/XWiki.hs index c35235650..0d7387eaa 100644 --- a/src/Text/Pandoc/Writers/XWiki.hs +++ b/src/Text/Pandoc/Writers/XWiki.hs @@ -74,8 +74,6 @@ blockListToXWiki blocks = blockToXWiki :: PandocMonad m => Block -> XWikiReader m Text -blockToXWiki Null = return "" - blockToXWiki (Div (id', _, _) blocks) = do content <- blockListToXWiki blocks return $ genAnchor id' <> content diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index df914f590..651da4e46 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -78,8 +78,6 @@ escapeText = T.replace "__" "''__''" . -- | Convert Pandoc block element to ZimWiki. blockToZimWiki :: PandocMonad m => WriterOptions -> Block -> ZW m Text -blockToZimWiki _ Null = return "" - blockToZimWiki opts (Div _attrs bs) = do contents <- blockListToZimWiki opts bs return $ contents <> "\n" diff --git a/stack.yaml b/stack.yaml index 40704814b..674bc357f 100644 --- a/stack.yaml +++ b/stack.yaml @@ -10,10 +10,15 @@ extra-deps: - skylighting-core-0.12 - skylighting-0.12 - doctemplates-0.10 +- git: https://github.com/jgm/pandoc-types.git + commit: f796401eaaab780f83c562e97dbb8c8d4b9974d1 - git: https://github.com/jgm/texmath.git - commit: 19700530733707284bb41f24add757f19ca23430 + commit: c046e6e5a93510f2c37dbc700f82a2c53ed87b5f - git: https://github.com/jgm/citeproc.git - commit: 4a7b98afabebd7a074489ba500d68ee6aa75d3a8 + commit: 673a7fb643d24a3bb0f60f8f29e189c0ba7ef15b +- git: https://github.com/jgm/commonmark-hs.git + commit: 3cba9f874db7516f49d221a94171b4af010b5bea + subdirs: [commonmark-pandoc] ghc-options: "$locals": -fhide-source-paths -Wno-missing-home-modules resolver: lts-18.10 -- cgit v1.2.3 From c636b5dd1640c1f13f21bb2828c817213455229f Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 12 Oct 2021 20:08:35 -0700 Subject: Revert "Depend on pandoc-types 1.23, remove Null constructor on Block." This reverts commit fb0d6c7cb63a791fa72becf21ed493282e65ea91. --- cabal.project | 2 +- pandoc.cabal | 4 ++-- src/Text/Pandoc/Lua/Marshaling/AST.hs | 2 ++ src/Text/Pandoc/Shared.hs | 1 + src/Text/Pandoc/Writers/AsciiDoc.hs | 1 + src/Text/Pandoc/Writers/ConTeXt.hs | 1 + src/Text/Pandoc/Writers/Custom.hs | 2 ++ src/Text/Pandoc/Writers/Docbook.hs | 1 + src/Text/Pandoc/Writers/Docx.hs | 1 + src/Text/Pandoc/Writers/DokuWiki.hs | 2 ++ src/Text/Pandoc/Writers/FB2.hs | 1 + src/Text/Pandoc/Writers/HTML.hs | 1 + src/Text/Pandoc/Writers/Haddock.hs | 1 + src/Text/Pandoc/Writers/ICML.hs | 1 + src/Text/Pandoc/Writers/JATS.hs | 1 + src/Text/Pandoc/Writers/Jira.hs | 1 + src/Text/Pandoc/Writers/LaTeX.hs | 1 + src/Text/Pandoc/Writers/Man.hs | 1 + src/Text/Pandoc/Writers/Markdown.hs | 3 ++- src/Text/Pandoc/Writers/MediaWiki.hs | 2 ++ src/Text/Pandoc/Writers/Ms.hs | 1 + src/Text/Pandoc/Writers/Muse.hs | 1 + src/Text/Pandoc/Writers/OpenDocument.hs | 1 + src/Text/Pandoc/Writers/Org.hs | 1 + src/Text/Pandoc/Writers/Powerpoint/Presentation.hs | 1 + src/Text/Pandoc/Writers/RST.hs | 1 + src/Text/Pandoc/Writers/RTF.hs | 1 + src/Text/Pandoc/Writers/TEI.hs | 1 + src/Text/Pandoc/Writers/Texinfo.hs | 2 ++ src/Text/Pandoc/Writers/Textile.hs | 2 ++ src/Text/Pandoc/Writers/XWiki.hs | 2 ++ src/Text/Pandoc/Writers/ZimWiki.hs | 2 ++ stack.yaml | 4 ++-- 33 files changed, 44 insertions(+), 6 deletions(-) (limited to 'src/Text/Pandoc/Writers/HTML.hs') diff --git a/cabal.project b/cabal.project index 64ab70164..04b79c0a7 100644 --- a/cabal.project +++ b/cabal.project @@ -16,7 +16,7 @@ source-repository-package source-repository-package type: git location: https://github.com/jgm/pandoc-types.git - tag: 87711e7e60a3981da0f1cc3df9e57f1134f1b82e + tag: 99402a46361a3e52805935b1fbe9dfe54f852d6a source-repository-package type: git diff --git a/pandoc.cabal b/pandoc.cabal index c13c768f4..615feaccb 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -561,7 +561,7 @@ library mtl >= 2.2 && < 2.3, network >= 2.6, network-uri >= 2.6 && < 2.8, - pandoc-types >= 1.23 && < 1.24, + pandoc-types >= 1.22 && < 1.23, parsec >= 3.1 && < 3.2, process >= 1.2.3 && < 1.7, random >= 1 && < 1.3, @@ -847,7 +847,7 @@ test-suite test-pandoc filepath >= 1.1 && < 1.5, hslua >= 1.1 && < 1.4, mtl >= 2.2 && < 2.3, - pandoc-types >= 1.23 && < 1.24, + pandoc-types >= 1.22 && < 1.23, process >= 1.2.3 && < 1.7, tasty >= 0.11 && < 1.5, tasty-golden >= 2.3 && < 2.4, diff --git a/src/Text/Pandoc/Lua/Marshaling/AST.hs b/src/Text/Pandoc/Lua/Marshaling/AST.hs index a1ad2cda3..8e12d232c 100644 --- a/src/Text/Pandoc/Lua/Marshaling/AST.hs +++ b/src/Text/Pandoc/Lua/Marshaling/AST.hs @@ -165,6 +165,7 @@ pushBlock = \case LineBlock blcks -> pushViaConstructor "LineBlock" blcks OrderedList lstAttr list -> pushViaConstructor "OrderedList" list (LuaListAttributes lstAttr) + Null -> pushViaConstructor "Null" Para blcks -> pushViaConstructor "Para" blcks Plain blcks -> pushViaConstructor "Plain" blcks RawBlock f cs -> pushViaConstructor "RawBlock" f cs @@ -188,6 +189,7 @@ peekBlock idx = defineHowTo "get Block value" $! do "OrderedList" -> (\(LuaListAttributes lstAttr, lst) -> OrderedList lstAttr lst) <$!> elementContent + "Null" -> return Null "Para" -> Para <$!> elementContent "Plain" -> Plain <$!> elementContent "RawBlock" -> uncurry RawBlock <$!> elementContent diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 6e1f29fb1..06fd052b9 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -920,6 +920,7 @@ blockToInlines (Table _ _ _ (TableHead _ hbd) bodies (TableFoot _ fbd)) = unTableBody (TableBody _ _ hd bd) = hd <> bd unTableBodies = concatMap unTableBody blockToInlines (Div _ blks) = blocksToInlines' blks +blockToInlines Null = mempty blocksToInlinesWithSep :: Inlines -> [Block] -> Inlines blocksToInlinesWithSep sep = diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index f0973178e..bcef4a089 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -140,6 +140,7 @@ blockToAsciiDoc :: PandocMonad m => WriterOptions -- ^ Options -> Block -- ^ Block element -> ADW m (Doc Text) +blockToAsciiDoc _ Null = return empty blockToAsciiDoc opts (Div (id',"section":_,_) (Header level (_,cls,kvs) ils : xs)) = do hdr <- blockToAsciiDoc opts (Header level (id',cls,kvs) ils) diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 0150f7dff..3cafcefba 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -154,6 +154,7 @@ toLabel z = T.concatMap go z -- | Convert Pandoc block element to ConTeXt. blockToConTeXt :: PandocMonad m => Block -> WM m (Doc Text) +blockToConTeXt Null = return empty blockToConTeXt (Div attr@(_,"section":_,_) (Header level _ title' : xs)) = do header' <- sectionHeader attr level title' diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs index d207f5093..1e9f37d2f 100644 --- a/src/Text/Pandoc/Writers/Custom.hs +++ b/src/Text/Pandoc/Writers/Custom.hs @@ -116,6 +116,8 @@ docToCustom opts (Pandoc (Meta metamap) blocks) = do blockToCustom :: Block -- ^ Block element -> Lua String +blockToCustom Null = return "" + blockToCustom (Plain inlines) = Lua.callFunc "Plain" (Stringify inlines) blockToCustom (Para [Image attr txt (src,tit)]) = diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 3cb68c311..33a6f5f0c 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -165,6 +165,7 @@ imageToDocbook _ attr src = selfClosingTag "imagedata" $ -- | Convert a Pandoc block element to Docbook. blockToDocbook :: PandocMonad m => WriterOptions -> Block -> DB m (Doc Text) +blockToDocbook _ Null = return empty -- Add ids to paragraphs in divs with ids - this is needed for -- pandoc-citeproc to get link anchors in bibliographies: blockToDocbook opts (Div (id',"section":_,_) (Header lvl (_,_,attrs) ils : xs)) = do diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index a3949792d..686a2f662 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -800,6 +800,7 @@ blockToOpenXML :: (PandocMonad m) => WriterOptions -> Block -> WS m [Content] blockToOpenXML opts blk = withDirection $ blockToOpenXML' opts blk blockToOpenXML' :: (PandocMonad m) => WriterOptions -> Block -> WS m [Content] +blockToOpenXML' _ Null = return [] blockToOpenXML' opts (Div (ident,_classes,kvs) bs) = do stylemod <- case lookup dynamicStyleKey kvs of Just (fromString . T.unpack -> sty) -> do diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 5fe64717a..602c70ebe 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -98,6 +98,8 @@ blockToDokuWiki :: PandocMonad m -> Block -- ^ Block element -> DokuWiki m Text +blockToDokuWiki _ Null = return "" + blockToDokuWiki opts (Div _attrs bs) = do contents <- blockListToDokuWiki opts bs return $ contents <> "\n" diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index f393f031f..6bad37404 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -358,6 +358,7 @@ blockToXml (Table _ blkCapt specs thead tbody tfoot) = do align_str AlignCenter = "center" align_str AlignRight = "right" align_str AlignDefault = "left" +blockToXml Null = return [] -- Replace plain text with paragraphs and add line break after paragraphs. -- It is used to convert plain text from tight list items to paragraphs. diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 5992c994f..8fc81ed24 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -730,6 +730,7 @@ adjustNumbers opts doc = showSecNum = T.intercalate "." . map tshow 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 diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 9a61c339a..75e14714b 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -90,6 +90,7 @@ blockToHaddock :: PandocMonad m => WriterOptions -- ^ Options -> Block -- ^ Block element -> StateT WriterState m (Doc Text) +blockToHaddock _ Null = return empty blockToHaddock opts (Div _ ils) = do contents <- blockListToHaddock opts ils return $ contents <> blankline diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index 8da931406..c254fbc58 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -381,6 +381,7 @@ blockToICML opts style (Table _ blkCapt specs thead tbody tfoot) = blockToICML opts style (Div (_ident, _, kvs) lst) = let dynamicStyle = maybeToList $ lookup dynamicStyleKey kvs in blocksToICML opts (dynamicStyle <> style) lst +blockToICML _ _ Null = return empty -- | Convert a list of lists of blocks to ICML list items. listItemsToICML :: PandocMonad m => WriterOptions -> Text -> Style -> Maybe ListAttributes -> [[Block]] -> WS m (Doc Text) diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs index f20178bd1..9db8723d1 100644 --- a/src/Text/Pandoc/Writers/JATS.hs +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -251,6 +251,7 @@ codeAttr opts (ident,classes,kvs) = (lang, attr) -- | Convert a Pandoc block element to JATS. blockToJATS :: PandocMonad m => WriterOptions -> Block -> JATS m (Doc Text) +blockToJATS _ Null = return empty blockToJATS opts (Div (id',"section":_,kvs) (Header _lvl _ ils : xs)) = do let idAttr = [ ("id", writerIdentifierPrefix opts <> escapeNCName id') | not (T.null id')] diff --git a/src/Text/Pandoc/Writers/Jira.hs b/src/Text/Pandoc/Writers/Jira.hs index 709064270..1351814e9 100644 --- a/src/Text/Pandoc/Writers/Jira.hs +++ b/src/Text/Pandoc/Writers/Jira.hs @@ -103,6 +103,7 @@ toJiraBlocks blocks = do Para xs -> singleton . Jira.Para <$> toJiraInlines xs Plain xs -> singleton . Jira.Para <$> toJiraInlines xs RawBlock fmt cs -> rawBlockToJira fmt cs + Null -> return mempty Table _ blkCapt specs thead tbody tfoot -> singleton <$> do let (_, _, _, hd, body) = toLegacyTable blkCapt specs thead tbody tfoot headerRow <- if all null hd diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 144c3d579..8c45c8db5 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -253,6 +253,7 @@ isListBlock _ = False blockToLaTeX :: PandocMonad m => Block -- ^ Block to convert -> LW m (Doc Text) +blockToLaTeX Null = return empty blockToLaTeX (Div attr@(identifier,"block":dclasses,_) (Header _ _ ils : bs)) = do let blockname diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 9514a1ce7..8a34bf47f 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -106,6 +106,7 @@ blockToMan :: PandocMonad m => WriterOptions -- ^ Options -> Block -- ^ Block element -> StateT WriterState m (Doc Text) +blockToMan _ Null = return empty blockToMan opts (Div _ bs) = blockListToMan opts bs blockToMan opts (Plain inlines) = splitSentences <$> inlineListToMan opts inlines diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 49fb873a9..fda2bbcef 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -313,6 +313,7 @@ blockToMarkdown' :: PandocMonad m => WriterOptions -- ^ Options -> Block -- ^ Block element -> MD m (Doc Text) +blockToMarkdown' _ Null = return empty blockToMarkdown' opts (Div attrs ils) = do contents <- blockListToMarkdown opts ils variant <- asks envVariant @@ -811,7 +812,7 @@ blockListToMarkdown opts blocks = do isListBlock (DefinitionList _) = True isListBlock _ = False commentSep - | variant == PlainText = RawBlock "html" "\n" + | variant == PlainText = Null | isEnabled Ext_raw_html opts = RawBlock "html" "\n" | otherwise = RawBlock "markdown" " \n" mconcat <$> mapM (blockToMarkdown opts) (fixBlocks blocks) diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 899e40418..5029be69f 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -81,6 +81,8 @@ blockToMediaWiki :: PandocMonad m => Block -- ^ Block element -> MediaWikiWriter m Text +blockToMediaWiki Null = return "" + blockToMediaWiki (Div attrs bs) = do contents <- blockListToMediaWiki bs return $ render Nothing (tagWithAttrs "div" attrs) <> "\n\n" <> diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs index 332368a67..eeb8eca62 100644 --- a/src/Text/Pandoc/Writers/Ms.hs +++ b/src/Text/Pandoc/Writers/Ms.hs @@ -110,6 +110,7 @@ blockToMs :: PandocMonad m => WriterOptions -- ^ Options -> Block -- ^ Block element -> MS m (Doc Text) +blockToMs _ Null = return empty blockToMs opts (Div (ident,cls,kvs) bs) = do let anchor = if T.null ident then empty diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 329522a48..d5100f43f 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -275,6 +275,7 @@ blockToMuse (Table _ blkCapt specs thead tbody tfoot) = (length aligns :| length widths : map length (headers:rows)) isSimple = onlySimpleTableCells (headers : rows) && all (== 0) widths blockToMuse (Div _ bs) = flatBlockListToMuse bs +blockToMuse Null = return empty -- | Return Muse representation of notes collected so far. currentNotesToMuse :: PandocMonad m diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 27473775b..5f3224c2f 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -398,6 +398,7 @@ blockToOpenDocument o = \case b@(RawBlock f s) -> if f == Format "opendocument" then return $ text $ T.unpack s else empty <$ report (BlockNotRendered b) + Null -> return empty where defList b = do setInDefinitionList True r <- vcat <$> mapM (deflistItemToOpenDocument o) b diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index aae6fe0ef..f4a22695c 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -102,6 +102,7 @@ isRawFormat f = blockToOrg :: PandocMonad m => Block -- ^ Block element -> Org m (Doc Text) +blockToOrg Null = return empty blockToOrg (Div attr bs) = divToOrg attr bs blockToOrg (Plain inlines) = inlineListToOrg inlines -- title beginning with fig: indicates that the image is a figure diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs index 99b016a63..fe34d24dc 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs @@ -1041,6 +1041,7 @@ blockIsBlank HorizontalRule -> True Table{} -> False Div _ bls -> all blockIsBlank bls + Null -> True textIsBlank :: T.Text -> Bool textIsBlank = T.all isSpace diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 88e185897..8b2002851 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -197,6 +197,7 @@ bordered contents c = blockToRST :: PandocMonad m => Block -- ^ Block element -> RST m (Doc Text) +blockToRST Null = return empty blockToRST (Div ("",["title"],[]) _) = return empty -- this is generated by the rst reader and can safely be -- omitted when we're generating rst diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 7e3e770ba..063371ebc 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -229,6 +229,7 @@ blockToRTF :: PandocMonad m -> Alignment -- ^ alignment -> Block -- ^ block to convert -> m Text +blockToRTF _ _ Null = return "" blockToRTF indent alignment (Div _ bs) = blocksToRTF indent alignment bs blockToRTF indent alignment (Plain lst) = diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index e8682018b..18015259d 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -97,6 +97,7 @@ imageToTEI opts attr src = return $ selfClosingTag "graphic" $ -- | Convert a Pandoc block element to TEI. blockToTEI :: PandocMonad m => WriterOptions -> Block -> m (Doc Text) +blockToTEI _ Null = return empty blockToTEI opts (Div attr@(_,"section":_,_) (Header lvl _ ils : xs)) = do -- TEI doesn't allow sections with no content, so insert some if needed diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index f817900e5..6a33b4283 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -115,6 +115,8 @@ blockToTexinfo :: PandocMonad m => Block -- ^ Block to convert -> TI m (Doc Text) +blockToTexinfo Null = return empty + blockToTexinfo (Div _ bs) = blockListToTexinfo bs blockToTexinfo (Plain lst) = diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index b1a4ed4a0..03d030477 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -100,6 +100,8 @@ blockToTextile :: PandocMonad m -> Block -- ^ Block element -> TW m Text +blockToTextile _ Null = return "" + blockToTextile opts (Div attr bs) = do let startTag = render Nothing $ tagWithAttrs "div" attr let endTag = "
    " diff --git a/src/Text/Pandoc/Writers/XWiki.hs b/src/Text/Pandoc/Writers/XWiki.hs index 0d7387eaa..c35235650 100644 --- a/src/Text/Pandoc/Writers/XWiki.hs +++ b/src/Text/Pandoc/Writers/XWiki.hs @@ -74,6 +74,8 @@ blockListToXWiki blocks = blockToXWiki :: PandocMonad m => Block -> XWikiReader m Text +blockToXWiki Null = return "" + blockToXWiki (Div (id', _, _) blocks) = do content <- blockListToXWiki blocks return $ genAnchor id' <> content diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index 651da4e46..df914f590 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -78,6 +78,8 @@ escapeText = T.replace "__" "''__''" . -- | Convert Pandoc block element to ZimWiki. blockToZimWiki :: PandocMonad m => WriterOptions -> Block -> ZW m Text +blockToZimWiki _ Null = return "" + blockToZimWiki opts (Div _attrs bs) = do contents <- blockListToZimWiki opts bs return $ contents <> "\n" diff --git a/stack.yaml b/stack.yaml index 3d99d80b5..d12ab3587 100644 --- a/stack.yaml +++ b/stack.yaml @@ -13,9 +13,9 @@ extra-deps: - emojis-0.1.2 - doclayout-0.3.1.1 - git: https://github.com/jgm/pandoc-types.git - commit: 87711e7e60a3981da0f1cc3df9e57f1134f1b82e + commit: 99402a46361a3e52805935b1fbe9dfe54f852d6a - git: https://github.com/jgm/texmath.git - commit: c046e6e5a93510f2c37dbc700f82a2c53ed87b5f + commit: 19700530733707284bb41f24add757f19ca23430 - git: https://github.com/jgm/citeproc.git commit: 673a7fb643d24a3bb0f60f8f29e189c0ba7ef15b - git: https://github.com/jgm/commonmark-hs.git -- cgit v1.2.3 From 921af3085422ed5896db6996c54009cf2a61a517 Mon Sep 17 00:00:00 2001 From: Aner Lucero <4rgento@gmail.com> Date: Wed, 9 Jun 2021 10:53:35 -0300 Subject: Use simpleFigure in Readers. --- src/Text/Pandoc/Readers/HTML.hs | 2 +- src/Text/Pandoc/Readers/LaTeX.hs | 33 ++++++++++++++++---------------- src/Text/Pandoc/Readers/Markdown.hs | 27 +++++++++++++------------- src/Text/Pandoc/Readers/MediaWiki.hs | 9 +++++++-- src/Text/Pandoc/Readers/Org/Blocks.hs | 19 +++++++++--------- src/Text/Pandoc/Readers/RST.hs | 4 ++-- src/Text/Pandoc/Writers/AsciiDoc.hs | 3 +-- src/Text/Pandoc/Writers/ConTeXt.hs | 5 +---- src/Text/Pandoc/Writers/Docbook.hs | 5 ++--- src/Text/Pandoc/Writers/Docx.hs | 3 +-- src/Text/Pandoc/Writers/DokuWiki.hs | 4 +--- src/Text/Pandoc/Writers/FB2.hs | 5 ++--- src/Text/Pandoc/Writers/HTML.hs | 4 ++-- src/Text/Pandoc/Writers/Haddock.hs | 3 +-- src/Text/Pandoc/Writers/ICML.hs | 6 ++---- src/Text/Pandoc/Writers/JATS.hs | 4 +--- src/Text/Pandoc/Writers/LaTeX.hs | 5 +---- src/Text/Pandoc/Writers/Markdown.hs | 6 ++---- src/Text/Pandoc/Writers/MediaWiki.hs | 4 +--- src/Text/Pandoc/Writers/OpenDocument.hs | 3 +-- src/Text/Pandoc/Writers/Org.hs | 4 +--- src/Text/Pandoc/Writers/RST.hs | 34 +++++++++++++++++++-------------- src/Text/Pandoc/Writers/Texinfo.hs | 3 +-- src/Text/Pandoc/Writers/Textile.hs | 4 +--- src/Text/Pandoc/Writers/ZimWiki.hs | 4 +--- 25 files changed, 93 insertions(+), 110 deletions(-) (limited to 'src/Text/Pandoc/Writers/HTML.hs') diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index fdf4f28e0..c78faebbd 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -551,7 +551,7 @@ pFigure = try $ do let caption = fromMaybe mempty mbcap case B.toList <$> mbimg of Just [Image attr _ (url, tit)] -> - return $ B.para $ B.imageWith attr url ("fig:" <> tit) caption + return $ B.simpleFigureWith attr caption url tit _ -> mzero pCodeBlock :: PandocMonad m => TagParser m Blocks diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 34eb53245..15148debb 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -1095,24 +1095,25 @@ figure = try $ do addImageCaption :: PandocMonad m => Blocks -> LP m Blocks addImageCaption = walkM go - where go (Image attr@(_, cls, kvs) alt (src,tit)) + where go p@(Para [Image attr@(_, cls, kvs) _ (src, tit)]) | not ("fig:" `T.isPrefixOf` tit) = do st <- getState - let (alt', tit') = case sCaption st of - Just ils -> (toList ils, "fig:" <> tit) - Nothing -> (alt, tit) - attr' = case sLastLabel st of - Just lab -> (lab, cls, kvs) - Nothing -> attr - case attr' of - ("", _, _) -> return () - (ident, _, _) -> do - num <- getNextNumber sLastFigureNum - setState - st{ sLastFigureNum = num - , sLabels = M.insert ident - [Str (renderDottedNum num)] (sLabels st) } - return $ Image attr' alt' (src, tit') + case sCaption st of + Nothing -> return p + Just figureCaption -> do + let attr' = case sLastLabel st of + Just lab -> (lab, cls, kvs) + Nothing -> attr + case attr' of + ("", _, _) -> return () + (ident, _, _) -> do + num <- getNextNumber sLastFigureNum + setState + st{ sLastFigureNum = num + , sLabels = M.insert ident + [Str (renderDottedNum num)] (sLabels st) } + + return $ SimpleFigure attr' (B.toList figureCaption) (src, tit) go x = return x coloredBlock :: PandocMonad m => Text -> LP m Blocks diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 03becd144..e7ab8efb4 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1015,19 +1015,18 @@ normalDefinitionList = do para :: PandocMonad m => MarkdownParser m (F Blocks) para = try $ do exts <- getOption readerExtensions - let implicitFigures x - | extensionEnabled Ext_implicit_figures exts = do - x' <- x - case B.toList x' of - [Image attr alt (src,tit)] - | not (null alt) -> - -- the fig: at beginning of title indicates a figure - return $ B.singleton - $ Image attr alt (src, "fig:" <> tit) - _ -> return x' - | otherwise = x - result <- implicitFigures . trimInlinesF <$> inlines1 - option (B.plain <$> result) + + result <- trimInlinesF <$> inlines1 + let figureOr constr inlns = + case B.toList inlns of + [Image attr figCaption (src, tit)] + | extensionEnabled Ext_implicit_figures exts + , not (null figCaption) -> do + B.simpleFigureWith attr (B.fromList figCaption) src tit + + _ -> constr inlns + + option (figureOr B.plain <$> result) $ try $ do newline (mempty <$ blanklines) @@ -1049,7 +1048,7 @@ para = try $ do if divLevel > 0 then lookAhead divFenceEnd else mzero - return $ B.para <$> result + return $ figureOr B.para <$> result plain :: PandocMonad m => MarkdownParser m (F Blocks) plain = fmap B.plain . trimInlinesF <$> inlines1 diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index 825e4a2eb..9348a8053 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -201,7 +201,12 @@ para = do contents <- trimInlines . mconcat <$> many1 inline if F.all (==Space) contents then return mempty - else return $ B.para contents + else case B.toList contents of + -- For the MediaWiki format all images are considered figures + [Image attr figureCaption (src, title)] -> + return $ B.simpleFigureWith + attr (B.fromList figureCaption) src title + _ -> return $ B.para contents table :: PandocMonad m => MWParser m Blocks table = do @@ -631,7 +636,7 @@ image = try $ do let attr = ("", [], kvs) caption <- (B.str fname <$ sym "]]") <|> try (char '|' *> (mconcat <$> manyTill inline (sym "]]"))) - return $ B.imageWith attr fname ("fig:" <> stringify caption) caption + return $ B.imageWith attr fname (stringify caption) caption imageOption :: PandocMonad m => MWParser m Text imageOption = try $ char '|' *> opt diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index 2ec97d903..9a689b0e8 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -474,15 +474,16 @@ figure = try $ do figCaption = fromMaybe mempty $ blockAttrCaption figAttrs figKeyVals = blockAttrKeyValues figAttrs attr = (figLabel, mempty, figKeyVals) - figTitle = (if isFigure then withFigPrefix else id) figName - in - B.para . B.imageWith attr imgSrc figTitle <$> figCaption - - withFigPrefix :: Text -> Text - withFigPrefix cs = - if "fig:" `T.isPrefixOf` cs - then cs - else "fig:" <> cs + in if isFigure + then (\c -> + B.simpleFigureWith + attr c imgSrc (unstackFig figName)) <$> figCaption + else B.para . B.imageWith attr imgSrc figName <$> figCaption + unstackFig :: Text -> Text + unstackFig figName = + if "fig:" `T.isPrefixOf` figName + then T.drop 4 figName + else figName -- | Succeeds if looking at the end of the current paragraph endOfParagraph :: Monad m => OrgParser m () diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 458a2d48b..8ee017342 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -725,8 +725,8 @@ directive' = do "figure" -> do (caption, legend) <- parseFromString' extractCaption body' let src = escapeURI $ trim top - return $ B.para (B.imageWith (imgAttr "figclass") src "fig:" - caption) <> legend + return $ B.simpleFigureWith + (imgAttr "figclass") caption src "" <> legend "image" -> do let src = escapeURI $ trim top let alt = B.str $ maybe "image" trim $ lookup "alt" fields diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index 4d3906c5f..24438370a 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -149,9 +149,8 @@ blockToAsciiDoc opts (Div (id',"section":_,_) blockToAsciiDoc opts (Plain inlines) = do contents <- inlineListToAsciiDoc opts inlines return $ contents <> blankline -blockToAsciiDoc opts (Para [Image attr alternate (src,tgt)]) +blockToAsciiDoc opts (SimpleFigure attr alternate (src, tit)) -- image::images/logo.png[Company logo, title="blah"] - | Just tit <- T.stripPrefix "fig:" tgt = (\args -> "image::" <> args <> blankline) <$> imageArguments opts attr alternate src tit blockToAsciiDoc opts (Para inlines) = do diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 3cafcefba..13970cbc3 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -162,10 +162,7 @@ blockToConTeXt (Div attr@(_,"section":_,_) innerContents <- blockListToConTeXt xs return $ header' $$ innerContents $$ footer' blockToConTeXt (Plain lst) = inlineListToConTeXt lst --- title beginning with fig: indicates that the image is a figure -blockToConTeXt (Para [Image attr txt (src,tgt)]) - | Just _ <- T.stripPrefix "fig:" tgt - = do +blockToConTeXt (SimpleFigure attr txt (src, _)) = do capt <- inlineListToConTeXt txt img <- inlineToConTeXt (Image attr txt (src, "")) let (ident, _, _) = attr diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 33a6f5f0c..c9e49517f 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -1,6 +1,5 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.Docbook Copyright : Copyright (C) 2006-2021 John MacFarlane @@ -188,7 +187,7 @@ blockToDocbook opts (Div (id',"section":_,_) (Header lvl (_,_,attrs) ils : xs)) -- standalone documents will include them in the template. then [("xmlns", "http://docbook.org/ns/docbook"),("xmlns:xlink", "http://www.w3.org/1999/xlink")] else [] - + -- Populate miscAttr with Header.Attr.attributes, filtering out non-valid DocBook section attributes, id, and xml:id miscAttr = filter (isSectionAttr version) attrs attribs = nsAttr <> idAttr <> miscAttr @@ -233,7 +232,7 @@ blockToDocbook _ h@Header{} = do return empty blockToDocbook opts (Plain lst) = inlinesToDocbook opts lst -- title beginning with fig: indicates that the image is a figure -blockToDocbook opts (Para [Image attr txt (src,T.stripPrefix "fig:" -> Just _)]) = do +blockToDocbook opts (SimpleFigure attr txt (src, _)) = do alt <- inlinesToDocbook opts txt let capt = if null txt then empty diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 686a2f662..fccbb0719 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -854,8 +854,7 @@ blockToOpenXML' opts (Plain lst) = do then withParaProp prop block else block -- title beginning with fig: indicates that the image is a figure -blockToOpenXML' opts (Para [Image attr@(imgident,_,_) alt - (src,T.stripPrefix "fig:" -> Just tit)]) = do +blockToOpenXML' opts (SimpleFigure attr@(imgident, _, _) alt (src, tit)) = do setFirstPara fignum <- gets stNextFigureNum unless (null alt) $ modify $ \st -> st{ stNextFigureNum = fignum + 1 } diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 602c70ebe..c77f20ec1 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -109,9 +109,7 @@ blockToDokuWiki opts (Plain inlines) = -- title beginning with fig: indicates that the image is a figure -- dokuwiki doesn't support captions - so combine together alt and caption into alt -blockToDokuWiki opts (Para [Image attr txt (src,tgt)]) - | Just tit <- T.stripPrefix "fig:" tgt - = do +blockToDokuWiki opts (SimpleFigure attr txt (src, tit)) = do capt <- if null txt then return "" else (" " <>) `fmap` inlineListToDokuWiki opts txt diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index 6bad37404..ce3fe25a9 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -299,9 +299,8 @@ blockToXml :: PandocMonad m => Block -> FBM m [Content] blockToXml (Plain ss) = cMapM toXml ss -- FIXME: can lead to malformed FB2 blockToXml (Para [Math DisplayMath formula]) = insertMath NormalImage formula -- title beginning with fig: indicates that the image is a figure -blockToXml (Para [Image atr alt (src,tgt)]) - | Just tit <- T.stripPrefix "fig:" tgt - = insertImage NormalImage (Image atr alt (src,tit)) +blockToXml (SimpleFigure atr alt (src, tit)) = + insertImage NormalImage (Image atr alt (src,tit)) blockToXml (Para ss) = list . el "p" <$> cMapM toXml ss blockToXml (CodeBlock _ s) = return . spaceBeforeAfter . map (el "p" . el "code") . T.lines $ s diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 8fc81ed24..0a4c47387 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -742,8 +742,8 @@ blockToHtmlInner 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 -blockToHtmlInner opts (Para [Image attr txt (s,T.stripPrefix "fig:" -> Just tit)]) = - figure opts attr txt (s,tit) +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 diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 75e14714b..dfd89bc54 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -98,8 +98,7 @@ blockToHaddock opts (Plain inlines) = do contents <- inlineListToHaddock opts inlines return $ contents <> cr -- title beginning with fig: indicates figure -blockToHaddock opts (Para [Image attr alt (src,tgt)]) - | Just tit <- T.stripPrefix "fig:" tgt +blockToHaddock opts (SimpleFigure attr alt (src, tit)) = blockToHaddock opts (Para [Image attr alt (src,tit)]) blockToHaddock opts (Para inlines) = -- TODO: if it contains linebreaks, we need to use a @...@ block diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index c254fbc58..ea6009fd1 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -1,7 +1,6 @@ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.ICML @@ -309,9 +308,8 @@ blocksToICML opts style lst = do -- | Convert a Pandoc block element to ICML. blockToICML :: PandocMonad m => WriterOptions -> Style -> Block -> WS m (Doc Text) blockToICML opts style (Plain lst) = parStyle opts style "" lst --- title beginning with fig: indicates that the image is a figure -blockToICML opts style (Para img@[Image _ txt (_,Text.stripPrefix "fig:" -> Just _)]) = do - figure <- parStyle opts (figureName:style) "" img +blockToICML opts style (SimpleFigure attr txt (src, tit)) = do + figure <- parStyle opts (figureName:style) "" [Image attr txt (src, tit)] caption <- parStyle opts (imgCaptionName:style) "" txt return $ intersperseBrs [figure, caption] blockToICML opts style (Para lst) = parStyle opts (paragraphName:style) "" lst diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs index 9db8723d1..d58da8bd2 100644 --- a/src/Text/Pandoc/Writers/JATS.hs +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -291,9 +291,7 @@ blockToJATS opts (Header _ _ title) = do return $ inTagsSimple "title" title' -- No Plain, everything needs to be in a block-level tag blockToJATS opts (Plain lst) = blockToJATS opts (Para lst) --- title beginning with fig: indicates that the image is a figure -blockToJATS opts (Para [Image (ident,_,kvs) txt - (src,T.stripPrefix "fig:" -> Just tit)]) = do +blockToJATS opts (SimpleFigure (ident, _, kvs) txt (src, tit)) = do alt <- inlinesToJATS opts txt let (maintype, subtype) = imageMimeType src kvs let capt = if null txt diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 8c45c8db5..f8847aa08 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -346,10 +346,7 @@ blockToLaTeX (Div (identifier,classes,kvs) bs) = do wrapNotes <$> wrapDiv (identifier,classes,kvs) result blockToLaTeX (Plain lst) = inlineListToLaTeX lst --- title beginning with fig: indicates that the image is a figure -blockToLaTeX (Para [Image attr@(ident, _, _) txt (src,tgt)]) - | Just tit <- T.stripPrefix "fig:" tgt - = do +blockToLaTeX (SimpleFigure attr@(ident, _, _) txt (src, tit)) = do (capt, captForLof, footnotes) <- getCaption inlineListToLaTeX True txt lab <- labelFor ident let caption = "\\caption" <> captForLof <> braces capt <> lab diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index fda2bbcef..f03dc375d 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -2,7 +2,6 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.Markdown Copyright : Copyright (C) 2006-2021 John MacFarlane @@ -365,14 +364,13 @@ blockToMarkdown' opts (Plain inlines) = do _ -> inlines contents <- inlineListToMarkdown opts inlines' return $ contents <> cr --- title beginning with fig: indicates figure -blockToMarkdown' opts (Para [Image attr alt (src,tgt@(T.stripPrefix "fig:" -> Just tit))]) +blockToMarkdown' opts (SimpleFigure attr alt (src, tit)) | isEnabled Ext_raw_html opts && not (isEnabled Ext_link_attributes opts || isEnabled Ext_attributes opts) && attr /= nullAttr = -- use raw HTML (<> blankline) . literal . T.strip <$> writeHtml5String opts{ writerTemplate = Nothing } - (Pandoc nullMeta [Para [Image attr alt (src,tgt)]]) + (Pandoc nullMeta [SimpleFigure attr alt (src, tit)]) | otherwise = blockToMarkdown opts (Para [Image attr alt (src,tit)]) blockToMarkdown' opts (Para inlines) = (<> blankline) `fmap` blockToMarkdown opts (Plain inlines) diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 5029be69f..c7c53943a 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -1,5 +1,4 @@ {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.MediaWiki Copyright : Copyright (C) 2008-2021 John MacFarlane @@ -91,8 +90,7 @@ blockToMediaWiki (Div attrs bs) = do blockToMediaWiki (Plain inlines) = inlineListToMediaWiki inlines --- title beginning with fig: indicates that the image is a figure -blockToMediaWiki (Para [Image attr txt (src,T.stripPrefix "fig:" -> Just tit)]) = do +blockToMediaWiki (SimpleFigure attr txt (src, tit)) = do capt <- inlineListToMediaWiki txt img <- imageToMediaWiki attr let opt = if T.null tit diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 5f3224c2f..a42c5df64 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -2,7 +2,6 @@ {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternGuards #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.OpenDocument Copyright : Copyright (C) 2008-2020 Andrea Rossato and John MacFarlane @@ -377,7 +376,7 @@ blockToOpenDocument o = \case Plain b -> if null b then return empty else inParagraphTags =<< inlinesToOpenDocument o b - Para [Image attr c (s,T.stripPrefix "fig:" -> Just t)] -> figure attr c s t + SimpleFigure attr c (s, t) -> figure attr c s t Para b -> if null b && not (isEnabled Ext_empty_paragraphs o) then return empty diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index f4a22695c..24e664ae4 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -105,9 +105,7 @@ blockToOrg :: PandocMonad m blockToOrg Null = return empty blockToOrg (Div attr bs) = divToOrg attr bs blockToOrg (Plain inlines) = inlineListToOrg inlines --- title beginning with fig: indicates that the image is a figure -blockToOrg (Para [Image attr txt (src,tgt)]) - | Just tit <- T.stripPrefix "fig:" tgt = do +blockToOrg (SimpleFigure attr txt (src, tit)) = do capt <- if null txt then return empty else ("#+caption: " <>) `fmap` inlineListToOrg txt diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 8b2002851..08733a792 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -219,28 +219,34 @@ blockToRST (Div (ident,classes,_kvs) bs) = do nest 3 contents $$ blankline blockToRST (Plain inlines) = inlineListToRST inlines -blockToRST (Para [Image attr txt (src, rawtit)]) = do +blockToRST (SimpleFigure attr txt (src, tit)) = do description <- inlineListToRST txt dims <- imageDimsToRST attr - -- title beginning with fig: indicates that the image is a figure - let (isfig, tit) = case T.stripPrefix "fig:" rawtit of - Nothing -> (False, rawtit) - Just tit' -> (True, tit') - let fig | isfig = "figure:: " <> literal src - | otherwise = "image:: " <> literal src - alt | isfig = ":alt: " <> if T.null tit then description else literal tit - | null txt = empty + let fig = "figure:: " <> literal src + alt = ":alt: " <> if T.null tit then description else literal tit + capt = description + (_,cls,_) = attr + classes = case cls of + [] -> empty + ["align-right"] -> ":align: right" + ["align-left"] -> ":align: left" + ["align-center"] -> ":align: center" + _ -> ":figclass: " <> literal (T.unwords cls) + return $ hang 3 ".. " (fig $$ alt $$ classes $$ dims $+$ capt) $$ blankline +blockToRST (Para [Image attr txt (src, _)]) = do + description <- inlineListToRST txt + dims <- imageDimsToRST attr + let fig = "image:: " <> literal src + alt | null txt = empty | otherwise = ":alt: " <> description - capt | isfig = description - | otherwise = empty + capt = empty (_,cls,_) = attr classes = case cls of [] -> empty ["align-right"] -> ":align: right" ["align-left"] -> ":align: left" ["align-center"] -> ":align: center" - _ | isfig -> ":figclass: " <> literal (T.unwords cls) - | otherwise -> ":class: " <> literal (T.unwords cls) + _ -> ":class: " <> literal (T.unwords cls) return $ hang 3 ".. " (fig $$ alt $$ classes $$ dims $+$ capt) $$ blankline blockToRST (Para inlines) | LineBreak `elem` inlines = @@ -407,7 +413,7 @@ blockListToRST' topLevel blocks = do toClose Header{} = False toClose LineBlock{} = False toClose HorizontalRule = False - toClose (Para [Image _ _ (_,t)]) = "fig:" `T.isPrefixOf` t + toClose SimpleFigure{} = True toClose Para{} = False toClose _ = True commentSep = RawBlock "rst" "..\n\n" diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index 6a33b4283..3c5591b3a 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -123,8 +123,7 @@ blockToTexinfo (Plain lst) = inlineListToTexinfo lst -- title beginning with fig: indicates that the image is a figure -blockToTexinfo (Para [Image attr txt (src,tgt)]) - | Just tit <- T.stripPrefix "fig:" tgt = do +blockToTexinfo (SimpleFigure attr txt (src, tit)) = do capt <- if null txt then return empty else (\c -> text "@caption" <> braces c) `fmap` diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index 03d030477..7f0d668e5 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -1,5 +1,4 @@ {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.Textile Copyright : Copyright (C) 2010-2021 John MacFarlane @@ -111,8 +110,7 @@ blockToTextile opts (Div attr bs) = do blockToTextile opts (Plain inlines) = inlineListToTextile opts inlines --- title beginning with fig: indicates that the image is a figure -blockToTextile opts (Para [Image attr txt (src,T.stripPrefix "fig:" -> Just tit)]) = do +blockToTextile opts (SimpleFigure attr txt (src, tit)) = do capt <- blockToTextile opts (Para txt) im <- inlineToTextile opts (Image attr txt (src,tit)) return $ im <> "\n" <> capt diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index df914f590..5722b6d2e 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -1,5 +1,4 @@ {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE ViewPatterns #-} {- | Module : Text.Pandoc.Writers.ZimWiki Copyright : © 2008-2021 John MacFarlane, @@ -86,9 +85,8 @@ blockToZimWiki opts (Div _attrs bs) = do blockToZimWiki opts (Plain inlines) = inlineListToZimWiki opts inlines --- title beginning with fig: indicates that the image is a figure -- ZimWiki doesn't support captions - so combine together alt and caption into alt -blockToZimWiki opts (Para [Image attr txt (src,T.stripPrefix "fig:" -> Just tit)]) = do +blockToZimWiki opts (SimpleFigure attr txt (src, tit)) = do capt <- if null txt then return "" else (" " <>) `fmap` inlineListToZimWiki opts txt -- cgit v1.2.3 From df5ae1c186ed625e25cf6f080ddf24549f7af22e Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Fri, 19 Nov 2021 08:50:18 -0800 Subject: HTML writer: Don't create invalid `data-` attribute... for empty attribute key. (It would be better to make these unrepresentable in the type system, but for now this is an improvement.) Closes #7546. --- src/Text/Pandoc/Writers/HTML.hs | 1 + test/command/7546.md | 6 ++++++ 2 files changed, 7 insertions(+) create mode 100644 test/command/7546.md (limited to 'src/Text/Pandoc/Writers/HTML.hs') diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 0a4c47387..247cddfc9 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -633,6 +633,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 diff --git a/test/command/7546.md b/test/command/7546.md new file mode 100644 index 000000000..aed17275e --- /dev/null +++ b/test/command/7546.md @@ -0,0 +1,6 @@ +``` +% pandoc -t html -f native +Span ("", [], [("","")]) [] +^D + +``` -- cgit v1.2.3 From 7a9832166e36f77402d5e0259647e9f5c7ba4e58 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Mon, 20 Dec 2021 13:44:03 -0800 Subject: Add text wrapping to HTML output. Previously the HTML writer was exceptional in not being sensitive to the `--wrap` option. With this change `--wrap` now works for HTML. The default (as with other formats) is automatic wrapping to 72 columns. A new internal module, T.P.Writers.Blaze, exports `layoutMarkup`. This converts a blaze Html structure into a doclayout Doc Text. In addition, we now add a line break between an `img` tag and the associated `figcaption`. Note: Output is never wrapped in `writeHtmlStringForEPUB`. This accords with previous behavior since previously the HTML writer was insensitive to `--wrap` settings. There's no real need to wrap HTML inside a zipped container. Note that the contents of script, textarea, and pre tags are always laid out with the `flush` combinator, so that unwanted spaces won't be introduced if these occur in an indented context in a template. Closes #7764. --- MANUAL.txt | 1 - pandoc.cabal | 1 + src/Text/Pandoc/Writers/Blaze.hs | 139 +++++++++++++++++++++++++++++++++++++++ src/Text/Pandoc/Writers/HTML.hs | 107 ++++++++++++++++-------------- test/command/262.md | 3 +- test/command/2649.md | 9 ++- test/command/3523.md | 8 ++- test/command/3534.md | 15 +++-- test/command/3577.md | 9 ++- test/command/3701.md | 3 +- test/command/3752.md | 18 +++-- test/command/3840.md | 3 +- test/command/4012.md | 3 +- test/command/4186.md | 3 +- test/command/4235.md | 10 ++- test/command/4639.md | 2 +- test/command/4677.md | 3 +- test/command/4743.md | 4 +- test/command/512.md | 3 +- test/command/5121.md | 3 +- test/command/5627.md | 12 ++-- test/command/5642.md | 3 +- test/command/5650.md | 6 +- test/command/5655.md | 10 ++- test/command/5813.md | 3 +- test/command/5986.md | 3 +- test/command/6739.md | 3 +- test/command/7006.md | 9 ++- test/command/7416.md | 6 +- test/command/7568.md | 7 +- test/command/7713.md | 3 +- test/command/853.md | 6 +- test/command/video-audio.md | 10 ++- test/ipynb/rank.out.html | 12 ++-- test/s5-basic.html | 3 +- test/s5-fancy.html | 7 +- test/s5-fragment.html | 3 +- test/s5-inserts.html | 3 +- test/tables.html5 | 6 +- test/writer.html4 | 85 ++++++++++++++++-------- test/writer.html5 | 100 +++++++++++++++++++--------- 41 files changed, 475 insertions(+), 172 deletions(-) create mode 100644 src/Text/Pandoc/Writers/Blaze.hs (limited to 'src/Text/Pandoc/Writers/HTML.hs') diff --git a/MANUAL.txt b/MANUAL.txt index 2e6d53ca6..008a0e657 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -790,7 +790,6 @@ header when requesting a document from a URL: preserve the wrapping from the source document (that is, where there are nonsemantic newlines in the source, there will be nonsemantic newlines in the output as well). - Automatic wrapping does not currently work in HTML output. In `ipynb` output, this option affects wrapping of the contents of markdown cells. diff --git a/pandoc.cabal b/pandoc.cabal index 3cad5bce7..dc6a92a5f 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -688,6 +688,7 @@ library Text.Pandoc.Writers.Markdown.Types, Text.Pandoc.Writers.Markdown.Inline, Text.Pandoc.Writers.Roff, + Text.Pandoc.Writers.Blaze, Text.Pandoc.Writers.Powerpoint.Presentation, Text.Pandoc.Writers.Powerpoint.Output, Text.Pandoc.Lua.ErrorConversion, diff --git a/src/Text/Pandoc/Writers/Blaze.hs b/src/Text/Pandoc/Writers/Blaze.hs new file mode 100644 index 000000000..0e3bd0f98 --- /dev/null +++ b/src/Text/Pandoc/Writers/Blaze.hs @@ -0,0 +1,139 @@ +{-# LANGUAGE OverloadedStrings #-} +{- | + Module : Text.Pandoc.Writers.Shared + Copyright : Copyright (C) 2021 John MacFarlane + License : GNU GPL, version 2 or above + + Maintainer : John MacFarlane + Stability : alpha + Portability : portable + +Render blaze-html Html to DocLayout document (so it can be wrapped). +-} +module Text.Pandoc.Writers.Blaze ( layoutMarkup ) +where +import Text.Blaze +import qualified Data.ByteString as S +import Data.List (isInfixOf) +import Data.Text.Encoding (decodeUtf8) +import qualified Data.Text as T +import Data.Text (Text) +import Text.DocLayout hiding (Text, Empty) +import Text.Blaze.Internal (ChoiceString(..), getText, MarkupM(..)) + +layoutMarkup :: Markup -> Doc T.Text +layoutMarkup = go True mempty + where + go :: Bool -> Doc T.Text -> MarkupM b -> Doc T.Text + go wrap attrs (Parent _ open close content) = + let open' = getText open + in literal open' + <> attrs + <> char '>' + <> (if allowsWrap open' + then go wrap mempty content + else flush $ go False mempty content) + <> literal (getText close) + go wrap attrs (CustomParent tag content) = + char '<' + <> fromChoiceString wrap tag + <> attrs + <> char '>' + <> go wrap mempty content + <> literal " fromChoiceString wrap tag + <> char '>' + go _wrap attrs (Leaf _ begin end _) = + literal (getText begin) + <> attrs + <> literal (getText end) + go wrap attrs (CustomLeaf tag close _) = + char '<' + <> fromChoiceString wrap tag + <> attrs + <> (if close then literal " />" else char '>') + go wrap attrs (AddAttribute rawkey _ value h) = + go wrap + (space' wrap + <> literal (getText rawkey) + <> char '=' + <> doubleQuotes (fromChoiceString wrap value) + <> attrs) h + go wrap attrs (AddCustomAttribute key value h) = + go wrap + (space' wrap + <> fromChoiceString wrap key + <> char '=' + <> doubleQuotes (fromChoiceString wrap value) + <> attrs) h + go wrap _ (Content content _) = fromChoiceString wrap content + go wrap _ (Comment comment _) = + literal "" + go wrap attrs (Append h1 h2) = go wrap attrs h1 <> go wrap attrs h2 + go _ _ (Empty _) = mempty + space' wrap = if wrap then space else char ' ' + +allowsWrap :: T.Text -> Bool +allowsWrap t = + not (t == " ChoiceString -- ^ String to render + -> Doc Text -- ^ Resulting builder +fromChoiceString wrap (Static s) = withWrap wrap $ getText s +fromChoiceString wrap (String s) = withWrap wrap $ + escapeMarkupEntities $ T.pack s +fromChoiceString wrap (Text s) = withWrap wrap $ escapeMarkupEntities s +fromChoiceString wrap (ByteString s) = withWrap wrap $ decodeUtf8 s +fromChoiceString _wrap (PreEscaped x) = -- don't wrap! + case x of + String s -> literal $ T.pack s + Text s -> literal s + s -> fromChoiceString False s +fromChoiceString wrap (External x) = case x of + -- Check that the sequence " if " if " if " fromChoiceString wrap s +fromChoiceString wrap (AppendChoiceString x y) = + fromChoiceString wrap x <> fromChoiceString wrap y +fromChoiceString _ EmptyChoiceString = mempty + +withWrap :: Bool -> Text -> Doc Text +withWrap wrap + | wrap = mconcat . toChunks + | otherwise = literal + +toChunks :: Text -> [Doc Text] +toChunks = map toDoc . T.groupBy sameStatus + where + toDoc t = + if T.any (== ' ') t + then space + else if T.any (== '\n') t + then cr + else literal t + sameStatus c d = + (c == ' ' && d == ' ') || + (c == '\n' && d == '\n') || + (c /= ' ' && d /= ' ' && c /= '\n' && d /= '\n') + + +-- | Escape predefined XML entities in a text value +-- +escapeMarkupEntities :: Text -- ^ Text to escape + -> Text -- ^ Resulting Doc +escapeMarkupEntities = T.concatMap escape + where + escape :: Char -> Text + escape '<' = "<" + escape '>' = ">" + escape '&' = "&" + escape '"' = """ + escape '\'' = "'" + escape x = T.singleton x diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 247cddfc9..664aeffb6 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -39,7 +39,7 @@ import qualified Data.Text as T import qualified Data.Text.Lazy as TL 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) @@ -70,6 +70,7 @@ 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 @@ -160,7 +161,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 @@ -207,17 +209,23 @@ writeHtmlString' :: PandocMonad m => WriterState -> WriterOptions -> Pandoc -> m Text writeHtmlString' st opts d = do (body, context) <- evalStateT (pandocToHtml opts d) st + let colwidth = case writerWrapText opts of + WrapAuto -> Just (writerColumns opts) + _ -> Nothing (if writerPreferAscii opts then toEntities else id) <$> case writerTemplate opts of - Nothing -> return $ renderHtml' body + 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 +236,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 = @@ -252,13 +260,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 $ @@ -267,7 +275,7 @@ pandocToHtml opts (Pandoc meta blocks) = do then blocks else prepSlides slideLevel blocks toc <- if writerTableOfContents opts && slideVariant /= S5Slides - then fmap renderHtml' <$> tableOfContents opts sects + then fmap layoutMarkup <$> tableOfContents opts sects else return Nothing blocks' <- blockListToHtml opts sects notes <- do @@ -281,7 +289,7 @@ pandocToHtml opts (Pandoc meta blocks) = do return notes st <- get 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 @@ -298,7 +306,7 @@ pandocToHtml opts (Pandoc meta blocks) = do nl opts 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 () {" @@ -324,15 +332,16 @@ pandocToHtml opts (Pandoc meta blocks) = do Just s | not (stHtml5 st) -> H.script ! A.type_ "text/javascript" $ preEscapedString - ("/* 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 +351,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,11 +370,12 @@ 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" True . defField "respondToHashChanges" True . @@ -377,7 +387,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 +395,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 +420,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) @@ -705,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 opts <>) . tocapt <$> inlineListToHtml opts txt + let inner = mconcat [nl opts, img, capt, nl opts] 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] @@ -1332,7 +1341,7 @@ inlineToHtml opts inline = do Space -> return $ strToHtml " " SoftBreak -> return $ case writerWrapText opts of WrapNone -> preEscapedText " " - WrapAuto -> preEscapedText " " + WrapAuto -> " " WrapPreserve -> preEscapedText "\n" LineBreak -> return $ do if html5 then H5.br else H.br diff --git a/test/command/262.md b/test/command/262.md index bda2acb35..61af20ede 100644 --- a/test/command/262.md +++ b/test/command/262.md @@ -5,7 +5,8 @@ .. _hello: .. _goodbye: example.com ^D -

    hello and goodbye

    +

    hello and goodbye

    ``` ``` diff --git a/test/command/2649.md b/test/command/2649.md index 52ae16ce4..4ab059ea0 100644 --- a/test/command/2649.md +++ b/test/command/2649.md @@ -90,17 +90,20 @@

    1

    -

    Sébastien Loeb

    +

    Sébastien +Loeb

    78

    2

    -

    Sébastien Ogier

    +

    Sébastien +Ogier

    38

    10

    -

    Hannu Mikkola

    +

    Hannu +Mikkola

    18

    diff --git a/test/command/3523.md b/test/command/3523.md index cb0089489..c3574943c 100644 --- a/test/command/3523.md +++ b/test/command/3523.md @@ -19,8 +19,12 @@ \end{document} ^D
    -

    Das Recht hat kein Dasein für sich, sein Wesen vielmehr ist das Leben des Menschen selbst, von einer besonderen Seite angesehen.

    -

    Das Recht hat kein Dasein für sich, sein Wesen vielmehr ist das Leben des Menschen selbst, von einer besonderen Seite angesehen.

    +

    Das Recht hat kein Dasein für sich, sein Wesen vielmehr +ist das Leben des Menschen selbst, von einer besonderen Seite +angesehen.

    +

    Das Recht hat kein Dasein für sich, sein Wesen vielmehr +ist das Leben des Menschen selbst, von einer besonderen Seite +angesehen.

    • hey

    • hey

    • diff --git a/test/command/3534.md b/test/command/3534.md index 8692007d2..42dca9207 100644 --- a/test/command/3534.md +++ b/test/command/3534.md @@ -2,7 +2,9 @@ % pandoc -f latex -t html I want to explain the interface of \lstinline[language=Java]{public class MyClass}. ^D -

      I want to explain the interface of public class MyClass.

      +

      I want to explain the interface of public class +MyClass.

      ``` @@ -10,7 +12,8 @@ I want to explain the interface of \lstinline[language=Java]{public class MyClas % pandoc -f latex -t html I want to explain the interface of \lstinline{public class MyClass}. ^D -

      I want to explain the interface of public class MyClass.

      +

      I want to explain the interface of public class +MyClass.

      ``` @@ -43,7 +46,9 @@ I want to explain the interface of \lstinline[language=Java]{public class MyClas % pandoc -f latex -t html I want to explain the interface of \mintinline{java}{public class MyClass}. ^D -

      I want to explain the interface of public class MyClass.

      +

      I want to explain the interface of public class +MyClass.

      ``` @@ -51,7 +56,9 @@ I want to explain the interface of \mintinline{java}{public class MyClass}. % pandoc -f latex -t html I want to explain the interface of \mintinline{java}|public class MyClass|. ^D -

      I want to explain the interface of public class MyClass.

      +

      I want to explain the interface of public class +MyClass.

      ``` diff --git a/test/command/3577.md b/test/command/3577.md index 2f415146d..2caeb7c11 100644 --- a/test/command/3577.md +++ b/test/command/3577.md @@ -16,10 +16,12 @@ \end{figure} ^D
      -Caption 1 +Caption 1 +
      -Caption 2 +Caption 2 +
      ``` ``` @@ -30,6 +32,7 @@ \end{figure} ^D
      -Caption 3 +Caption 3 +
      ``` diff --git a/test/command/3701.md b/test/command/3701.md index 01e438639..bd70fae59 100644 --- a/test/command/3701.md +++ b/test/command/3701.md @@ -55,6 +55,7 @@ ^D

      a

      a

      -

      a A a

      +

      a A a

      a

      ``` diff --git a/test/command/3752.md b/test/command/3752.md index 863e3f2d4..7db581cfe 100644 --- a/test/command/3752.md +++ b/test/command/3752.md @@ -32,11 +32,14 @@ A spider: [spider] ^D

      Chapter one

      A spider: spider

      -

      Another spider: another spider

      +

      Another spider: another
+spider

      The moon: moon

      Link to spider picture.

      -

      URL left alone: manual.

      -

      Absolute path left alone: absolute.

      +

      URL left alone: manual.

      +

      Absolute path left alone: absolute.

      Link to fragment: chapter two.

      Empty path: empty.

      Chapter two

      @@ -48,11 +51,14 @@ A spider: [spider] ^D

      Chapter one

      A spider: spider

      -

      Another spider: another spider

      +

      Another spider: another
+spider

      The moon: moon

      Link to spider picture.

      -

      URL left alone: manual.

      -

      Absolute path left alone: absolute.

      +

      URL left alone: manual.

      +

      Absolute path left alone: absolute.

      Link to fragment: chapter two.

      Empty path: empty.

      Chapter two

      diff --git a/test/command/3840.md b/test/command/3840.md index ceb1d1e51..a0dd314d3 100644 --- a/test/command/3840.md +++ b/test/command/3840.md @@ -2,7 +2,8 @@ % pandoc [@Alhazen1572-qk, V.9]: "competentius est" ^D -

      [@Alhazen1572-qk, V.9]: “competentius est”

      +

      [@Alhazen1572-qk, +V.9]: “competentius est”

      ``` ``` diff --git a/test/command/4012.md b/test/command/4012.md index 9e32692d6..26e971d4e 100644 --- a/test/command/4012.md +++ b/test/command/4012.md @@ -4,5 +4,6 @@ [image]: http://example.com/image.jpg {height=35mm} ^D -

      image

      +

      ``` diff --git a/test/command/4186.md b/test/command/4186.md index 90ac1271b..b2a2bd6e9 100644 --- a/test/command/4186.md +++ b/test/command/4186.md @@ -57,7 +57,8 @@ Outside all lists.
    This belongs to the outer list element, and is aligned accordingly, since the NAME attribute is not indented deeply enough. It is not enough for the BEGIN alone to be aligned deeply if the block is meant to have a NAME.
     
    -

    Still in the shallower list element since the preceding example block forced the deeper list element to terminate.

    +

    Still in the shallower list element since the preceding example block +forced the deeper list element to terminate.

    Outside all lists.

    ``` diff --git a/test/command/4235.md b/test/command/4235.md index 4f2644dd6..5b534b6d7 100644 --- a/test/command/4235.md +++ b/test/command/4235.md @@ -2,11 +2,15 @@ % pandoc --id-prefix=foo This.^[Has a footnote.] ^D -

    This.1

    -
    +

    This.1

    +

      -
    1. Has a footnote.↩︎

    2. +
    3. Has a footnote.↩︎

    ``` diff --git a/test/command/4639.md b/test/command/4639.md index c35df1749..31ac3a5d9 100644 --- a/test/command/4639.md +++ b/test/command/4639.md @@ -5,6 +5,6 @@ \end{equation} ^D

    \[\begin{equation} - E=mc^2 +E=mc^2 \end{equation}\]

    ``` diff --git a/test/command/4677.md b/test/command/4677.md index 2694624b9..64c436005 100644 --- a/test/command/4677.md +++ b/test/command/4677.md @@ -3,6 +3,7 @@ ![Caption](img.png){#img:1} ^D
    -Caption +Caption +
    ``` diff --git a/test/command/4743.md b/test/command/4743.md index 582540736..a75ec1078 100644 --- a/test/command/4743.md +++ b/test/command/4743.md @@ -41,5 +41,7 @@ My:thumbsup:emoji:heart: My:thumbsup:emoji:heart:x :hearts: xyz ^D

    0️⃣ header

    -

    My👍emoji❤️x ♥️ xyz

    +

    My👍emoji❤️x ♥️ xyz

    ``` diff --git a/test/command/512.md b/test/command/512.md index b95921309..21b3ea9a7 100644 --- a/test/command/512.md +++ b/test/command/512.md @@ -8,7 +8,8 @@ __ link1_ __ link2_ ^D -

    click here or click here

    +

    click here or click here

    ``` Multiple indirection: diff --git a/test/command/5121.md b/test/command/5121.md index 1ee6bda77..f1b972fb4 100644 --- a/test/command/5121.md +++ b/test/command/5121.md @@ -5,7 +5,8 @@ ## Header 2 ^D
    -My caption +My caption +
    ## Header 2 diff --git a/test/command/5627.md b/test/command/5627.md index 9910e76c5..dde4c99d6 100644 --- a/test/command/5627.md +++ b/test/command/5627.md @@ -20,8 +20,10 @@ Something
  3. Two -->something<!--
  4. Three
-
--><!--<script>alert('Escaped!')</script>
-
Something
+
--><!--<script>alert('Escaped!')</script>
+
Something
``` ``` @@ -46,8 +48,10 @@ Something
  • -->something<!--
  • bye -->something else<!--
  • -
    --><!--<script>alert('Escaped!')</script>
    -
    Something
    +
    --><!--<script>alert('Escaped!')</script>
    +
    Something
    ``` ``` diff --git a/test/command/5642.md b/test/command/5642.md index cd60df812..120a88ada 100644 --- a/test/command/5642.md +++ b/test/command/5642.md @@ -3,6 +3,7 @@ ![test](foo){aria-describedby="barbaz"} ^D
    -test +test +
    ``` diff --git a/test/command/5650.md b/test/command/5650.md index a2dd215bc..1e96aeaa4 100644 --- a/test/command/5650.md +++ b/test/command/5650.md @@ -5,7 +5,8 @@ a b ``` ^D -
    a
    +
    a
     b
    ```` @@ -16,7 +17,8 @@ a b ``` ^D -
    a
    +
    a
     b
    ```` diff --git a/test/command/5655.md b/test/command/5655.md index 692009562..72ad46e5e 100644 --- a/test/command/5655.md +++ b/test/command/5655.md @@ -2,13 +2,19 @@ % pandoc --webtex $T_n={n+1 \choose 2}$ ^D -

    T_n={n+1 \choose 2}

    +

    ```` ```` % pandoc --webtex $$T_n={n+1 \choose 2}$$ ^D -

    T_n={n+1 \choose 2}

    +

    ```` diff --git a/test/command/5813.md b/test/command/5813.md index 927a161ed..51f774524 100644 --- a/test/command/5813.md +++ b/test/command/5813.md @@ -2,5 +2,6 @@ % pandoc -f gfm ### Jekyll Plugins & Gems :gem: ^D -

    Jekyll Plugins & Gems 💎

    +

    Jekyll Plugins & Gems 💎

    ``` diff --git a/test/command/5986.md b/test/command/5986.md index c181e33ad..aaa1e6568 100644 --- a/test/command/5986.md +++ b/test/command/5986.md @@ -6,7 +6,8 @@

    diff --git a/test/command/6739.md b/test/command/6739.md index 7c9ed24a2..ff2d4bc75 100644 --- a/test/command/6739.md +++ b/test/command/6739.md @@ -4,7 +4,8 @@ * `--argA | --argB` This item has a pipe character ^D
      -
    • --argument This item does not have a pipe character
    • +
    • --argument This item does not have a pipe +character
    • --argA | --argB This item has a pipe character
    ``` diff --git a/test/command/7006.md b/test/command/7006.md index 7e2215cdf..22aaf84ad 100644 --- a/test/command/7006.md +++ b/test/command/7006.md @@ -6,13 +6,16 @@ Test.[^fn] ![Caption.](/image.jpg) ^D -

    Test.1

    -
    +

    Test.1

    +

    1. Foo:

      -Caption. +Caption. +
      ↩︎
    diff --git a/test/command/7416.md b/test/command/7416.md index 2f9577f10..d440725ab 100644 --- a/test/command/7416.md +++ b/test/command/7416.md @@ -4,7 +4,8 @@ ^D
    -alt
    caption
    +alt +
    caption
    ``` @@ -14,6 +15,7 @@ ^D
    -caption +caption +
    ``` diff --git a/test/command/7568.md b/test/command/7568.md index 42f1e37b1..487da0861 100644 --- a/test/command/7568.md +++ b/test/command/7568.md @@ -7,5 +7,10 @@ holds a useful spot. .. _Labyrinth Lord\: Revised Edition: https://www.drivethrurpg.com/product/64332/Labyrinth-Lord-Revised-Edition ^D -

    While Labyrinth Lord: Revised Edition (LLRE; PDF and POD) has been criticized for not being a completely faithful retro-clone of the Moldvay/Cook/Marsh Basic/Expert D&D rules (B/X), I think it still holds a useful spot.

    +

    While Labyrinth +Lord: Revised Edition (LLRE; PDF and POD) has been criticized for +not being a completely faithful retro-clone of the Moldvay/Cook/Marsh +Basic/Expert D&D rules (B/X), I think it still holds a useful +spot.

    ``` diff --git a/test/command/7713.md b/test/command/7713.md index d42dcd9b8..851cb4729 100644 --- a/test/command/7713.md +++ b/test/command/7713.md @@ -21,7 +21,8 @@ -cccccccccc cccccccccc cccccccccc cccccccccc cccccccccc cccccccccc +cccccccccc cccccccccc cccccccccc cccccccccc cccccccccc +cccccccccc diff --git a/test/command/853.md b/test/command/853.md index 54eb416a9..bcc3b4654 100644 --- a/test/command/853.md +++ b/test/command/853.md @@ -7,11 +7,13 @@ Here is a citation reference: [CIT2002]_. .. [CIT2002] This is the citation. It's just like a footnote, except the label is textual. ^D -

    Here is a citation reference: [CIT2002].

    +

    Here is a citation reference: [CIT2002].

    CIT2002
    -

    This is the citation. It's just like a footnote, except the label is textual.

    +

    This is the citation. It's just like a footnote, except the label +is textual.

    diff --git a/test/command/video-audio.md b/test/command/video-audio.md index 451b614d8..4fbd58db3 100644 --- a/test/command/video-audio.md +++ b/test/command/video-audio.md @@ -10,9 +10,13 @@ ![](./test.jpg) ^D -

    -

    -

    +

    +

    +

    ``` diff --git a/test/ipynb/rank.out.html b/test/ipynb/rank.out.html index eb5176509..a82fe8bbc 100644 --- a/test/ipynb/rank.out.html +++ b/test/ipynb/rank.out.html @@ -1,8 +1,12 @@ -
    -
    import matplotlib.pyplot as plt
    +
    +
    import matplotlib.pyplot as plt
    -
    -
    fig, ax = plt.subplots(figsize=(1, 1), dpi=4)
    +
    +
    fig, ax = plt.subplots(figsize=(1, 1), dpi=4)
     ax.imshow([[0, 1], [2, 3]]);

    you should see this when converting from ipynb to html instead of the image below.

    diff --git a/test/s5-basic.html b/test/s5-basic.html index 7440b575b..3a225da83 100644 --- a/test/s5-basic.html +++ b/test/s5-basic.html @@ -56,7 +56,8 @@

    Math

      -
    • $\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$
    • +
    • $\frac{d}{dx}f(x)=\lim_{h\to +0}\frac{f(x+h)-f(x)}{h}$
    diff --git a/test/s5-fancy.html b/test/s5-fancy.html index f5c41e561..00b25e80c 100644 --- a/test/s5-fancy.html +++ b/test/s5-fancy.html @@ -28,7 +28,9 @@ - +
    @@ -56,7 +58,8 @@

    Math

      -
    • \(\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}\)
    • +
    • \(\frac{d}{dx}f(x)=\lim_{h\to +0}\frac{f(x+h)-f(x)}{h}\)
    diff --git a/test/s5-fragment.html b/test/s5-fragment.html index 81c578d25..1a8d4839d 100644 --- a/test/s5-fragment.html +++ b/test/s5-fragment.html @@ -5,5 +5,6 @@

    Math

      -
    • $\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$
    • +
    • $\frac{d}{dx}f(x)=\lim_{h\to +0}\frac{f(x+h)-f(x)}{h}$
    diff --git a/test/s5-inserts.html b/test/s5-inserts.html index 1df9dd018..04dfc134a 100644 --- a/test/s5-inserts.html +++ b/test/s5-inserts.html @@ -35,7 +35,8 @@ STUFF INSERTED

    Math

      -
    • $\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$
    • +
    • $\frac{d}{dx}f(x)=\lim_{h\to +0}\frac{f(x+h)-f(x)}{h}$
    STUFF INSERTED diff --git a/test/tables.html5 b/test/tables.html5 index 533d2fd25..b3ee0ec79 100644 --- a/test/tables.html5 +++ b/test/tables.html5 @@ -121,7 +121,8 @@ Second row 5.0 -Here’s another one. Note the blank line between rows. +Here’s another one. Note the blank line between +rows. @@ -152,7 +153,8 @@ Second row 5.0 -Here’s another one. Note the blank line between rows. +Here’s another one. Note the blank line between +rows. diff --git a/test/writer.html4 b/test/writer.html4 index 257d86ddb..e2adcf5bc 100644 --- a/test/writer.html4 +++ b/test/writer.html4 @@ -156,10 +156,12 @@

    Anonymous

    July 17, 2006

    -

    This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite.

    +

    This is a set of tests for pandoc. Most of them are adapted from John +Gruber’s markdown test suite.


    Headers

    - +

    Level 3 with emphasis

    Level 4

    Level 5
    @@ -172,7 +174,9 @@

    Paragraphs

    Here’s a regular paragraph.

    -

    In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item.

    +

    In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. +Because a hard-wrapped line in the middle of a paragraph looked like a list +item.

    Here’s one with a bullet. * criminey.

    There should be a hard line break
    here.

    @@ -283,7 +287,8 @@ These should not be escaped: \$ \\ \> \[ \{

    Multiple paragraphs:

    1. Item 1, graf one.

      -

      Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.

    2. +

      Item 1. graf two. The quick brown fox jumped over the lazy dog’s +back.

    3. Item 2.

    4. Item 3.

    @@ -540,18 +545,22 @@ Blah

    So is this word.

    This is strong and em.

    So is this word.

    -

    This is code: >, $, \, \$, <html>.

    +

    This is code: >, $, \, +\$, <html>.

    This is strikeout.

    -

    Superscripts: abcd ahello ahello there.

    +

    Superscripts: abcd ahello +ahello there.

    Subscripts: H2O, H23O, Hmany of themO.

    -

    These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d.

    +

    These should not be superscripts or subscripts, because of the unescaped +spaces: a^b c^d, a~b c~d.


    Smart quotes, ellipses, dashes

    “Hello,” said the spider. “‘Shelob’ is my name.”

    ‘A’, ‘B’, and ‘C’ are letters.

    ‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’

    ‘He said, “I want to go.”’ Were you alive in the 70’s?

    -

    Here is some quoted ‘code’ and a “quoted link”.

    +

    Here is some quoted ‘code’ and a “quoted link”.

    Some dashes: one—two — three—four — five.

    Dashes between numbers: 5–7, 255–66, 1987–1999.

    Ellipses…and…and….

    @@ -564,13 +573,16 @@ Blah
  • α ∧ ω
  • 223
  • p-Tree
  • -
  • Here’s some display math: $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$
  • -
  • Here’s one that has a line break in it: α + ω × x2.
  • +
  • Here’s some display math: $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$
  • +
  • Here’s one that has a line break in it: α + ω × x2.
  • These shouldn’t be math:

    • To get the famous equation, write $e = mc^2$.
    • -
    • $22,000 is a lot of money. So is $34,000. (It worked if “lot” is emphasized.)
    • +
    • $22,000 is a lot of money. So is $34,000. (It worked if “lot” is +emphasized.)
    • Shoes ($20) and socks ($5).
    • Escaped $: $73 this should be emphasized 23$.
    @@ -613,7 +625,8 @@ Blah

    URL and title.

    URL and title.

    URL and title.

    -

    URL and title

    +

    URL and +title

    URL and title

    with_underscore

    Email link

    @@ -630,22 +643,29 @@ Blah

    Foo bar.

    Foo biz.

    With ampersands

    -

    Here’s a link with an ampersand in the URL.

    -

    Here’s a link with an amersand in the link text: AT&T.

    +

    Here’s a link with an ampersand +in the URL.

    +

    Here’s a link with an amersand in the link text: AT&T.

    Here’s an inline link.

    -

    Here’s an inline link in pointy braces.

    +

    Here’s an inline link in pointy +braces.

    -

    With an ampersand: http://example.com/?foo=1&bar=2

    +

    With an ampersand: http://example.com/?foo=1&bar=2

    -

    An e-mail address:

    +

    An e-mail address: nobody@nowhere.net

    -

    Blockquoted: http://example.com/

    +

    Blockquoted: http://example.com/

    -

    Auto-links should not occur here: <http://example.com/>

    +

    Auto-links should not occur here: +<http://example.com/>

    or here: <http://example.com/>

    Images

    @@ -657,23 +677,36 @@ Blah

    Here is a movie movie icon.


    Footnotes

    -

    Here is a footnote reference,1 and another.2 This should not be a footnote reference, because it contains a space.[^my note] Here is an inline note.3

    +

    Here is a footnote reference,1 and another.2 This should not be a footnote reference, +because it contains a space.[^my note] Here is an inline note.3

    -

    Notes can go in quotes.4

    +

    Notes can go in quotes.4

      -
    1. And in list items.5
    2. +
    3. And in list items.5

    This paragraph should not be part of the note, as it is not indented.


      -
    1. Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.↩︎

    2. +
    3. Here is the footnote. It can go anywhere after the footnote +reference. It need not be placed at the end of the document.↩︎

    4. Here’s the long note. This one contains multiple blocks.

      -

      Subsequent blocks are indented to show that they belong to the footnote (as with list items).

      +

      Subsequent blocks are indented to show that they belong to the footnote (as +with list items).

        { <code> }
      -

      If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.↩︎

    5. -
    6. This is easier to type. Inline notes may contain links and ] verbatim characters, as well as [bracketed text].↩︎

    7. +

      If you want, you can indent every line, but you can also be lazy and just +indent the first line of each block.↩︎

      +
    8. This is easier to type. Inline notes may contain links and ] verbatim characters, as +well as [bracketed text].↩︎

    9. In quote.↩︎

    10. In list.↩︎

    diff --git a/test/writer.html5 b/test/writer.html5 index 0141bf9fe..cdfcf042f 100644 --- a/test/writer.html5 +++ b/test/writer.html5 @@ -159,10 +159,12 @@

    Anonymous

    July 17, 2006

    -

    This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite.

    +

    This is a set of tests for pandoc. Most of them are adapted from John +Gruber’s markdown test suite.


    Headers

    - +

    Level 3 with emphasis

    Level 4

    Level 5
    @@ -175,7 +177,9 @@

    Paragraphs

    Here’s a regular paragraph.

    -

    In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item.

    +

    In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. +Because a hard-wrapped line in the middle of a paragraph looked like a list +item.

    Here’s one with a bullet. * criminey.

    There should be a hard line break
    here.

    @@ -286,7 +290,8 @@ These should not be escaped: \$ \\ \> \[ \{

    Multiple paragraphs:

    1. Item 1, graf one.

      -

      Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.

    2. +

      Item 1. graf two. The quick brown fox jumped over the lazy dog’s +back.

    3. Item 2.

    4. Item 3.

    @@ -543,18 +548,22 @@ Blah

    So is this word.

    This is strong and em.

    So is this word.

    -

    This is code: >, $, \, \$, <html>.

    +

    This is code: >, $, \, +\$, <html>.

    This is strikeout.

    -

    Superscripts: abcd ahello ahello there.

    +

    Superscripts: abcd ahello +ahello there.

    Subscripts: H2O, H23O, Hmany of themO.

    -

    These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d.

    +

    These should not be superscripts or subscripts, because of the unescaped +spaces: a^b c^d, a~b c~d.


    Smart quotes, ellipses, dashes

    “Hello,” said the spider. “‘Shelob’ is my name.”

    ‘A’, ‘B’, and ‘C’ are letters.

    ‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’

    ‘He said, “I want to go.”’ Were you alive in the 70’s?

    -

    Here is some quoted ‘code’ and a “quoted link”.

    +

    Here is some quoted ‘code’ and a “quoted link”.

    Some dashes: one—two — three—four — five.

    Dashes between numbers: 5–7, 255–66, 1987–1999.

    Ellipses…and…and….

    @@ -567,13 +576,16 @@ Blah
  • α ∧ ω
  • 223
  • p-Tree
  • -
  • Here’s some display math: $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$
  • -
  • Here’s one that has a line break in it: α + ω × x2.
  • +
  • Here’s some display math: $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$
  • +
  • Here’s one that has a line break in it: α + ω × x2.
  • These shouldn’t be math:

    • To get the famous equation, write $e = mc^2$.
    • -
    • $22,000 is a lot of money. So is $34,000. (It worked if “lot” is emphasized.)
    • +
    • $22,000 is a lot of money. So is $34,000. (It worked if “lot” is +emphasized.)
    • Shoes ($20) and socks ($5).
    • Escaped $: $73 this should be emphasized 23$.
    @@ -616,7 +628,8 @@ Blah

    URL and title.

    URL and title.

    URL and title.

    -

    URL and title

    +

    URL and +title

    URL and title

    with_underscore

    Email link

    @@ -633,51 +646,78 @@ Blah

    Foo bar.

    Foo biz.

    With ampersands

    -

    Here’s a link with an ampersand in the URL.

    -

    Here’s a link with an amersand in the link text: AT&T.

    +

    Here’s a link with an ampersand +in the URL.

    +

    Here’s a link with an amersand in the link text: AT&T.

    Here’s an inline link.

    -

    Here’s an inline link in pointy braces.

    +

    Here’s an inline link in pointy +braces.

    -

    With an ampersand: http://example.com/?foo=1&bar=2

    +

    With an ampersand: http://example.com/?foo=1&bar=2

    -

    An e-mail address:

    +

    An e-mail address: nobody@nowhere.net

    -

    Blockquoted: http://example.com/

    +

    Blockquoted: http://example.com/

    -

    Auto-links should not occur here: <http://example.com/>

    +

    Auto-links should not occur here: +<http://example.com/>

    or here: <http://example.com/>

    Images

    From “Voyage dans la Lune” by Georges Melies (1902):

    -lalune +lalune +

    Here is a movie movie icon.


    Footnotes

    -

    Here is a footnote reference,1 and another.2 This should not be a footnote reference, because it contains a space.[^my note] Here is an inline note.3

    +

    Here is a footnote reference,1 and another.2 This should +not be a footnote reference, because it contains a space.[^my note] +Here is an inline note.3

    -

    Notes can go in quotes.4

    +

    Notes can go in quotes.4

      -
    1. And in list items.5
    2. +
    3. And in list items.5

    This paragraph should not be part of the note, as it is not indented.


      -
    1. Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.↩︎

    2. -
    3. Here’s the long note. This one contains multiple blocks.

      -

      Subsequent blocks are indented to show that they belong to the footnote (as with list items).

      +
    4. Here is the footnote. It can go anywhere +after the footnote reference. It need not be placed at the end of the +document.↩︎

    5. +
    6. Here’s the long note. This one contains +multiple blocks.

      +

      Subsequent blocks are indented to show that they belong to the footnote (as +with list items).

        { <code> }
      -

      If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.↩︎

    7. -
    8. This is easier to type. Inline notes may contain links and ] verbatim characters, as well as [bracketed text].↩︎

    9. -
    10. In quote.↩︎

    11. -
    12. In list.↩︎

    13. +

      If you want, you can indent every line, but you can also be lazy and just +indent the first line of each block.↩︎

      +
    14. This is easier to type. Inline notes +may contain links and ] verbatim +characters, as well as [bracketed text].↩︎

    15. +
    16. In quote.↩︎

    17. +
    18. In list.↩︎

    -- cgit v1.2.3 From c4f6e6cb57e4fdda9ad59ff7220988810583ec60 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Tue, 21 Dec 2021 22:53:22 -0800 Subject: HTML writer: make line breaks more consistent. - With `--wrap=none`, we now output line breaks between block-level elements. Previously they were omitted entirely, so the whole document was on one line, unless there were literal line breaks in pre sections. This makes the HTML writer's behavior more consistent with that of other writers. - Put newline after `
    `. - Put newlines after block-level elements in footnote section. --- src/Text/Pandoc/Writers/HTML.hs | 119 ++++++++++++++++++++-------------------- test/Tests/Writers/HTML.hs | 73 +++++++++++++++++++----- test/command/853.md | 5 +- test/writer.html4 | 66 ++++++++++++++-------- test/writer.html5 | 66 ++++++++++++++-------- 5 files changed, 208 insertions(+), 121 deletions(-) (limited to 'src/Text/Pandoc/Writers/HTML.hs') diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 664aeffb6..8c5548196 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -132,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 @@ -284,7 +282,7 @@ pandocToHtml opts (Pandoc meta blocks) = do if null (stNotes st) then return mempty else do - notes <- footnoteSection opts EndOfDocument (stEmittedNotes st + 1) (reverse (stNotes st)) + notes <- footnoteSection EndOfDocument (stEmittedNotes st + 1) (reverse (stNotes st)) modify (\st' -> st'{ stNotes = mempty, stEmittedNotes = stEmittedNotes st' + length (stNotes st') }) return notes st <- get @@ -303,7 +301,7 @@ 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 :: [Doc Text]) -> "true" @@ -323,7 +321,7 @@ pandocToHtml opts (Pandoc meta blocks) = do , " });" , "}}});" ] - nl opts + nl H.link ! A.rel "stylesheet" ! A.href (toValue $ url <> "katex.min.css") @@ -459,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 @@ -489,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 @@ -513,11 +511,13 @@ tableOfContents opts sects = do -- | Convert list of Note blocks to a footnote
    . -- Assumes notes are sorted. footnoteSection :: - PandocMonad m => WriterOptions -> ReferenceLocation -> Int -> [Html] -> StateT WriterState m Html -footnoteSection opts refLocation startCounter notes = do + PandocMonad m => ReferenceLocation -> Int -> [Html] -> StateT WriterState m Html +footnoteSection refLocation startCounter notes = do html5 <- gets stHtml5 slideVariant <- gets stSlideVariant - let hrtag = if refLocation /= EndOfBlock then (if html5 then H5.hr else H.hr) else mempty + 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" @@ -538,17 +538,17 @@ footnoteSection opts refLocation startCounter notes = do if null notes then mempty else do - nl opts + nl container $ do - nl opts + nl hrtag - nl opts -- Keep the previous output exactly the same if we don't -- have multiple notes sections if startCounter == 1 - then H.ol $ mconcat notes >> nl opts - else H.ol ! A.start (fromString (show startCounter)) $ mconcat notes >> nl opts - nl opts + 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) @@ -715,8 +715,8 @@ figure opts attr@(_, _, attrList) txt (s,tit) = do img <- inlineToHtml opts (Image attr alt (s,tit)) capt <- if null txt then return mempty - else (nl opts <>) . tocapt <$> inlineListToHtml opts txt - let inner = mconcat [nl opts, img, capt, nl opts] + else (nl <>) . tocapt <$> inlineListToHtml opts txt + let inner = mconcat [nl, img, capt, nl] return $ if html5 then H5.figure inner else H.div ! A.class_ "figure" $ inner @@ -820,32 +820,32 @@ blockToHtmlInner 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 + else nl <> innerContents blockToHtmlInner opts (Div attr@(ident, classes, kvs') bs) = do html5 <- gets stHtml5 slideVariant <- gets stSlideVariant @@ -883,7 +883,7 @@ blockToHtmlInner 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') @@ -964,10 +964,10 @@ blockToHtmlInner 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 + 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 @@ -1022,10 +1022,10 @@ blockToHtmlInner opts (OrderedList (startnum, numstyle, _) 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 blockToHtmlInner opts (Table attr caption colspecs thead tbody tfoot) = tableToHtml opts (Ann.toTable attr caption colspecs thead tbody tfoot) @@ -1052,7 +1052,7 @@ blockToHtml opts block = do then do notes <- if null (stNotes st) then return mempty - else footnoteSection opts (writerReferenceLocation opts) (stEmittedNotes st + 1) (reverse (stNotes st)) + 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 @@ -1071,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 @@ -1091,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 @@ -1144,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) = @@ -1185,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 @@ -1206,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 @@ -1234,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 @@ -1297,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 @@ -1340,9 +1339,9 @@ inlineToHtml opts inline = do (Str str) -> return $ strToHtml str Space -> return $ strToHtml " " SoftBreak -> return $ case writerWrapText opts of - WrapNone -> preEscapedText " " + WrapNone -> " " WrapAuto -> " " - WrapPreserve -> preEscapedText "\n" + WrapPreserve -> nl LineBreak -> return $ do if html5 then H5.br else H.br strToHtml "\n" @@ -1607,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 diff --git a/test/Tests/Writers/HTML.hs b/test/Tests/Writers/HTML.hs index 50775b171..a81badae8 100644 --- a/test/Tests/Writers/HTML.hs +++ b/test/Tests/Writers/HTML.hs @@ -2,6 +2,7 @@ module Tests.Writers.HTML (tests) where import Data.Text (unpack) +import qualified Data.Text as T import Test.Tasty import Tests.Helpers import Text.Pandoc @@ -68,7 +69,7 @@ tests = , testGroup "blocks" [ "definition list with empty
    " =: definitionList [(mempty, [para $ text "foo bar"])] - =?> "

    foo bar

    " + =?> "
    \n
    \n
    \n

    foo bar

    \n
    \n
    " , "heading with disallowed attributes" =: headerWith ("", [], [("invalid","1"), ("lang", "en")]) 1 "test" =?> @@ -108,37 +109,66 @@ tests = [ test (htmlWithOpts def{writerReferenceLocation=EndOfDocument}) "at the end of a document" $ noteTestDoc =?> - concat + T.unlines [ "

    Page title

    " , "

    First section

    " , "

    This is a footnote.1 And this is a link.

    " - , "

    A note inside a block quote.2

    A second paragraph.

    " + , "
    " + , "

    A note inside a block quote.2

    " + , "

    A second paragraph.

    " + , "
    " , "

    Second section

    " , "

    Some more text.

    " - , "

    1. Down here.↩︎

    2. The second note.↩︎

    " + , "
    " + , "
    " + , "
      " + , "
    1. Down here.↩︎

    2. " + , "
    3. The second note.↩︎

    4. " + , "
    " + , "
    " ] , test (htmlWithOpts def{writerReferenceLocation=EndOfBlock}) "at the end of a block" $ noteTestDoc =?> - concat + T.unlines [ "

    Page title

    " , "

    First section

    " , "

    This is a footnote.1 And this is a link.

    " - , "
    1. Down here.↩︎

    " - , "

    A note inside a block quote.2

    A second paragraph.

    " - , "
    1. The second note.↩︎

    " + , "
    " + , "
      " + , "
    1. Down here.↩︎

    2. " + , "
    " + , "
    " + , "
    " + , "

    A note inside a block quote.2

    " + , "

    A second paragraph.

    " + , "
    " + , "
    " + , "
      " + , "
    1. The second note.↩︎

    2. " + , "
    " + , "
    " , "

    Second section

    " , "

    Some more text.

    " ] , test (htmlWithOpts def{writerReferenceLocation=EndOfSection}) "at the end of a section" $ noteTestDoc =?> - concat + T.unlines [ "

    Page title

    " , "

    First section

    " , "

    This is a footnote.1 And this is a link.

    " - , "

    A note inside a block quote.2

    A second paragraph.

    " - , "

    1. Down here.↩︎

    2. The second note.↩︎

    " + , "
    " + , "

    A note inside a block quote.2

    " + , "

    A second paragraph.

    " + , "
    " + , "
    " + , "
    " + , "
      " + , "
    1. Down here.↩︎

    2. " + , "
    3. The second note.↩︎

    4. " + , "
    " + , "
    " , "

    Second section

    " , "

    Some more text.

    " ] @@ -147,15 +177,28 @@ tests = noteTestDoc =?> -- Footnotes are rendered _after_ their section (in this case after the level2 section -- that contains it). - concat + T.unlines [ "
    " , "

    Page title

    " , "
    " , "

    First section

    " - , "

    This is a footnote.1 And this is a link.

    A note inside a block quote.2

    A second paragraph.

    " + , "

    This is a footnote.1 And this is a link.

    " + , "
    " + , "

    A note inside a block quote.2

    " + , "

    A second paragraph.

    " + , "
    " + , "
    " + , "
    " + , "
    " + , "
      " + , "
    1. Down here.↩︎

    2. " + , "
    3. The second note.↩︎

    4. " + , "
    " + , "
    " + , "
    " + , "

    Second section

    " + , "

    Some more text.

    " , "
    " - , "

    1. Down here.↩︎

    2. The second note.↩︎

    " - , "

    Second section

    Some more text.

    " , "
    " ] ] diff --git a/test/command/853.md b/test/command/853.md index bcc3b4654..518c6593b 100644 --- a/test/command/853.md +++ b/test/command/853.md @@ -12,8 +12,9 @@ class="citation">[CIT2002].

    CIT2002
    -

    This is the citation. It's just like a footnote, except the label -is textual.

    +
    +

    This is the citation. It's just like a footnote, except the label is +textual.

    diff --git a/test/writer.html4 b/test/writer.html4 index e2adcf5bc..1e255fa70 100644 --- a/test/writer.html4 +++ b/test/writer.html4 @@ -376,47 +376,58 @@ back.

    Tight using spaces:

    apple
    -
    red fruit +
    +red fruit
    orange
    -
    orange fruit +
    +orange fruit
    banana
    -
    yellow fruit +
    +yellow fruit

    Tight using tabs:

    apple
    -
    red fruit +
    +red fruit
    orange
    -
    orange fruit +
    +orange fruit
    banana
    -
    yellow fruit +
    +yellow fruit

    Loose:

    apple
    -

    red fruit

    +
    +

    red fruit

    orange
    -

    orange fruit

    +
    +

    orange fruit

    banana
    -

    yellow fruit

    +
    +

    yellow fruit

    Multiple blocks with italics:

    apple
    -

    red fruit

    +
    +

    red fruit

    contains seeds, crisp, pleasant to taste

    orange
    -

    orange fruit

    +
    +

    orange fruit

    { orange code block }

    orange block quote

    @@ -426,38 +437,49 @@ back.

    Multiple definitions, tight:

    apple
    -
    red fruit +
    +red fruit
    -
    computer +
    +computer
    orange
    -
    orange fruit +
    +orange fruit
    -
    bank +
    +bank

    Multiple definitions, loose:

    apple
    -

    red fruit

    +
    +

    red fruit

    -

    computer

    +
    +

    computer

    orange
    -

    orange fruit

    +
    +

    orange fruit

    -

    bank

    +
    +

    bank

    Blank line after term, indented marker, alternate markers:

    apple
    -

    red fruit

    +
    +

    red fruit

    -

    computer

    +
    +

    computer

    orange
    -

    orange fruit

    +
    +

    orange fruit

    1. sublist
    2. sublist
    3. diff --git a/test/writer.html5 b/test/writer.html5 index cdfcf042f..d8e89b3e2 100644 --- a/test/writer.html5 +++ b/test/writer.html5 @@ -379,47 +379,58 @@ back.

      Tight using spaces:

      apple
      -
      red fruit +
      +red fruit
      orange
      -
      orange fruit +
      +orange fruit
      banana
      -
      yellow fruit +
      +yellow fruit

      Tight using tabs:

      apple
      -
      red fruit +
      +red fruit
      orange
      -
      orange fruit +
      +orange fruit
      banana
      -
      yellow fruit +
      +yellow fruit

      Loose:

      apple
      -

      red fruit

      +
      +

      red fruit

      orange
      -

      orange fruit

      +
      +

      orange fruit

      banana
      -

      yellow fruit

      +
      +

      yellow fruit

      Multiple blocks with italics:

      apple
      -

      red fruit

      +
      +

      red fruit

      contains seeds, crisp, pleasant to taste

      orange
      -

      orange fruit

      +
      +

      orange fruit

      { orange code block }

      orange block quote

      @@ -429,38 +440,49 @@ back.

      Multiple definitions, tight:

      apple
      -
      red fruit +
      +red fruit
      -
      computer +
      +computer
      orange
      -
      orange fruit +
      +orange fruit
      -
      bank +
      +bank

      Multiple definitions, loose:

      apple
      -

      red fruit

      +
      +

      red fruit

      -

      computer

      +
      +

      computer

      orange
      -

      orange fruit

      +
      +

      orange fruit

      -

      bank

      +
      +

      bank

      Blank line after term, indented marker, alternate markers:

      apple
      -

      red fruit

      +
      +

      red fruit

      -

      computer

      +
      +

      computer

      orange
      -

      orange fruit

      +
      +

      orange fruit

      1. sublist
      2. sublist
      3. -- cgit v1.2.3