Skip to content

Commit

Permalink
Extract EXIF orientation metadata from images
Browse files Browse the repository at this point in the history
  • Loading branch information
silby committed Nov 14, 2024
1 parent bdfe336 commit 7e19347
Showing 1 changed file with 40 additions and 0 deletions.
40 changes: 40 additions & 0 deletions src/Text/Pandoc/ImageSize.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,13 +14,17 @@ Functions for determining the size of a PNG, JPEG, or GIF image.
-}
module Text.Pandoc.ImageSize ( ImageType(..)
, ImageSize(..)
, ImageTransform(..)
, imageType
, imageSize
, imageTransform
, sizeInPixels
, sizeInPoints
, desiredSizeInPoints
, Dimension(..)
, Direction(..)
, Flip(..)
, Rotate(..)
, dimension
, lengthToDim
, scaleDimension
Expand Down Expand Up @@ -52,6 +56,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 Codec.Picture.Metadata.Exif (ExifTag(TagOrientation), ExifData(..))
import Codec.Picture (decodeImageWithMetadata)

-- quick and dirty functions to get image sizes
Expand Down Expand Up @@ -80,6 +85,19 @@ instance Show Dimension where
show (Percent a) = show a ++ "%"
show (Em a) = T.unpack (showFl a) ++ "em"

data Flip = NoFlip | FlipH | FlipV deriving Show

data Rotate = R0 | R90 | R180 | R270 deriving Show

data ImageTransform = ImageTransform
{ tFlip :: Flip,
tRotate :: Rotate
}
deriving (Show)

instance Default ImageTransform where
def = ImageTransform NoFlip R0

data ImageSize = ImageSize{
pxX :: Integer
, pxY :: Integer
Expand Down Expand Up @@ -376,3 +394,25 @@ emfSize img =
case parseheader . BL.fromStrict $ img of
Left _ -> Nothing
Right (_, _, size) -> Just size

imageTransform :: ByteString -> Either T.Text ImageTransform
imageTransform img = do
case decodeImageWithMetadata img of
Left e -> Left (T.pack e)
Right (_, meta) -> do
mbExif <- maybe (Right ExifNone)
Right $ Metadata.lookup (Metadata.Exif TagOrientation) meta
Right (exifToTransform (word mbExif))
where
word ExifNone = 1
word (ExifShort w) = w
word _ = 1
exifToTransform 1 = def
exifToTransform 2 = def{tFlip = FlipH}
exifToTransform 3 = def{tRotate = R180}
exifToTransform 4 = def{tFlip = FlipV}
exifToTransform 5 = def{tFlip = FlipH, tRotate = R270}
exifToTransform 6 = def{tRotate = R90}
exifToTransform 7 = def{tFlip = FlipH, tRotate = R90}
exifToTransform 8 = def{tRotate = R270}
exifToTransform _ = def

0 comments on commit 7e19347

Please sign in to comment.