{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.KinesisVideo.Types.ImageGenerationConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.KinesisVideo.Types.ImageGenerationConfiguration where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.KinesisVideo.Types.ConfigurationStatus
import Amazonka.KinesisVideo.Types.Format
import Amazonka.KinesisVideo.Types.FormatConfigKey
import Amazonka.KinesisVideo.Types.ImageGenerationDestinationConfig
import Amazonka.KinesisVideo.Types.ImageSelectorType
import qualified Amazonka.Prelude as Prelude

-- | The structure that contains the information required for the KVS images
-- delivery. If null, the configuration will be deleted from the stream.
--
-- /See:/ 'newImageGenerationConfiguration' smart constructor.
data ImageGenerationConfiguration = ImageGenerationConfiguration'
  { -- | The list of a key-value pair structure that contains extra parameters
    -- that can be applied when the image is generated. The @FormatConfig@ key
    -- is the @JPEGQuality@, which indicates the JPEG quality key to be used to
    -- generate the image. The @FormatConfig@ value accepts ints from 1 to 100.
    -- If the value is 1, the image will be generated with less quality and the
    -- best compression. If the value is 100, the image will be generated with
    -- the best quality and less compression. If no value is provided, the
    -- default value of the @JPEGQuality@ key will be set to 80.
    ImageGenerationConfiguration
-> Maybe (HashMap FormatConfigKey Text)
formatConfig :: Prelude.Maybe (Prelude.HashMap FormatConfigKey Prelude.Text),
    -- | The height of the output image that is used in conjunction with the
    -- @WidthPixels@ parameter. When both @HeightPixels@ and @WidthPixels@
    -- parameters are provided, the image will be stretched to fit the
    -- specified aspect ratio. If only the @HeightPixels@ parameter is
    -- provided, its original aspect ratio will be used to calculate the
    -- @WidthPixels@ ratio. If neither parameter is provided, the original
    -- image size will be returned.
    ImageGenerationConfiguration -> Maybe Natural
heightPixels :: Prelude.Maybe Prelude.Natural,
    -- | The width of the output image that is used in conjunction with the
    -- @HeightPixels@ parameter. When both @WidthPixels@ and @HeightPixels@
    -- parameters are provided, the image will be stretched to fit the
    -- specified aspect ratio. If only the @WidthPixels@ parameter is provided,
    -- its original aspect ratio will be used to calculate the @HeightPixels@
    -- ratio. If neither parameter is provided, the original image size will be
    -- returned.
    ImageGenerationConfiguration -> Maybe Natural
widthPixels :: Prelude.Maybe Prelude.Natural,
    -- | Indicates whether the @ContinuousImageGenerationConfigurations@ API is
    -- enabled or disabled.
    ImageGenerationConfiguration -> ConfigurationStatus
status :: ConfigurationStatus,
    -- | The origin of the Server or Producer timestamps to use to generate the
    -- images.
    ImageGenerationConfiguration -> ImageSelectorType
imageSelectorType :: ImageSelectorType,
    -- | The structure that contains the information required to deliver images
    -- to a customer.
    ImageGenerationConfiguration -> ImageGenerationDestinationConfig
destinationConfig :: ImageGenerationDestinationConfig,
    -- | The time interval in milliseconds (ms) at which the images need to be
    -- generated from the stream. The minimum value that can be provided is 33
    -- ms, because a camera that generates content at 30 FPS would create a
    -- frame every 33.3 ms. If the timestamp range is less than the sampling
    -- interval, the Image from the @StartTimestamp@ will be returned if
    -- available.
    ImageGenerationConfiguration -> Natural
samplingInterval :: Prelude.Natural,
    -- | The accepted image format.
    ImageGenerationConfiguration -> Format
format :: Format
  }
  deriving (ImageGenerationConfiguration
-> ImageGenerationConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageGenerationConfiguration
-> ImageGenerationConfiguration -> Bool
$c/= :: ImageGenerationConfiguration
-> ImageGenerationConfiguration -> Bool
== :: ImageGenerationConfiguration
-> ImageGenerationConfiguration -> Bool
$c== :: ImageGenerationConfiguration
-> ImageGenerationConfiguration -> Bool
Prelude.Eq, ReadPrec [ImageGenerationConfiguration]
ReadPrec ImageGenerationConfiguration
Int -> ReadS ImageGenerationConfiguration
ReadS [ImageGenerationConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImageGenerationConfiguration]
$creadListPrec :: ReadPrec [ImageGenerationConfiguration]
readPrec :: ReadPrec ImageGenerationConfiguration
$creadPrec :: ReadPrec ImageGenerationConfiguration
readList :: ReadS [ImageGenerationConfiguration]
$creadList :: ReadS [ImageGenerationConfiguration]
readsPrec :: Int -> ReadS ImageGenerationConfiguration
$creadsPrec :: Int -> ReadS ImageGenerationConfiguration
Prelude.Read, Int -> ImageGenerationConfiguration -> ShowS
[ImageGenerationConfiguration] -> ShowS
ImageGenerationConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImageGenerationConfiguration] -> ShowS
$cshowList :: [ImageGenerationConfiguration] -> ShowS
show :: ImageGenerationConfiguration -> String
$cshow :: ImageGenerationConfiguration -> String
showsPrec :: Int -> ImageGenerationConfiguration -> ShowS
$cshowsPrec :: Int -> ImageGenerationConfiguration -> ShowS
Prelude.Show, forall x.
Rep ImageGenerationConfiguration x -> ImageGenerationConfiguration
forall x.
ImageGenerationConfiguration -> Rep ImageGenerationConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ImageGenerationConfiguration x -> ImageGenerationConfiguration
$cfrom :: forall x.
ImageGenerationConfiguration -> Rep ImageGenerationConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'ImageGenerationConfiguration' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'formatConfig', 'imageGenerationConfiguration_formatConfig' - The list of a key-value pair structure that contains extra parameters
-- that can be applied when the image is generated. The @FormatConfig@ key
-- is the @JPEGQuality@, which indicates the JPEG quality key to be used to
-- generate the image. The @FormatConfig@ value accepts ints from 1 to 100.
-- If the value is 1, the image will be generated with less quality and the
-- best compression. If the value is 100, the image will be generated with
-- the best quality and less compression. If no value is provided, the
-- default value of the @JPEGQuality@ key will be set to 80.
--
-- 'heightPixels', 'imageGenerationConfiguration_heightPixels' - The height of the output image that is used in conjunction with the
-- @WidthPixels@ parameter. When both @HeightPixels@ and @WidthPixels@
-- parameters are provided, the image will be stretched to fit the
-- specified aspect ratio. If only the @HeightPixels@ parameter is
-- provided, its original aspect ratio will be used to calculate the
-- @WidthPixels@ ratio. If neither parameter is provided, the original
-- image size will be returned.
--
-- 'widthPixels', 'imageGenerationConfiguration_widthPixels' - The width of the output image that is used in conjunction with the
-- @HeightPixels@ parameter. When both @WidthPixels@ and @HeightPixels@
-- parameters are provided, the image will be stretched to fit the
-- specified aspect ratio. If only the @WidthPixels@ parameter is provided,
-- its original aspect ratio will be used to calculate the @HeightPixels@
-- ratio. If neither parameter is provided, the original image size will be
-- returned.
--
-- 'status', 'imageGenerationConfiguration_status' - Indicates whether the @ContinuousImageGenerationConfigurations@ API is
-- enabled or disabled.
--
-- 'imageSelectorType', 'imageGenerationConfiguration_imageSelectorType' - The origin of the Server or Producer timestamps to use to generate the
-- images.
--
-- 'destinationConfig', 'imageGenerationConfiguration_destinationConfig' - The structure that contains the information required to deliver images
-- to a customer.
--
-- 'samplingInterval', 'imageGenerationConfiguration_samplingInterval' - The time interval in milliseconds (ms) at which the images need to be
-- generated from the stream. The minimum value that can be provided is 33
-- ms, because a camera that generates content at 30 FPS would create a
-- frame every 33.3 ms. If the timestamp range is less than the sampling
-- interval, the Image from the @StartTimestamp@ will be returned if
-- available.
--
-- 'format', 'imageGenerationConfiguration_format' - The accepted image format.
newImageGenerationConfiguration ::
  -- | 'status'
  ConfigurationStatus ->
  -- | 'imageSelectorType'
  ImageSelectorType ->
  -- | 'destinationConfig'
  ImageGenerationDestinationConfig ->
  -- | 'samplingInterval'
  Prelude.Natural ->
  -- | 'format'
  Format ->
  ImageGenerationConfiguration
newImageGenerationConfiguration :: ConfigurationStatus
-> ImageSelectorType
-> ImageGenerationDestinationConfig
-> Natural
-> Format
-> ImageGenerationConfiguration
newImageGenerationConfiguration
  ConfigurationStatus
pStatus_
  ImageSelectorType
pImageSelectorType_
  ImageGenerationDestinationConfig
pDestinationConfig_
  Natural
pSamplingInterval_
  Format
pFormat_ =
    ImageGenerationConfiguration'
      { $sel:formatConfig:ImageGenerationConfiguration' :: Maybe (HashMap FormatConfigKey Text)
formatConfig =
          forall a. Maybe a
Prelude.Nothing,
        $sel:heightPixels:ImageGenerationConfiguration' :: Maybe Natural
heightPixels = forall a. Maybe a
Prelude.Nothing,
        $sel:widthPixels:ImageGenerationConfiguration' :: Maybe Natural
widthPixels = forall a. Maybe a
Prelude.Nothing,
        $sel:status:ImageGenerationConfiguration' :: ConfigurationStatus
status = ConfigurationStatus
pStatus_,
        $sel:imageSelectorType:ImageGenerationConfiguration' :: ImageSelectorType
imageSelectorType = ImageSelectorType
pImageSelectorType_,
        $sel:destinationConfig:ImageGenerationConfiguration' :: ImageGenerationDestinationConfig
destinationConfig = ImageGenerationDestinationConfig
pDestinationConfig_,
        $sel:samplingInterval:ImageGenerationConfiguration' :: Natural
samplingInterval = Natural
pSamplingInterval_,
        $sel:format:ImageGenerationConfiguration' :: Format
format = Format
pFormat_
      }

-- | The list of a key-value pair structure that contains extra parameters
-- that can be applied when the image is generated. The @FormatConfig@ key
-- is the @JPEGQuality@, which indicates the JPEG quality key to be used to
-- generate the image. The @FormatConfig@ value accepts ints from 1 to 100.
-- If the value is 1, the image will be generated with less quality and the
-- best compression. If the value is 100, the image will be generated with
-- the best quality and less compression. If no value is provided, the
-- default value of the @JPEGQuality@ key will be set to 80.
imageGenerationConfiguration_formatConfig :: Lens.Lens' ImageGenerationConfiguration (Prelude.Maybe (Prelude.HashMap FormatConfigKey Prelude.Text))
imageGenerationConfiguration_formatConfig :: Lens'
  ImageGenerationConfiguration (Maybe (HashMap FormatConfigKey Text))
imageGenerationConfiguration_formatConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageGenerationConfiguration' {Maybe (HashMap FormatConfigKey Text)
formatConfig :: Maybe (HashMap FormatConfigKey Text)
$sel:formatConfig:ImageGenerationConfiguration' :: ImageGenerationConfiguration
-> Maybe (HashMap FormatConfigKey Text)
formatConfig} -> Maybe (HashMap FormatConfigKey Text)
formatConfig) (\s :: ImageGenerationConfiguration
s@ImageGenerationConfiguration' {} Maybe (HashMap FormatConfigKey Text)
a -> ImageGenerationConfiguration
s {$sel:formatConfig:ImageGenerationConfiguration' :: Maybe (HashMap FormatConfigKey Text)
formatConfig = Maybe (HashMap FormatConfigKey Text)
a} :: ImageGenerationConfiguration) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The height of the output image that is used in conjunction with the
-- @WidthPixels@ parameter. When both @HeightPixels@ and @WidthPixels@
-- parameters are provided, the image will be stretched to fit the
-- specified aspect ratio. If only the @HeightPixels@ parameter is
-- provided, its original aspect ratio will be used to calculate the
-- @WidthPixels@ ratio. If neither parameter is provided, the original
-- image size will be returned.
imageGenerationConfiguration_heightPixels :: Lens.Lens' ImageGenerationConfiguration (Prelude.Maybe Prelude.Natural)
imageGenerationConfiguration_heightPixels :: Lens' ImageGenerationConfiguration (Maybe Natural)
imageGenerationConfiguration_heightPixels = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageGenerationConfiguration' {Maybe Natural
heightPixels :: Maybe Natural
$sel:heightPixels:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> Maybe Natural
heightPixels} -> Maybe Natural
heightPixels) (\s :: ImageGenerationConfiguration
s@ImageGenerationConfiguration' {} Maybe Natural
a -> ImageGenerationConfiguration
s {$sel:heightPixels:ImageGenerationConfiguration' :: Maybe Natural
heightPixels = Maybe Natural
a} :: ImageGenerationConfiguration)

