Skip to content

Commit

Permalink
ImageSize: use exif width and height when available.
Browse files Browse the repository at this point in the history
After the move to JuicyPixels, we were getting incorrect
width and heigh information for some images (see #6936, test-3.jpg).

The correct information was encoded in Exif tags that
JuicyPixels seemed to ignore. So we check these first
before looking at the Width and Height identified by
JuicyPixels.

Closes #6936.
  • Loading branch information
jgm committed Dec 14, 2020
1 parent c43e2dc commit 39153ea
Showing 1 changed file with 13 additions and 0 deletions.
13 changes: 13 additions & 0 deletions src/Text/Pandoc/ImageSize.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,6 +50,7 @@ import qualified Data.Text.Encoding as TE
import Control.Applicative
import qualified Data.Attoparsec.ByteString.Char8 as A
import qualified Codec.Picture.Metadata as Metadata
import qualified Codec.Picture.Metadata.Exif as Exif
import Codec.Picture (decodeImageWithMetadata)

-- quick and dirty functions to get image sizes
Expand Down Expand Up @@ -300,8 +301,16 @@ getSize img =
Left e -> Left (T.pack e)
Right (_, meta) -> do
pxx <- maybe (Left "Could not determine width") Right $
-- first look for exif image width, then width
(Metadata.lookup
(Metadata.Exif (Exif.TagUnknown 0xA002)) meta >>=
exifDataToWord) <|>
Metadata.lookup Metadata.Width meta
pxy <- maybe (Left "Could not determine height") Right $
-- first look for exif image height, then height
(Metadata.lookup
(Metadata.Exif (Exif.TagUnknown 0xA003)) meta >>=
exifDataToWord) <|>
Metadata.lookup Metadata.Height meta
dpix <- maybe (Right 72) Right $ Metadata.lookup Metadata.DpiX meta
dpiy <- maybe (Right 72) Right $ Metadata.lookup Metadata.DpiY meta
Expand All @@ -310,6 +319,10 @@ getSize img =
, pxY = fromIntegral pxy
, dpiX = fromIntegral dpix
, dpiY = fromIntegral dpiy }
where
exifDataToWord (Exif.ExifLong x) = Just $ fromIntegral x
exifDataToWord (Exif.ExifShort x) = Just $ fromIntegral x
exifDataToWord _ = Nothing


svgSize :: WriterOptions -> ByteString -> Maybe ImageSize
Expand Down

0 comments on commit 39153ea

Please sign in to comment.