Improve pdfSize in ImageSize.

Improves fix to #4322.
This commit is contained in:
John MacFarlane 2019-03-20 12:22:17 -07:00
parent 6be8f4e953
commit 957314143f
2 changed files with 27 additions and 21 deletions

View file

@ -404,7 +404,8 @@ library
case-insensitive >= 1.2 && < 1.3,
unicode-transforms >= 0.3 && < 0.4,
HsYAML >= 0.1.1.1 && < 0.2,
ipynb >= 0.1 && < 0.2
ipynb >= 0.1 && < 0.2,
attoparsec >= 0.12 && < 0.14
if impl(ghc < 8.0)
build-depends: semigroups == 0.18.*,
-- basement 0.0.8 and foundation 0.0.21, transitive

View file

@ -50,7 +50,9 @@ import qualified Text.Pandoc.UTF8 as UTF8
import qualified Text.XML.Light as Xml
import qualified Data.Map as M
import Control.Monad.Except
import Control.Applicative
import Data.Maybe (fromMaybe)
import qualified Data.Attoparsec.ByteString.Char8 as A
-- quick and dirty functions to get image sizes
-- algorithms borrowed from wwwis.pl
@ -267,26 +269,29 @@ epsSize img = do
pdfSize :: ByteString -> Maybe ImageSize
pdfSize img =
case dropWhile (\l -> not (l == "stream" ||
"/MediaBox" `B.isPrefixOf` l)) (B.lines img) of
(x:_)
| "/MediaBox" `B.isPrefixOf` x
-> case B.words . B.takeWhile (/=']')
. B.drop 1
. B.dropWhile (/='[')
$ x of
[x1, y1, x2, y2] -> do
x1' <- safeRead $ B.unpack x1
x2' <- safeRead $ B.unpack x2
y1' <- safeRead $ B.unpack y1
y2' <- safeRead $ B.unpack y2
return ImageSize{
pxX = x2' - x1'
, pxY = y2' - y1'
, dpiX = 72
, dpiY = 72 }
_ -> mzero
_ -> mzero
case A.parseOnly pPdfSize img of
Left _ -> Nothing
Right sz -> Just sz
pPdfSize :: A.Parser ImageSize
pPdfSize = do
A.skipWhile (/='/')
A.char8 '/'
(do A.string "MediaBox"
A.char8 '['
[x1,y1,x2,y2] <- A.count 4 $ do
A.skipWhile (==' ')
raw <- A.many1 $ A.satisfy (\c -> isDigit c || c == '.')
case safeRead raw of
Just (r :: Double) -> return $ floor r
Nothing -> mzero
A.char8 ']'
return $ ImageSize{
pxX = x2 - x1
, pxY = y2 - y1
, dpiX = 72
, dpiY = 72 }
) <|> pPdfSize
pngSize :: ByteString -> Maybe ImageSize
pngSize img = do