-- | The width of the output image that is used in conjunction with the
-- @HeightPixels@ parameter. When both @WidthPixels@ and @HeightPixels@
-- parameters are provided, the image will be stretched to fit the
-- specified aspect ratio. If only the @WidthPixels@ parameter is provided,
-- its original aspect ratio will be used to calculate the @HeightPixels@
-- ratio. If neither parameter is provided, the original image size will be
-- returned.
imageGenerationConfiguration_widthPixels :: Lens.Lens' ImageGenerationConfiguration (Prelude.Maybe Prelude.Natural)
imageGenerationConfiguration_widthPixels :: Lens' ImageGenerationConfiguration (Maybe Natural)
imageGenerationConfiguration_widthPixels = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageGenerationConfiguration' {Maybe Natural
widthPixels :: Maybe Natural
$sel:widthPixels:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> Maybe Natural
widthPixels} -> Maybe Natural
widthPixels) (\s :: ImageGenerationConfiguration
s@ImageGenerationConfiguration' {} Maybe Natural
a -> ImageGenerationConfiguration
s {$sel:widthPixels:ImageGenerationConfiguration' :: Maybe Natural
widthPixels = Maybe Natural
a} :: ImageGenerationConfiguration)

-- | Indicates whether the @ContinuousImageGenerationConfigurations@ API is
-- enabled or disabled.
imageGenerationConfiguration_status :: Lens.Lens' ImageGenerationConfiguration ConfigurationStatus
imageGenerationConfiguration_status :: Lens' ImageGenerationConfiguration ConfigurationStatus
imageGenerationConfiguration_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageGenerationConfiguration' {ConfigurationStatus
status :: ConfigurationStatus
$sel:status:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> ConfigurationStatus
status} -> ConfigurationStatus
status) (\s :: ImageGenerationConfiguration
s@ImageGenerationConfiguration' {} ConfigurationStatus
a -> ImageGenerationConfiguration
s {$sel:status:ImageGenerationConfiguration' :: ConfigurationStatus
status = ConfigurationStatus
a} :: ImageGenerationConfiguration)

