{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
-- |
-- Module      : Data.Massiv.Array.IO.Image.JuicyPixels.PNG
-- 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.PNG
  ( PNG(..)
  , decodePNG
  , decodeWithMetadataPNG
  , decodeAutoPNG
  , decodeAutoWithMetadataPNG
  , encodePNG
  , encodeAutoPNG
  ) where

import qualified Codec.Picture as JP
import qualified Codec.Picture.Metadata as JP
import qualified Codec.Picture.Png 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

--------------------------------------------------------------------------------
-- PNG Format ------------------------------------------------------------------
--------------------------------------------------------------------------------


-- | Portable Network Graphics image with @.png@ extension.
data PNG = PNG deriving Int -> PNG -> ShowS
[PNG] -> ShowS
PNG -> String
(Int -> PNG -> ShowS)
-> (PNG -> String) -> ([PNG] -> ShowS) -> Show PNG
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PNG] -> ShowS
$cshowList :: [PNG] -> ShowS
show :: PNG -> String
$cshow :: PNG -> String
showsPrec :: Int -> PNG -> ShowS
$cshowsPrec :: Int -> PNG -> ShowS
Show

instance FileFormat PNG where
  type Metadata PNG = JP.Metadatas
  ext :: PNG -> String
ext PNG
_ = String
".png"

instance Writable PNG (Image S CM.X Word8) where
  encodeM :: PNG -> WriteOptions PNG -> Image S X Word8 -> m ByteString
encodeM PNG
PNG WriteOptions PNG
_ Image S X Word8
img = ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> m ByteString) -> ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ Image Word8 -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (Image S X Word8 -> Image Word8
forall r.
Source r Ix2 (Pixel X Word8) =>
Image r X Word8 -> Image Word8
toJPImageY8 Image S X Word8
img)

instance Writable PNG (Image S CM.X Word16) where
  encodeM :: PNG -> WriteOptions PNG -> Image S X Word16 -> m ByteString
encodeM PNG
PNG WriteOptions PNG
_ Image S X Word16
img = ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> m ByteString) -> ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ Image Word16 -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (Image S X Word16 -> Image Word16
forall r.
Source r Ix2 (Pixel X Word16) =>
Image r X Word16 -> Image Word16
toJPImageY16 Image S X Word16
img)

instance Writable PNG (Image S (Alpha CM.X) Word8) where
  encodeM :: PNG -> WriteOptions PNG -> Image S (Alpha X) Word8 -> m ByteString
encodeM PNG
PNG WriteOptions PNG
_ Image S (Alpha X) Word8
img = ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> m ByteString) -> ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ Image PixelYA8 -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (Image S (Alpha X) Word8 -> Image PixelYA8
forall r.
Source r Ix2 (Pixel (Alpha X) Word8) =>
Image r (Alpha X) Word8 -> Image PixelYA8
toJPImageYA8 Image S (Alpha X) Word8
img)

instance Writable PNG (Image S (Alpha CM.X) Word16) where
  encodeM :: PNG -> WriteOptions PNG -> Image S (Alpha X) Word16 -> m ByteString
encodeM PNG
PNG WriteOptions PNG
_ Image S (Alpha X) Word16
img = ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> m ByteString) -> ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ Image PixelYA16 -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (Image S (Alpha X) Word16 -> Image PixelYA16
forall r.
Source r Ix2 (Pixel (Alpha X) Word16) =>
Image r (Alpha X) Word16 -> Image PixelYA16
toJPImageYA16 Image S (Alpha X) Word16
img)

instance Writable PNG (Image S CM.RGB Word8) where
  encodeM :: PNG -> WriteOptions PNG -> Image S RGB Word8 -> m ByteString
encodeM PNG
PNG WriteOptions PNG
_ Image S RGB Word8
img = ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> m ByteString) -> ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ Image PixelRGB8 -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (Image S RGB Word8 -> Image PixelRGB8
forall r.
Source r Ix2 (Pixel RGB Word8) =>
Image r RGB Word8 -> Image PixelRGB8
toJPImageRGB8 Image S RGB Word8
img)

instance Writable PNG (Image S CM.RGB Word16) where
  encodeM :: PNG -> WriteOptions PNG -> Image S RGB Word16 -> m ByteString
