{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
-- |
-- Module      : Data.Massiv.Array.IO.Image.JuicyPixels.JPG
-- Copyright   : (c) Alexey Kuleshevich 2019-2020
-- License     : BSD3
-- Maintainer  : Alexey Kuleshevich <lehins@yandex.ru>
-- Stability   : experimental
-- Portability : non-portable
--
module Data.Massiv.Array.IO.Image.JuicyPixels.JPG
  ( JPG(..)
  , JpegOptions(..)
  , decodeJPG
  , decodeWithMetadataJPG
  , decodeAutoJPG
  , decodeAutoWithMetadataJPG
  , encodeJPG
  , encodeAutoJPG
  ) where

import qualified Codec.Picture as JP
import qualified Codec.Picture.Jpg as JP
import qualified Codec.Picture.Metadata as JP
import Control.Monad (msum)
import Data.Bifunctor (first)
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL (ByteString)
import Data.Massiv.Array as A
import Data.Massiv.Array.IO.Base
import Data.Massiv.Array.IO.Image.JuicyPixels.Base
import Data.Maybe (fromMaybe)
import Data.Typeable
import qualified Graphics.Pixel as CM
import Graphics.Pixel.ColorSpace
import Prelude as P

--------------------------------------------------------------------------------
-- JPG Format ------------------------------------------------------------------
--------------------------------------------------------------------------------

-- TODOs: Check if JP is capable of writing Jpegs with PixelYA8 (No instance for
-- JpegEncodable, but it can read 'em)

data JpegOptions = JpegOptions
  { JpegOptions -> Word8
jpegQuality  :: !Word8
  , JpegOptions -> Metadatas
jpegMetadata :: !JP.Metadatas
  } deriving (Int -> JpegOptions -> ShowS
[JpegOptions] -> ShowS
JpegOptions -> String
(Int -> JpegOptions -> ShowS)
-> (JpegOptions -> String)
-> ([JpegOptions] -> ShowS)
-> Show JpegOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JpegOptions] -> ShowS
$cshowList :: [JpegOptions] -> ShowS
show :: JpegOptions -> String
$cshow :: JpegOptions -> String
showsPrec :: Int -> JpegOptions -> ShowS
$cshowsPrec :: Int -> JpegOptions -> ShowS
Show)

instance Default JpegOptions where
  def :: JpegOptions
def = Word8 -> Metadatas -> JpegOptions
JpegOptions Word8
100 Metadatas
forall a. Monoid a => a
mempty


-- | Joint Photographic Experts Group image with @.jpg@ or @.jpeg@ extension.
data JPG = JPG deriving Int -> JPG -> ShowS
[JPG] -> ShowS
JPG -> String
(Int -> JPG -> ShowS)
-> (JPG -> String) -> ([JPG] -> ShowS) -> Show JPG
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JPG] -> ShowS
$cshowList :: [JPG] -> ShowS
show :: JPG -> String
$cshow :: JPG -> String
showsPrec :: Int -> JPG -> ShowS
$cshowsPrec :: Int -> JPG -> ShowS
Show

instance FileFormat JPG where
  type WriteOptions JPG = JpegOptions
  type Metadata JPG = JP.Metadatas
  ext :: JPG -> String
ext JPG
_ = String
".jpg"
  exts :: JPG -> [String]
exts JPG
_ = [String
".jpg", String
".jpeg"]

instance Writable JPG (Image A.S CM.X Bit) where
  encodeM :: JPG -> WriteOptions JPG -> Image S X Bit -> m ByteString
encodeM JPG
f WriteOptions JPG
opts Image S X Bit
img = JPG
-> WriteOptions JPG -> Array S Ix2 (Pixel X Word8) -> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM JPG
f WriteOptions JPG
opts (Image S X Bit -> Array S Ix2 (Pixel X Word8)
coerceBinaryImage Image S X Bit
img)

instance Writable JPG (Image S CM.X Word8) where
  encodeM :: JPG
-> WriteOptions JPG -> Array S Ix2 (Pixel X Word8) -> m ByteString
encodeM JPG
JPG JpegOptions {jpegQuality, jpegMetadata} =
    ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> m ByteString)
-> (Array S Ix2 (Pixel X Word8) -> ByteString)
-> Array S Ix2 (Pixel X Word8)
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Metadatas -> Image Word8 -> ByteString
forall px.
JpgEncodable px =>
Word8 -> Metadatas -> Image px -> ByteString
JP.encodeDirectJpegAtQualityWithMetadata Word8
jpegQuality Metadatas
jpegMetadata (Image Word8 -> ByteString)
-> (Array S Ix2 (Pixel X Word8) -> Image Word8)
-> Array S Ix2 (Pixel X Word8)
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array S Ix2 (Pixel X Word8) -> Image Word8
forall r.
Source r Ix2 (Pixel X Word8) =>
Image r X Word8 -> Image Word8
toJPImageY8

instance Writable JPG (Image S CM.RGB Word8) where
  encodeM :: JPG -> WriteOptions JPG -> Image S RGB Word8 -> m ByteString
encodeM JPG
JPG JpegOptions {jpegQuality, jpegMetadata} =
    ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> m ByteString)