-- | The origin of the Server or Producer timestamps to use to generate the
-- images.
imageGenerationConfiguration_imageSelectorType :: Lens.Lens' ImageGenerationConfiguration ImageSelectorType
imageGenerationConfiguration_imageSelectorType :: Lens' ImageGenerationConfiguration ImageSelectorType
imageGenerationConfiguration_imageSelectorType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageGenerationConfiguration' {ImageSelectorType
imageSelectorType :: ImageSelectorType
$sel:imageSelectorType:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> ImageSelectorType
imageSelectorType} -> ImageSelectorType
imageSelectorType) (\s :: ImageGenerationConfiguration
s@ImageGenerationConfiguration' {} ImageSelectorType
a -> ImageGenerationConfiguration
s {$sel:imageSelectorType:ImageGenerationConfiguration' :: ImageSelectorType
imageSelectorType = ImageSelectorType
a} :: ImageGenerationConfiguration)

-- | The structure that contains the information required to deliver images
-- to a customer.
imageGenerationConfiguration_destinationConfig :: Lens.Lens' ImageGenerationConfiguration ImageGenerationDestinationConfig
imageGenerationConfiguration_destinationConfig :: Lens' ImageGenerationConfiguration ImageGenerationDestinationConfig
imageGenerationConfiguration_destinationConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageGenerationConfiguration' {ImageGenerationDestinationConfig
destinationConfig :: ImageGenerationDestinationConfig
$sel:destinationConfig:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> ImageGenerationDestinationConfig
destinationConfig} -> ImageGenerationDestinationConfig
destinationConfig) (\s :: ImageGenerationConfiguration
s@ImageGenerationConfiguration' {} ImageGenerationDestinationConfig
a -> ImageGenerationConfiguration
s {$sel:destinationConfig:ImageGenerationConfiguration' :: ImageGenerationDestinationConfig
destinationConfig = ImageGenerationDestinationConfig
a} :: ImageGenerationConfiguration)

