aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2023-07-25 23:24:43 -0600
committerJohn MacFarlane <[email protected]>2023-07-25 23:24:43 -0600
commit704a07d9639e65d9efd4b9d49b3685b0e4206601 (patch)
tree70824f7b558e0b2ca3d911ab79f34cd800d40ad1 /src
parent77e01242da8ab64af52a75459d42dc230282647a (diff)
SelfContained: Improve inline SVGs.
- Ensure that width and height attributes don't get specified twice is both the img tag and the svg include them. - Omit unnecessary attributes xmlns, xmlns:xlink, and version on svg element. - Use 20 character rather than 40 character hashes for generated IDs. Closes #8965.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/SelfContained.hs29
1 files changed, 21 insertions, 8 deletions
diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs
index bfbfc6f6f..428a18f0f 100644
--- a/src/Text/Pandoc/SelfContained.hs
+++ b/src/Text/Pandoc/SelfContained.hs
@@ -23,7 +23,7 @@ import Data.ByteString.Base64 (encodeBase64)
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy as L
import qualified Data.Text as T
-import Data.Char (isAlphaNum, isAscii)
+import Data.Char (isAlphaNum, isAscii, isDigit)
import Data.Digest.Pure.SHA (sha1, showDigest)
import Network.URI (escapeURIString)
import System.FilePath (takeDirectory, takeExtension, (</>))
@@ -189,9 +189,9 @@ convertTags (t@(TagOpen tagname as):ts)
Fetched ("image/svg+xml", bs) -> do
-- we filter CR in the hash to ensure that Windows
-- and non-Windows tests agree:
- let hash = T.pack (showDigest
- (sha1 (L.fromStrict
- (B.filter (/='\r') bs))))
+ let hash = T.pack $ take 20 $ showDigest $
+ sha1 $ L.fromStrict
+ $ B.filter (/='\r') bs
return $ Left (hash, getSvgTags (toText bs))
Fetched (mt,bs) -> return $ Right (x, makeDataURI (mt,bs))
CouldNotFetch _ -> return $ Right (x, y)
@@ -214,13 +214,26 @@ combineSvgAttrs svgAttrs imgAttrs =
(Nothing, Just h, Just w) -> -- calculate viewBox
combinedAttrs ++ [("viewBox", T.unwords ["0", "0", tshow w, tshow h])]
(Just (llx,lly,urx,ury), Nothing, Nothing) -> -- calculate width, height
- combinedAttrs ++
- [ ("width", tshow (floor urx - floor llx :: Int))
- , ("height", tshow (floor ury - floor lly :: Int)) ]
+ combinedAttrs ++
+ [ ("width", tshow (floor urx - floor llx :: Int)) |
+ isNothing (lookup "width" combinedAttrs) ] ++
+ [ ("height", tshow (floor ury - floor lly :: Int)) |
+ isNothing (lookup "height" combinedAttrs) ]
_ -> combinedAttrs
where
combinedAttrs = imgAttrs ++
- [(k,v) | (k,v) <- svgAttrs, isNothing (lookup k imgAttrs)]
+ [(k,v') | (k,v) <- svgAttrs
+ , v' <- fixAttr k v
+ , isNothing (lookup k imgAttrs)
+ , k `notElem` ["xmlns", "xmlns:xlink", "version"]]
+ fixAttr k v =
+ if k == "width" || k == "height"
+ then if T.all isDigit v
+ then [v]
+ else case T.stripSuffix "px" v of
+ Just v' | T.all isDigit v' -> [v']
+ _ -> []
+ else [v]
parseViewBox t =
case map (safeRead . addZero) $ T.words t of
[Just llx, Just lly, Just urx, Just ury] -> Just (llx, lly, urx, ury)