-> (Image S RGB Word8 -> ByteString)
-> Image S RGB Word8
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Metadatas -> Image PixelRGB8 -> ByteString
forall px.
JpgEncodable px =>
Word8 -> Metadatas -> Image px -> ByteString
JP.encodeDirectJpegAtQualityWithMetadata Word8
jpegQuality Metadatas
jpegMetadata (Image PixelRGB8 -> ByteString)
-> (Image S RGB Word8 -> Image PixelRGB8)
-> Image S RGB Word8
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Image S RGB Word8 -> Image PixelRGB8
forall r.
Source r Ix2 (Pixel RGB Word8) =>
Image r RGB Word8 -> Image PixelRGB8
toJPImageRGB8

instance Writable JPG (Image S CM.YCbCr Word8) where
  encodeM :: JPG -> WriteOptions JPG -> Image S YCbCr Word8 -> m ByteString
encodeM JPG
JPG JpegOptions {jpegQuality, jpegMetadata} =
    ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> m ByteString)
-> (Image S YCbCr Word8 -> ByteString)
-> Image S YCbCr Word8
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Metadatas -> Image PixelYCbCr8 -> ByteString
JP.encodeJpegAtQualityWithMetadata Word8
jpegQuality Metadatas
jpegMetadata (Image PixelYCbCr8 -> ByteString)
-> (Image S YCbCr Word8 -> Image PixelYCbCr8)
-> Image S YCbCr Word8
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Image S YCbCr Word8 -> Image PixelYCbCr8
forall r.
Source r Ix2 (Pixel YCbCr Word8) =>
Image r YCbCr Word8 -> Image PixelYCbCr8
toJPImageYCbCr8

instance Writable JPG (Image S CM.CMYK Word8) where
  encodeM :: JPG -> WriteOptions JPG -> Image S CMYK Word8 -> m ByteString
encodeM JPG
JPG JpegOptions {jpegQuality, jpegMetadata} =
    ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> m ByteString)
-> (Image S CMYK Word8 -> ByteString)
-> Image S CMYK Word8
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Metadatas -> Image PixelCMYK8 -> ByteString
forall px.
JpgEncodable px =>
Word8 -> Metadatas -> Image px -> ByteString
JP.encodeDirectJpegAtQualityWithMetadata Word8
jpegQuality Metadatas
jpegMetadata (Image PixelCMYK8 -> ByteString)
-> (Image S CMYK Word8 -> Image PixelCMYK8)
-> Image S CMYK Word8
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Image S CMYK Word8 -> Image PixelCMYK8
forall r.
Source r Ix2 (Pixel CMYK Word8) =>
Image r CMYK Word8 -> Image PixelCMYK8
toJPImageCMYK8

