Skip to content

Commit 0f45ea1

Browse files
committed
fix(docx): use proper DPI when creating fallback images
Introduce getOrCreateFallback, and pass the desired size in points to rsvg-convert. Otherwise it'll guess the size based on the SVG's viewbox and completely ignore the DPI argument. Signed-off-by: Edwin Török <[email protected]>
1 parent 682f972 commit 0f45ea1

File tree

3 files changed

+43
-33
lines changed

3 files changed

+43
-33
lines changed

src/Text/Pandoc/App.hs

Lines changed: 2 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ module Text.Pandoc.App (
2828
, applyFilters
2929
) where
3030
import qualified Control.Exception as E
31-
import Control.Monad ( (>=>), when, forM, forM_ )
31+
import Control.Monad ( (>=>), when, forM )
3232
import Control.Monad.Trans ( MonadIO(..) )
3333
import Control.Monad.Catch ( MonadMask )
3434
import Control.Monad.Except (throwError)
@@ -49,7 +49,6 @@ import System.IO (nativeNewline, stdout)
4949
import qualified System.IO as IO (Newline (..))
5050
import Text.Pandoc
5151
import Text.Pandoc.Builder (setMeta)
52-
import Text.Pandoc.MediaBag (mediaItems)
5352
import Text.Pandoc.App.Opt (Opt (..), LineEnding (..), defaultOpts,
5453
IpynbOutput (..), OptInfo(..))
5554
import Text.Pandoc.App.CommandLineOptions (parseOptions, parseOptionsFromArgs,
@@ -64,7 +63,7 @@ import Text.Pandoc.PDF (makePDF)
6463
import Text.Pandoc.Scripting (ScriptingEngine (..), CustomComponents(..))
6564
import Text.Pandoc.SelfContained (makeSelfContained)
6665
import Text.Pandoc.Shared (eastAsianLineBreakFilter,
67-
headerShift, filterIpynbOutput, tshow)
66+
headerShift, filterIpynbOutput)
6867
import Text.Pandoc.URI (isURI)
6968
import Text.Pandoc.Writers.Shared (lookupMetaString)
7069
import Text.Pandoc.Readers.Markdown (yamlToMeta)
@@ -306,9 +305,6 @@ convertWithOpts' scriptingEngine istty datadir opts = do
306305
>=> maybe return extractMedia (optExtractMedia opts)
307306
)
308307

309-
when (format == "docx" && not (optSandbox opts)) $ do
310-
createPngFallbacks (writerDpi writerOptions)
311-
312308
output <- case writer of
313309
ByteStringWriter f
314310
| format == "chunkedhtml" -> ZipOutput <$> f writerOptions doc
@@ -371,21 +367,6 @@ readAbbreviations mbfilepath =
371367
>>= fmap (Set.fromList . filter (not . T.null) . T.lines) .
372368
toTextM (fromMaybe mempty mbfilepath)
373369

374-
createPngFallbacks :: (PandocMonad m) => Int -> m ()
375-
createPngFallbacks dpi = do
376-
-- create fallback pngs for svgs
377-
items <- mediaItems <$> getMediaBag
378-
forM_ items $ \(fp, mt, bs) ->
379-
case T.takeWhile (/=';') mt of
380-
"image/svg+xml" -> do
381-
res <- svgToPng (dpi, Nothing, Nothing, bs)
382-
case res of
383-
Right bs' -> do
384-
let fp' = fp <> ".png"
385-
insertMedia fp' (Just "image/png") bs'
386-
Left e -> report $ CouldNotConvertImage (T.pack fp) (tshow e)
387-
_ -> return ()
388-
389370
getMetadataFromFiles :: PandocMonad m
390371
=> Text -> ReaderOptions -> [FilePath] -> m Meta
391372
getMetadataFromFiles readerFormat readerOpts = \case

src/Text/Pandoc/Image.hs

Lines changed: 17 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ Portability : portable
1010
1111
Functions for converting images.
1212
-}
13-
module Text.Pandoc.Image ( svgToPngIO ) where
13+
module Text.Pandoc.Image ( createPngFallback, svgToPngIO ) where
1414
import Text.Pandoc.Process (pipeProcess)
1515
import qualified Data.ByteString.Lazy as L
1616
import System.Exit
@@ -20,6 +20,9 @@ import qualified Control.Exception as E
2020
import Control.Monad.IO.Class (MonadIO(liftIO))
2121
import Text.Pandoc.Class.PandocMonad
2222
import qualified Data.Text as T
23+
import Text.Pandoc.Logging (LogMessage(CouldNotConvertImage))
24+
import Data.ByteString.Lazy (ByteString)
25+
import Text.Pandoc.MediaBag (MediaItem, lookupMedia)
2326
import Text.Printf (printf)
2427