-- | The time interval in milliseconds (ms) at which the images need to be
-- generated from the stream. The minimum value that can be provided is 33
-- ms, because a camera that generates content at 30 FPS would create a
-- frame every 33.3 ms. If the timestamp range is less than the sampling
-- interval, the Image from the @StartTimestamp@ will be returned if
-- available.
imageGenerationConfiguration_samplingInterval :: Lens.Lens' ImageGenerationConfiguration Prelude.Natural
imageGenerationConfiguration_samplingInterval :: Lens' ImageGenerationConfiguration Natural
imageGenerationConfiguration_samplingInterval = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageGenerationConfiguration' {Natural
samplingInterval :: Natural
$sel:samplingInterval:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> Natural
samplingInterval} -> Natural
samplingInterval) (\s :: ImageGenerationConfiguration
s@ImageGenerationConfiguration' {} Natural
a -> ImageGenerationConfiguration
s {$sel:samplingInterval:ImageGenerationConfiguration' :: Natural
samplingInterval = Natural
a} :: ImageGenerationConfiguration)

-- | The accepted image format.
imageGenerationConfiguration_format :: Lens.Lens' ImageGenerationConfiguration Format
imageGenerationConfiguration_format :: Lens' ImageGenerationConfiguration Format
imageGenerationConfiguration_format = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImageGenerationConfiguration' {Format
format :: Format
$sel:format:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> Format
format} -> Format
format) (\s :: ImageGenerationConfiguration
s@ImageGenerationConfiguration' {} Format
a -> ImageGenerationConfiguration
s {$sel:format:ImageGenerationConfiguration' :: Format
format = Format
a} :: ImageGenerationConfiguration)