instance Writable JPG (Image S (Y' SRGB) Word8) where
  encodeM :: JPG -> WriteOptions JPG -> Image S (Y' SRGB) Word8 -> m ByteString
encodeM JPG
f WriteOptions JPG
opts = JPG
-> WriteOptions JPG -> Array S Ix2 (Pixel X Word8) -> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM JPG
f WriteOptions JPG
opts (Array S Ix2 (Pixel X Word8) -> m ByteString)
-> (Image S (Y' SRGB) Word8 -> Array S Ix2 (Pixel X Word8))
-> Image S (Y' SRGB) Word8
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Image S (Y' SRGB) Word8 -> Array S Ix2 (Pixel X Word8)
forall cs e.
Array S Ix2 (Pixel cs e) -> Array S Ix2 (Pixel (BaseModel cs) e)
toImageBaseModel

instance Writable JPG (Image S (Y D65) Word8) where
  encodeM :: JPG -> WriteOptions JPG -> Image S (Y D65) Word8 -> m ByteString
encodeM JPG
f WriteOptions JPG
opts = JPG
-> WriteOptions JPG -> Array S Ix2 (Pixel X Word8) -> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM JPG
f WriteOptions JPG
opts (Array S Ix2 (Pixel X Word8) -> m ByteString)
-> (Image S (Y D65) Word8 -> Array S Ix2 (Pixel X Word8))
-> Image S (Y D65) Word8
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Image S (Y D65) Word8 -> Array S Ix2 (Pixel X Word8)
forall cs e.
Array S Ix2 (Pixel cs e) -> Array S Ix2 (Pixel (BaseModel cs) e)
toImageBaseModel

instance Writable JPG (Image S (SRGB 'NonLinear) Word8) where
  encodeM :: JPG
-> WriteOptions JPG
-> Image S (SRGB 'NonLinear) Word8
-> m ByteString
encodeM JPG
f WriteOptions JPG
opts = JPG -> WriteOptions JPG -> Image S RGB Word8 -> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM JPG
f WriteOptions JPG
opts (Image S RGB Word8 -> m ByteString)
-> (Image S (SRGB 'NonLinear) Word8 -> Image S RGB Word8)
-> Image S (SRGB 'NonLinear) Word8
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Image S (SRGB 'NonLinear) Word8 -> Image S RGB Word8
forall cs e.
Array S Ix2 (Pixel cs e) -> Array S Ix2 (Pixel (BaseModel cs) e)
toImageBaseModel

instance Writable JPG (Image S (Y'CbCr SRGB) Word8) where
  encodeM :: JPG
-> WriteOptions JPG -> Image S (Y'CbCr SRGB) Word8 -> m ByteString
encodeM JPG
f WriteOptions JPG
opts = JPG -> WriteOptions JPG -> Image S YCbCr Word8 -> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM JPG
f WriteOptions JPG
opts (Image S YCbCr Word8 -> m ByteString)
-> (Image S (Y'CbCr SRGB) Word8 -> Image S YCbCr Word8)
-> Image S (Y'CbCr SRGB) Word8
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Image S (Y'CbCr SRGB) Word8 -> Image S YCbCr Word8
forall cs e.
Array S Ix2 (Pixel cs e) -> Array S Ix2 (Pixel (BaseModel cs) e)
toImageBaseModel

instance Writable JPG (Image S (CMYK (SRGB 'NonLinear)) Word8) where
  encodeM :: JPG
-> WriteOptions JPG
-> Image S (CMYK (SRGB 'NonLinear)) Word8
-> m ByteString
encodeM JPG
f WriteOptions JPG
opts = JPG -> WriteOptions JPG -> Image S CMYK Word8 -> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM JPG
f WriteOptions JPG
opts (Image S CMYK Word8 -> m ByteString)
-> (Image S (CMYK (SRGB 'NonLinear)) Word8 -> Image S CMYK Word8)
-> Image S (CMYK (SRGB 'NonLinear)) Word8
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Image S (CMYK (SRGB 'NonLinear)) Word8 -> Image S CMYK Word8
forall cs e.
Array S Ix2 (Pixel cs e) -> Array S Ix2 (Pixel (BaseModel cs) e)
toImageBaseModel

instance (ColorSpace cs i e, ColorSpace (BaseSpace cs) i e, Source r Ix2 (Pixel cs e)) =>
         Writable (Auto JPG) (Image r cs e) where
  encodeM :: Auto JPG -> WriteOptions (Auto JPG) -> Image r cs e -> m ByteString
encodeM Auto JPG
f WriteOptions (Auto JPG)
opts = ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> m ByteString)
-> (Image r cs e -> ByteString) -> Image r cs e -> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Auto JPG -> JpegOptions -> Image r cs e -> ByteString
forall r cs i e.
(ColorSpace (BaseSpace cs) i e, ColorSpace cs i e,
 Source r Ix2 (Pixel cs e)) =>
Auto JPG -> JpegOptions -> Image r cs e -> ByteString
encodeAutoJPG Auto JPG
f WriteOptions (Auto JPG)
JpegOptions
opts


instance Readable JPG (Image S CM.X Word8) where
  decodeWithMetadataM :: JPG -> ByteString -> m (Array S Ix2 (Pixel X Word8), Metadata JPG)
decodeWithMetadataM = JPG -> ByteString -> m (Array S Ix2 (Pixel X Word8), Metadata JPG)
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
JPG -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataJPG

instance Readable JPG (Image S (Alpha CM.X) Word8) where
  decodeWithMetadataM :: JPG -> ByteString -> m (Image S (Alpha X) Word8, Metadata JPG)
decodeWithMetadataM = JPG -> ByteString -> m (Image S (Alpha X) Word8, Metadata JPG)
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
JPG -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataJPG

instance Readable JPG (Image S CM.RGB Word8) where
  decodeWithMetadataM :: JPG -> ByteString -> m (Image S RGB Word8, Metadata JPG)
decodeWithMetadataM = JPG -> ByteString -> m (Image S RGB Word8, Metadata JPG)
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
JPG -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataJPG

instance Readable JPG (Image S CM.CMYK Word8) where
  decodeWithMetadataM :: JPG -> ByteString -> m (Image S CMYK Word8, Metadata JPG)
decodeWithMetadataM = JPG -> ByteString -> m (Image S CMYK Word8, Metadata JPG)
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
JPG -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataJPG

instance Readable JPG (Image S CM.YCbCr Word8) where
  decodeWithMetadataM :: JPG -> ByteString -> m (Image S YCbCr Word8, Metadata JPG)
decodeWithMetadataM = JPG -> ByteString -> m (Image S YCbCr Word8, Metadata JPG)
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
JPG -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataJPG

instance Readable JPG (Image S (Y' SRGB) Word8) where
  decodeWithMetadataM :: JPG -> ByteString -> m (Image S (Y' SRGB) Word8, Metadata JPG)
decodeWithMetadataM JPG
f = ((Array S Ix2 (Pixel X Word8), Metadatas)
 -> (Image S (Y' SRGB) Word8, Metadatas))
-> m (Array S Ix2 (Pixel X Word8), Metadatas)
-> m (Image S (Y' SRGB) Word8, Metadatas)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Array S Ix2 (Pixel X Word8) -> Image S (Y' SRGB) Word8)
-> (Array S Ix2 (Pixel X Word8), Metadatas)
-> (Image S (Y' SRGB) Word8, Metadatas)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Array S Ix2 (Pixel X Word8) -> Image S (Y' SRGB) Word8
forall cs e.
Array S Ix2 (Pixel (BaseModel cs) e) -> Array S Ix2 (Pixel cs e)
fromImageBaseModel) (m (Array S Ix2 (Pixel X Word8), Metadatas)
 -> m (Image S (Y' SRGB) Word8, Metadatas))
-> (ByteString -> m (Array S Ix2 (Pixel X Word8), Metadatas))
-> ByteString
-> m (Image S (Y' SRGB) Word8, Metadatas)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JPG -> ByteString -> m (Array S Ix2 (Pixel X Word8), Metadata JPG)
forall f arr (m :: * -> *).
(Readable f arr, MonadThrow m) =>
f -> ByteString -> m (arr, Metadata f)
decodeWithMetadataM JPG
f

instance Readable JPG (Image S (Alpha (Y' SRGB)) Word8) where
  decodeWithMetadataM :: JPG
-> ByteString -> m (Image S (Alpha (Y' SRGB)) Word8, Metadata JPG)
decodeWithMetadataM JPG
f = ((Image S (Alpha X) Word8, Metadatas)
 -> (Image S (Alpha (Y' SRGB)) Word8, Metadatas))
-> m (Image S (Alpha X) Word8, Metadatas)
-> m (Image S (Alpha (Y' SRGB)) Word8, Metadatas)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Image S (Alpha X) Word8 -> Image S (Alpha (Y' SRGB)) Word8)
-> (Image S (Alpha X) Word8, Metadatas)
-> (Image S (Alpha (Y' SRGB)) Word8, Metadatas)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Image S (Alpha X) Word8 -> Image S (Alpha (Y' SRGB)) Word8
forall cs e.
Array S Ix2 (Pixel (BaseModel cs) e) -> Array S Ix2 (Pixel cs e)
fromImageBaseModel) (m (Image S (Alpha X) Word8, Metadatas)
 -> m (Image S (Alpha (Y' SRGB)) Word8, Metadatas))
-> (ByteString -> m (Image S (Alpha X) Word8, Metadatas))
-> ByteString
-> m (Image S (Alpha (Y' SRGB)) Word8, Metadatas)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JPG -> ByteString -> m (Image S (Alpha X) Word8, Metadata JPG)
forall f arr (m :: * -> *).
(Readable f arr, MonadThrow m) =>
f -> ByteString -> m (arr, Metadata f)
decodeWithMetadataM JPG
f

instance Readable JPG (Image S (Y D65) Word8) where
  decodeWithMetadataM :: JPG -> ByteString -> m (Image S (Y D65) Word8, Metadata JPG)
decodeWithMetadataM JPG
f = ((Array S Ix2 (Pixel X Word8), Metadatas)
 -> (Image S (Y D65) Word8, Metadatas))
-> m (Array S Ix2 (Pixel X Word8), Metadatas)
-> m (Image S (Y D65) Word8, Metadatas)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Array S Ix2 (Pixel X Word8) -> Image S (Y D65) Word8)
-> (Array S Ix2 (Pixel X Word8), Metadatas)
-> (Image S (Y D65) Word8, Metadatas)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Array S Ix2 (Pixel X Word8) -> Image S (Y D65) Word8
forall cs e.
Array S Ix2 (Pixel (BaseModel cs) e) -> Array S Ix2 (Pixel cs e)
fromImageBaseModel) (m (Array S Ix2 (Pixel X Word8), Metadatas)
 -> m (Image S (Y D65) Word8, Metadatas))
-> (ByteString -> m (Array S Ix2 (Pixel X Word8), Metadatas))
-> ByteString
-> m (Image S (Y D65) Word8, Metadatas)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JPG -> ByteString -> m (Array S Ix2 (Pixel X Word8), Metadata JPG)
forall f arr (m :: * -> *).
(Readable f arr, MonadThrow m) =>
f -> ByteString -> m (arr, Metadata f)
decodeWithMetadataM JPG
f

instance Readable JPG (Image S (Alpha (Y D65)) Word8) where
  decodeWithMetadataM :: JPG
-> ByteString -> m (Image S (Alpha (Y D65)) Word8, Metadata JPG)
decodeWithMetadataM JPG
f = ((Image S (Alpha X) Word8, Metadatas)
 -> (Image S (Alpha (Y D65)) Word8, Metadatas))
-> m (Image S (Alpha X) Word8, Metadatas)
-> m (Image S (Alpha (Y D65)) Word8, Metadatas)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Image S (Alpha X) Word8 -> Image S (Alpha (Y D65)) Word8)
-> (Image S (Alpha X) Word8, Metadatas)
-> (Image S (Alpha (Y D65)) Word8, Metadatas)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Image S (Alpha X) Word8 -> Image S (Alpha (Y D65)) Word8
forall cs e.
Array S Ix2 (Pixel (BaseModel cs) e) -> Array S Ix2 (Pixel cs e)
fromImageBaseModel) (m (Image S (Alpha X) Word8, Metadatas)
 -> m (Image S (Alpha (Y D65)) Word8, Metadatas))
-> (ByteString -> m (Image S (Alpha X) Word8, Metadatas))
-> ByteString
-> m (Image S (Alpha (Y D65)) Word8, Metadatas)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JPG -> ByteString -> m (Image S (Alpha X) Word8, Metadata JPG)
forall f arr (m :: * -> *).
(Readable f arr, MonadThrow m) =>
f -> ByteString -> m (arr, Metadata f)
decodeWithMetadataM JPG
f

instance Readable JPG (Image S (SRGB 'NonLinear) Word8) where
  decodeWithMetadataM :: JPG
-> ByteString -> m (Image S (SRGB 'NonLinear) Word8, Metadata JPG)
decodeWithMetadataM JPG
f = ((Image S RGB Word8, Metadatas)
 -> (Image S (SRGB 'NonLinear) Word8, Metadatas))
-> m (Image S RGB Word8, Metadatas)
-> m (Image S (SRGB 'NonLinear) Word8, Metadatas)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Image S RGB Word8 -> Image S (SRGB 'NonLinear) Word8)
-> (Image S RGB Word8, Metadatas)
-> (Image S (SRGB 'NonLinear) Word8, Metadatas)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Image S RGB Word8 -> Image S (SRGB 'NonLinear) Word8
forall cs e.
Array S Ix2 (Pixel (BaseModel cs) e) -> Array S Ix2 (Pixel cs e)
fromImageBaseModel) (m (Image S RGB Word8, Metadatas)
 -> m (Image S (SRGB 'NonLinear) Word8, Metadatas))
-> (ByteString -> m (Image S RGB Word8, Metadatas))
-> ByteString
-> m (Image S (SRGB 'NonLinear) Word8, Metadatas)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JPG -> ByteString -> m (Image S RGB Word8, Metadata JPG)
forall f arr (m :: * -> *).
(Readable f arr, MonadThrow m) =>
f -> ByteString -> m (arr, Metadata f)
decodeWithMetadataM JPG
f

instance Readable JPG (Image S (CMYK (SRGB 'NonLinear)) Word8) where
  decodeWithMetadataM :: JPG
-> ByteString
-> m (Image S (CMYK (SRGB 'NonLinear)) Word8, Metadata JPG)
decodeWithMetadataM JPG
f = ((Image S CMYK Word8, Metadatas)
 -> (Image S (CMYK (SRGB 'NonLinear)) Word8, Metadatas))
-> m (Image S CMYK Word8, Metadatas)
-> m (Image S (CMYK (SRGB 'NonLinear)) Word8, Metadatas)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Image S CMYK Word8 -> Image S (CMYK (SRGB 'NonLinear)) Word8)
-> (Image S CMYK Word8, Metadatas)
-> (Image S (CMYK (SRGB 'NonLinear)) Word8, Metadatas)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Image S CMYK Word8 -> Image S (CMYK (SRGB 'NonLinear)) Word8
forall cs e.
Array S Ix2 (Pixel (BaseModel cs) e) -> Array S Ix2 (Pixel cs e)
fromImageBaseModel) (m (Image S CMYK Word8, Metadatas)
 -> m (Image S (CMYK (SRGB 'NonLinear)) Word8, Metadatas))
-> (ByteString -> m (Image S CMYK Word8, Metadatas))
-> ByteString
-> m (Image S (CMYK (SRGB 'NonLinear)) Word8, Metadatas)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JPG -> ByteString -> m (Image S CMYK Word8, Metadata JPG)
forall f arr (m :: * -> *).
(Readable f arr, MonadThrow m) =>
f -> ByteString -> m (arr, Metadata f)
decodeWithMetadataM JPG
f

instance Readable JPG (Image S (Y'CbCr SRGB) Word8) where
  decodeWithMetadataM :: JPG -> ByteString -> m (Image S (Y'CbCr SRGB) Word8, Metadata JPG)
decodeWithMetadataM JPG
f = ((Image S YCbCr Word8, Metadatas)
 -> (Image S (Y'CbCr SRGB) Word8, Metadatas))
-> m (Image S YCbCr Word8, Metadatas)
-> m (Image S (Y'CbCr SRGB) Word8, Metadatas)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Image S YCbCr Word8 -> Image S (Y'CbCr SRGB) Word8)
-> (Image S YCbCr Word8, Metadatas)
-> (Image S (Y'CbCr SRGB) Word8, Metadatas)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Image S YCbCr Word8 -> Image S (Y'CbCr SRGB) Word8
forall cs e.
Array S Ix2 (Pixel (BaseModel cs) e) -> Array S Ix2 (Pixel cs e)
fromImageBaseModel) (m (Image S YCbCr Word8, Metadatas)
 -> m (Image S (Y'CbCr SRGB) Word8, Metadatas))
-> (ByteString -> m (Image S YCbCr Word8, Metadatas))
-> ByteString
-> m (Image S (Y'CbCr SRGB) Word8, Metadatas)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. JPG -> ByteString -> m (Image S YCbCr Word8, Metadata JPG)
forall f arr (m :: * -> *).
(Readable f arr, MonadThrow m) =>
f -> ByteString -> m (arr, Metadata f)
decodeWithMetadataM JPG
f


-- | Decode a Jpeg Image
decodeJPG :: (ColorModel cs e, MonadThrow m) => JPG -> B.ByteString -> m (Image S cs e)
decodeJPG :: JPG -> ByteString -> m (Image S cs e)
decodeJPG JPG
f ByteString
bs = JPG -> Either String DynamicImage -> m (Image S cs e)
forall (m :: * -> *) cs e f.
(MonadThrow m, ColorModel cs e, FileFormat f) =>
f -> Either String DynamicImage -> m (Image S cs e)
convertWith JPG
f (ByteString -> Either String DynamicImage
JP.decodeJpeg ByteString
bs)

-- | Decode a Jpeg Image
decodeWithMetadataJPG ::
     (ColorModel cs e, MonadThrow m) => JPG -> B.ByteString -> m (Image S cs e, JP.Metadatas)
decodeWithMetadataJPG :: JPG -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataJPG JPG
f ByteString
bs = JPG
-> Either String (DynamicImage, Metadata JPG)
-> m (Image S cs e, Metadata JPG)
forall (m :: * -> *) cs e f.
(MonadThrow m, ColorModel cs e, FileFormat f) =>
f
-> Either String (DynamicImage, Metadata f)
-> m (Image S cs e, Metadata f)
convertWithMetadata JPG
f (ByteString -> Either String (DynamicImage, Metadatas)
JP.decodeJpegWithMetadata ByteString
bs)


-- | Decode a Jpeg Image
decodeAutoJPG ::
     (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m)
  => Auto JPG
  -> B.ByteString
  -> m (Image r cs e)
decodeAutoJPG :: Auto JPG -> ByteString -> m (Image r cs e)
decodeAutoJPG Auto JPG
f ByteString
bs = Auto JPG -> Either String DynamicImage -> m (Image r cs e)
forall (m :: * -> *) r cs e i f.
(MonadThrow m, Mutable r Ix2 (Pixel cs e), ColorSpace cs i e) =>
Auto f -> Either String DynamicImage -> m (Image r cs e)
convertAutoWith Auto JPG
f (ByteString -> Either String DynamicImage
JP.decodeJpeg ByteString
bs)

-- | Decode a Jpeg Image
decodeAutoWithMetadataJPG ::
     (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m)
  => Auto JPG
  -> B.ByteString
  -> m (Image r cs e, JP.Metadatas)
decodeAutoWithMetadataJPG :: Auto JPG -> ByteString -> m (Image r cs e, Metadatas)
decodeAutoWithMetadataJPG Auto JPG
f ByteString
bs = Auto JPG
-> Either String (DynamicImage, Metadata JPG)
-> m (Image r cs e, Metadata JPG)
forall (m :: * -> *) r cs e i f.
(MonadThrow m, Mutable r Ix2 (Pixel cs e), ColorSpace cs i e) =>
Auto f
-> Either String (DynamicImage, Metadata f)
-> m (Image r cs e, Metadata f)
convertAutoWithMetadata Auto JPG
f (ByteString -> Either String (DynamicImage, Metadatas)
JP.decodeJpegWithMetadata ByteString
bs)

instance (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e) =>
         Readable (Auto JPG) (Image r cs e) where
  decodeM :: Auto JPG -> ByteString -> m (Image r cs e)
decodeM = Auto JPG -> ByteString -> m (Image r cs e)
forall r cs e i (m :: * -> *).
(Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) =>
Auto JPG -> ByteString -> m (Image r cs e)
decodeAutoJPG
  decodeWithMetadataM :: Auto JPG -> ByteString -> m (Image r cs e, Metadata (Auto JPG))
decodeWithMetadataM = Auto JPG -> ByteString -> m (Image r cs e, Metadata (Auto JPG))
forall r cs e i (m :: * -> *).
(Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) =>
Auto JPG -> ByteString -> m (Image r cs e, Metadatas)
decodeAutoWithMetadataJPG

encodeJPG ::
     forall cs e m. (ColorModel cs e, MonadThrow m)
  => JPG
  -> JpegOptions
  -> Image S cs e
  -> m BL.ByteString
encodeJPG :: JPG -> JpegOptions -> Image S cs e -> m ByteString
encodeJPG JPG
f opts :: JpegOptions
opts@JpegOptions {Word8
jpegQuality :: Word8
jpegQuality :: JpegOptions -> Word8
jpegQuality, Metadatas
jpegMetadata :: Metadatas
jpegMetadata :: JpegOptions -> Metadatas
jpegMetadata} Image S cs e
img =
  JPG -> Proxy (Image S cs e) -> Maybe ByteString -> m ByteString
forall f r cs e b (m :: * -> *).
(ColorModel cs e, FileFormat f, Typeable r, MonadThrow m) =>
f -> Proxy (Image r cs e) -> Maybe b -> m b
fromMaybeEncode JPG
f (Proxy (Image S cs e)
forall k (t :: k). Proxy t
Proxy :: Proxy (Image S cs e)) Maybe ByteString
encoded
  where
    encoded :: Maybe ByteString
encoded
      | Just Pixel cs e :~: Pixel X Bit
Refl <- Maybe (Pixel cs e :~: Pixel X Bit)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (Pixel cs e :~: Pixel CM.X Bit) = JPG -> WriteOptions JPG -> Image S cs e -> Maybe ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM JPG
JPG WriteOptions JPG
JpegOptions
opts Image S cs e
img
      | Just e :~: Word8
Refl <- Maybe (e :~: Word8)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (e :~: Word8) =
        [Maybe ByteString] -> Maybe ByteString
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum
          [ Word8 -> Metadatas -> Image Word8 -> ByteString
forall px.
JpgEncodable px =>
Word8 -> Metadatas -> Image px -> ByteString
JP.encodeDirectJpegAtQualityWithMetadata Word8
jpegQuality Metadatas
jpegMetadata (Image Word8 -> ByteString)
-> Maybe (Image Word8) -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Image S cs Word8 -> Maybe (Image Word8)
forall cs.
(Typeable cs, Source S Ix2 (Pixel cs Word8)) =>
Image S cs Word8 -> Maybe (Image Word8)
maybeJPImageY8 Image S cs e
Image S cs Word8
img
          , Word8 -> Metadatas -> Image PixelRGB8 -> ByteString
forall px.
JpgEncodable px =>
Word8 -> Metadatas -> Image px -> ByteString
JP.encodeDirectJpegAtQualityWithMetadata Word8
jpegQuality Metadatas
jpegMetadata (Image PixelRGB8 -> ByteString)
-> Maybe (Image PixelRGB8) -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
            Image S cs Word8 -> Maybe (Image PixelRGB8)
forall cs.
(Typeable cs, Source S Ix2 (Pixel cs Word8)) =>
Image S cs Word8 -> Maybe (Image PixelRGB8)
maybeJPImageRGB8 Image S cs e
Image S cs Word8
img
          , Word8 -> Metadatas -> Image PixelYCbCr8 -> ByteString
forall px.
JpgEncodable px =>
Word8 -> Metadatas -> Image px -> ByteString
JP.encodeDirectJpegAtQualityWithMetadata Word8
jpegQuality Metadatas
jpegMetadata (Image PixelYCbCr8 -> ByteString)
-> Maybe (Image PixelYCbCr8) -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
            Image S cs Word8 -> Maybe (Image PixelYCbCr8)
forall cs.
(Typeable cs, Source S Ix2 (Pixel cs Word8)) =>
Image S cs Word8 -> Maybe (Image PixelYCbCr8)
maybeJPImageYCbCr8 Image S cs e
Image S cs Word8
img
          , Word8 -> Metadatas -> Image PixelCMYK8 -> ByteString
forall px.
JpgEncodable px =>
Word8 -> Metadatas -> Image px -> ByteString
JP.encodeDirectJpegAtQualityWithMetadata Word8
jpegQuality Metadatas
jpegMetadata (Image PixelCMYK8 -> ByteString)
-> Maybe (Image PixelCMYK8) -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
            Image S cs Word8 -> Maybe (Image PixelCMYK8)
forall cs.
(Typeable cs, Source S Ix2 (Pixel cs Word8)) =>
Image S cs Word8 -> Maybe (Image PixelCMYK8)
maybeJPImageCMYK8 Image S cs e
Image S cs Word8
img
          ]
      | Bool
otherwise = Maybe ByteString
forall a. Maybe a
Nothing


encodeAutoJPG ::
     forall r cs i e. (ColorSpace (BaseSpace cs) i e, ColorSpace cs i e, Source r Ix2 (Pixel cs e))
  => Auto JPG
  -> JpegOptions
  -> Image r cs e
  -> BL.ByteString
encodeAutoJPG :: Auto JPG -> JpegOptions -> Image r cs e -> ByteString
encodeAutoJPG Auto JPG
_ JpegOptions {Word8
jpegQuality :: Word8
jpegQuality :: JpegOptions -> Word8
jpegQuality, Metadatas
jpegMetadata :: Metadatas
jpegMetadata :: JpegOptions -> Metadatas
jpegMetadata} Image r cs e
img =
  ByteString -> Maybe ByteString -> ByteString
forall a. a -> Maybe a -> a
fromMaybe ((Array D Ix2 (Pixel YCbCr Word8) -> Image PixelYCbCr8)
-> (Pixel cs e -> Pixel YCbCr Word8) -> Image r cs e -> ByteString
forall px ix a b.
(JpgEncodable px, Source r ix a) =>
(Array D ix b -> Image px)
-> (a -> b) -> Array r ix a -> ByteString
toJpeg Array D Ix2 (Pixel YCbCr Word8) -> Image PixelYCbCr8
forall r.
Source r Ix2 (Pixel YCbCr Word8) =>
Image r YCbCr Word8 -> Image PixelYCbCr8
toJPImageYCbCr8 Pixel cs e -> Pixel YCbCr Word8
forall cs i e. ColorSpace cs i e => Pixel cs e -> Pixel YCbCr Word8
toYCbCr8 Image r cs e
img) (Maybe ByteString -> ByteString) -> Maybe ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$
  [Maybe ByteString] -> Maybe ByteString
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum
    [ do BaseModel cs :~: X
Refl <- Maybe (BaseModel cs :~: X)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (BaseModel cs :~: CM.X)
         [Maybe ByteString] -> Maybe ByteString
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum
           [ do e :~: Bit
Refl <- Maybe (e :~: Bit)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (e :~: Bit)
                ByteString -> Maybe ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ (Array D Ix2 (Pixel X Word8) -> Image Word8)
-> (Pixel cs e -> Pixel X Word8) -> Image r cs e -> ByteString
forall px ix a b.
(JpgEncodable px, Source r ix a) =>
(Array D ix b -> Image px)
-> (a -> b) -> Array r ix a -> ByteString
toJpeg Array D Ix2 (Pixel X Word8) -> Image Word8
forall r.
Source r Ix2 (Pixel X Word8) =>
Image r X Word8 -> Image Word8
toJPImageY8 (Pixel X e -> Pixel X Word8
forall cs e. ColorModel cs e => Pixel cs e -> Pixel cs Word8
toPixel8 (Pixel X e -> Pixel X Word8)
-> (Pixel cs e -> Pixel X e) -> Pixel cs e -> Pixel X Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pixel cs e -> Pixel X e
forall k cs (i :: k) e.
ColorSpace cs i e =>
Pixel cs e -> Pixel (BaseModel cs) e
toPixelBaseModel) Image r cs e
img
           , ByteString -> Maybe ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ (Array D Ix2 (Pixel X Word8) -> Image Word8)
-> (Pixel cs e -> Pixel X Word8) -> Image r cs e -> ByteString
forall px ix a b.
(JpgEncodable px, Source r ix a) =>
(Array D ix b -> Image px)
-> (a -> b) -> Array r ix a -> ByteString
toJpeg Array D Ix2 (Pixel X Word8) -> Image Word8
forall r.
Source r Ix2 (Pixel X Word8) =>
Image r X Word8 -> Image Word8
toJPImageY8 (Pixel X e -> Pixel X Word8
forall cs e. ColorModel cs e => Pixel cs e -> Pixel cs Word8
toPixel8 (Pixel X e -> Pixel X Word8)
-> (Pixel cs e -> Pixel X e) -> Pixel cs e -> Pixel X Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pixel cs e -> Pixel X e
forall k cs (i :: k) e.
ColorSpace cs i e =>
Pixel cs e -> Pixel (BaseModel cs) e
toPixelBaseModel) Image r cs e
img
           ]
    , do BaseModel cs :~: CMYK
Refl <- Maybe (BaseModel cs :~: CMYK)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (BaseModel cs :~: CM.CMYK)
         ByteString -> Maybe ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ (Array D Ix2 (Pixel CMYK Word8) -> Image PixelCMYK8)
-> (Pixel cs e -> Pixel CMYK Word8) -> Image r cs e -> ByteString
forall px ix a b.
(JpgEncodable px, Source r ix a) =>
(Array D ix b -> Image px)
-> (a -> b) -> Array r ix a -> ByteString
toJpeg Array D Ix2 (Pixel CMYK Word8) -> Image PixelCMYK8
forall r.
Source r Ix2 (Pixel CMYK Word8) =>
Image r CMYK Word8 -> Image PixelCMYK8
toJPImageCMYK8 Pixel cs e -> Pixel CMYK Word8
forall cs i e. ColorSpace cs i e => Pixel cs e -> Pixel CMYK Word8
toCMYK8 Image r cs e
img
    , do BaseModel cs :~: RGB
Refl <- Maybe (BaseModel cs :~: RGB)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (BaseModel cs :~: CM.RGB)
         ByteString -> Maybe ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ (Array D Ix2 (Pixel RGB Word8) -> Image PixelRGB8)
-> (Pixel cs e -> Pixel RGB Word8) -> Image r cs e -> ByteString
forall px ix a b.
(JpgEncodable px, Source r ix a) =>
(Array D ix b -> Image px)
-> (a -> b) -> Array r ix a -> ByteString
toJpeg Array D Ix2 (Pixel RGB Word8) -> Image PixelRGB8
forall r.
Source r Ix2 (Pixel RGB Word8) =>
Image r RGB Word8 -> Image PixelRGB8
toJPImageRGB8 Pixel cs e -> Pixel RGB Word8
forall cs i e. ColorSpace cs i e => Pixel cs e -> Pixel RGB Word8
toSRGB8 Image r cs e
img
    ]
  where
    toJpeg ::
         (JP.JpgEncodable px, Source r ix a)
      => (Array D ix b -> JP.Image px)
      -> (a -> b)
      -> Array r ix a
      -> BL.ByteString
    toJpeg :: (Array D ix b -> Image px)
-> (a -> b) -> Array r ix a -> ByteString
toJpeg Array D ix b -> Image px
toJP a -> b
adjustPixel =
      Word8 -> Metadatas -> Image px -> ByteString
forall px.
JpgEncodable px =>
Word8 -> Metadatas -> Image px -> ByteString
JP.encodeDirectJpegAtQualityWithMetadata Word8
jpegQuality Metadatas
jpegMetadata (Image px -> ByteString)
-> (Array r ix a -> Image px) -> Array r ix a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array D ix b -> Image px
toJP (Array D ix b -> Image px)
-> (Array r ix a -> Array D ix b) -> Array r ix a -> Image px
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> Array r ix a -> Array D ix b
forall r ix e' e.
Source r ix e' =>
(e' -> e) -> Array r ix e' -> Array D ix e
A.map a -> b
adjustPixel