Skip to content

Commit

Permalink
--self-contained: Handle url() in style elements.
Browse files Browse the repository at this point in the history
Previously we handled these in included CSS files but not
in style elements.

Closes #8193.
  • Loading branch information
jgm committed Jul 22, 2022
1 parent e04ea99 commit 4ea51b6
Showing 1 changed file with 8 additions and 0 deletions.
8 changes: 8 additions & 0 deletions src/Text/Pandoc/SelfContained.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TupleSections #-}
{- |
Module : Text.Pandoc.SelfContained
Expand Down Expand Up @@ -62,6 +63,13 @@ convertTags :: PandocMonad m => [Tag T.Text] -> m [Tag T.Text]
convertTags [] = return []
convertTags (t@TagOpen{}:ts)
| fromAttrib "data-external" t == "1" = (t:) <$> convertTags ts
convertTags (t@(TagOpen "style" _):ts) =
case span isTagText ts of
(xs,rest) -> do
xs' <- mapM (\case
TagText s -> TagText . toText <$> cssURLs "" (fromText s)
tag -> return tag) xs
((t:xs') ++) <$> convertTags rest
convertTags (t@(TagOpen "script" as):tc@(TagClose "script"):ts) =
case fromAttrib "src" t of
"" -> (t:) <$> convertTags ts
Expand Down

0 comments on commit 4ea51b6

Please sign in to comment.