instance Data.FromJSON ImageGenerationConfiguration where
  parseJSON :: Value -> Parser ImageGenerationConfiguration
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ImageGenerationConfiguration"
      ( \Object
x ->
          Maybe (HashMap FormatConfigKey Text)
-> Maybe Natural
-> Maybe Natural
-> ConfigurationStatus
-> ImageSelectorType
-> ImageGenerationDestinationConfig
-> Natural
-> Format
-> ImageGenerationConfiguration
ImageGenerationConfiguration'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"FormatConfig" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"HeightPixels")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"WidthPixels")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"ImageSelectorType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"DestinationConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"SamplingInterval")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Format")
      )

instance
  Prelude.Hashable
    ImageGenerationConfiguration
  where
  hashWithSalt :: Int -> ImageGenerationConfiguration -> Int
hashWithSalt Int
_salt ImageGenerationConfiguration' {Natural
Maybe Natural
Maybe (HashMap FormatConfigKey Text)
ConfigurationStatus
Format
ImageGenerationDestinationConfig
ImageSelectorType
format :: Format
samplingInterval :: Natural
destinationConfig :: ImageGenerationDestinationConfig
imageSelectorType :: ImageSelectorType
status :: ConfigurationStatus
widthPixels :: Maybe Natural
heightPixels :: Maybe Natural
formatConfig :: Maybe (HashMap FormatConfigKey Text)
$sel:format:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> Format
$sel:samplingInterval:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> Natural
$sel:destinationConfig:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> ImageGenerationDestinationConfig
$sel:imageSelectorType:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> ImageSelectorType
$sel:status:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> ConfigurationStatus
$sel:widthPixels:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> Maybe Natural
$sel:heightPixels:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> Maybe Natural
$sel:formatConfig:ImageGenerationConfiguration' :: ImageGenerationConfiguration
-> Maybe (HashMap FormatConfigKey Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap FormatConfigKey Text)
formatConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
heightPixels
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
widthPixels
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ConfigurationStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ImageSelectorType
imageSelectorType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ImageGenerationDestinationConfig
destinationConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
samplingInterval
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Format
format

