HTML writer: ensure headings only have valid attribs in HTML4

Fixes: #5944
This commit is contained in:
Albert Krewinkel 2021-05-17 15:37:25 +02:00
parent 4417dacc44
commit 25f5b92777
No known key found for this signature in database
GPG key ID: 388DC0B21F631124
2 changed files with 71 additions and 54 deletions

View file

@ -882,7 +882,7 @@ blockToHtml opts (BlockQuote blocks) = do
else do else do
contents <- blockListToHtml opts blocks contents <- blockListToHtml opts blocks
return $ H.blockquote $ nl opts >> contents >> nl opts return $ H.blockquote $ nl opts >> contents >> nl opts
blockToHtml opts (Header level attr@(_,classes,kvs) lst) = do blockToHtml opts (Header level (ident,classes,kvs) lst) = do
contents <- inlineListToHtml opts lst contents <- inlineListToHtml opts lst
let secnum = fromMaybe mempty $ lookup "number" kvs let secnum = fromMaybe mempty $ lookup "number" kvs
let contents' = if writerNumberSections opts && not (T.null secnum) let contents' = if writerNumberSections opts && not (T.null secnum)
@ -890,7 +890,13 @@ blockToHtml opts (Header level attr@(_,classes,kvs) lst) = do
then (H.span ! A.class_ "header-section-number" then (H.span ! A.class_ "header-section-number"
$ toHtml secnum) >> strToHtml " " >> contents $ toHtml secnum) >> strToHtml " " >> contents
else contents else contents
addAttrs opts attr html5 <- gets stHtml5
let kvs' = if html5
then kvs
else [ (k, v) | (k, v) <- kvs
, k `elem` (["lang", "dir", "title", "style"
, "align"] ++ intrinsicEventsHTML4)]
addAttrs opts (ident,classes,kvs')
$ case level of $ case level of
1 -> H.h1 contents' 1 -> H.h1 contents'
2 -> H.h2 contents' 2 -> H.h2 contents'
@ -1526,6 +1532,12 @@ allowsMathEnvironments MathML = True
allowsMathEnvironments (WebTeX _) = True allowsMathEnvironments (WebTeX _) = True
allowsMathEnvironments _ = False allowsMathEnvironments _ = False
-- | List of intrinsic event attributes allowed on all elements in HTML4.
intrinsicEventsHTML4 :: [Text]
intrinsicEventsHTML4 =
[ "onclick", "ondblclick", "onmousedown", "onmouseup", "onmouseover"
, "onmouseout", "onmouseout", "onkeypress", "onkeydown", "onkeyup"]
isRawHtml :: PandocMonad m => Format -> StateT WriterState m Bool isRawHtml :: PandocMonad m => Format -> StateT WriterState m Bool
isRawHtml f = do isRawHtml f = do
html5 <- gets stHtml5 html5 <- gets stHtml5

View file

@ -34,55 +34,60 @@ infix 4 =:
(=:) = test html (=:) = test html
tests :: [TestTree] tests :: [TestTree]
tests = [ testGroup "inline code" tests =
[ "basic" =: code "@&" =?> "<code>@&amp;</code>" [ testGroup "inline code"
, "haskell" =: codeWith ("",["haskell"],[]) ">>=" [ "basic" =: code "@&" =?> "<code>@&amp;</code>"
=?> "<code class=\"sourceCode haskell\"><span class=\"op\">&gt;&gt;=</span></code>" , "haskell" =: codeWith ("",["haskell"],[]) ">>="
, "nolanguage" =: codeWith ("",["nolanguage"],[]) ">>=" =?> "<code class=\"sourceCode haskell\"><span class=\"op\">&gt;&gt;=</span></code>"
=?> "<code class=\"nolanguage\">&gt;&gt;=</code>" , "nolanguage" =: codeWith ("",["nolanguage"],[]) ">>="
] =?> "<code class=\"nolanguage\">&gt;&gt;=</code>"
, testGroup "images" ]
[ "alt with formatting" =: , testGroup "images"
image "/url" "title" ("my " <> emph "image") [ "alt with formatting" =:
=?> "<img src=\"/url\" title=\"title\" alt=\"my image\" />" image "/url" "title" ("my " <> emph "image")
] =?> "<img src=\"/url\" title=\"title\" alt=\"my image\" />"
, testGroup "blocks" ]
[ "definition list with empty <dt>" =: , testGroup "blocks"
definitionList [(mempty, [para $ text "foo bar"])] [ "definition list with empty <dt>" =:
=?> "<dl><dt></dt><dd><p>foo bar</p></dd></dl>" definitionList [(mempty, [para $ text "foo bar"])]
] =?> "<dl><dt></dt><dd><p>foo bar</p></dd></dl>"
, testGroup "quotes" , "heading with disallowed attributes" =:
[ "quote with cite attribute (without q-tags)" =: headerWith ("", [], [("invalid","1"), ("lang", "en")]) 1 "test"
doubleQuoted (spanWith ("", [], [("cite", "http://example.org")]) (str "examples")) =?>
=?> "“<span cite=\"http://example.org\">examples</span>”" "<h1 lang=\"en\">test</h1>"
, tQ "quote with cite attribute (with q-tags)" $ ]
doubleQuoted (spanWith ("", [], [("cite", "http://example.org")]) (str "examples")) , testGroup "quotes"
=?> "<q cite=\"http://example.org\">examples</q>" [ "quote with cite attribute (without q-tags)" =:
] doubleQuoted (spanWith ("", [], [("cite", "http://example.org")]) (str "examples"))
, testGroup "sample" =?> "“<span cite=\"http://example.org\">examples</span>”"
[ "sample should be rendered correctly" =: , tQ "quote with cite attribute (with q-tags)" $
plain (codeWith ("",["sample"],[]) "Answer is 42") =?> doubleQuoted (spanWith ("", [], [("cite", "http://example.org")]) (str "examples"))
"<samp>Answer is 42</samp>" =?> "<q cite=\"http://example.org\">examples</q>"
] ]
, testGroup "variable" , testGroup "sample"
[ "variable should be rendered correctly" =: [ "sample should be rendered correctly" =:
plain (codeWith ("",["variable"],[]) "result") =?> plain (codeWith ("",["sample"],[]) "Answer is 42") =?>
"<var>result</var>" "<samp>Answer is 42</samp>"
] ]
, testGroup "sample with style" , testGroup "variable"
[ "samp should wrap highlighted code" =: [ "variable should be rendered correctly" =:
codeWith ("",["sample","haskell"],[]) ">>=" plain (codeWith ("",["variable"],[]) "result") =?>
=?> ("<samp><code class=\"sourceCode haskell\">" ++ "<var>result</var>"
"<span class=\"op\">&gt;&gt;=</span></code></samp>") ]
] , testGroup "sample with style"
, testGroup "variable with style" [ "samp should wrap highlighted code" =:
[ "var should wrap highlighted code" =: codeWith ("",["sample","haskell"],[]) ">>="
codeWith ("",["haskell","variable"],[]) ">>=" =?> ("<samp><code class=\"sourceCode haskell\">" ++
=?> ("<var><code class=\"sourceCode haskell\">" ++ "<span class=\"op\">&gt;&gt;=</span></code></samp>")
"<span class=\"op\">&gt;&gt;=</span></code></var>") ]
] , testGroup "variable with style"
] [ "var should wrap highlighted code" =:
where codeWith ("",["haskell","variable"],[]) ">>="
tQ :: (ToString a, ToPandoc a) =?> ("<var><code class=\"sourceCode haskell\">" ++
=> String -> (a, String) -> TestTree "<span class=\"op\">&gt;&gt;=</span></code></var>")
tQ = test htmlQTags ]
]
where
tQ :: (ToString a, ToPandoc a)
=> String -> (a, String) -> TestTree
tQ = test htmlQTags