encodeM PNG
PNG WriteOptions PNG
_ Image S RGB Word16
img = ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> m ByteString) -> ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ Image PixelRGB16 -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (Image S RGB Word16 -> Image PixelRGB16
forall r.
Source r Ix2 (Pixel RGB Word16) =>
Image r RGB Word16 -> Image PixelRGB16
toJPImageRGB16 Image S RGB Word16
img)

instance Writable PNG (Image S (Alpha CM.RGB) Word8) where
  encodeM :: PNG
-> WriteOptions PNG -> Image S (Alpha RGB) Word8 -> m ByteString
encodeM PNG
PNG WriteOptions PNG
_ Image S (Alpha RGB) Word8
img = ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> m ByteString) -> ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ Image PixelRGBA8 -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (Image S (Alpha RGB) Word8 -> Image PixelRGBA8
forall r.
Source r Ix2 (Pixel (Alpha RGB) Word8) =>
Image r (Alpha RGB) Word8 -> Image PixelRGBA8
toJPImageRGBA8 Image S (Alpha RGB) Word8
img)

instance Writable PNG (Image S (Alpha CM.RGB) Word16) where
  encodeM :: PNG
-> WriteOptions PNG -> Image S (Alpha RGB) Word16 -> m ByteString
encodeM PNG
PNG WriteOptions PNG
_ Image S (Alpha RGB) Word16
img = ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> m ByteString) -> ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ Image PixelRGBA16 -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (Image S (Alpha RGB) Word16 -> Image PixelRGBA16
forall r.
Source r Ix2 (Pixel (Alpha RGB) Word16) =>
Image r (Alpha RGB) Word16 -> Image PixelRGBA16
toJPImageRGBA16 Image S (Alpha RGB) Word16
img)


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

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

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

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

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

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

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

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

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

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