2528
-- | Convert svg image to png. rsvg-convert
@@ -44,4 +47,16 @@ svgToPngIO dpi widthPt heightPt bs = do
4447
else Left "conversion from SVG failed")
4548
(\(e :: E.SomeException) -> return $ Left $
4649
"check that rsvg-convert is in path.\n" <> tshow e)
47-
where pt name = maybe [] $ \points -> ["--" <> name, printf "%.6fpt" points]
50+
where pt name = maybe [] $ \points -> ["--" <> name, printf "%.6fpt" points]
51+
52+
createPngFallback :: (PandocMonad m) => Int -> (Double, Double) -> FilePath -> ByteString -> m (Maybe MediaItem)
53+
createPngFallback dpi (xPt, yPt) fp bs = do
54+
-- create fallback pngs for svgs
55+
res <- svgToPng (dpi, Just xPt, Just yPt, bs)
56+
case res of
57+
Right bs' -> do
58+
insertMedia fp (Just "image/png") bs'
59+
lookupMedia fp <$> getMediaBag
60+
Left e -> do
61+
report $ CouldNotConvertImage (T.pack fp) (tshow e)
62+
return Nothing

src/Text/Pandoc/Writers/Docx.hs

Lines changed: 24 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -77,6 +77,9 @@ import Text.Pandoc.Writers.OOXML
7777
import Text.Pandoc.XML.Light as XML
7878
import Data.Generics (mkT, everywhere)
7979
import Text.Collate.Lang (renderLang, Lang(..))
80+
import Text.Pandoc.Image (createPngFallback)
81+
import Data.ByteString (ByteString)
82+
import Text.Printf (printf)
8083

8184
-- from wml.xsd EG_RPrBase
8285
rPrTagOrder :: M.Map Text Int
@@ -1321,6 +1324,15 @@ formattedRun els = do
13211324
props <- getTextProps
13221325
return [ mknode "w:r" [] $ props ++ els ]
13231326

1327+
getOrCreateFallback :: PandocMonad m => Int -> (Integer, Integer) -> FilePath -> ByteString -> m (Maybe MediaItem)
1328+
getOrCreateFallback dpi (xemu, yemu) src' img = do
1329+
mediabag <- getMediaBag
1330+
let src = printf "%s_%d_%d.png" src' xemu yemu
1331+
let xyPt = (fromIntegral xemu / 12700.0, fromIntegral yemu / 12700.0)
1332+
case lookupMedia src mediabag of
1333+
Just item -> return $ Just item
1334+
Nothing -> createPngFallback dpi xyPt src $ BL.fromStrict img
1335+
13241336
-- | Convert an inline element to OpenXML.
13251337
inlineToOpenXML :: PandocMonad m => WriterOptions -> Inline -> WS m [Content]
13261338
inlineToOpenXML opts il = withDirection $ inlineToOpenXML' opts il
@@ -1522,17 +1534,26 @@ inlineToOpenXML' opts (Image attr@(imgident, _, _) alt (src, title)) = do
15221534
imgs <- gets stImages
15231535
let
15241536
stImage = M.lookup (T.unpack src) imgs
1525-
generateImgElt (ident, _fp, mt, img) = do
1537+
generateImgElt (ident, fp, mt, img) = do
15261538
docprid <- getUniqueId
15271539
nvpicprid <- getUniqueId
1540+
let
1541+
(xpt,ypt) = desiredSizeInPoints opts attr
1542+
(either (const def) id (imageSize opts img))
1543+
-- 12700 emu = 1 pt
1544+
pageWidthPt = case dimension Width attr of
1545+
Just (Percent a) -> pageWidth * floor (a * 127)
1546+
_ -> pageWidth * 12700
1547+
(xemu,yemu) = fitToPage (xpt * 12700, ypt * 12700) pageWidthPt
15281548
(blipAttrs, blipContents) <-
15291549
case T.takeWhile (/=';') <$> mt of
15301550
Just "image/svg+xml" -> do
15311551
-- get fallback png
1532-
mediabag <- getMediaBag
1552+
fallback <- getOrCreateFallback (writerDpi opts) (xemu, yemu) fp img
15331553
mbFallback <-
1534-
case lookupMedia (T.unpack (src <> ".png")) mediabag of
1554+
case fallback of
15351555
Just item -> do
1556+
P.trace $ "Found fallback " <> tshow (mediaPath item)
15361557
id' <- T.unpack . ("rId" <>) <$> getUniqueId
15371558
let fp' = "media/" <> id' <> ".png"
15381559
let imgdata = (id',
@@ -1559,13 +1580,6 @@ inlineToOpenXML' opts (Image attr@(imgident, _, _) alt (src, title)) = do
15591580
[extLst])
15601581
_ -> return ([("r:embed", T.pack ident)], [])
15611582
let
1562-
(xpt,ypt) = desiredSizeInPoints opts attr
1563-
(either (const def) id (imageSize opts img))
1564-
-- 12700 emu = 1 pt
1565-
pageWidthPt = case dimension Width attr of
1566-
Just (Percent a) -> pageWidth * floor (a * 127)
1567-
_ -> pageWidth * 12700
1568-
(xemu,yemu) = fitToPage (xpt * 12700, ypt * 12700) pageWidthPt
15691583
cNvPicPr = mknode "pic:cNvPicPr" [] $
15701584
mknode "a:picLocks" [("noChangeArrowheads","1")
15711585
,("noChangeAspect","1")] ()

0 commit comments

Comments
 (0)