ODT writer now sizes images appropriately.
OpenDocument writer: a title like "123x467" is interpreted as size in *points*. ODT writer: while adding images to the archive, computes their sizes and inserts a title attribute with the size before calling opendocument writer. Size is computed as follows: size in points = size in pixels * 96 / 72
This commit is contained in:
parent
0d1740ea08
commit
28a043fe44
2 changed files with 10 additions and 3 deletions
|
@ -37,6 +37,7 @@ import Codec.Archive.Zip
|
|||
import System.Time
|
||||
import Paths_pandoc ( getDataFileName )
|
||||
import Text.Pandoc.Shared ( WriterOptions(..) )
|
||||
import Text.Pandoc.ImageSize ( readImageSize )
|
||||
import Text.Pandoc.MIME ( getMimeType )
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Generic
|
||||
|
@ -102,11 +103,17 @@ writeODT mbRefOdt opts doc = do
|
|||
transformPic :: FilePath -> IORef [Entry] -> Inline -> IO Inline
|
||||
transformPic sourceDir entriesRef (Image lab (src,tit)) = do
|
||||
let src' = unEscapeString src
|
||||
mbSize <- readImageSize src'
|
||||
let pxToPoints px = px * 72 `div` 96
|
||||
let tit' = case mbSize of
|
||||
Just (w,h) -> show (pxToPoints w) ++ "x" ++
|
||||
show (pxToPoints h)
|
||||
Nothing -> tit
|
||||
entries <- readIORef entriesRef
|
||||
let newsrc = "Pictures/" ++ show (length entries) ++ takeExtension src'
|
||||
catch (readEntry [] (sourceDir </> src') >>= \entry ->
|
||||
modifyIORef entriesRef (entry{ eRelativePath = newsrc } :) >>
|
||||
return (Image lab (newsrc, tit)))
|
||||
return (Image lab (newsrc, tit')))
|
||||
(\_ -> return (Emph lab))
|
||||
transformPic _ _ x = return x
|
||||
|
||||
|
|
|
@ -404,11 +404,11 @@ inlineToOpenDocument o ils
|
|||
return nn
|
||||
|
||||
-- a title of the form "120x140" will be interpreted as image
|
||||
-- size in pixels.
|
||||
-- size in points.
|
||||
attrsFromTitle :: String -> [(String,String)]
|
||||
attrsFromTitle s = if null xs || null ys
|
||||
then []
|
||||
else [("svg:x",xs),("svg:y",ys)]
|
||||
else [("svg:width",xs ++ "pt"),("svg:height",ys ++ "pt")]
|
||||
where (xs,rest) = span isDigit s
|
||||
ys = case rest of
|
||||
('x':zs) | all isDigit zs -> zs
|
||||
|
|
Loading…
Add table
Reference in a new issue