instance Writable PNG (Image S (Alpha (SRGB 'NonLinear)) Word16) where
  encodeM :: PNG
-> WriteOptions PNG
-> Image S (Alpha (SRGB 'NonLinear)) Word16
-> m ByteString
encodeM PNG
f WriteOptions PNG
opts = PNG
-> WriteOptions PNG -> Image S (Alpha RGB) Word16 -> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM PNG
f WriteOptions PNG
opts (Image S (Alpha RGB) Word16 -> m ByteString)
-> (Image S (Alpha (SRGB 'NonLinear)) Word16
    -> Image S (Alpha RGB) Word16)
-> Image S (Alpha (SRGB 'NonLinear)) Word16
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Image S (Alpha (SRGB 'NonLinear)) Word16
-> Image S (Alpha RGB) Word16
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 PNG) (Image r cs e) where
  encodeM :: Auto PNG -> WriteOptions (Auto PNG) -> Image r cs e -> m ByteString
encodeM Auto PNG
f WriteOptions (Auto PNG)
_ = 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 PNG -> 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 PNG -> Image r cs e -> ByteString
encodeAutoPNG Auto PNG
f


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

instance Readable PNG (Image S CM.X Word16) where
  decodeWithMetadataM :: PNG -> ByteString -> m (Image S X Word16, Metadata PNG)
decodeWithMetadataM = PNG -> ByteString -> m (Image S X Word16, Metadata PNG)
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
PNG -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataPNG

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

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

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

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

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

instance Readable PNG (Image S (Alpha CM.RGB) Word16) where
  decodeWithMetadataM :: PNG -> ByteString -> m (Image S (Alpha RGB) Word16, Metadata PNG)
decodeWithMetadataM = PNG -> ByteString -> m (Image S (Alpha RGB) Word16, Metadata PNG)
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
PNG -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataPNG


instance Readable PNG (Image S (Y' SRGB) Word8) where
  decodeWithMetadataM :: PNG -> ByteString -> m (Image S (Y' SRGB) Word8, Metadata PNG)
decodeWithMetadataM PNG
f = ((Image S X Word8, Metadatas)
 -> (Image S (Y' SRGB) Word8, Metadatas))
-> m (Image S X Word8, Metadatas)
-> m (Image S (Y' SRGB) Word8, Metadatas)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Image S X Word8 -> Image S (Y' SRGB) Word8)
-> (Image S 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 Image S 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 (Image S X Word8, Metadatas)
 -> m (Image S (Y' SRGB) Word8, Metadatas))
-> (ByteString -> m (Image S X Word8, Metadatas))
-> ByteString
-> m (Image S (Y' SRGB) Word8, Metadatas)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PNG -> ByteString -> m (Image S X Word8, Metadatas)
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
PNG -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataPNG PNG
f

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

instance Readable PNG (Image S (Alpha (Y' SRGB)) Word8) where
  decodeWithMetadataM :: PNG
-> ByteString -> m (Image S (Alpha (Y' SRGB)) Word8, Metadata PNG)
decodeWithMetadataM PNG
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
. PNG -> ByteString -> m (Image S (Alpha X) Word8, Metadatas)
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
PNG -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataPNG PNG
f

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

instance Readable PNG (Image S (Y D65) Word8) where
  decodeWithMetadataM :: PNG -> ByteString -> m (Image S (Y D65) Word8, Metadata PNG)
decodeWithMetadataM PNG
f = ((Image S X Word8, Metadatas)
 -> (Image S (Y D65) Word8, Metadatas))
-> m (Image S X Word8, Metadatas)
-> m (Image S (Y D65) Word8, Metadatas)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Image S X Word8 -> Image S (Y D65) Word8)
-> (Image S 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 Image S 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 (Image S X Word8, Metadatas)
 -> m (Image S (Y D65) Word8, Metadatas))
-> (ByteString -> m (Image S X Word8, Metadatas))
-> ByteString
-> m (Image S (Y D65) Word8, Metadatas)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PNG -> ByteString -> m (Image S X Word8, Metadatas)
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
PNG -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataPNG PNG
f

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

instance Readable PNG (Image S (Alpha (Y D65)) Word8) where
  decodeWithMetadataM :: PNG
-> ByteString -> m (Image S (Alpha (Y D65)) Word8, Metadata PNG)
decodeWithMetadataM PNG
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
. PNG -> ByteString -> m (Image S (Alpha X) Word8, Metadatas)
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
PNG -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataPNG PNG
f

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

instance Readable PNG (Image S (SRGB 'NonLinear) Word8) where
  decodeWithMetadataM :: PNG
-> ByteString -> m (Image S (SRGB 'NonLinear) Word8, Metadata PNG)
decodeWithMetadataM PNG
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
. PNG -> ByteString -> m (Image S RGB Word8, Metadatas)
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
PNG -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataPNG PNG
f

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

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

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

-- | Decode a Png Image
decodePNG :: (ColorModel cs e, MonadThrow m) => PNG -> B.ByteString -> m (Image S cs e)
decodePNG :: PNG -> ByteString -> m (Image S cs e)
decodePNG PNG
f ByteString
bs = PNG -> 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 PNG
f (ByteString -> Either String DynamicImage
JP.decodePng ByteString
bs)

-- | Decode a Png Image
decodeWithMetadataPNG ::
     (ColorModel cs e, MonadThrow m) => PNG -> B.ByteString -> m (Image S cs e, JP.Metadatas)
decodeWithMetadataPNG :: PNG -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataPNG PNG
f ByteString
bs = PNG
-> Either String (DynamicImage, Metadata PNG)
-> m (Image S cs e, Metadata PNG)
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 PNG
f (ByteString -> Either String (DynamicImage, Metadatas)
JP.decodePngWithMetadata ByteString
bs)


-- | Decode a Png Image
decodeAutoPNG ::
     (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m)
  => Auto PNG
  -> B.ByteString
  -> m (Image r cs e)
decodeAutoPNG :: Auto PNG -> ByteString -> m (Image r cs e)
decodeAutoPNG Auto PNG
f ByteString
bs = Auto PNG -> 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 PNG
f (ByteString -> Either String DynamicImage
JP.decodePng ByteString
bs)

-- | Decode a Png Image
decodeAutoWithMetadataPNG ::
     (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m)
  => Auto PNG
  -> B.ByteString
  -> m (Image r cs e, JP.Metadatas)
decodeAutoWithMetadataPNG :: Auto PNG -> ByteString -> m (Image r cs e, Metadatas)
decodeAutoWithMetadataPNG Auto PNG
f ByteString
bs = Auto PNG
-> Either String (DynamicImage, Metadata PNG)
-> m (Image r cs e, Metadata PNG)
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 PNG
f (ByteString -> Either String (DynamicImage, Metadatas)
JP.decodePngWithMetadata ByteString
bs)

instance (Mutable r Ix2 (Pixel cs e), ColorSpace cs i e) =>
         Readable (Auto PNG) (Image r cs e) where
  decodeM :: Auto PNG -> ByteString -> m (Image r cs e)
decodeM = Auto PNG -> 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 PNG -> ByteString -> m (Image r cs e)
decodeAutoPNG
  decodeWithMetadataM :: Auto PNG -> ByteString -> m (Image r cs e, Metadata (Auto PNG))
decodeWithMetadataM = Auto PNG -> ByteString -> m (Image r cs e, Metadata (Auto PNG))
forall r cs e i (m :: * -> *).
(Mutable r Ix2 (Pixel cs e), ColorSpace cs i e, MonadThrow m) =>
Auto PNG -> ByteString -> m (Image r cs e, Metadatas)
decodeAutoWithMetadataPNG

encodePNG ::
     forall cs e m. (ColorModel cs e, MonadThrow m)
  => PNG
  -> Image S cs e
  -> m BL.ByteString
encodePNG :: PNG -> Image S cs e -> m ByteString
encodePNG PNG
f Image S cs e
img =
  PNG -> 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 PNG
f (Proxy (Image S cs e)
forall k (t :: k). Proxy t
Proxy :: Proxy (Image S cs e)) (Maybe ByteString -> m ByteString)
-> Maybe ByteString -> m 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 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
           [ Image Word8 -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (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
           , Image PixelRGB8 -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (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
           , do cs :~: Alpha (Opaque cs)
Refl <- Maybe (cs :~: Alpha (Opaque cs))
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (cs :~: Alpha (Opaque cs))
                [Maybe ByteString] -> Maybe ByteString
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum [Image PixelYA8 -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (Image PixelYA8 -> ByteString)
-> Maybe (Image PixelYA8) -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Image S (Alpha (Opaque cs)) Word8 -> Maybe (Image PixelYA8)
forall cs.
(Typeable cs, Source S Ix2 (Pixel (Alpha cs) Word8)) =>
Image S (Alpha cs) Word8 -> Maybe (Image PixelYA8)
maybeJPImageYA8 Image S cs e
Image S (Alpha (Opaque cs)) Word8
img, Image PixelRGBA8 -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (Image PixelRGBA8 -> ByteString)
-> Maybe (Image PixelRGBA8) -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Image S (Alpha (Opaque cs)) Word8 -> Maybe (Image PixelRGBA8)
forall cs.
(Typeable cs, Source S Ix2 (Pixel (Alpha cs) Word8)) =>
Image S (Alpha cs) Word8 -> Maybe (Image PixelRGBA8)
maybeJPImageRGBA8 Image S cs e
Image S (Alpha (Opaque cs)) Word8
img]
           ]
    , do e :~: Word16
Refl <- Maybe (e :~: Word16)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (e :~: Word16)
         [Maybe ByteString] -> Maybe ByteString
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum
           [ Image Word16 -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (Image Word16 -> ByteString)
-> Maybe (Image Word16) -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Image S cs Word16 -> Maybe (Image Word16)
forall cs.
(Typeable cs, Source S Ix2 (Pixel cs Word16)) =>
Image S cs Word16 -> Maybe (Image Word16)
maybeJPImageY16 Image S cs e
Image S cs Word16
img
           , Image PixelRGB16 -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (Image PixelRGB16 -> ByteString)
-> Maybe (Image PixelRGB16) -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Image S cs Word16 -> Maybe (Image PixelRGB16)
forall cs.
(Typeable cs, Source S Ix2 (Pixel cs Word16)) =>
Image S cs Word16 -> Maybe (Image PixelRGB16)
maybeJPImageRGB16 Image S cs e
Image S cs Word16
img
           , do cs :~: Alpha (Opaque cs)
Refl <- Maybe (cs :~: Alpha (Opaque cs))
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (cs :~: Alpha (Opaque cs))
                [Maybe ByteString] -> Maybe ByteString
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum
                  [Image PixelYA16 -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (Image PixelYA16 -> ByteString)
-> Maybe (Image PixelYA16) -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Image S (Alpha (Opaque cs)) Word16 -> Maybe (Image PixelYA16)
forall cs.
(Typeable cs, Source S Ix2 (Pixel (Alpha cs) Word16)) =>
Image S (Alpha cs) Word16 -> Maybe (Image PixelYA16)
maybeJPImageYA16 Image S cs e
Image S (Alpha (Opaque cs)) Word16
img, Image PixelRGBA16 -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (Image PixelRGBA16 -> ByteString)
-> Maybe (Image PixelRGBA16) -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Image S (Alpha (Opaque cs)) Word16 -> Maybe (Image PixelRGBA16)
forall cs.
(Typeable cs, Source S Ix2 (Pixel (Alpha cs) Word16)) =>
Image S (Alpha cs) Word16 -> Maybe (Image PixelRGBA16)
maybeJPImageRGBA16 Image S cs e
Image S (Alpha (Opaque cs)) Word16
img]
           ]
    ]


encodeAutoPNG ::
     forall r cs i e. (ColorSpace (BaseSpace cs) i e, ColorSpace cs i e, Source r Ix2 (Pixel cs e))
  => Auto PNG
  -> Image r cs e
  -> BL.ByteString
encodeAutoPNG :: Auto PNG -> Image r cs e -> ByteString
encodeAutoPNG Auto PNG
_ Image r cs e
img =
  ByteString -> Maybe ByteString -> ByteString
forall a. a -> Maybe a -> a
fromMaybe ((Array D Ix2 (Pixel RGB Word16) -> Image PixelRGB16)
-> (Pixel cs e -> Pixel RGB Word16) -> Image r cs e -> ByteString
forall px ix a b.
(PngSavable px, Source r ix a) =>
(Array D ix b -> Image px)
-> (a -> b) -> Array r ix a -> ByteString
toPng Array D Ix2 (Pixel RGB Word16) -> Image PixelRGB16
forall r.
Source r Ix2 (Pixel RGB Word16) =>
Image r RGB Word16 -> Image PixelRGB16
toJPImageRGB16 Pixel cs e -> Pixel RGB Word16
forall cs i e. ColorSpace cs i e => Pixel cs e -> Pixel RGB Word16
toSRGB16 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.
(PngSavable px, Source r ix a) =>
(Array D ix b -> Image px)
-> (a -> b) -> Array r ix a -> ByteString
toPng 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 e :~: Word8
Refl <- Maybe (e :~: Word8)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (e :~: Word8)
                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 Word8 -> Pixel X Word8)
-> Array r Ix2 (Pixel cs Word8)
-> ByteString
forall px ix a b.
(PngSavable px, Source r ix a) =>
(Array D ix b -> Image px)
-> (a -> b) -> Array r ix a -> ByteString
toPng Array D Ix2 (Pixel X Word8) -> Image Word8
forall r.
Source r Ix2 (Pixel X Word8) =>
Image r X Word8 -> Image Word8
toJPImageY8 Pixel cs Word8 -> Pixel X Word8
forall k cs (i :: k) e.
ColorSpace cs i e =>
Pixel cs e -> Pixel (BaseModel cs) e
toPixelBaseModel Image r cs e
Array r Ix2 (Pixel cs Word8)
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 Word16) -> Image Word16)
-> (Pixel cs e -> Pixel X Word16) -> Image r cs e -> ByteString
forall px ix a b.
(PngSavable px, Source r ix a) =>
(Array D ix b -> Image px)
-> (a -> b) -> Array r ix a -> ByteString
toPng Array D Ix2 (Pixel X Word16) -> Image Word16
forall r.
Source r Ix2 (Pixel X Word16) =>
Image r X Word16 -> Image Word16
toJPImageY16 (Pixel X e -> Pixel X Word16
forall cs e. ColorModel cs e => Pixel cs e -> Pixel cs Word16
toPixel16 (Pixel X e -> Pixel X Word16)
-> (Pixel cs e -> Pixel X e) -> Pixel cs e -> Pixel X Word16
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 :~: Alpha X
Refl <- Maybe (BaseModel cs :~: Alpha X)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (BaseModel cs :~: Alpha CM.X)
         [Maybe ByteString] -> Maybe ByteString
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum
           [ do e :~: Word8
Refl <- Maybe (e :~: Word8)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (e :~: Word8)
                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 (Alpha X) Word8) -> Image PixelYA8)
-> (Pixel cs Word8 -> Pixel (Alpha X) Word8)
-> Array r Ix2 (Pixel cs Word8)
-> ByteString
forall px ix a b.
(PngSavable px, Source r ix a) =>
(Array D ix b -> Image px)
-> (a -> b) -> Array r ix a -> ByteString
toPng Array D Ix2 (Pixel (Alpha X) Word8) -> Image PixelYA8
forall r.
Source r Ix2 (Pixel (Alpha X) Word8) =>
Image r (Alpha X) Word8 -> Image PixelYA8
toJPImageYA8 Pixel cs Word8 -> Pixel (Alpha X) Word8
forall k cs (i :: k) e.
ColorSpace cs i e =>
Pixel cs e -> Pixel (BaseModel cs) e
toPixelBaseModel Image r cs e
Array r Ix2 (Pixel cs Word8)
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 (Alpha X) Word16) -> Image PixelYA16)
-> (Pixel cs e -> Pixel (Alpha X) Word16)
-> Image r cs e
-> ByteString
forall px ix a b.
(PngSavable px, Source r ix a) =>
(Array D ix b -> Image px)
-> (a -> b) -> Array r ix a -> ByteString
toPng Array D Ix2 (Pixel (Alpha X) Word16) -> Image PixelYA16
forall r.
Source r Ix2 (Pixel (Alpha X) Word16) =>
Image r (Alpha X) Word16 -> Image PixelYA16
toJPImageYA16 (Pixel (Alpha X) e -> Pixel (Alpha X) Word16
forall cs e. ColorModel cs e => Pixel cs e -> Pixel cs Word16
toPixel16 (Pixel (Alpha X) e -> Pixel (Alpha X) Word16)
-> (Pixel cs e -> Pixel (Alpha X) e)
-> Pixel cs e
-> Pixel (Alpha X) Word16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pixel cs e -> Pixel (Alpha 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 cs :~: Alpha (Opaque cs)
Refl <- Maybe (cs :~: Alpha (Opaque cs))
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (cs :~: Alpha (Opaque cs))
         [Maybe ByteString] -> Maybe ByteString
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum
           [ do e :~: Word8
Refl <- Maybe (e :~: Word8)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (e :~: Word8)
                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 (Alpha RGB) Word8) -> Image PixelRGBA8)
-> (Pixel cs e -> Pixel (Alpha RGB) Word8)
-> Image r cs e
-> ByteString
forall px ix a b.
(PngSavable px, Source r ix a) =>
(Array D ix b -> Image px)
-> (a -> b) -> Array r ix a -> ByteString
toPng Array D Ix2 (Pixel (Alpha RGB) Word8) -> Image PixelRGBA8
forall r.
Source r Ix2 (Pixel (Alpha RGB) Word8) =>
Image r (Alpha RGB) Word8 -> Image PixelRGBA8
toJPImageRGBA8 Pixel cs e -> Pixel (Alpha RGB) Word8
forall cs i e.
ColorSpace cs i e =>
Pixel cs e -> Pixel (Alpha RGB) Word8
toSRGBA8 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 (Alpha RGB) Word16) -> Image PixelRGBA16)
-> (Pixel cs e -> Pixel (Alpha RGB) Word16)
-> Image r cs e
-> ByteString
forall px ix a b.
(PngSavable px, Source r ix a) =>
(Array D ix b -> Image px)
-> (a -> b) -> Array r ix a -> ByteString
toPng Array D Ix2 (Pixel (Alpha RGB) Word16) -> Image PixelRGBA16
forall r.
Source r Ix2 (Pixel (Alpha RGB) Word16) =>
Image r (Alpha RGB) Word16 -> Image PixelRGBA16
toJPImageRGBA16 Pixel cs e -> Pixel (Alpha RGB) Word16
forall cs i e.
ColorSpace cs i e =>
Pixel cs e -> Pixel (Alpha RGB) Word16
toSRGBA16 Image r cs e
img
           ]
    , do e :~: Word8
Refl <- Maybe (e :~: Word8)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (e :~: Word8)
         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.
(PngSavable px, Source r ix a) =>
(Array D ix b -> Image px)
-> (a -> b) -> Array r ix a -> ByteString
toPng 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
    toPng ::
         (JP.PngSavable px, Source r ix a)
      => (Array D ix b -> JP.Image px)
      -> (a -> b)
      -> Array r ix a
      -> BL.ByteString
    toPng :: (Array D ix b -> Image px)
-> (a -> b) -> Array r ix a -> ByteString
toPng Array D ix b -> Image px
toJP a -> b
adjustPixel = Image px -> ByteString
forall a. PngSavable a => Image a -> ByteString
JP.encodePng (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