{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Massiv.Array.IO.Image.JuicyPixels.GIF
( GIF(..)
, GifOptions(..)
, SequenceGifOptions(..)
, JP.GifDelay
, JP.GifLooping(..)
, JP.PaletteOptions(..)
, JP.PaletteCreationMethod(..)
, JP.GifDisposalMethod(..)
, decodeGIF
, decodeWithMetadataGIF
, decodeAutoGIF
, decodeAutoWithMetadataGIF
, encodeGIF
, encodeAutoGIF
, decodeSequenceGIF
, decodeSequenceWithMetadataGIF
, decodeAutoSequenceGIF
, decodeAutoSequenceWithMetadataGIF
) where
import qualified Codec.Picture as JP
import qualified Codec.Picture.ColorQuant as JP
import qualified Codec.Picture.Gif 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.List.NonEmpty as NE
import Data.Massiv.Array as A
import Data.Massiv.Array.IO.Base
import Data.Massiv.Array.IO.Image.JuicyPixels.Base
import Data.Typeable
import qualified Graphics.Pixel as CM
import Graphics.Pixel.ColorSpace
import Prelude as P
newtype GifOptions = GifOptions
{ GifOptions -> PaletteOptions
gifPaletteOptions :: JP.PaletteOptions
}
instance Default GifOptions where
def :: GifOptions
def = PaletteOptions -> GifOptions
GifOptions PaletteOptions
JP.defaultPaletteOptions
data GIF = GIF deriving Int -> GIF -> ShowS
[GIF] -> ShowS
GIF -> String
(Int -> GIF -> ShowS)
-> (GIF -> String) -> ([GIF] -> ShowS) -> Show GIF
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GIF] -> ShowS
$cshowList :: [GIF] -> ShowS
show :: GIF -> String
$cshow :: GIF -> String
showsPrec :: Int -> GIF -> ShowS
$cshowsPrec :: Int -> GIF -> ShowS
Show
instance FileFormat GIF where
type WriteOptions GIF = GifOptions
type Metadata GIF = JP.Metadatas
ext :: GIF -> String
ext GIF
_ = String
".gif"
instance Writable GIF (Image A.S CM.X Bit) where
encodeM :: GIF -> WriteOptions GIF -> Image S X Bit -> m ByteString
encodeM GIF
f WriteOptions GIF
opts Image S X Bit
img = GIF -> WriteOptions GIF -> Matrix S (Pixel X Word8) -> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM GIF
f WriteOptions GIF
opts (Image S X Bit -> Matrix S (Pixel X Word8)
coerceBinaryImage Image S X Bit
img)
instance Writable GIF (Image S CM.X Word8) where
encodeM :: GIF -> WriteOptions GIF -> Matrix S (Pixel X Word8) -> m ByteString
encodeM GIF
GIF WriteOptions GIF
_ = ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> m ByteString)
-> (Matrix S (Pixel X Word8) -> ByteString)
-> Matrix S (Pixel X Word8)
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Image Word8 -> ByteString
JP.encodeGifImage (Image Word8 -> ByteString)
-> (Matrix S (Pixel X Word8) -> Image Word8)
-> Matrix S (Pixel X Word8)
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Matrix S (Pixel X Word8) -> Image Word8
forall r.
Source r (Pixel X Word8) =>
Image r X Word8 -> Image Word8
toJPImageY8
instance Writable GIF (Image S CM.RGB Word8) where
encodeM :: GIF -> WriteOptions GIF -> Image S RGB Word8 -> m ByteString
encodeM GIF
GIF = WriteOptions GIF -> Image S RGB Word8 -> m ByteString
forall (m :: * -> *) r.
(MonadThrow m, Source r (Pixel RGB Word8)) =>
GifOptions -> Image r RGB Word8 -> m ByteString
encodePalettizedRGB
instance Writable GIF (Image S (Y' SRGB) Word8) where
encodeM :: GIF -> WriteOptions GIF -> Image S (Y' SRGB) Word8 -> m ByteString
encodeM GIF
GIF WriteOptions GIF
opts = GIF -> WriteOptions GIF -> Matrix S (Pixel X Word8) -> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM GIF
GIF WriteOptions GIF
opts (Matrix S (Pixel X Word8) -> m ByteString)
-> (Image S (Y' SRGB) Word8 -> Matrix S (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 -> Matrix S (Pixel X Word8)
forall cs e.
Matrix S (Pixel cs e) -> Matrix S (Pixel (BaseModel cs) e)
toImageBaseModel
instance Writable GIF (Image S (Y D65) Word8) where
encodeM :: GIF -> WriteOptions GIF -> Image S (Y D65) Word8 -> m ByteString
encodeM GIF
GIF WriteOptions GIF
opts = GIF -> WriteOptions GIF -> Matrix S (Pixel X Word8) -> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM GIF
GIF WriteOptions GIF
opts (Matrix S (Pixel X Word8) -> m ByteString)
-> (Image S (Y D65) Word8 -> Matrix S (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 -> Matrix S (Pixel X Word8)
forall cs e.
Matrix S (Pixel cs e) -> Matrix S (Pixel (BaseModel cs) e)
toImageBaseModel
instance Writable GIF (Image S (SRGB 'NonLinear) Word8) where
encodeM :: GIF
-> WriteOptions GIF
-> Image S (SRGB 'NonLinear) Word8
-> m ByteString
encodeM GIF
GIF WriteOptions GIF
opts = GIF -> WriteOptions GIF -> Image S RGB Word8 -> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM GIF
GIF WriteOptions GIF
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.
Matrix S (Pixel cs e) -> Matrix S (Pixel (BaseModel cs) e)
toImageBaseModel
encodePalettizedRGB ::
(MonadThrow m, Source r (Pixel CM.RGB Word8))
=> GifOptions
-> Image r CM.RGB Word8
-> m BL.ByteString
encodePalettizedRGB :: GifOptions -> Image r RGB Word8 -> m ByteString
encodePalettizedRGB GifOptions {PaletteOptions
gifPaletteOptions :: PaletteOptions
gifPaletteOptions :: GifOptions -> PaletteOptions
gifPaletteOptions} =
Either String ByteString -> m ByteString
forall (m :: * -> *) a. MonadThrow m => Either String a -> m a
encodeError (Either String ByteString -> m ByteString)
-> (Image r RGB Word8 -> Either String ByteString)
-> Image r RGB Word8
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(Image Word8 -> Palette -> Either String ByteString)
-> (Image Word8, Palette) -> Either String ByteString
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Image Word8 -> Palette -> Either String ByteString
JP.encodeGifImageWithPalette ((Image Word8, Palette) -> Either String ByteString)
-> (Image r RGB Word8 -> (Image Word8, Palette))
-> Image r RGB Word8
-> Either String ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PaletteOptions -> Palette -> (Image Word8, Palette)
JP.palettize PaletteOptions
gifPaletteOptions (Palette -> (Image Word8, Palette))
-> (Image r RGB Word8 -> Palette)
-> Image r RGB Word8
-> (Image Word8, Palette)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Image r RGB Word8 -> Palette
forall r.
Source r (Pixel RGB Word8) =>
Image r RGB Word8 -> Palette
toJPImageRGB8
instance (ColorSpace cs i e, ColorSpace (BaseSpace cs) i e, Source r (Pixel cs e)) =>
Writable (Auto GIF) (Image r cs e) where
encodeM :: Auto GIF -> WriteOptions (Auto GIF) -> Image r cs e -> m ByteString
encodeM = Auto GIF -> WriteOptions (Auto GIF) -> Image r cs e -> m ByteString
forall r cs i e (m :: * -> *).
(ColorSpace cs i e, Source r (Pixel cs e), MonadThrow m) =>
Auto GIF -> GifOptions -> Image r cs e -> m ByteString
encodeAutoGIF
instance Readable GIF (Image S CM.RGB Word8) where
decodeM :: GIF -> ByteString -> m (Image S RGB Word8)
decodeM = GIF -> ByteString -> m (Image S RGB Word8)
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
GIF -> ByteString -> m (Image S cs e)
decodeGIF
decodeWithMetadataM :: GIF -> ByteString -> m (Image S RGB Word8, Metadata GIF)
decodeWithMetadataM = GIF -> ByteString -> m (Image S RGB Word8, Metadata GIF)
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
GIF -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataGIF
instance Readable GIF (Image S (Alpha CM.RGB) Word8) where
decodeM :: GIF -> ByteString -> m (Image S (Alpha RGB) Word8)
decodeM = GIF -> ByteString -> m (Image S (Alpha RGB) Word8)
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
GIF -> ByteString -> m (Image S cs e)
decodeGIF
decodeWithMetadataM :: GIF -> ByteString -> m (Image S (Alpha RGB) Word8, Metadata GIF)
decodeWithMetadataM = GIF -> ByteString -> m (Image S (Alpha RGB) Word8, Metadata GIF)
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
GIF -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataGIF
instance Readable GIF (Image S (SRGB 'NonLinear) Word8) where
decodeM :: GIF -> ByteString -> m (Image S (SRGB 'NonLinear) Word8)
decodeM GIF
f = (Image S RGB Word8 -> Image S (SRGB 'NonLinear) Word8)
-> m (Image S RGB Word8) -> m (Image S (SRGB 'NonLinear) Word8)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Image S RGB Word8 -> Image S (SRGB 'NonLinear) Word8
forall cs e.
Matrix S (Pixel (BaseModel cs) e) -> Matrix S (Pixel cs e)
fromImageBaseModel (m (Image S RGB Word8) -> m (Image S (SRGB 'NonLinear) Word8))
-> (ByteString -> m (Image S RGB Word8))
-> ByteString
-> m (Image S (SRGB 'NonLinear) Word8)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GIF -> ByteString -> m (Image S RGB Word8)
forall f arr (m :: * -> *).
(Readable f arr, MonadThrow m) =>
f -> ByteString -> m arr
decodeM GIF
f
decodeWithMetadataM :: GIF
-> ByteString -> m (Image S (SRGB 'NonLinear) Word8, Metadata GIF)
decodeWithMetadataM GIF
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.
Matrix S (Pixel (BaseModel cs) e) -> Matrix S (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
. GIF -> ByteString -> m (Image S RGB Word8, Metadata GIF)
forall f arr (m :: * -> *).
(Readable f arr, MonadThrow m) =>
f -> ByteString -> m (arr, Metadata f)
decodeWithMetadataM GIF
f
instance Readable GIF (Image S (Alpha (SRGB 'NonLinear)) Word8) where
decodeM :: GIF -> ByteString -> m (Image S (Alpha (SRGB 'NonLinear)) Word8)
decodeM GIF
f = (Image S (Alpha RGB) Word8
-> Image S (Alpha (SRGB 'NonLinear)) Word8)
-> m (Image S (Alpha RGB) Word8)
-> m (Image S (Alpha (SRGB 'NonLinear)) Word8)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Image S (Alpha RGB) Word8
-> Image S (Alpha (SRGB 'NonLinear)) Word8
forall cs e.
Matrix S (Pixel (BaseModel cs) e) -> Matrix S (Pixel cs e)
fromImageBaseModel (m (Image S (Alpha RGB) Word8)
-> m (Image S (Alpha (SRGB 'NonLinear)) Word8))
-> (ByteString -> m (Image S (Alpha RGB) Word8))
-> ByteString
-> m (Image S (Alpha (SRGB 'NonLinear)) Word8)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GIF -> ByteString -> m (Image S (Alpha RGB) Word8)
forall f arr (m :: * -> *).
(Readable f arr, MonadThrow m) =>
f -> ByteString -> m arr
decodeM GIF
f
decodeWithMetadataM :: GIF
-> ByteString
-> m (Image S (Alpha (SRGB 'NonLinear)) Word8, Metadata GIF)
decodeWithMetadataM GIF
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.
Matrix S (Pixel (BaseModel cs) e) -> Matrix S (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
. GIF -> ByteString -> m (Image S (Alpha RGB) Word8, Metadata GIF)
forall f arr (m :: * -> *).
(Readable f arr, MonadThrow m) =>
f -> ByteString -> m (arr, Metadata f)
decodeWithMetadataM GIF
f
decodeGIF :: (ColorModel cs e, MonadThrow m) => GIF -> B.ByteString -> m (Image S cs e)
decodeGIF :: GIF -> ByteString -> m (Image S cs e)
decodeGIF GIF
f ByteString
bs = GIF -> 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 GIF
f (ByteString -> Either String DynamicImage
JP.decodeGif ByteString
bs)
{-# INLINE decodeGIF #-}
decodeWithMetadataGIF ::
(ColorModel cs e, MonadThrow m) => GIF -> B.ByteString -> m (Image S cs e, JP.Metadatas)
decodeWithMetadataGIF :: GIF -> ByteString -> m (Image S cs e, Metadatas)
decodeWithMetadataGIF GIF
f ByteString
bs = GIF
-> Either String (DynamicImage, Metadata GIF)
-> m (Image S cs e, Metadata GIF)
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 GIF
f (ByteString -> Either String (DynamicImage, Metadatas)
JP.decodeGifWithMetadata ByteString
bs)
{-# INLINE decodeWithMetadataGIF #-}
decodeAutoGIF ::
(Manifest r (Pixel cs e), ColorSpace cs i e, MonadThrow m)
=> Auto GIF
-> B.ByteString
-> m (Image r cs e)
decodeAutoGIF :: Auto GIF -> ByteString -> m (Image r cs e)
decodeAutoGIF Auto GIF
f ByteString
bs = Auto GIF -> Either String DynamicImage -> m (Image r cs e)
forall (m :: * -> *) r cs e i f.
(MonadThrow m, Manifest r (Pixel cs e), ColorSpace cs i e) =>
Auto f -> Either String DynamicImage -> m (Image r cs e)
convertAutoWith Auto GIF
f (ByteString -> Either String DynamicImage
JP.decodeGif ByteString
bs)
{-# INLINE decodeAutoGIF #-}
decodeAutoWithMetadataGIF ::
(Manifest r (Pixel cs e), ColorSpace cs i e, MonadThrow m)
=> Auto GIF
-> B.ByteString
-> m (Image r cs e, JP.Metadatas)
decodeAutoWithMetadataGIF :: Auto GIF -> ByteString -> m (Image r cs e, Metadatas)
decodeAutoWithMetadataGIF Auto GIF
f ByteString
bs = Auto GIF
-> Either String (DynamicImage, Metadata GIF)
-> m (Image r cs e, Metadata GIF)
forall (m :: * -> *) r cs e i f.
(MonadThrow m, Manifest r (Pixel cs e), ColorSpace cs i e) =>
Auto f
-> Either String (DynamicImage, Metadata f)
-> m (Image r cs e, Metadata f)
convertAutoWithMetadata Auto GIF
f (ByteString -> Either String (DynamicImage, Metadatas)
JP.decodeGifWithMetadata ByteString
bs)
{-# INLINE decodeAutoWithMetadataGIF #-}
instance (Manifest r (Pixel cs e), ColorSpace cs i e) =>
Readable (Auto GIF) (Image r cs e) where
decodeM :: Auto GIF -> ByteString -> m (Image r cs e)
decodeM = Auto GIF -> ByteString -> m (Image r cs e)
forall r cs e i (m :: * -> *).
(Manifest r (Pixel cs e), ColorSpace cs i e, MonadThrow m) =>
Auto GIF -> ByteString -> m (Image r cs e)
decodeAutoGIF
decodeWithMetadataM :: Auto GIF -> ByteString -> m (Image r cs e, Metadata (Auto GIF))
decodeWithMetadataM = Auto GIF -> ByteString -> m (Image r cs e, Metadata (Auto GIF))
forall r cs e i (m :: * -> *).
(Manifest r (Pixel cs e), ColorSpace cs i e, MonadThrow m) =>
Auto GIF -> ByteString -> m (Image r cs e, Metadatas)
decodeAutoWithMetadataGIF
encodeGIF ::
forall cs e m. (ColorModel cs e, MonadThrow m)
=> GIF
-> GifOptions
-> Image S cs e
-> m BL.ByteString
encodeGIF :: GIF -> GifOptions -> Image S cs e -> m ByteString
encodeGIF GIF
f GifOptions
opts Image S cs e
img =
Maybe ByteString -> m ByteString
fallbackEncodePalettizedRGB (Maybe ByteString -> m ByteString)
-> Maybe ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ do
e :~: Word8
Refl <- Maybe (e :~: Word8)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (e :~: Word8)
Image Word8 -> ByteString
JP.encodeGifImage (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, Storable (Pixel cs Word8)) =>
Image S cs Word8 -> Maybe (Image Word8)
maybeJPImageY8 Image S cs e
Image S cs Word8
img
where
fallbackEncodePalettizedRGB :: Maybe ByteString -> m ByteString
fallbackEncodePalettizedRGB =
\case
Just ByteString
bs -> ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
bs
Maybe ByteString
Nothing
| 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)) ->
GIF -> WriteOptions GIF -> Image S cs e -> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM GIF
f WriteOptions GIF
GifOptions
opts Image S cs e
img
| Just Pixel cs e :~: Pixel RGB Word8
Refl <- (Maybe (Pixel cs e :~: Pixel RGB Word8)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (Pixel cs e :~: Pixel CM.RGB Word8)) ->
GifOptions -> Image S RGB Word8 -> m ByteString
forall (m :: * -> *) r.
(MonadThrow m, Source r (Pixel RGB Word8)) =>
GifOptions -> Image r RGB Word8 -> m ByteString
encodePalettizedRGB GifOptions
opts Image S cs e
Image S RGB Word8
img
| Just Pixel cs e :~: Pixel (SRGB 'NonLinear) Word8
Refl <- (Maybe (Pixel cs e :~: Pixel (SRGB 'NonLinear) Word8)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (Pixel cs e :~: Pixel (SRGB 'NonLinear) Word8)) ->
GifOptions -> Image S RGB Word8 -> m ByteString
forall (m :: * -> *) r.
(MonadThrow m, Source r (Pixel RGB Word8)) =>
GifOptions -> Image r RGB Word8 -> m ByteString
encodePalettizedRGB GifOptions
opts (Image S RGB Word8 -> m ByteString)
-> Image S RGB Word8 -> m ByteString
forall a b. (a -> b) -> a -> b
$ Image S cs e -> Matrix S (Pixel (BaseModel cs) e)
forall cs e.
Matrix S (Pixel cs e) -> Matrix S (Pixel (BaseModel cs) e)
toImageBaseModel Image S cs e
img
| Just Pixel cs e :~: Pixel (AdobeRGB 'NonLinear) Word8
Refl <- (Maybe (Pixel cs e :~: Pixel (AdobeRGB 'NonLinear) Word8)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (Pixel cs e :~: Pixel (AdobeRGB 'NonLinear) Word8)) ->
GifOptions -> Image S RGB Word8 -> m ByteString
forall (m :: * -> *) r.
(MonadThrow m, Source r (Pixel RGB Word8)) =>
GifOptions -> Image r RGB Word8 -> m ByteString
encodePalettizedRGB GifOptions
opts (Image S RGB Word8 -> m ByteString)
-> Image S RGB Word8 -> m ByteString
forall a b. (a -> b) -> a -> b
$ Image S cs e -> Matrix S (Pixel (BaseModel cs) e)
forall cs e.
Matrix S (Pixel cs e) -> Matrix S (Pixel (BaseModel cs) e)
toImageBaseModel Image S cs e
img
Maybe ByteString
Nothing -> GIF -> 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 GIF
f (Proxy (Image S cs e)
forall k (t :: k). Proxy t
Proxy :: Proxy (Image S cs e)) Maybe ByteString
forall a. Maybe a
Nothing
encodeAutoGIF ::
forall r cs i e m. (ColorSpace cs i e, Source r (Pixel cs e), MonadThrow m)
=> Auto GIF
-> GifOptions
-> Image r cs e
-> m BL.ByteString
encodeAutoGIF :: Auto GIF -> GifOptions -> Image r cs e -> m ByteString
encodeAutoGIF Auto GIF
_ GifOptions
opts Image r cs e
img =
Maybe ByteString -> m ByteString
fallbackEncodePalettizedRGB (Maybe ByteString -> m ByteString)
-> Maybe ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$ do
[Maybe ByteString] -> Maybe ByteString
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum
[ do r :~: S
Refl <- Maybe (r :~: S)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (r :~: S)
case Maybe (e :~: Word8)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT :: Maybe (e :~: Word8) of
Just e :~: Word8
Refl
| Just 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)) ->
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
$ Image Word8 -> ByteString
JP.encodeGifImage (Image Word8 -> ByteString) -> Image Word8 -> ByteString
forall a b. (a -> b) -> a -> b
$ Matrix S (Pixel X Word8) -> Image Word8
forall r.
Source r (Pixel X Word8) =>
Image r X Word8 -> Image Word8
toJPImageY8 (Matrix S (Pixel cs e) -> Matrix S (Pixel (BaseModel cs) e)
forall cs e.
Matrix S (Pixel cs e) -> Matrix S (Pixel (BaseModel cs) e)
toImageBaseModel Image r cs e
Matrix S (Pixel cs e)
img)
| Just 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)) ->
GifOptions -> Image S RGB Word8 -> Maybe ByteString
forall (m :: * -> *) r.
(MonadThrow m, Source r (Pixel RGB Word8)) =>
GifOptions -> Image r RGB Word8 -> m ByteString
encodePalettizedRGB GifOptions
opts (Matrix S (Pixel cs e) -> Matrix S (Pixel (BaseModel cs) e)
forall cs e.
Matrix S (Pixel cs e) -> Matrix S (Pixel (BaseModel cs) e)
toImageBaseModel Image r cs e
Matrix S (Pixel cs e)
img)
Maybe (e :~: Word8)
_ -> Maybe ByteString
forall a. Maybe a
Nothing
, 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)
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
$ Image Word8 -> ByteString
JP.encodeGifImage (Image Word8 -> ByteString) -> Image Word8 -> ByteString
forall a b. (a -> b) -> a -> b
$ Image D X Word8 -> Image Word8
forall r.
Source r (Pixel X Word8) =>
Image r X Word8 -> Image Word8
toJPImageY8 (Image D X Word8 -> Image Word8) -> Image D X Word8 -> Image Word8
forall a b. (a -> b) -> a -> b
$ (Pixel cs e -> Pixel X Word8) -> Image r cs e -> Image D X Word8
forall ix r e' e.
(Index ix, Source r e') =>
(e' -> e) -> Array r ix e' -> Array D ix e
A.map (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
]
where
fallbackEncodePalettizedRGB :: Maybe ByteString -> m ByteString
fallbackEncodePalettizedRGB =
\case
Just ByteString
bs -> ByteString -> m ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
bs
Maybe ByteString
Nothing -> GifOptions -> Image D RGB Word8 -> m ByteString
forall (m :: * -> *) r.
(MonadThrow m, Source r (Pixel RGB Word8)) =>
GifOptions -> Image r RGB Word8 -> m ByteString
encodePalettizedRGB GifOptions
opts (Image D RGB Word8 -> m ByteString)
-> Image D RGB Word8 -> m ByteString
forall a b. (a -> b) -> a -> b
$ (Pixel cs e -> Pixel RGB Word8)
-> Image r cs e -> Image D RGB Word8
forall ix r e' e.
(Index ix, Source r e') =>
(e' -> e) -> Array r ix e' -> Array D ix e
A.map 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
data SequenceGifOptions = SequenceGifOptions
{ SequenceGifOptions -> PaletteOptions
sequenceGifPaletteOptions :: !JP.PaletteOptions
, SequenceGifOptions -> GifLooping
sequenceGifLooping :: !JP.GifLooping
}
instance Default SequenceGifOptions where
def :: SequenceGifOptions
def =
SequenceGifOptions :: PaletteOptions -> GifLooping -> SequenceGifOptions
SequenceGifOptions
{sequenceGifPaletteOptions :: PaletteOptions
sequenceGifPaletteOptions = PaletteOptions
JP.defaultPaletteOptions, sequenceGifLooping :: GifLooping
sequenceGifLooping = GifLooping
JP.LoopingNever}
instance FileFormat (Sequence GIF) where
type WriteOptions (Sequence GIF) = SequenceGifOptions
type Metadata (Sequence GIF) = [JP.GifDelay]
ext :: Sequence GIF -> String
ext Sequence GIF
_ = GIF -> String
forall f. FileFormat f => f -> String
ext GIF
GIF
instance Readable (Sequence GIF) [Image S CM.RGB Word8] where
decodeM :: Sequence GIF -> ByteString -> m [Image S RGB Word8]
decodeM = Sequence GIF -> ByteString -> m [Image S RGB Word8]
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
Sequence GIF -> ByteString -> m [Image S cs e]
decodeSequenceGIF
decodeWithMetadataM :: Sequence GIF
-> ByteString -> m ([Image S RGB Word8], Metadata (Sequence GIF))
decodeWithMetadataM = Sequence GIF
-> ByteString -> m ([Image S RGB Word8], Metadata (Sequence GIF))
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
Sequence GIF -> ByteString -> m ([Image S cs e], [Int])
decodeSequenceWithMetadataGIF
instance Readable (Sequence GIF) [Image S (Alpha CM.RGB) Word8] where
decodeM :: Sequence GIF -> ByteString -> m [Image S (Alpha RGB) Word8]
decodeM = Sequence GIF -> ByteString -> m [Image S (Alpha RGB) Word8]
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
Sequence GIF -> ByteString -> m [Image S cs e]
decodeSequenceGIF
decodeWithMetadataM :: Sequence GIF
-> ByteString
-> m ([Image S (Alpha RGB) Word8], Metadata (Sequence GIF))
decodeWithMetadataM = Sequence GIF
-> ByteString
-> m ([Image S (Alpha RGB) Word8], Metadata (Sequence GIF))
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
Sequence GIF -> ByteString -> m ([Image S cs e], [Int])
decodeSequenceWithMetadataGIF
instance Readable (Sequence GIF) [Image S (SRGB 'NonLinear) Word8] where
decodeM :: Sequence GIF -> ByteString -> m [Image S (SRGB 'NonLinear) Word8]
decodeM Sequence GIF
f = ([Image S RGB Word8] -> [Image S (SRGB 'NonLinear) Word8])
-> m [Image S RGB Word8] -> m [Image S (SRGB 'NonLinear) Word8]
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] -> [Image S (SRGB 'NonLinear) Word8]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Image S RGB Word8 -> Image S (SRGB 'NonLinear) Word8
forall cs e.
Matrix S (Pixel (BaseModel cs) e) -> Matrix S (Pixel cs e)
fromImageBaseModel) (m [Image S RGB Word8] -> m [Image S (SRGB 'NonLinear) Word8])
-> (ByteString -> m [Image S RGB Word8])
-> ByteString
-> m [Image S (SRGB 'NonLinear) Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sequence GIF -> ByteString -> m [Image S RGB Word8]
forall f arr (m :: * -> *).
(Readable f arr, MonadThrow m) =>
f -> ByteString -> m arr
decodeM Sequence GIF
f
decodeWithMetadataM :: Sequence GIF
-> ByteString
-> m ([Image S (SRGB 'NonLinear) Word8], Metadata (Sequence GIF))
decodeWithMetadataM Sequence GIF
f = (([Image S RGB Word8], [Int])
-> ([Image S (SRGB 'NonLinear) Word8], [Int]))
-> m ([Image S RGB Word8], [Int])
-> m ([Image S (SRGB 'NonLinear) Word8], [Int])
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], [Int])
-> ([Image S (SRGB 'NonLinear) Word8], [Int])
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)
-> [Image S RGB Word8] -> [Image S (SRGB 'NonLinear) Word8]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Image S RGB Word8 -> Image S (SRGB 'NonLinear) Word8
forall cs e.
Matrix S (Pixel (BaseModel cs) e) -> Matrix S (Pixel cs e)
fromImageBaseModel)) (m ([Image S RGB Word8], [Int])
-> m ([Image S (SRGB 'NonLinear) Word8], [Int]))
-> (ByteString -> m ([Image S RGB Word8], [Int]))
-> ByteString
-> m ([Image S (SRGB 'NonLinear) Word8], [Int])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sequence GIF
-> ByteString -> m ([Image S RGB Word8], Metadata (Sequence GIF))
forall f arr (m :: * -> *).
(Readable f arr, MonadThrow m) =>
f -> ByteString -> m (arr, Metadata f)
decodeWithMetadataM Sequence GIF
f
instance Readable (Sequence GIF) [Image S (Alpha (SRGB 'NonLinear)) Word8] where
decodeM :: Sequence GIF
-> ByteString -> m [Image S (Alpha (SRGB 'NonLinear)) Word8]
decodeM Sequence GIF
f = ([Image S (Alpha RGB) Word8]
-> [Image S (Alpha (SRGB 'NonLinear)) Word8])
-> m [Image S (Alpha RGB) Word8]
-> m [Image S (Alpha (SRGB 'NonLinear)) Word8]
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]
-> [Image S (Alpha (SRGB 'NonLinear)) Word8]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Image S (Alpha RGB) Word8
-> Image S (Alpha (SRGB 'NonLinear)) Word8
forall cs e.
Matrix S (Pixel (BaseModel cs) e) -> Matrix S (Pixel cs e)
fromImageBaseModel) (m [Image S (Alpha RGB) Word8]
-> m [Image S (Alpha (SRGB 'NonLinear)) Word8])
-> (ByteString -> m [Image S (Alpha RGB) Word8])
-> ByteString
-> m [Image S (Alpha (SRGB 'NonLinear)) Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sequence GIF -> ByteString -> m [Image S (Alpha RGB) Word8]
forall f arr (m :: * -> *).
(Readable f arr, MonadThrow m) =>
f -> ByteString -> m arr
decodeM Sequence GIF
f
decodeWithMetadataM :: Sequence GIF
-> ByteString
-> m ([Image S (Alpha (SRGB 'NonLinear)) Word8],
Metadata (Sequence GIF))
decodeWithMetadataM Sequence GIF
f = (([Image S (Alpha RGB) Word8], [Int])
-> ([Image S (Alpha (SRGB 'NonLinear)) Word8], [Int]))
-> m ([Image S (Alpha RGB) Word8], [Int])
-> m ([Image S (Alpha (SRGB 'NonLinear)) Word8], [Int])
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], [Int])
-> ([Image S (Alpha (SRGB 'NonLinear)) Word8], [Int])
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)
-> [Image S (Alpha RGB) Word8]
-> [Image S (Alpha (SRGB 'NonLinear)) Word8]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Image S (Alpha RGB) Word8
-> Image S (Alpha (SRGB 'NonLinear)) Word8
forall cs e.
Matrix S (Pixel (BaseModel cs) e) -> Matrix S (Pixel cs e)
fromImageBaseModel)) (m ([Image S (Alpha RGB) Word8], [Int])
-> m ([Image S (Alpha (SRGB 'NonLinear)) Word8], [Int]))
-> (ByteString -> m ([Image S (Alpha RGB) Word8], [Int]))
-> ByteString
-> m ([Image S (Alpha (SRGB 'NonLinear)) Word8], [Int])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sequence GIF
-> ByteString
-> m ([Image S (Alpha RGB) Word8], Metadata (Sequence GIF))
forall f arr (m :: * -> *).
(Readable f arr, MonadThrow m) =>
f -> ByteString -> m (arr, Metadata f)
decodeWithMetadataM Sequence GIF
f
instance (Manifest r (Pixel cs e), ColorSpace cs i e) =>
Readable (Auto (Sequence GIF)) [Image r cs e] where
decodeM :: Auto (Sequence GIF) -> ByteString -> m [Image r cs e]
decodeM = Auto (Sequence GIF) -> ByteString -> m [Image r cs e]
forall r cs e i (m :: * -> *).
(Manifest r (Pixel cs e), ColorSpace cs i e, MonadThrow m) =>
Auto (Sequence GIF) -> ByteString -> m [Image r cs e]
decodeAutoSequenceGIF
decodeWithMetadataM :: Auto (Sequence GIF)
-> ByteString -> m ([Image r cs e], Metadata (Auto (Sequence GIF)))
decodeWithMetadataM = Auto (Sequence GIF)
-> ByteString -> m ([Image r cs e], Metadata (Auto (Sequence GIF)))
forall r cs e i (m :: * -> *).
(Manifest r (Pixel cs e), ColorSpace cs i e, MonadThrow m) =>
Auto (Sequence GIF) -> ByteString -> m ([Image r cs e], [Int])
decodeAutoSequenceWithMetadataGIF
decodeSequenceGIF ::
(ColorModel cs e, MonadThrow m) => Sequence GIF -> B.ByteString -> m [Image S cs e]
decodeSequenceGIF :: Sequence GIF -> ByteString -> m [Image S cs e]
decodeSequenceGIF Sequence GIF
f ByteString
bs = Sequence GIF -> Either String [DynamicImage] -> m [Image S cs e]
forall (m :: * -> *) cs e f.
(MonadThrow m, ColorModel cs e, FileFormat (Sequence f)) =>
Sequence f -> Either String [DynamicImage] -> m [Image S cs e]
convertSequenceWith Sequence GIF
f (ByteString -> Either String [DynamicImage]
JP.decodeGifImages ByteString
bs)
decodeSequenceWithMetadataGIF ::
(ColorModel cs e, MonadThrow m)
=> Sequence GIF
-> B.ByteString
-> m ([Image S cs e], [JP.GifDelay])
decodeSequenceWithMetadataGIF :: Sequence GIF -> ByteString -> m ([Image S cs e], [Int])
decodeSequenceWithMetadataGIF = (Sequence GIF -> ByteString -> m [Image S cs e])
-> Sequence GIF -> ByteString -> m ([Image S cs e], [Int])
forall (m :: * -> *) t a.
MonadThrow m =>
(t -> ByteString -> m a) -> t -> ByteString -> m (a, [Int])
decodeSeqMetadata Sequence GIF -> ByteString -> m [Image S cs e]
forall cs e (m :: * -> *).
(ColorModel cs e, MonadThrow m) =>
Sequence GIF -> ByteString -> m [Image S cs e]
decodeSequenceGIF
decodeAutoSequenceGIF ::
(Manifest r (Pixel cs e), ColorSpace cs i e, MonadThrow m)
=> Auto (Sequence GIF)
-> B.ByteString
-> m [Image r cs e]
decodeAutoSequenceGIF :: Auto (Sequence GIF) -> ByteString -> m [Image r cs e]
decodeAutoSequenceGIF Auto (Sequence GIF)
f ByteString
bs = Auto (Sequence GIF)
-> Either String [DynamicImage] -> m [Image r cs e]
forall (m :: * -> *) r cs e i f.
(MonadThrow m, Manifest r (Pixel cs e), ColorSpace cs i e) =>
Auto (Sequence f)
-> Either String [DynamicImage] -> m [Image r cs e]
convertAutoSequenceWith Auto (Sequence GIF)
f (ByteString -> Either String [DynamicImage]
JP.decodeGifImages ByteString
bs)
decodeAutoSequenceWithMetadataGIF ::
(Manifest r (Pixel cs e), ColorSpace cs i e, MonadThrow m)
=> Auto (Sequence GIF)
-> B.ByteString
-> m ([Image r cs e], [JP.GifDelay])
decodeAutoSequenceWithMetadataGIF :: Auto (Sequence GIF) -> ByteString -> m ([Image r cs e], [Int])
decodeAutoSequenceWithMetadataGIF = (Auto (Sequence GIF) -> ByteString -> m [Image r cs e])
-> Auto (Sequence GIF) -> ByteString -> m ([Image r cs e], [Int])
forall (m :: * -> *) t a.
MonadThrow m =>
(t -> ByteString -> m a) -> t -> ByteString -> m (a, [Int])
decodeSeqMetadata Auto (Sequence GIF) -> ByteString -> m [Image r cs e]
forall r cs e i (m :: * -> *).
(Manifest r (Pixel cs e), ColorSpace cs i e, MonadThrow m) =>
Auto (Sequence GIF) -> ByteString -> m [Image r cs e]
decodeAutoSequenceGIF
decodeSeqMetadata ::
MonadThrow m => (t -> B.ByteString -> m a) -> t -> B.ByteString -> m (a, [JP.GifDelay])
decodeSeqMetadata :: (t -> ByteString -> m a) -> t -> ByteString -> m (a, [Int])
decodeSeqMetadata t -> ByteString -> m a
decode t
f ByteString
bs = do
a
imgs <- t -> ByteString -> m a
decode t
f ByteString
bs
[Int]
delays <- Either String [Int] -> m [Int]
forall (m :: * -> *) a. MonadThrow m => Either String a -> m a
decodeError (Either String [Int] -> m [Int]) -> Either String [Int] -> m [Int]
forall a b. (a -> b) -> a -> b
$ ByteString -> Either String [Int]
JP.getDelaysGifImages ByteString
bs
(a, [Int]) -> m (a, [Int])
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a
imgs, [Int]
delays)
instance Writable (Sequence GIF) (NE.NonEmpty (JP.GifDelay, Image S CM.X Bit)) where
encodeM :: Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, Image S X Bit)
-> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts NonEmpty (Int, Image S X Bit)
imgs = Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, Matrix S (Pixel X Word8))
-> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts (((Int, Image S X Bit) -> (Int, Matrix S (Pixel X Word8)))
-> NonEmpty (Int, Image S X Bit)
-> NonEmpty (Int, Matrix S (Pixel X Word8))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Image S X Bit -> Matrix S (Pixel X Word8))
-> (Int, Image S X Bit) -> (Int, Matrix S (Pixel X Word8))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Image S X Bit -> Matrix S (Pixel X Word8)
coerceBinaryImage) NonEmpty (Int, Image S X Bit)
imgs)
instance Writable (Sequence GIF) (NE.NonEmpty (JP.GifDelay, Image S CM.X Word8)) where
encodeM :: Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, Matrix S (Pixel X Word8))
-> m ByteString
encodeM Sequence GIF
_ SequenceGifOptions {sequenceGifLooping} NonEmpty (Int, Matrix S (Pixel X Word8))
gifs =
Either String ByteString -> m ByteString
forall (m :: * -> *) a. MonadThrow m => Either String a -> m a
encodeError (Either String ByteString -> m ByteString)
-> Either String ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$
GifEncode -> Either String ByteString
JP.encodeComplexGifImage (GifEncode -> Either String ByteString)
-> GifEncode -> Either String ByteString
forall a b. (a -> b) -> a -> b
$
GifEncode :: Int
-> Int
-> Maybe Palette
-> Maybe Int
-> GifLooping
-> [GifFrame]
-> GifEncode
JP.GifEncode
{ geWidth :: Int
JP.geWidth = Int
cols
, geHeight :: Int
JP.geHeight = Int
rows
, gePalette :: Maybe Palette
JP.gePalette = Palette -> Maybe Palette
forall a. a -> Maybe a
Just Palette
JP.greyPalette
, geBackground :: Maybe Int
JP.geBackground = Maybe Int
forall a. Maybe a
Nothing
, geLooping :: GifLooping
JP.geLooping = GifLooping
sequenceGifLooping
, geFrames :: [GifFrame]
JP.geFrames =
(((Int, Matrix S (Pixel X Word8)) -> GifFrame)
-> [(Int, Matrix S (Pixel X Word8))] -> [GifFrame])
-> [(Int, Matrix S (Pixel X Word8))]
-> ((Int, Matrix S (Pixel X Word8)) -> GifFrame)
-> [GifFrame]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((Int, Matrix S (Pixel X Word8)) -> GifFrame)
-> [(Int, Matrix S (Pixel X Word8))] -> [GifFrame]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (NonEmpty (Int, Matrix S (Pixel X Word8))
-> [(Int, Matrix S (Pixel X Word8))]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty (Int, Matrix S (Pixel X Word8))
gifs) (((Int, Matrix S (Pixel X Word8)) -> GifFrame) -> [GifFrame])
-> ((Int, Matrix S (Pixel X Word8)) -> GifFrame) -> [GifFrame]
forall a b. (a -> b) -> a -> b
$ \(Int
gifDelay, Matrix S (Pixel X Word8)
gif) ->
GifFrame :: Int
-> Int
-> Maybe Palette
-> Maybe Int
-> Int
-> GifDisposalMethod
-> Image Word8
-> GifFrame
JP.GifFrame
{ gfXOffset :: Int
JP.gfXOffset = Int
0
, gfYOffset :: Int
JP.gfYOffset = Int
0
, gfPalette :: Maybe Palette
JP.gfPalette = Maybe Palette
forall a. Maybe a
Nothing
, gfTransparent :: Maybe Int
JP.gfTransparent = Maybe Int
forall a. Maybe a
Nothing
, gfDelay :: Int
JP.gfDelay = Int
gifDelay
, gfDisposal :: GifDisposalMethod
JP.gfDisposal = GifDisposalMethod
JP.DisposalAny
, gfPixels :: Image Word8
JP.gfPixels = Matrix S (Pixel X Word8) -> Image Word8
forall r.
Source r (Pixel X Word8) =>
Image r X Word8 -> Image Word8
toJPImageY8 Matrix S (Pixel X Word8)
gif
}
}
where
(Int
rows :. Int
cols) = (Ix2 -> Ix2 -> Ix2) -> NonEmpty Ix2 -> Ix2
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 ((Int -> Int -> Int) -> Ix2 -> Ix2 -> Ix2
forall ix. Index ix => (Int -> Int -> Int) -> ix -> ix -> ix
liftIndex2 Int -> Int -> Int
forall a. Ord a => a -> a -> a
max) (NonEmpty Ix2 -> Ix2) -> NonEmpty Ix2 -> Ix2
forall a b. (a -> b) -> a -> b
$ ((Int, Matrix S (Pixel X Word8)) -> Ix2)
-> NonEmpty (Int, Matrix S (Pixel X Word8)) -> NonEmpty Ix2
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Sz Ix2 -> Ix2
forall ix. Sz ix -> ix
unSz (Sz Ix2 -> Ix2)
-> ((Int, Matrix S (Pixel X Word8)) -> Sz Ix2)
-> (Int, Matrix S (Pixel X Word8))
-> Ix2
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Matrix S (Pixel X Word8) -> Sz Ix2
forall r ix e. Size r => Array r ix e -> Sz ix
size (Matrix S (Pixel X Word8) -> Sz Ix2)
-> ((Int, Matrix S (Pixel X Word8)) -> Matrix S (Pixel X Word8))
-> (Int, Matrix S (Pixel X Word8))
-> Sz Ix2
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, Matrix S (Pixel X Word8)) -> Matrix S (Pixel X Word8)
forall a b. (a, b) -> b
snd) NonEmpty (Int, Matrix S (Pixel X Word8))
gifs
instance Writable (Sequence GIF) (NE.NonEmpty ( JP.GifDelay
, JP.GifDisposalMethod
, Image S CM.RGB Word8)) where
encodeM :: Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, GifDisposalMethod, Image S RGB Word8)
-> m ByteString
encodeM Sequence GIF
_ SequenceGifOptions {sequenceGifLooping, sequenceGifPaletteOptions} NonEmpty (Int, GifDisposalMethod, Image S RGB Word8)
gifs =
Either String ByteString -> m ByteString
forall (m :: * -> *) a. MonadThrow m => Either String a -> m a
encodeError (Either String ByteString -> m ByteString)
-> Either String ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$
GifEncode -> Either String ByteString
JP.encodeComplexGifImage (GifEncode -> Either String ByteString)
-> GifEncode -> Either String ByteString
forall a b. (a -> b) -> a -> b
$
GifEncode :: Int
-> Int
-> Maybe Palette
-> Maybe Int
-> GifLooping
-> [GifFrame]
-> GifEncode
JP.GifEncode
{ geWidth :: Int
JP.geWidth = Int
cols
, geHeight :: Int
JP.geHeight = Int
rows
, gePalette :: Maybe Palette
JP.gePalette = Maybe Palette
forall a. Maybe a
Nothing
, geBackground :: Maybe Int
JP.geBackground = Maybe Int
forall a. Maybe a
Nothing
, geLooping :: GifLooping
JP.geLooping = GifLooping
sequenceGifLooping
, geFrames :: [GifFrame]
JP.geFrames =
(((Int, GifDisposalMethod, Image S RGB Word8) -> GifFrame)
-> [(Int, GifDisposalMethod, Image S RGB Word8)] -> [GifFrame])
-> [(Int, GifDisposalMethod, Image S RGB Word8)]
-> ((Int, GifDisposalMethod, Image S RGB Word8) -> GifFrame)
-> [GifFrame]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((Int, GifDisposalMethod, Image S RGB Word8) -> GifFrame)
-> [(Int, GifDisposalMethod, Image S RGB Word8)] -> [GifFrame]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (NonEmpty (Int, GifDisposalMethod, Image S RGB Word8)
-> [(Int, GifDisposalMethod, Image S RGB Word8)]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty (Int, GifDisposalMethod, Image S RGB Word8)
gifs) (((Int, GifDisposalMethod, Image S RGB Word8) -> GifFrame)
-> [GifFrame])
-> ((Int, GifDisposalMethod, Image S RGB Word8) -> GifFrame)
-> [GifFrame]
forall a b. (a -> b) -> a -> b
$ \(Int
gifDelay, GifDisposalMethod
disposalMethod, Image S RGB Word8
gif) ->
let (Image Word8
img, Palette
palette) = PaletteOptions -> Palette -> (Image Word8, Palette)
JP.palettize PaletteOptions
sequenceGifPaletteOptions (Palette -> (Image Word8, Palette))
-> Palette -> (Image Word8, Palette)
forall a b. (a -> b) -> a -> b
$ Image S RGB Word8 -> Palette
forall r.
Source r (Pixel RGB Word8) =>
Image r RGB Word8 -> Palette
toJPImageRGB8 Image S RGB Word8
gif
in GifFrame :: Int
-> Int
-> Maybe Palette
-> Maybe Int
-> Int
-> GifDisposalMethod
-> Image Word8
-> GifFrame
JP.GifFrame
{ gfXOffset :: Int
JP.gfXOffset = Int
0
, gfYOffset :: Int
JP.gfYOffset = Int
0
, gfPalette :: Maybe Palette
JP.gfPalette = Palette -> Maybe Palette
forall a. a -> Maybe a
Just Palette
palette
, gfTransparent :: Maybe Int
JP.gfTransparent = Maybe Int
forall a. Maybe a
Nothing
, gfDelay :: Int
JP.gfDelay = Int
gifDelay
, gfDisposal :: GifDisposalMethod
JP.gfDisposal = GifDisposalMethod
disposalMethod
, gfPixels :: Image Word8
JP.gfPixels = Image Word8
img
}
}
where
(Int
rows :. Int
cols) = (Ix2 -> Ix2 -> Ix2) -> NonEmpty Ix2 -> Ix2
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 ((Int -> Int -> Int) -> Ix2 -> Ix2 -> Ix2
forall ix. Index ix => (Int -> Int -> Int) -> ix -> ix -> ix
liftIndex2 Int -> Int -> Int
forall a. Ord a => a -> a -> a
max) (NonEmpty Ix2 -> Ix2) -> NonEmpty Ix2 -> Ix2
forall a b. (a -> b) -> a -> b
$ ((Int, GifDisposalMethod, Image S RGB Word8) -> Ix2)
-> NonEmpty (Int, GifDisposalMethod, Image S RGB Word8)
-> NonEmpty Ix2
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Int
_, GifDisposalMethod
_, Image S RGB Word8
i) -> Sz Ix2 -> Ix2
forall ix. Sz ix -> ix
unSz (Sz Ix2 -> Ix2) -> Sz Ix2 -> Ix2
forall a b. (a -> b) -> a -> b
$ Image S RGB Word8 -> Sz Ix2
forall r ix e. Size r => Array r ix e -> Sz ix
size Image S RGB Word8
i) NonEmpty (Int, GifDisposalMethod, Image S RGB Word8)
gifs
instance Writable (Sequence GIF) (NE.NonEmpty (JP.GifDelay, Image S CM.RGB Word8)) where
encodeM :: Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, Image S RGB Word8)
-> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts = Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, GifDisposalMethod, Image S RGB Word8)
-> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts (NonEmpty (Int, GifDisposalMethod, Image S RGB Word8)
-> m ByteString)
-> (NonEmpty (Int, Image S RGB Word8)
-> NonEmpty (Int, GifDisposalMethod, Image S RGB Word8))
-> NonEmpty (Int, Image S RGB Word8)
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, Image S RGB Word8)
-> (Int, GifDisposalMethod, Image S RGB Word8))
-> NonEmpty (Int, Image S RGB Word8)
-> NonEmpty (Int, GifDisposalMethod, Image S RGB Word8)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Int
d, Image S RGB Word8
i) -> (Int
d, GifDisposalMethod
JP.DisposalAny, Image S RGB Word8
i))
instance Writable (Sequence GIF) (NE.NonEmpty ( JP.GifDelay
, JP.GifDisposalMethod
, Image S (Alpha CM.RGB) Word8)) where
encodeM :: Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, GifDisposalMethod, Image S (Alpha RGB) Word8)
-> m ByteString
encodeM Sequence GIF
_ SequenceGifOptions {sequenceGifLooping} NonEmpty (Int, GifDisposalMethod, Image S (Alpha RGB) Word8)
gifsNE =
Either String ByteString -> m ByteString
forall (m :: * -> *) a. MonadThrow m => Either String a -> m a
encodeError (Either String ByteString -> m ByteString)
-> Either String ByteString -> m ByteString
forall a b. (a -> b) -> a -> b
$
GifEncode -> Either String ByteString
JP.encodeComplexGifImage (GifEncode -> Either String ByteString)
-> GifEncode -> Either String ByteString
forall a b. (a -> b) -> a -> b
$
GifEncode :: Int
-> Int
-> Maybe Palette
-> Maybe Int
-> GifLooping
-> [GifFrame]
-> GifEncode
JP.GifEncode
{ geWidth :: Int
JP.geWidth = Int
cols
, geHeight :: Int
JP.geHeight = Int
rows
, gePalette :: Maybe Palette
JP.gePalette = Maybe Palette
forall a. Maybe a
Nothing
, geBackground :: Maybe Int
JP.geBackground = Maybe Int
forall a. Maybe a
Nothing
, geLooping :: GifLooping
JP.geLooping = GifLooping
sequenceGifLooping
, geFrames :: [GifFrame]
JP.geFrames =
(GifDisposalMethod -> GifFrame -> GifFrame)
-> [GifDisposalMethod] -> [GifFrame] -> [GifFrame]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
P.zipWith (\GifDisposalMethod
d GifFrame
f -> GifFrame
f {gfDisposal :: GifDisposalMethod
JP.gfDisposal = GifDisposalMethod
d}) [GifDisposalMethod]
disposals ([GifFrame] -> [GifFrame]) -> [GifFrame] -> [GifFrame]
forall a b. (a -> b) -> a -> b
$
[(Int, Image PixelRGBA8)] -> GifDisposalMethod -> [GifFrame]
JP.palettizeWithAlpha ([Int] -> [Image PixelRGBA8] -> [(Int, Image PixelRGBA8)]
forall a b. [a] -> [b] -> [(a, b)]
P.zip [Int]
delays ([Image PixelRGBA8] -> [(Int, Image PixelRGBA8)])
-> [Image PixelRGBA8] -> [(Int, Image PixelRGBA8)]
forall a b. (a -> b) -> a -> b
$ (Image S (Alpha RGB) Word8 -> Image PixelRGBA8)
-> [Image S (Alpha RGB) Word8] -> [Image PixelRGBA8]
forall a b. (a -> b) -> [a] -> [b]
P.map Image S (Alpha RGB) Word8 -> Image PixelRGBA8
forall r.
Source r (Pixel (Alpha RGB) Word8) =>
Image r (Alpha RGB) Word8 -> Image PixelRGBA8
toJPImageRGBA8 [Image S (Alpha RGB) Word8]
images) GifDisposalMethod
JP.DisposalAny
}
where
([Int]
delays, [GifDisposalMethod]
disposals, [Image S (Alpha RGB) Word8]
images) = [(Int, GifDisposalMethod, Image S (Alpha RGB) Word8)]
-> ([Int], [GifDisposalMethod], [Image S (Alpha RGB) Word8])
forall a b c. [(a, b, c)] -> ([a], [b], [c])
P.unzip3 ([(Int, GifDisposalMethod, Image S (Alpha RGB) Word8)]
-> ([Int], [GifDisposalMethod], [Image S (Alpha RGB) Word8]))
-> [(Int, GifDisposalMethod, Image S (Alpha RGB) Word8)]
-> ([Int], [GifDisposalMethod], [Image S (Alpha RGB) Word8])
forall a b. (a -> b) -> a -> b
$ NonEmpty (Int, GifDisposalMethod, Image S (Alpha RGB) Word8)
-> [(Int, GifDisposalMethod, Image S (Alpha RGB) Word8)]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty (Int, GifDisposalMethod, Image S (Alpha RGB) Word8)
gifsNE
(Int
rows :. Int
cols) = (Ix2 -> Ix2 -> Ix2) -> [Ix2] -> Ix2
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 ((Int -> Int -> Int) -> Ix2 -> Ix2 -> Ix2
forall ix. Index ix => (Int -> Int -> Int) -> ix -> ix -> ix
liftIndex2 Int -> Int -> Int
forall a. Ord a => a -> a -> a
max) ([Ix2] -> Ix2) -> [Ix2] -> Ix2
forall a b. (a -> b) -> a -> b
$ (Image S (Alpha RGB) Word8 -> Ix2)
-> [Image S (Alpha RGB) Word8] -> [Ix2]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Sz Ix2 -> Ix2
forall ix. Sz ix -> ix
unSz (Sz Ix2 -> Ix2)
-> (Image S (Alpha RGB) Word8 -> Sz Ix2)
-> Image S (Alpha RGB) Word8
-> Ix2
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Image S (Alpha RGB) Word8 -> Sz Ix2
forall r ix e. Size r => Array r ix e -> Sz ix
size) [Image S (Alpha RGB) Word8]
images
instance Writable (Sequence GIF) (NE.NonEmpty (JP.GifDelay, Image S (Alpha CM.RGB) Word8)) where
encodeM :: Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, Image S (Alpha RGB) Word8)
-> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts = Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, GifDisposalMethod, Image S (Alpha RGB) Word8)
-> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts (NonEmpty (Int, GifDisposalMethod, Image S (Alpha RGB) Word8)
-> m ByteString)
-> (NonEmpty (Int, Image S (Alpha RGB) Word8)
-> NonEmpty (Int, GifDisposalMethod, Image S (Alpha RGB) Word8))
-> NonEmpty (Int, Image S (Alpha RGB) Word8)
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, Image S (Alpha RGB) Word8)
-> (Int, GifDisposalMethod, Image S (Alpha RGB) Word8))
-> NonEmpty (Int, Image S (Alpha RGB) Word8)
-> NonEmpty (Int, GifDisposalMethod, Image S (Alpha RGB) Word8)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Int
d, Image S (Alpha RGB) Word8
i) -> (Int
d, GifDisposalMethod
JP.DisposalRestoreBackground, Image S (Alpha RGB) Word8
i))
instance Writable (Sequence GIF) (NE.NonEmpty (JP.GifDelay, Image S (Y' SRGB) Word8)) where
encodeM :: Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, Image S (Y' SRGB) Word8)
-> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts = Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, Matrix S (Pixel X Word8))
-> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts (NonEmpty (Int, Matrix S (Pixel X Word8)) -> m ByteString)
-> (NonEmpty (Int, Image S (Y' SRGB) Word8)
-> NonEmpty (Int, Matrix S (Pixel X Word8)))
-> NonEmpty (Int, Image S (Y' SRGB) Word8)
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, Image S (Y' SRGB) Word8) -> (Int, Matrix S (Pixel X Word8)))
-> NonEmpty (Int, Image S (Y' SRGB) Word8)
-> NonEmpty (Int, Matrix S (Pixel X Word8))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Image S (Y' SRGB) Word8 -> Matrix S (Pixel X Word8))
-> (Int, Image S (Y' SRGB) Word8)
-> (Int, Matrix S (Pixel X Word8))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Image S (Y' SRGB) Word8 -> Matrix S (Pixel X Word8)
forall cs e.
Matrix S (Pixel cs e) -> Matrix S (Pixel (BaseModel cs) e)
toImageBaseModel)
instance Writable (Sequence GIF) (NE.NonEmpty (JP.GifDelay, Image S (Y D65) Word8)) where
encodeM :: Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, Image S (Y D65) Word8)
-> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts = Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, Matrix S (Pixel X Word8))
-> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts (NonEmpty (Int, Matrix S (Pixel X Word8)) -> m ByteString)
-> (NonEmpty (Int, Image S (Y D65) Word8)
-> NonEmpty (Int, Matrix S (Pixel X Word8)))
-> NonEmpty (Int, Image S (Y D65) Word8)
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, Image S (Y D65) Word8) -> (Int, Matrix S (Pixel X Word8)))
-> NonEmpty (Int, Image S (Y D65) Word8)
-> NonEmpty (Int, Matrix S (Pixel X Word8))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Image S (Y D65) Word8 -> Matrix S (Pixel X Word8))
-> (Int, Image S (Y D65) Word8) -> (Int, Matrix S (Pixel X Word8))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Image S (Y D65) Word8 -> Matrix S (Pixel X Word8)
forall cs e.
Matrix S (Pixel cs e) -> Matrix S (Pixel (BaseModel cs) e)
toImageBaseModel)
instance Writable (Sequence GIF) (NE.NonEmpty (JP.GifDelay, Image S (SRGB 'NonLinear) Word8)) where
encodeM :: Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, Image S (SRGB 'NonLinear) Word8)
-> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts = Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, Image S RGB Word8)
-> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts (NonEmpty (Int, Image S RGB Word8) -> m ByteString)
-> (NonEmpty (Int, Image S (SRGB 'NonLinear) Word8)
-> NonEmpty (Int, Image S RGB Word8))
-> NonEmpty (Int, Image S (SRGB 'NonLinear) Word8)
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, Image S (SRGB 'NonLinear) Word8)
-> (Int, Image S RGB Word8))
-> NonEmpty (Int, Image S (SRGB 'NonLinear) Word8)
-> NonEmpty (Int, Image S RGB Word8)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Image S (SRGB 'NonLinear) Word8 -> Image S RGB Word8)
-> (Int, Image S (SRGB 'NonLinear) Word8)
-> (Int, Image S RGB Word8)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Image S (SRGB 'NonLinear) Word8 -> Image S RGB Word8
forall cs e.
Matrix S (Pixel cs e) -> Matrix S (Pixel (BaseModel cs) e)
toImageBaseModel)
instance Writable (Sequence GIF) (NE.NonEmpty (JP.GifDelay, Image S (Alpha (SRGB 'NonLinear)) Word8)) where
encodeM :: Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, Image S (Alpha (SRGB 'NonLinear)) Word8)
-> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts = Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, Image S (Alpha RGB) Word8)
-> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts (NonEmpty (Int, Image S (Alpha RGB) Word8) -> m ByteString)
-> (NonEmpty (Int, Image S (Alpha (SRGB 'NonLinear)) Word8)
-> NonEmpty (Int, Image S (Alpha RGB) Word8))
-> NonEmpty (Int, Image S (Alpha (SRGB 'NonLinear)) Word8)
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, Image S (Alpha (SRGB 'NonLinear)) Word8)
-> (Int, Image S (Alpha RGB) Word8))
-> NonEmpty (Int, Image S (Alpha (SRGB 'NonLinear)) Word8)
-> NonEmpty (Int, Image S (Alpha RGB) Word8)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Image S (Alpha (SRGB 'NonLinear)) Word8
-> Image S (Alpha RGB) Word8)
-> (Int, Image S (Alpha (SRGB 'NonLinear)) Word8)
-> (Int, Image S (Alpha RGB) Word8)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Image S (Alpha (SRGB 'NonLinear)) Word8
-> Image S (Alpha RGB) Word8
forall cs e.
Matrix S (Pixel cs e) -> Matrix S (Pixel (BaseModel cs) e)
toImageBaseModel)
instance Writable (Sequence GIF) (NE.NonEmpty ( JP.GifDelay
, JP.GifDisposalMethod
, Image S (SRGB 'NonLinear) Word8)) where
encodeM :: Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty
(Int, GifDisposalMethod, Image S (SRGB 'NonLinear) Word8)
-> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts = Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, GifDisposalMethod, Image S RGB Word8)
-> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts (NonEmpty (Int, GifDisposalMethod, Image S RGB Word8)
-> m ByteString)
-> (NonEmpty
(Int, GifDisposalMethod, Image S (SRGB 'NonLinear) Word8)
-> NonEmpty (Int, GifDisposalMethod, Image S RGB Word8))
-> NonEmpty
(Int, GifDisposalMethod, Image S (SRGB 'NonLinear) Word8)
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, GifDisposalMethod, Image S (SRGB 'NonLinear) Word8)
-> (Int, GifDisposalMethod, Image S RGB Word8))
-> NonEmpty
(Int, GifDisposalMethod, Image S (SRGB 'NonLinear) Word8)
-> NonEmpty (Int, GifDisposalMethod, Image S RGB Word8)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Int
dl, GifDisposalMethod
dp, Image S (SRGB 'NonLinear) Word8
i) -> (Int
dl, GifDisposalMethod
dp, Image S (SRGB 'NonLinear) Word8
-> Matrix S (Pixel (BaseModel (SRGB 'NonLinear)) Word8)
forall cs e.
Matrix S (Pixel cs e) -> Matrix S (Pixel (BaseModel cs) e)
toImageBaseModel Image S (SRGB 'NonLinear) Word8
i))
instance Writable (Sequence GIF) (NE.NonEmpty ( JP.GifDelay
, JP.GifDisposalMethod
, Image S (Alpha (SRGB 'NonLinear)) Word8)) where
encodeM :: Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty
(Int, GifDisposalMethod, Image S (Alpha (SRGB 'NonLinear)) Word8)
-> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts = Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, GifDisposalMethod, Image S (Alpha RGB) Word8)
-> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM Sequence GIF
f WriteOptions (Sequence GIF)
opts (NonEmpty (Int, GifDisposalMethod, Image S (Alpha RGB) Word8)
-> m ByteString)
-> (NonEmpty
(Int, GifDisposalMethod, Image S (Alpha (SRGB 'NonLinear)) Word8)
-> NonEmpty (Int, GifDisposalMethod, Image S (Alpha RGB) Word8))
-> NonEmpty
(Int, GifDisposalMethod, Image S (Alpha (SRGB 'NonLinear)) Word8)
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, GifDisposalMethod, Image S (Alpha (SRGB 'NonLinear)) Word8)
-> (Int, GifDisposalMethod, Image S (Alpha RGB) Word8))
-> NonEmpty
(Int, GifDisposalMethod, Image S (Alpha (SRGB 'NonLinear)) Word8)
-> NonEmpty (Int, GifDisposalMethod, Image S (Alpha RGB) Word8)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Int
dl, GifDisposalMethod
dp, Image S (Alpha (SRGB 'NonLinear)) Word8
i) -> (Int
dl, GifDisposalMethod
dp, Image S (Alpha (SRGB 'NonLinear)) Word8
-> Matrix S (Pixel (BaseModel (Alpha (SRGB 'NonLinear))) Word8)
forall cs e.
Matrix S (Pixel cs e) -> Matrix S (Pixel (BaseModel cs) e)
toImageBaseModel Image S (Alpha (SRGB 'NonLinear)) Word8
i))
instance (Manifest r (Pixel cs e), ColorSpace cs i e) =>
Writable (Auto (Sequence GIF)) (NE.NonEmpty (JP.GifDelay, Image r cs e)) where
encodeM :: Auto (Sequence GIF)
-> WriteOptions (Auto (Sequence GIF))
-> NonEmpty (Int, Image r cs e)
-> m ByteString
encodeM (Auto Sequence GIF
f) WriteOptions (Auto (Sequence GIF))
opts =
Sequence GIF
-> WriteOptions (Sequence GIF)
-> NonEmpty (Int, Image S (SRGB 'NonLinear) Word8)
-> m ByteString
forall f arr (m :: * -> *).
(Writable f arr, MonadThrow m) =>
f -> WriteOptions f -> arr -> m ByteString
encodeM Sequence GIF
f WriteOptions (Auto (Sequence GIF))
WriteOptions (Sequence GIF)
opts (NonEmpty (Int, Image S (SRGB 'NonLinear) Word8) -> m ByteString)
-> (NonEmpty (Int, Image r cs e)
-> NonEmpty (Int, Image S (SRGB 'NonLinear) Word8))
-> NonEmpty (Int, Image r cs e)
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
((Int, Image r cs e) -> (Int, Image S (SRGB 'NonLinear) Word8))
-> NonEmpty (Int, Image r cs e)
-> NonEmpty (Int, Image S (SRGB 'NonLinear) Word8)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Image r cs e -> Image S (SRGB 'NonLinear) Word8)
-> (Int, Image r cs e) -> (Int, Image S (SRGB 'NonLinear) Word8)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (S
-> Array D Ix2 (Pixel (SRGB 'NonLinear) Word8)
-> Image S (SRGB 'NonLinear) Word8
forall r e r' ix.
(Manifest r e, Load r' ix e) =>
r -> Array r' ix e -> Array r ix e
computeAs S
S (Array D Ix2 (Pixel (SRGB 'NonLinear) Word8)
-> Image S (SRGB 'NonLinear) Word8)
-> (Image r cs e -> Array D Ix2 (Pixel (SRGB 'NonLinear) Word8))
-> Image r cs e
-> Image S (SRGB 'NonLinear) Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Image r cs e -> Array D Ix2 (Pixel (SRGB 'NonLinear) Word8)
forall r' cs' e' i' cs i e.
(Source r' (Pixel cs' e'), ColorSpace cs' i' e',
ColorSpace cs i e) =>
Image r' cs' e' -> Image D cs e
convertImage :: Image r cs e -> Image D (SRGB 'NonLinear) Word8)))