From 0a3cc0be4563514c05a929844f729b46be508c5c Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Tue, 3 Sep 2019 17:26:12 -0700 Subject: SelfContained: omit content-type on type attribute for `<style>`. It doesn't seem to be valid for HTML5, and as a result Chrome ignores the style element. Closes #5725. --- src/Text/Pandoc/SelfContained.hs | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs index d3851cc0e..f3fca9c07 100644 --- a/src/Text/Pandoc/SelfContained.hs +++ b/src/Text/Pandoc/SelfContained.hs @@ -1,5 +1,6 @@ {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TupleSections #-} {- | Module : Text.Pandoc.SelfContained Copyright : Copyright (C) 2011-2019 John MacFarlane @@ -112,7 +113,7 @@ convertTags (t@(TagOpen "link" as):ts) = rest <- convertTags $ dropWhile (==TagClose "link") ts return $ - TagOpen "style" [("type", mime)] + TagOpen "style" [("type", "text/css")] -- see #5725 : TagText (toString bs) : TagClose "style" : rest @@ -210,12 +211,14 @@ handleCSSUrl d (url, fallback) = res <- lift $ getData "" url' case res of Left uri -> return $ Left (B.pack $ "url(" ++ uri ++ ")") - Right (mt, raw) -> do + Right (mt', raw) -> do -- note that the downloaded CSS may -- itself contain url(...). - b <- if "text/css" `isPrefixOf` mt - then cssURLs d raw - else return raw + (mt, b) <- if "text/css" `isPrefixOf` mt' + -- see #5725: in HTML5, content type + -- isn't allowed on style type attribute + then ("text/css",) <$> cssURLs d raw + else return (mt', raw) return $ Right (mt, b) getDataURI :: PandocMonad m => MimeType -> String -> m String -- cgit v1.2.3