2015-05-09 22:28:49 -07:00
|
|
|
{-# LANGUAGE OverloadedStrings, ScopedTypeVariables, CPP #-}
|
2015-01-19 12:00:29 +00:00
|
|
|
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
|
2012-01-08 19:16:06 -08:00
|
|
|
{-
|
2017-05-13 23:30:13 +02:00
|
|
|
Copyright (C) 2011-2017 John MacFarlane <jgm@berkeley.edu>
|
2012-01-08 19:16:06 -08:00
|
|
|
|
2012-01-15 15:40:26 -08:00
|
|
|
This program is free software; you can redistribute it and/or modify
|
|
|
|
it under the terms of the GNU General Public License as published by
|
|
|
|
the Free Software Foundation; either version 2 of the License, or
|
|
|
|
(at your option) any later version.
|
2012-01-08 19:16:06 -08:00
|
|
|
|
2012-01-15 15:43:52 -08:00
|
|
|
This program is distributed in the hope that it will be useful, but WITHOUT
|
|
|
|
ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
|
|
|
|
FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for
|
|
|
|
more details.
|
2012-01-08 19:16:06 -08:00
|
|
|
|
2012-01-15 15:43:52 -08:00
|
|
|
You should have received a copy of the GNU General Public License along
|
|
|
|
with this program; if not, write to the Free Software Foundation, Inc., 59
|
|
|
|
Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|
|
|
-}
|
2012-01-08 19:16:06 -08:00
|
|
|
|
|
|
|
{- |
|
2012-01-15 15:40:26 -08:00
|
|
|
Module : Text.Pandoc.ImageSize
|
2017-05-13 23:30:13 +02:00
|
|
|
Copyright : Copyright (C) 2011-2017 John MacFarlane
|
2012-01-15 15:43:52 -08:00
|
|
|
License : GNU GPL, version 2 or above
|
2012-01-08 19:16:06 -08:00
|
|
|
|
2012-01-15 15:43:52 -08:00
|
|
|
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
|
|
|
Stability : alpha
|
|
|
|
Portability : portable
|
2012-01-08 19:16:06 -08:00
|
|
|
|
2012-01-15 15:43:52 -08:00
|
|
|
Functions for determining the size of a PNG, JPEG, or GIF image.
|
|
|
|
-}
|
2015-04-02 21:02:39 -07:00
|
|
|
module Text.Pandoc.ImageSize ( ImageType(..)
|
|
|
|
, imageType
|
|
|
|
, imageSize
|
|
|
|
, sizeInPixels
|
|
|
|
, sizeInPoints
|
|
|
|
, desiredSizeInPoints
|
|
|
|
, Dimension(..)
|
|
|
|
, Direction(..)
|
|
|
|
, dimension
|
2017-02-26 23:40:09 +01:00
|
|
|
, lengthToDim
|
|
|
|
, scaleDimension
|
2015-04-02 21:02:39 -07:00
|
|
|
, inInch
|
2017-02-22 12:17:32 +01:00
|
|
|
, inPixel
|
2015-04-02 21:02:39 -07:00
|
|
|
, inPoints
|
2017-05-25 22:48:27 +02:00
|
|
|
, inEm
|
2015-04-02 21:02:39 -07:00
|
|
|
, numUnit
|
|
|
|
, showInInch
|
|
|
|
, showInPixel
|
|
|
|
, showFl
|
|
|
|
) where
|
2013-01-11 12:11:37 -08:00
|
|
|
import Data.ByteString (ByteString, unpack)
|
|
|
|
import qualified Data.ByteString.Char8 as B
|
2014-01-09 11:16:17 -08:00
|
|
|
import qualified Data.ByteString.Lazy as BL
|
2015-04-02 21:02:39 -07:00
|
|
|
import Data.Char (isDigit)
|
2012-01-08 19:16:06 -08:00
|
|
|
import Control.Monad
|
|
|
|
import Data.Bits
|
2014-01-09 11:16:17 -08:00
|
|
|
import Data.Binary
|
|
|
|
import Data.Binary.Get
|
2016-12-11 22:17:10 +01:00
|
|
|
import Text.Pandoc.Shared (safeRead)
|
2015-04-02 21:02:39 -07:00
|
|
|
import Data.Default (Default)
|
|
|
|
import Numeric (showFFloat)
|
|
|
|
import Text.Pandoc.Definition
|
|
|
|
import Text.Pandoc.Options
|
2017-02-22 12:17:32 +01:00
|
|
|
import qualified Text.Pandoc.UTF8 as UTF8
|
|
|
|
import qualified Text.XML.Light as Xml
|
2014-01-09 11:16:17 -08:00
|
|
|
import qualified Data.Map as M
|
2016-08-31 17:44:07 -04:00
|
|
|
import Control.Monad.Except
|
2015-01-19 12:00:29 +00:00
|
|
|
import Data.Maybe (fromMaybe)
|
2012-01-08 19:16:06 -08:00
|
|
|
|
|
|
|
-- quick and dirty functions to get image sizes
|
|
|
|
-- algorithms borrowed from wwwis.pl
|
|
|
|
|
2017-02-22 12:17:32 +01:00
|
|
|
data ImageType = Png | Gif | Jpeg | Svg | Pdf | Eps deriving Show
|
2015-04-02 21:02:39 -07:00
|
|
|
data Direction = Width | Height
|
|
|
|
instance Show Direction where
|
|
|
|
show Width = "width"
|
|
|
|
show Height = "height"
|
|
|
|
|
|
|
|
data Dimension = Pixel Integer
|
|
|
|
| Centimeter Double
|
2017-10-31 11:58:43 -07:00
|
|
|
| Millimeter Double
|
2015-04-02 21:02:39 -07:00
|
|
|
| Inch Double
|
|
|
|
| Percent Double
|
2017-05-25 22:48:27 +02:00
|
|
|
| Em Double
|
2017-02-26 23:40:09 +01:00
|
|
|
|
2015-04-02 21:02:39 -07:00
|
|
|
instance Show Dimension where
|
|
|
|
show (Pixel a) = show a ++ "px"
|
|
|
|
show (Centimeter a) = showFl a ++ "cm"
|
2017-10-31 11:58:43 -07:00
|
|
|
show (Millimeter a) = showFl a ++ "mm"
|
2015-04-02 21:02:39 -07:00
|
|
|
show (Inch a) = showFl a ++ "in"
|
|
|
|
show (Percent a) = show a ++ "%"
|
2017-05-25 22:48:27 +02:00
|
|
|
show (Em a) = showFl a ++ "em"
|
2012-01-08 19:16:06 -08:00
|
|
|
|
2012-01-15 15:40:26 -08:00
|
|
|
data ImageSize = ImageSize{
|
|
|
|
pxX :: Integer
|
|
|
|
, pxY :: Integer
|
|
|
|
, dpiX :: Integer
|
|
|
|
, dpiY :: Integer
|
|
|
|
} deriving (Read, Show, Eq)
|
2015-04-02 21:02:39 -07:00
|
|
|
instance Default ImageSize where
|
|
|
|
def = ImageSize 300 200 72 72
|
2012-01-08 19:16:06 -08:00
|
|
|
|
2015-04-02 21:02:39 -07:00
|
|
|
showFl :: (RealFloat a) => a -> String
|
2017-05-25 22:48:27 +02:00
|
|
|
showFl a = removeExtra0s $ showFFloat (Just 5) a ""
|
|
|
|
|
|
|
|
removeExtra0s :: String -> String
|
|
|
|
removeExtra0s s =
|
|
|
|
case dropWhile (=='0') $ reverse s of
|
|
|
|
'.':xs -> reverse xs
|
|
|
|
xs -> reverse xs
|
2012-01-15 15:40:26 -08:00
|
|
|
|
2012-01-08 19:16:06 -08:00
|
|
|
imageType :: ByteString -> Maybe ImageType
|
|
|
|
imageType img = case B.take 4 img of
|
|
|
|
"\x89\x50\x4e\x47" -> return Png
|
|
|
|
"\x47\x49\x46\x38" -> return Gif
|
2014-01-08 19:33:14 -08:00
|
|
|
"\xff\xd8\xff\xe0" -> return Jpeg -- JFIF
|
|
|
|
"\xff\xd8\xff\xe1" -> return Jpeg -- Exif
|
2013-02-23 23:03:56 -08:00
|
|
|
"%PDF" -> return Pdf
|
2017-02-22 12:17:32 +01:00
|
|
|
"<svg" -> return Svg
|
|
|
|
"<?xm"
|
2017-04-16 19:39:24 +02:00
|
|
|
| findSvgTag img
|
2017-02-22 12:17:32 +01:00
|
|
|
-> return Svg
|
2013-07-16 22:04:59 -07:00
|
|
|
"%!PS"
|
2017-06-02 15:06:14 +02:00
|
|
|
| B.take 4 (B.drop 1 $ B.dropWhile (/=' ') img) == "EPSF"
|
2013-07-16 22:04:59 -07:00
|
|
|
-> return Eps
|
2015-05-09 21:55:19 -07:00
|
|
|
_ -> mzero
|
2017-04-16 19:39:24 +02:00
|
|
|
|
|
|
|
findSvgTag :: ByteString -> Bool
|
2017-04-20 11:11:01 +02:00
|
|
|
findSvgTag img = "<svg" `B.isInfixOf` img || "<SVG" `B.isInfixOf` img
|
2012-01-08 19:16:06 -08:00
|
|
|
|
2017-02-22 14:38:32 +01:00
|
|
|
imageSize :: WriterOptions -> ByteString -> Either String ImageSize
|
|
|
|
imageSize opts img =
|
2015-05-09 21:32:31 -07:00
|
|
|
case imageType img of
|
|
|
|
Just Png -> mbToEither "could not determine PNG size" $ pngSize img
|
|
|
|
Just Gif -> mbToEither "could not determine GIF size" $ gifSize img
|
2015-05-09 21:55:19 -07:00
|
|
|
Just Jpeg -> jpegSize img
|
2017-02-22 14:38:32 +01:00
|
|
|
Just Svg -> mbToEither "could not determine SVG size" $ svgSize opts img
|
2015-05-09 21:32:31 -07:00
|
|
|
Just Eps -> mbToEither "could not determine EPS size" $ epsSize img
|
|
|
|
Just Pdf -> Left "could not determine PDF size" -- TODO
|
|
|
|
Nothing -> Left "could not determine image type"
|
|
|
|
where mbToEither msg Nothing = Left msg
|
|
|
|
mbToEither _ (Just x) = Right x
|
2012-01-08 19:16:06 -08:00
|
|
|
|
2014-06-20 10:58:26 -07:00
|
|
|
defaultSize :: (Integer, Integer)
|
|
|
|
defaultSize = (72, 72)
|
|
|
|
|
2012-01-15 15:40:26 -08:00
|
|
|
sizeInPixels :: ImageSize -> (Integer, Integer)
|
|
|
|
sizeInPixels s = (pxX s, pxY s)
|
|
|
|
|
2015-04-02 21:02:39 -07:00
|
|
|
-- | Calculate (height, width) in points using the image file's dpi metadata,
|
|
|
|
-- using 72 Points == 1 Inch.
|
|
|
|
sizeInPoints :: ImageSize -> (Double, Double)
|
|
|
|
sizeInPoints s = (pxXf * 72 / dpiXf, pxYf * 72 / dpiYf)
|
|
|
|
where
|
|
|
|
pxXf = fromIntegral $ pxX s
|
|
|
|
pxYf = fromIntegral $ pxY s
|
|
|
|
dpiXf = fromIntegral $ dpiX s
|
|
|
|
dpiYf = fromIntegral $ dpiY s
|
|
|
|
|
|
|
|
-- | Calculate (height, width) in points, considering the desired dimensions in the
|
|
|
|
-- attribute, while falling back on the image file's dpi metadata if no dimensions
|
|
|
|
-- are specified in the attribute (or only dimensions in percentages).
|
|
|
|
desiredSizeInPoints :: WriterOptions -> Attr -> ImageSize -> (Double, Double)
|
|
|
|
desiredSizeInPoints opts attr s =
|
|
|
|
case (getDim Width, getDim Height) of
|
|
|
|
(Just w, Just h) -> (w, h)
|
|
|
|
(Just w, Nothing) -> (w, w / ratio)
|
|
|
|
(Nothing, Just h) -> (h * ratio, h)
|
|
|
|
(Nothing, Nothing) -> sizeInPoints s
|
|
|
|
where
|
|
|
|
ratio = fromIntegral (pxX s) / fromIntegral (pxY s)
|
2017-06-02 15:06:14 +02:00
|
|
|
getDim dir = case dimension dir attr of
|
2015-04-02 21:02:39 -07:00
|
|
|
Just (Percent _) -> Nothing
|
|
|
|
Just dim -> Just $ inPoints opts dim
|
|
|
|
Nothing -> Nothing
|
|
|
|
|
|
|
|
inPoints :: WriterOptions -> Dimension -> Double
|
|
|
|
inPoints opts dim = 72 * inInch opts dim
|
|
|
|
|
2017-05-25 22:48:27 +02:00
|
|
|
inEm :: WriterOptions -> Dimension -> Double
|
|
|
|
inEm opts dim = (64/11) * inInch opts dim
|
|
|
|
|
2015-04-02 21:02:39 -07:00
|
|
|
inInch :: WriterOptions -> Dimension -> Double
|
|
|
|
inInch opts dim =
|
|
|
|
case dim of
|
2017-06-02 15:06:14 +02:00
|
|
|
(Pixel a) -> fromIntegral a / fromIntegral (writerDpi opts)
|
2015-04-02 21:02:39 -07:00
|
|
|
(Centimeter a) -> a * 0.3937007874
|
2017-10-31 11:58:43 -07:00
|
|
|
(Millimeter a) -> a * 0.03937007874
|
2015-04-02 21:02:39 -07:00
|
|
|
(Inch a) -> a
|
|
|
|
(Percent _) -> 0
|
2017-05-25 22:48:27 +02:00
|
|
|
(Em a) -> a * (11/64)
|
2015-04-02 21:02:39 -07:00
|
|
|
|
2017-02-22 12:17:32 +01:00
|
|
|
inPixel :: WriterOptions -> Dimension -> Integer
|
|
|
|
inPixel opts dim =
|
|
|
|
case dim of
|
|
|
|
(Pixel a) -> a
|
|
|
|
(Centimeter a) -> floor $ dpi * a * 0.3937007874 :: Integer
|
2017-10-31 11:58:43 -07:00
|
|
|
(Millimeter a) -> floor $ dpi * a * 0.03937007874 :: Integer
|
2017-02-22 12:17:32 +01:00
|
|
|
(Inch a) -> floor $ dpi * a :: Integer
|
2017-05-25 22:48:27 +02:00
|
|
|
(Percent _) -> 0
|
|
|
|
(Em a) -> floor $ dpi * a * (11/64) :: Integer
|
2017-02-22 12:17:32 +01:00
|
|
|
where
|
|
|
|
dpi = fromIntegral $ writerDpi opts
|
|
|
|
|
2015-04-02 21:02:39 -07:00
|
|
|
-- | Convert a Dimension to a String denoting its equivalent in inches, for example "2.00000".
|
|
|
|
-- Note: Dimensions in percentages are converted to the empty string.
|
|
|
|
showInInch :: WriterOptions -> Dimension -> String
|
|
|
|
showInInch _ (Percent _) = ""
|
|
|
|
showInInch opts dim = showFl $ inInch opts dim
|
|
|
|
|
|
|
|
-- | Convert a Dimension to a String denoting its equivalent in pixels, for example "600".
|
|
|
|
-- Note: Dimensions in percentages are converted to the empty string.
|
|
|
|
showInPixel :: WriterOptions -> Dimension -> String
|
2017-02-22 12:17:32 +01:00
|
|
|
showInPixel _ (Percent _) = ""
|
|
|
|
showInPixel opts dim = show $ inPixel opts dim
|
2015-04-02 21:02:39 -07:00
|
|
|
|
|
|
|
-- | Maybe split a string into a leading number and trailing unit, e.g. "3cm" to Just (3.0, "cm")
|
|
|
|
numUnit :: String -> Maybe (Double, String)
|
|
|
|
numUnit s =
|
|
|
|
let (nums, unit) = span (\c -> isDigit c || ('.'==c)) s
|
2015-11-21 08:46:01 -08:00
|
|
|
in case safeRead nums of
|
2015-04-02 21:02:39 -07:00
|
|
|
Just n -> Just (n, unit)
|
|
|
|
Nothing -> Nothing
|
|
|
|
|
2017-02-26 23:40:09 +01:00
|
|
|
-- | Scale a dimension by a factor.
|
|
|
|
scaleDimension :: Double -> Dimension -> Dimension
|
|
|
|
scaleDimension factor dim =
|
|
|
|
case dim of
|
|
|
|
Pixel x -> Pixel (round $ factor * fromIntegral x)
|
|
|
|
Centimeter x -> Centimeter (factor * x)
|
2017-10-31 11:58:43 -07:00
|
|
|
Millimeter x -> Millimeter (factor * x)
|
2017-02-26 23:40:09 +01:00
|
|
|
Inch x -> Inch (factor * x)
|
|
|
|
Percent x -> Percent (factor * x)
|
2017-05-25 22:48:27 +02:00
|
|
|
Em x -> Em (factor * x)
|
2017-02-26 23:40:09 +01:00
|
|
|
|
2015-04-02 21:02:39 -07:00
|
|
|
-- | Read a Dimension from an Attr attribute.
|
|
|
|
-- `dimension Width attr` might return `Just (Pixel 3)` or for example `Just (Centimeter 2.0)`, etc.
|
|
|
|
dimension :: Direction -> Attr -> Maybe Dimension
|
|
|
|
dimension dir (_, _, kvs) =
|
|
|
|
case dir of
|
|
|
|
Width -> extractDim "width"
|
|
|
|
Height -> extractDim "height"
|
|
|
|
where
|
2017-02-22 12:17:32 +01:00
|
|
|
extractDim key = lookup key kvs >>= lengthToDim
|
|
|
|
|
|
|
|
lengthToDim :: String -> Maybe Dimension
|
|
|
|
lengthToDim s = numUnit s >>= uncurry toDim
|
|
|
|
where
|
2015-04-02 21:02:39 -07:00
|
|
|
toDim a "cm" = Just $ Centimeter a
|
2017-10-31 11:58:43 -07:00
|
|
|
toDim a "mm" = Just $ Millimeter a
|
2015-04-02 21:02:39 -07:00
|
|
|
toDim a "in" = Just $ Inch a
|
|
|
|
toDim a "inch" = Just $ Inch a
|
|
|
|
toDim a "%" = Just $ Percent a
|
|
|
|
toDim a "px" = Just $ Pixel (floor a::Integer)
|
|
|
|
toDim a "" = Just $ Pixel (floor a::Integer)
|
2017-02-22 12:17:32 +01:00
|
|
|
toDim a "pt" = Just $ Inch (a / 72)
|
|
|
|
toDim a "pc" = Just $ Inch (a / 6)
|
2017-05-25 22:48:27 +02:00
|
|
|
toDim a "em" = Just $ Em a
|
2015-04-02 21:02:39 -07:00
|
|
|
toDim _ _ = Nothing
|
2012-01-15 15:40:26 -08:00
|
|
|
|
2013-07-16 22:04:59 -07:00
|
|
|
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
|
2017-06-02 15:06:14 +02:00
|
|
|
[_, _, _, ux, uy] -> do
|
2013-07-16 22:04:59 -07:00
|
|
|
ux' <- safeRead $ B.unpack ux
|
|
|
|
uy' <- safeRead $ B.unpack uy
|
|
|
|
return ImageSize{
|
|
|
|
pxX = ux'
|
|
|
|
, pxY = uy'
|
|
|
|
, dpiX = 72
|
|
|
|
, dpiY = 72 }
|
|
|
|
_ -> mzero
|
|
|
|
|
2012-01-15 15:40:26 -08:00
|
|
|
pngSize :: ByteString -> Maybe ImageSize
|
2012-01-08 19:16:06 -08:00
|
|
|
pngSize img = do
|
|
|
|
let (h, rest) = B.splitAt 8 img
|
|
|
|
guard $ h == "\x8a\x4d\x4e\x47\x0d\x0a\x1a\x0a" ||
|
|
|
|
h == "\x89\x50\x4e\x47\x0d\x0a\x1a\x0a"
|
|
|
|
let (i, rest') = B.splitAt 4 $ B.drop 4 rest
|
|
|
|
guard $ i == "MHDR" || i == "IHDR"
|
2012-01-15 15:40:26 -08:00
|
|
|
let (sizes, rest'') = B.splitAt 8 rest'
|
2017-06-02 15:06:14 +02:00
|
|
|
(x,y) <- case map fromIntegral $unpack sizes of
|
2012-01-15 15:40:26 -08:00
|
|
|
([w1,w2,w3,w4,h1,h2,h3,h4] :: [Integer]) -> return
|
2017-06-02 15:06:14 +02:00
|
|
|
(shift w1 24 + shift w2 16 + shift w3 8 + w4,
|
|
|
|
shift h1 24 + shift h2 16 + shift h3 8 + h4)
|
2016-12-11 22:17:10 +01:00
|
|
|
_ -> Nothing -- "PNG parse error"
|
2012-01-15 15:40:26 -08:00
|
|
|
let (dpix, dpiy) = findpHYs rest''
|
2017-06-02 15:06:14 +02:00
|
|
|
return ImageSize { pxX = x, pxY = y, dpiX = dpix, dpiY = dpiy }
|
2012-01-15 15:40:26 -08:00
|
|
|
|
|
|
|
findpHYs :: ByteString -> (Integer, Integer)
|
2017-06-02 15:06:14 +02:00
|
|
|
findpHYs x
|
|
|
|
| B.null x || "IDAT" `B.isPrefixOf` x = (72,72)
|
|
|
|
| "pHYs" `B.isPrefixOf` x =
|
|
|
|
let [x1,x2,x3,x4,y1,y2,y3,y4,u] =
|
|
|
|
map fromIntegral $ unpack $ B.take 9 $ B.drop 4 x
|
|
|
|
factor = if u == 1 -- dots per meter
|
|
|
|
then \z -> z * 254 `div` 10000
|
|
|
|
else const 72
|
2017-11-01 14:20:03 +03:00
|
|
|
in ( factor $ shift x1 24 + shift x2 16 + shift x3 8 + x4,
|
|
|
|
factor $ shift y1 24 + shift y2 16 + shift y3 8 + y4 )
|
2017-06-02 15:06:14 +02:00
|
|
|
| otherwise = findpHYs $ B.drop 1 x -- read another byte
|
2012-01-15 15:40:26 -08:00
|
|
|
|
|
|
|
gifSize :: ByteString -> Maybe ImageSize
|
2012-01-08 19:16:06 -08:00
|
|
|
gifSize img = do
|
|
|
|
let (h, rest) = B.splitAt 6 img
|
|
|
|
guard $ h == "GIF87a" || h == "GIF89a"
|
|
|
|
case map fromIntegral $ unpack $ B.take 4 rest of
|
2012-01-15 15:40:26 -08:00
|
|
|
[w2,w1,h2,h1] -> return ImageSize {
|
|
|
|
pxX = shift w1 8 + w2,
|
|
|
|
pxY = shift h1 8 + h2,
|
|
|
|
dpiX = 72,
|
|
|
|
dpiY = 72
|
|
|
|
}
|
2016-12-11 22:17:10 +01:00
|
|
|
_ -> Nothing -- "GIF parse error"
|
2012-01-08 19:16:06 -08:00
|
|
|
|
2017-02-22 14:38:32 +01:00
|
|
|
svgSize :: WriterOptions -> ByteString -> Maybe ImageSize
|
|
|
|
svgSize opts img = do
|
2017-02-22 12:17:32 +01:00
|
|
|
doc <- Xml.parseXMLDoc $ UTF8.toString img
|
|
|
|
let dpi = fromIntegral $ writerDpi opts
|
|
|
|
let dirToInt dir = do
|
|
|
|
dim <- Xml.findAttrBy (== Xml.QName dir Nothing Nothing) doc >>= lengthToDim
|
|
|
|
return $ inPixel opts dim
|
|
|
|
w <- dirToInt "width"
|
|
|
|
h <- dirToInt "height"
|
|
|
|
return ImageSize {
|
|
|
|
pxX = w
|
|
|
|
, pxY = h
|
|
|
|
, dpiX = dpi
|
|
|
|
, dpiY = dpi
|
|
|
|
}
|
|
|
|
|
2015-05-09 21:55:19 -07:00
|
|
|
jpegSize :: ByteString -> Either String ImageSize
|
|
|
|
jpegSize img =
|
2012-01-15 15:40:26 -08:00
|
|
|
let (hdr, rest) = B.splitAt 4 img
|
2015-05-09 21:55:19 -07:00
|
|
|
in if B.length rest < 14
|
|
|
|
then Left "unable to determine JPEG size"
|
|
|
|
else case hdr of
|
|
|
|
"\xff\xd8\xff\xe0" -> jfifSize rest
|
2015-05-10 16:52:37 -07:00
|
|
|
"\xff\xd8\xff\xe1" -> exifSize rest
|
2015-05-09 21:55:19 -07:00
|
|
|
_ -> Left "unable to determine JPEG size"
|
|
|
|
|
|
|
|
jfifSize :: ByteString -> Either String ImageSize
|
|
|
|
jfifSize rest =
|
2012-01-15 15:40:26 -08:00
|
|
|
let [dpiDensity,dpix1,dpix2,dpiy1,dpiy2] = map fromIntegral
|
2017-06-02 15:06:14 +02:00
|
|
|
$ unpack $ B.take 5 $B.drop 9 rest
|
2015-05-09 21:55:19 -07:00
|
|
|
factor = case dpiDensity of
|
2012-01-15 15:40:26 -08:00
|
|
|
1 -> id
|
2017-06-02 15:06:14 +02:00
|
|
|
2 -> \x -> x * 254 `div` 10
|
2012-01-15 15:40:26 -08:00
|
|
|
_ -> const 72
|
2015-05-09 21:55:19 -07:00
|
|
|
dpix = factor (shift dpix1 8 + dpix2)
|
|
|
|
dpiy = factor (shift dpiy1 8 + dpiy2)
|
|
|
|
in case findJfifSize rest of
|
|
|
|
Left msg -> Left msg
|
2017-06-02 15:06:14 +02:00
|
|
|
Right (w,h) ->Right ImageSize { pxX = w
|
2015-05-09 21:55:19 -07:00
|
|
|
, pxY = h
|
|
|
|
, dpiX = dpix
|
|
|
|
, dpiY = dpiy }
|
|
|
|
|
|
|
|
findJfifSize :: ByteString -> Either String (Integer,Integer)
|
|
|
|
findJfifSize bs =
|
2012-01-08 19:16:06 -08:00
|
|
|
let bs' = B.dropWhile (=='\xff') $ B.dropWhile (/='\xff') bs
|
2015-05-09 21:55:19 -07:00
|
|
|
in case B.uncons bs' of
|
|
|
|
Just (c,bs'') | c >= '\xc0' && c <= '\xc3' ->
|
2012-01-08 19:16:06 -08:00
|
|
|
case map fromIntegral $ unpack $ B.take 4 $ B.drop 3 bs'' of
|
2015-05-09 21:55:19 -07:00
|
|
|
[h1,h2,w1,w2] -> Right (shift w1 8 + w2, shift h1 8 + h2)
|
|
|
|
_ -> Left "JFIF parse error"
|
|
|
|
Just (_,bs'') ->
|
2012-01-08 19:16:06 -08:00
|
|
|
case map fromIntegral $ unpack $ B.take 2 bs'' of
|
2015-05-09 21:55:19 -07:00
|
|
|
[c1,c2] ->
|
2012-01-08 19:16:06 -08:00
|
|
|
let len = shift c1 8 + c2
|
|
|
|
-- skip variables
|
2015-05-09 21:55:19 -07:00
|
|
|
in findJfifSize $ B.drop len bs''
|
|
|
|
_ -> Left "JFIF parse error"
|
|
|
|
Nothing -> Left "Did not find JFIF length record"
|
2012-01-08 19:16:06 -08:00
|
|
|
|
2015-05-09 22:28:49 -07:00
|
|
|
runGet' :: Get (Either String a) -> BL.ByteString -> Either String a
|
|
|
|
runGet' p bl =
|
|
|
|
#if MIN_VERSION_binary(0,7,0)
|
|
|
|
case runGetOrFail p bl of
|
|
|
|
Left (_,_,msg) -> Left msg
|
|
|
|
Right (_,_,x) -> x
|
|
|
|
#else
|
|
|
|
runGet p bl
|
|
|
|
#endif
|
|
|
|
|
|
|
|
|
2015-05-09 21:55:19 -07:00
|
|
|
exifSize :: ByteString -> Either String ImageSize
|
2017-06-02 15:06:14 +02:00
|
|
|
exifSize bs =runGet' header bl
|
2014-01-24 16:00:02 -08:00
|
|
|
where bl = BL.fromChunks [bs]
|
2015-01-19 12:00:29 +00:00
|
|
|
header = runExceptT $ exifHeader bl
|
2014-01-14 10:12:33 -08:00
|
|
|
-- NOTE: It would be nicer to do
|
|
|
|
-- runGet ((Just <$> exifHeader) <|> return Nothing)
|
|
|
|
-- which would prevent pandoc from raising an error when an exif header can't
|
|
|
|
-- be parsed. But we only get an Alternative instance for Get in binary 0.6,
|
|
|
|
-- and binary 0.5 ships with ghc 7.6.
|
2012-01-08 19:16:06 -08:00
|
|
|
|
2015-01-19 12:00:29 +00:00
|
|
|
exifHeader :: BL.ByteString -> ExceptT String Get ImageSize
|
2014-01-24 16:00:02 -08:00
|
|
|
exifHeader hdr = do
|
2015-01-19 12:00:29 +00:00
|
|
|
_app1DataSize <- lift getWord16be
|
|
|
|
exifHdr <- lift getWord32be
|
|
|
|
unless (exifHdr == 0x45786966) $ throwError "Did not find exif header"
|
|
|
|
zeros <- lift getWord16be
|
|
|
|
unless (zeros == 0) $ throwError "Expected zeros after exif header"
|
2014-01-09 11:16:17 -08:00
|
|
|
-- beginning of tiff header -- we read whole thing to use
|
|
|
|
-- in getting data from offsets:
|
2014-01-24 16:00:02 -08:00
|
|
|
let tiffHeader = BL.drop 8 hdr
|
2015-01-19 12:00:29 +00:00
|
|
|
byteAlign <- lift getWord16be
|
2014-01-09 11:16:17 -08:00
|
|
|
let bigEndian = byteAlign == 0x4d4d
|
|
|
|
let (getWord16, getWord32, getWord64) =
|
|
|
|
if bigEndian
|
|
|
|
then (getWord16be, getWord32be, getWord64be)
|
|
|
|
else (getWord16le, getWord32le, getWord64le)
|
|
|
|
let getRational = do
|
|
|
|
num <- getWord32
|
|
|
|
den <- getWord32
|
|
|
|
return $ fromIntegral num / fromIntegral den
|
2015-01-19 12:00:29 +00:00
|
|
|
tagmark <- lift getWord16
|
|
|
|
unless (tagmark == 0x002a) $ throwError "Failed alignment sanity check"
|
|
|
|
ifdOffset <- lift getWord32
|
|
|
|
lift $ skip (fromIntegral ifdOffset - 8) -- skip to IDF
|
|
|
|
numentries <- lift getWord16
|
|
|
|
let ifdEntry :: ExceptT String Get (TagType, DataFormat)
|
|
|
|
ifdEntry = do
|
|
|
|
tag <- fromMaybe UnknownTagType . flip M.lookup tagTypeTable
|
|
|
|
<$> lift getWord16
|
|
|
|
dataFormat <- lift getWord16
|
|
|
|
numComponents <- lift getWord32
|
2014-01-09 11:16:17 -08:00
|
|
|
(fmt, bytesPerComponent) <-
|
|
|
|
case dataFormat of
|
2015-05-10 16:52:37 -07:00
|
|
|
1 -> return (UnsignedByte <$> getWord8, 1)
|
|
|
|
2 -> return (AsciiString <$>
|
|
|
|
getLazyByteString
|
|
|
|
(fromIntegral numComponents), 1)
|
|
|
|
3 -> return (UnsignedShort <$> getWord16, 2)
|
|
|
|
4 -> return (UnsignedLong <$> getWord32, 4)
|
|
|
|
5 -> return (UnsignedRational <$> getRational, 8)
|
|
|
|
6 -> return (SignedByte <$> getWord8, 1)
|
|
|
|
7 -> return (Undefined <$> getLazyByteString
|
|
|
|
(fromIntegral numComponents), 1)
|
|
|
|
8 -> return (SignedShort <$> getWord16, 2)
|
|
|
|
9 -> return (SignedLong <$> getWord32, 4)
|
|
|
|
10 -> return (SignedRational <$> getRational, 8)
|
|
|
|
11 -> return (SingleFloat <$> getWord32 {- TODO -}, 4)
|
|
|
|
12 -> return (DoubleFloat <$> getWord64 {- TODO -}, 8)
|
2015-01-19 12:00:29 +00:00
|
|
|
_ -> throwError $ "Unknown data format " ++ show dataFormat
|
2014-01-09 11:16:17 -08:00
|
|
|
let totalBytes = fromIntegral $ numComponents * bytesPerComponent
|
2015-05-10 16:52:37 -07:00
|
|
|
payload <- if totalBytes <= 4 -- data is right here
|
|
|
|
then lift $ fmt <* skip (4 - totalBytes)
|
2014-01-09 11:16:17 -08:00
|
|
|
else do -- get data from offset
|
2015-05-10 16:52:37 -07:00
|
|
|
offs <- lift getWord32
|
|
|
|
let bytesAtOffset =
|
|
|
|
BL.take (fromIntegral totalBytes)
|
|
|
|
$ BL.drop (fromIntegral offs) tiffHeader
|
|
|
|
case runGet' (Right <$> fmt) bytesAtOffset of
|
|
|
|
Left msg -> throwError msg
|
|
|
|
Right x -> return x
|
2014-01-09 11:16:17 -08:00
|
|
|
return (tag, payload)
|
2017-06-02 15:06:14 +02:00
|
|
|
entries <- replicateM (fromIntegral numentries) ifdEntry
|
2014-01-09 11:16:17 -08:00
|
|
|
subentries <- case lookup ExifOffset entries of
|
2015-04-02 21:02:39 -07:00
|
|
|
Just (UnsignedLong offset') -> do
|
2015-01-19 12:00:29 +00:00
|
|
|
pos <- lift bytesRead
|
2015-04-02 21:02:39 -07:00
|
|
|
lift $ skip (fromIntegral offset' - (fromIntegral pos - 8))
|
2015-01-19 12:00:29 +00:00
|
|
|
numsubentries <- lift getWord16
|
2017-06-02 15:06:14 +02:00
|
|
|
replicateM (fromIntegral numsubentries) ifdEntry
|
2014-01-09 11:16:17 -08:00
|
|
|
_ -> return []
|
|
|
|
let allentries = entries ++ subentries
|
2015-04-02 21:02:39 -07:00
|
|
|
(wdth, hght) <- case (lookup ExifImageWidth allentries,
|
|
|
|
lookup ExifImageHeight allentries) of
|
|
|
|
(Just (UnsignedLong w), Just (UnsignedLong h)) ->
|
|
|
|
return (fromIntegral w, fromIntegral h)
|
|
|
|
_ -> return defaultSize
|
|
|
|
-- we return a default width and height when
|
|
|
|
-- the exif header doesn't contain these
|
2014-01-09 11:16:17 -08:00
|
|
|
let resfactor = case lookup ResolutionUnit allentries of
|
2017-06-02 15:06:14 +02:00
|
|
|
Just (UnsignedShort 1) -> 100 / 254
|
2014-01-09 11:16:17 -08:00
|
|
|
_ -> 1
|
|
|
|
let xres = maybe 72 (\(UnsignedRational x) -> floor $ x * resfactor)
|
|
|
|
$ lookup XResolution allentries
|
|
|
|
let yres = maybe 72 (\(UnsignedRational x) -> floor $ x * resfactor)
|
|
|
|
$ lookup YResolution allentries
|
2017-06-02 15:06:14 +02:00
|
|
|
return ImageSize{
|
2015-04-02 21:02:39 -07:00
|
|
|
pxX = wdth
|
|
|
|
, pxY = hght
|
2014-01-09 11:16:17 -08:00
|
|
|
, dpiX = xres
|
|
|
|
, dpiY = yres }
|
|
|
|
|
|
|
|
data DataFormat = UnsignedByte Word8
|
|
|
|
| AsciiString BL.ByteString
|
|
|
|
| UnsignedShort Word16
|
|
|
|
| UnsignedLong Word32
|
|
|
|
| UnsignedRational Rational
|
|
|
|
| SignedByte Word8
|
2015-05-10 16:52:37 -07:00
|
|
|
| Undefined BL.ByteString
|
2014-01-09 11:16:17 -08:00
|
|
|
| SignedShort Word16
|
|
|
|
| SignedLong Word32
|
|
|
|
| SignedRational Rational
|
|
|
|
| SingleFloat Word32
|
|
|
|
| DoubleFloat Word64
|
|
|
|
deriving (Show)
|
|
|
|
|
|
|
|
data TagType = ImageDescription
|
|
|
|
| Make
|
|
|
|
| Model
|
|
|
|
| Orientation
|
|
|
|
| XResolution
|
|
|
|
| YResolution
|
|
|
|
| ResolutionUnit
|
|
|
|
| Software
|
|
|
|
| DateTime
|
|
|
|
| WhitePoint
|
|
|
|
| PrimaryChromaticities
|
|
|
|
| YCbCrCoefficients
|
|
|
|
| YCbCrPositioning
|
|
|
|
| ReferenceBlackWhite
|
|
|
|
| Copyright
|
|
|
|
| ExifOffset
|
|
|
|
| ExposureTime
|
|
|
|
| FNumber
|
|
|
|
| ExposureProgram
|
|
|
|
| ISOSpeedRatings
|
|
|
|
| ExifVersion
|
|
|
|
| DateTimeOriginal
|
|
|
|
| DateTimeDigitized
|
|
|
|
| ComponentConfiguration
|
|
|
|
| CompressedBitsPerPixel
|
|
|
|
| ShutterSpeedValue
|
|
|
|
| ApertureValue
|
|
|
|
| BrightnessValue
|
|
|
|
| ExposureBiasValue
|
|
|
|
| MaxApertureValue
|
|
|
|
| SubjectDistance
|
|
|
|
| MeteringMode
|
|
|
|
| LightSource
|
|
|
|
| Flash
|
|
|
|
| FocalLength
|
|
|
|
| MakerNote
|
|
|
|
| UserComment
|
|
|
|
| FlashPixVersion
|
|
|
|
| ColorSpace
|
|
|
|
| ExifImageWidth
|
|
|
|
| ExifImageHeight
|
|
|
|
| RelatedSoundFile
|
|
|
|
| ExifInteroperabilityOffset
|
|
|
|
| FocalPlaneXResolution
|
|
|
|
| FocalPlaneYResolution
|
|
|
|
| FocalPlaneResolutionUnit
|
|
|
|
| SensingMethod
|
|
|
|
| FileSource
|
|
|
|
| SceneType
|
2014-06-19 14:30:03 -07:00
|
|
|
| UnknownTagType
|
2014-01-09 11:16:17 -08:00
|
|
|
deriving (Show, Eq, Ord)
|
|
|
|
|
|
|
|
tagTypeTable :: M.Map Word16 TagType
|
|
|
|
tagTypeTable = M.fromList
|
|
|
|
[ (0x010e, ImageDescription)
|
|
|
|
, (0x010f, Make)
|
|
|
|
, (0x0110, Model)
|
|
|
|
, (0x0112, Orientation)
|
|
|
|
, (0x011a, XResolution)
|
|
|
|
, (0x011b, YResolution)
|
|
|
|
, (0x0128, ResolutionUnit)
|
|
|
|
, (0x0131, Software)
|
|
|
|
, (0x0132, DateTime)
|
|
|
|
, (0x013e, WhitePoint)
|
|
|
|
, (0x013f, PrimaryChromaticities)
|
|
|
|
, (0x0211, YCbCrCoefficients)
|
|
|
|
, (0x0213, YCbCrPositioning)
|
|
|
|
, (0x0214, ReferenceBlackWhite)
|
|
|
|
, (0x8298, Copyright)
|
|
|
|
, (0x8769, ExifOffset)
|
|
|
|
, (0x829a, ExposureTime)
|
|
|
|
, (0x829d, FNumber)
|
|
|
|
, (0x8822, ExposureProgram)
|
|
|
|
, (0x8827, ISOSpeedRatings)
|
|
|
|
, (0x9000, ExifVersion)
|
|
|
|
, (0x9003, DateTimeOriginal)
|
|
|
|
, (0x9004, DateTimeDigitized)
|
|
|
|
, (0x9101, ComponentConfiguration)
|
|
|
|
, (0x9102, CompressedBitsPerPixel)
|
|
|
|
, (0x9201, ShutterSpeedValue)
|
|
|
|
, (0x9202, ApertureValue)
|
|
|
|
, (0x9203, BrightnessValue)
|
|
|
|
, (0x9204, ExposureBiasValue)
|
|
|
|
, (0x9205, MaxApertureValue)
|
|
|
|
, (0x9206, SubjectDistance)
|
|
|
|
, (0x9207, MeteringMode)
|
|
|
|
, (0x9208, LightSource)
|
|
|
|
, (0x9209, Flash)
|
|
|
|
, (0x920a, FocalLength)
|
|
|
|
, (0x927c, MakerNote)
|
|
|
|
, (0x9286, UserComment)
|
|
|
|
, (0xa000, FlashPixVersion)
|
|
|
|
, (0xa001, ColorSpace)
|
|
|
|
, (0xa002, ExifImageWidth)
|
|
|
|
, (0xa003, ExifImageHeight)
|
|
|
|
, (0xa004, RelatedSoundFile)
|
|
|
|
, (0xa005, ExifInteroperabilityOffset)
|
|
|
|
, (0xa20e, FocalPlaneXResolution)
|
|
|
|
, (0xa20f, FocalPlaneYResolution)
|
|
|
|
, (0xa210, FocalPlaneResolutionUnit)
|
|
|
|
, (0xa217, SensingMethod)
|
|
|
|
, (0xa300, FileSource)
|
|
|
|
, (0xa301, SceneType)
|
|
|
|
]
|