instance Prelude.NFData ImageGenerationConfiguration where
  rnf :: ImageGenerationConfiguration -> ()
rnf ImageGenerationConfiguration' {Natural
Maybe Natural
Maybe (HashMap FormatConfigKey Text)
ConfigurationStatus
Format
ImageGenerationDestinationConfig
ImageSelectorType
format :: Format
samplingInterval :: Natural
destinationConfig :: ImageGenerationDestinationConfig
imageSelectorType :: ImageSelectorType
status :: ConfigurationStatus
widthPixels :: Maybe Natural
heightPixels :: Maybe Natural
formatConfig :: Maybe (HashMap FormatConfigKey Text)
$sel:format:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> Format
$sel:samplingInterval:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> Natural
$sel:destinationConfig:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> ImageGenerationDestinationConfig
$sel:imageSelectorType:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> ImageSelectorType
$sel:status:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> ConfigurationStatus
$sel:widthPixels:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> Maybe Natural
$sel:heightPixels:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> Maybe Natural
$sel:formatConfig:ImageGenerationConfiguration' :: ImageGenerationConfiguration
-> Maybe (HashMap FormatConfigKey Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap FormatConfigKey Text)
formatConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
heightPixels
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
widthPixels
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ConfigurationStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ImageSelectorType
imageSelectorType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ImageGenerationDestinationConfig
destinationConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
samplingInterval
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Format
format

instance Data.ToJSON ImageGenerationConfiguration where
  toJSON :: ImageGenerationConfiguration -> Value
toJSON ImageGenerationConfiguration' {Natural
Maybe Natural
Maybe (HashMap FormatConfigKey Text)
ConfigurationStatus
Format
ImageGenerationDestinationConfig
ImageSelectorType
format :: Format
samplingInterval :: Natural
destinationConfig :: ImageGenerationDestinationConfig
imageSelectorType :: ImageSelectorType
status :: ConfigurationStatus
widthPixels :: Maybe Natural
heightPixels :: Maybe Natural
formatConfig :: Maybe (HashMap FormatConfigKey Text)
$sel:format:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> Format
$sel:samplingInterval:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> Natural
$sel:destinationConfig:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> ImageGenerationDestinationConfig
$sel:imageSelectorType:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> ImageSelectorType
$sel:status:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> ConfigurationStatus
$sel:widthPixels:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> Maybe Natural
$sel:heightPixels:ImageGenerationConfiguration' :: ImageGenerationConfiguration -> Maybe Natural
$sel:formatConfig:ImageGenerationConfiguration' :: ImageGenerationConfiguration
-> Maybe (HashMap FormatConfigKey Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"FormatConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap FormatConfigKey Text)
formatConfig,
            (Key
"HeightPixels" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
heightPixels,
            (Key
"WidthPixels" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
widthPixels,
            forall a. a -> Maybe a
Prelude.Just (Key
"Status" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ConfigurationStatus
status),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ImageSelectorType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ImageSelectorType
imageSelectorType),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"DestinationConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ImageGenerationDestinationConfig
destinationConfig),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"SamplingInterval" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Natural
samplingInterval),
            forall a. a -> Maybe a
Prelude.Just (Key
"Format" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Format
format)
          ]
      )