aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2013-07-16 22:04:59 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2013-07-16 22:04:59 -0700
commitb2385d0e9bf13f2fc152a3983893c47f2ab5d4c0 (patch)
tree5db30348228092c2244913832900adc8e4f0fba0 /src
parent94c9825468692a343af7ef1686b1c92e1ec71adf (diff)
downloadpandoc-b2385d0e9bf13f2fc152a3983893c47f2ab5d4c0.tar.gz
Text.Pandoc.ImageSize: Handle EPS.
Closes #903. This change will make EPS images properly sized on conversion to Word.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/ImageSize.hs24
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs1
2 files changed, 24 insertions, 1 deletions
diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs
index 273a1a428..9b0850efb 100644
--- a/src/Text/Pandoc/ImageSize.hs
+++ b/src/Text/Pandoc/ImageSize.hs
@@ -34,11 +34,12 @@ import Data.ByteString (ByteString, unpack)
import qualified Data.ByteString.Char8 as B
import Control.Monad
import Data.Bits
+import Text.Pandoc.Shared (safeRead)
-- quick and dirty functions to get image sizes
-- algorithms borrowed from wwwis.pl
-data ImageType = Png | Gif | Jpeg | Pdf deriving Show
+data ImageType = Png | Gif | Jpeg | Pdf | Eps deriving Show
data ImageSize = ImageSize{
pxX :: Integer
@@ -54,6 +55,9 @@ imageType img = case B.take 4 img of
"\x47\x49\x46\x38" -> return Gif
"\xff\xd8\xff\xe0" -> return Jpeg
"%PDF" -> return Pdf
+ "%!PS"
+ | (B.take 4 $ B.drop 1 $ B.dropWhile (/=' ') img) == "EPSF"
+ -> return Eps
_ -> fail "Unknown image type"
imageSize :: ByteString -> Maybe ImageSize
@@ -63,6 +67,7 @@ imageSize img = do
Png -> pngSize img
Gif -> gifSize img
Jpeg -> jpegSize img
+ Eps -> epsSize img
Pdf -> Nothing -- TODO
sizeInPixels :: ImageSize -> (Integer, Integer)
@@ -71,6 +76,23 @@ sizeInPixels s = (pxX s, pxY s)
sizeInPoints :: ImageSize -> (Integer, Integer)
sizeInPoints s = (pxX s * 72 `div` dpiX s, pxY s * 72 `div` dpiY s)
+epsSize :: ByteString -> Maybe ImageSize
+epsSize img = do
+ let ls = takeWhile ("%" `B.isPrefixOf`) $ B.lines img
+ let ls' = dropWhile (not . ("%%BoundingBox:" `B.isPrefixOf`)) ls
+ case ls' of
+ [] -> mzero
+ (x:_) -> case B.words x of
+ (_:_:_:ux:uy:[]) -> do
+ ux' <- safeRead $ B.unpack ux
+ uy' <- safeRead $ B.unpack uy
+ return ImageSize{
+ pxX = ux'
+ , pxY = uy'
+ , dpiX = 72
+ , dpiY = 72 }
+ _ -> mzero
+
pngSize :: ByteString -> Maybe ImageSize
pngSize img = do
let (h, rest) = B.splitAt 8 img
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index d579d4fa6..1ed8c2fa5 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -776,6 +776,7 @@ inlineToOpenXML opts (Image alt (src, tit)) = do
Just Jpeg -> ".jpeg"
Just Gif -> ".gif"
Just Pdf -> ".pdf"
+ Just Eps -> ".eps"
Nothing -> takeExtension src
if null imgext
then -- without an extension there is no rule for content type