{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# 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.UpdateImageGenerationConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the @StreamInfo@ and @ImageProcessingConfiguration@ fields.
module Amazonka.KinesisVideo.UpdateImageGenerationConfiguration
  ( -- * Creating a Request
    UpdateImageGenerationConfiguration (..),
    newUpdateImageGenerationConfiguration,

    -- * Request Lenses
    updateImageGenerationConfiguration_imageGenerationConfiguration,
    updateImageGenerationConfiguration_streamARN,
    updateImageGenerationConfiguration_streamName,

    -- * Destructuring the Response
    UpdateImageGenerationConfigurationResponse (..),
    newUpdateImageGenerationConfigurationResponse,

    -- * Response Lenses
    updateImageGenerationConfigurationResponse_httpStatus,
  )
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
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateImageGenerationConfiguration' smart constructor.
data UpdateImageGenerationConfiguration = UpdateImageGenerationConfiguration'
  { -- | The structure that contains the information required for the KVS images
    -- delivery. If the structure is null, the configuration will be deleted
    -- from the stream.
    UpdateImageGenerationConfiguration
-> Maybe ImageGenerationConfiguration
imageGenerationConfiguration :: Prelude.Maybe ImageGenerationConfiguration,
    -- | The Amazon Resource Name (ARN) of the Kinesis video stream from where
    -- you want to update the image generation configuration. You must specify
    -- either the @StreamName@ or the @StreamARN@.
    UpdateImageGenerationConfiguration -> Maybe Text
streamARN :: Prelude.Maybe Prelude.Text,
    -- | The name of the stream from which to update the image generation
    -- configuration. You must specify either the @StreamName@ or the
    -- @StreamARN@.
    UpdateImageGenerationConfiguration -> Maybe Text
streamName :: Prelude.Maybe Prelude.Text
  }
  deriving (UpdateImageGenerationConfiguration
-> UpdateImageGenerationConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateImageGenerationConfiguration
-> UpdateImageGenerationConfiguration -> Bool
$c/= :: UpdateImageGenerationConfiguration
-> UpdateImageGenerationConfiguration -> Bool
== :: UpdateImageGenerationConfiguration
-> UpdateImageGenerationConfiguration -> Bool
$c== :: UpdateImageGenerationConfiguration
-> UpdateImageGenerationConfiguration -> Bool
Prelude.Eq, ReadPrec [UpdateImageGenerationConfiguration]
ReadPrec UpdateImageGenerationConfiguration
Int -> ReadS UpdateImageGenerationConfiguration
ReadS [UpdateImageGenerationConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateImageGenerationConfiguration]
$creadListPrec :: ReadPrec [UpdateImageGenerationConfiguration]
readPrec :: ReadPrec UpdateImageGenerationConfiguration
$creadPrec :: ReadPrec UpdateImageGenerationConfiguration
readList :: ReadS [UpdateImageGenerationConfiguration]
$creadList :: ReadS [UpdateImageGenerationConfiguration]
readsPrec :: Int -> ReadS UpdateImageGenerationConfiguration
$creadsPrec :: Int -> ReadS UpdateImageGenerationConfiguration
Prelude.Read, Int -> UpdateImageGenerationConfiguration -> ShowS
[UpdateImageGenerationConfiguration] -> ShowS
UpdateImageGenerationConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateImageGenerationConfiguration] -> ShowS
$cshowList :: [UpdateImageGenerationConfiguration] -> ShowS
show :: UpdateImageGenerationConfiguration -> String
$cshow :: UpdateImageGenerationConfiguration -> String
showsPrec :: Int -> UpdateImageGenerationConfiguration -> ShowS
$cshowsPrec :: Int -> UpdateImageGenerationConfiguration -> ShowS
Prelude.Show, forall x.
Rep UpdateImageGenerationConfiguration x
-> UpdateImageGenerationConfiguration
forall x.
UpdateImageGenerationConfiguration
-> Rep UpdateImageGenerationConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateImageGenerationConfiguration x
-> UpdateImageGenerationConfiguration
$cfrom :: forall x.
UpdateImageGenerationConfiguration
-> Rep UpdateImageGenerationConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'UpdateImageGenerationConfiguration' 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:
--
-- 'imageGenerationConfiguration', 'updateImageGenerationConfiguration_imageGenerationConfiguration' - The structure that contains the information required for the KVS images
-- delivery. If the structure is null, the configuration will be deleted
-- from the stream.
--
-- 'streamARN', 'updateImageGenerationConfiguration_streamARN' - The Amazon Resource Name (ARN) of the Kinesis video stream from where
-- you want to update the image generation configuration. You must specify
-- either the @StreamName@ or the @StreamARN@.
--
-- 'streamName', 'updateImageGenerationConfiguration_streamName' - The name of the stream from which to update the image generation
-- configuration. You must specify either the @StreamName@ or the
-- @StreamARN@.
newUpdateImageGenerationConfiguration ::
  UpdateImageGenerationConfiguration
newUpdateImageGenerationConfiguration :: UpdateImageGenerationConfiguration
newUpdateImageGenerationConfiguration =
  UpdateImageGenerationConfiguration'
    { $sel:imageGenerationConfiguration:UpdateImageGenerationConfiguration' :: Maybe ImageGenerationConfiguration
imageGenerationConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:streamARN:UpdateImageGenerationConfiguration' :: Maybe Text
streamARN = forall a. Maybe a
Prelude.Nothing,
      $sel:streamName:UpdateImageGenerationConfiguration' :: Maybe Text
streamName = forall a. Maybe a
Prelude.Nothing
    }

-- | The structure that contains the information required for the KVS images
-- delivery. If the structure is null, the configuration will be deleted
-- from the stream.
updateImageGenerationConfiguration_imageGenerationConfiguration :: Lens.Lens' UpdateImageGenerationConfiguration (Prelude.Maybe ImageGenerationConfiguration)
updateImageGenerationConfiguration_imageGenerationConfiguration :: Lens'
  UpdateImageGenerationConfiguration
  (Maybe ImageGenerationConfiguration)
updateImageGenerationConfiguration_imageGenerationConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateImageGenerationConfiguration' {Maybe ImageGenerationConfiguration
imageGenerationConfiguration :: Maybe ImageGenerationConfiguration
$sel:imageGenerationConfiguration:UpdateImageGenerationConfiguration' :: UpdateImageGenerationConfiguration
-> Maybe ImageGenerationConfiguration
imageGenerationConfiguration} -> Maybe ImageGenerationConfiguration
imageGenerationConfiguration) (\s :: UpdateImageGenerationConfiguration
s@UpdateImageGenerationConfiguration' {} Maybe ImageGenerationConfiguration
a -> UpdateImageGenerationConfiguration
s {$sel:imageGenerationConfiguration:UpdateImageGenerationConfiguration' :: Maybe ImageGenerationConfiguration
imageGenerationConfiguration = Maybe ImageGenerationConfiguration
a} :: UpdateImageGenerationConfiguration)

-- | The Amazon Resource Name (ARN) of the Kinesis video stream from where
-- you want to update the image generation configuration. You must specify
-- either the @StreamName@ or the @StreamARN@.
updateImageGenerationConfiguration_streamARN :: Lens.Lens' UpdateImageGenerationConfiguration (Prelude.Maybe Prelude.Text)
updateImageGenerationConfiguration_streamARN :: Lens' UpdateImageGenerationConfiguration (Maybe Text)
updateImageGenerationConfiguration_streamARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateImageGenerationConfiguration' {Maybe Text
streamARN :: Maybe Text
$sel:streamARN:UpdateImageGenerationConfiguration' :: UpdateImageGenerationConfiguration -> Maybe Text
streamARN} -> Maybe Text
streamARN) (\s :: UpdateImageGenerationConfiguration
s@UpdateImageGenerationConfiguration' {} Maybe Text
a -> UpdateImageGenerationConfiguration
s {$sel:streamARN:UpdateImageGenerationConfiguration' :: Maybe Text
streamARN = Maybe Text
a} :: UpdateImageGenerationConfiguration)

-- | The name of the stream from which to update the image generation
-- configuration. You must specify either the @StreamName@ or the
-- @StreamARN@.
updateImageGenerationConfiguration_streamName :: Lens.Lens' UpdateImageGenerationConfiguration (Prelude.Maybe Prelude.Text)
updateImageGenerationConfiguration_streamName :: Lens' UpdateImageGenerationConfiguration (Maybe Text)
updateImageGenerationConfiguration_streamName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateImageGenerationConfiguration' {Maybe Text
streamName :: Maybe Text
$sel:streamName:UpdateImageGenerationConfiguration' :: UpdateImageGenerationConfiguration -> Maybe Text
streamName} -> Maybe Text
streamName) (\s :: UpdateImageGenerationConfiguration
s@UpdateImageGenerationConfiguration' {} Maybe Text
a -> UpdateImageGenerationConfiguration
s {$sel:streamName:UpdateImageGenerationConfiguration' :: Maybe Text
streamName = Maybe Text
a} :: UpdateImageGenerationConfiguration)

instance
  Core.AWSRequest
    UpdateImageGenerationConfiguration
  where
  type
    AWSResponse UpdateImageGenerationConfiguration =
      UpdateImageGenerationConfigurationResponse
  request :: (Service -> Service)
-> UpdateImageGenerationConfiguration
-> Request UpdateImageGenerationConfiguration
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateImageGenerationConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse UpdateImageGenerationConfiguration)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> UpdateImageGenerationConfigurationResponse
UpdateImageGenerationConfigurationResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance
  Prelude.Hashable
    UpdateImageGenerationConfiguration
  where
  hashWithSalt :: Int -> UpdateImageGenerationConfiguration -> Int
hashWithSalt
    Int
_salt
    UpdateImageGenerationConfiguration' {Maybe Text
Maybe ImageGenerationConfiguration
streamName :: Maybe Text
streamARN :: Maybe Text
imageGenerationConfiguration :: Maybe ImageGenerationConfiguration
$sel:streamName:UpdateImageGenerationConfiguration' :: UpdateImageGenerationConfiguration -> Maybe Text
$sel:streamARN:UpdateImageGenerationConfiguration' :: UpdateImageGenerationConfiguration -> Maybe Text
$sel:imageGenerationConfiguration:UpdateImageGenerationConfiguration' :: UpdateImageGenerationConfiguration
-> Maybe ImageGenerationConfiguration
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ImageGenerationConfiguration
imageGenerationConfiguration
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
streamARN
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
streamName

instance
  Prelude.NFData
    UpdateImageGenerationConfiguration
  where
  rnf :: UpdateImageGenerationConfiguration -> ()
rnf UpdateImageGenerationConfiguration' {Maybe Text
Maybe ImageGenerationConfiguration
streamName :: Maybe Text
streamARN :: Maybe Text
imageGenerationConfiguration :: Maybe ImageGenerationConfiguration
$sel:streamName:UpdateImageGenerationConfiguration' :: UpdateImageGenerationConfiguration -> Maybe Text
$sel:streamARN:UpdateImageGenerationConfiguration' :: UpdateImageGenerationConfiguration -> Maybe Text
$sel:imageGenerationConfiguration:UpdateImageGenerationConfiguration' :: UpdateImageGenerationConfiguration
-> Maybe ImageGenerationConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ImageGenerationConfiguration
imageGenerationConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
streamARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
streamName

instance
  Data.ToHeaders
    UpdateImageGenerationConfiguration
  where
  toHeaders :: UpdateImageGenerationConfiguration -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance
  Data.ToJSON
    UpdateImageGenerationConfiguration
  where
  toJSON :: UpdateImageGenerationConfiguration -> Value
toJSON UpdateImageGenerationConfiguration' {Maybe Text
Maybe ImageGenerationConfiguration
streamName :: Maybe Text
streamARN :: Maybe Text
imageGenerationConfiguration :: Maybe ImageGenerationConfiguration
$sel:streamName:UpdateImageGenerationConfiguration' :: UpdateImageGenerationConfiguration -> Maybe Text
$sel:streamARN:UpdateImageGenerationConfiguration' :: UpdateImageGenerationConfiguration -> Maybe Text
$sel:imageGenerationConfiguration:UpdateImageGenerationConfiguration' :: UpdateImageGenerationConfiguration
-> Maybe ImageGenerationConfiguration
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ImageGenerationConfiguration" 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 ImageGenerationConfiguration
imageGenerationConfiguration,
            (Key
"StreamARN" 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 Text
streamARN,
            (Key
"StreamName" 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 Text
streamName
          ]
      )

instance
  Data.ToPath
    UpdateImageGenerationConfiguration
  where
  toPath :: UpdateImageGenerationConfiguration -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const ByteString
"/updateImageGenerationConfiguration"

instance
  Data.ToQuery
    UpdateImageGenerationConfiguration
  where
  toQuery :: UpdateImageGenerationConfiguration -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newUpdateImageGenerationConfigurationResponse' smart constructor.
data UpdateImageGenerationConfigurationResponse = UpdateImageGenerationConfigurationResponse'
  { -- | The response's http status code.
    UpdateImageGenerationConfigurationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateImageGenerationConfigurationResponse
-> UpdateImageGenerationConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateImageGenerationConfigurationResponse
-> UpdateImageGenerationConfigurationResponse -> Bool
$c/= :: UpdateImageGenerationConfigurationResponse
-> UpdateImageGenerationConfigurationResponse -> Bool
== :: UpdateImageGenerationConfigurationResponse
-> UpdateImageGenerationConfigurationResponse -> Bool
$c== :: UpdateImageGenerationConfigurationResponse
-> UpdateImageGenerationConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [UpdateImageGenerationConfigurationResponse]
ReadPrec UpdateImageGenerationConfigurationResponse
Int -> ReadS UpdateImageGenerationConfigurationResponse
ReadS [UpdateImageGenerationConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateImageGenerationConfigurationResponse]
$creadListPrec :: ReadPrec [UpdateImageGenerationConfigurationResponse]
readPrec :: ReadPrec UpdateImageGenerationConfigurationResponse
$creadPrec :: ReadPrec UpdateImageGenerationConfigurationResponse
readList :: ReadS [UpdateImageGenerationConfigurationResponse]
$creadList :: ReadS [UpdateImageGenerationConfigurationResponse]
readsPrec :: Int -> ReadS UpdateImageGenerationConfigurationResponse
$creadsPrec :: Int -> ReadS UpdateImageGenerationConfigurationResponse
Prelude.Read, Int -> UpdateImageGenerationConfigurationResponse -> ShowS
[UpdateImageGenerationConfigurationResponse] -> ShowS
UpdateImageGenerationConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateImageGenerationConfigurationResponse] -> ShowS
$cshowList :: [UpdateImageGenerationConfigurationResponse] -> ShowS
show :: UpdateImageGenerationConfigurationResponse -> String
$cshow :: UpdateImageGenerationConfigurationResponse -> String
showsPrec :: Int -> UpdateImageGenerationConfigurationResponse -> ShowS
$cshowsPrec :: Int -> UpdateImageGenerationConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateImageGenerationConfigurationResponse x
-> UpdateImageGenerationConfigurationResponse
forall x.
UpdateImageGenerationConfigurationResponse
-> Rep UpdateImageGenerationConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateImageGenerationConfigurationResponse x
-> UpdateImageGenerationConfigurationResponse
$cfrom :: forall x.
UpdateImageGenerationConfigurationResponse
-> Rep UpdateImageGenerationConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateImageGenerationConfigurationResponse' 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:
--
-- 'httpStatus', 'updateImageGenerationConfigurationResponse_httpStatus' - The response's http status code.
newUpdateImageGenerationConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateImageGenerationConfigurationResponse
newUpdateImageGenerationConfigurationResponse :: Int -> UpdateImageGenerationConfigurationResponse
newUpdateImageGenerationConfigurationResponse
  Int
pHttpStatus_ =
    UpdateImageGenerationConfigurationResponse'
      { $sel:httpStatus:UpdateImageGenerationConfigurationResponse' :: Int
httpStatus =
          Int
pHttpStatus_
      }

-- | The response's http status code.
updateImageGenerationConfigurationResponse_httpStatus :: Lens.Lens' UpdateImageGenerationConfigurationResponse Prelude.Int
updateImageGenerationConfigurationResponse_httpStatus :: Lens' UpdateImageGenerationConfigurationResponse Int
updateImageGenerationConfigurationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateImageGenerationConfigurationResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateImageGenerationConfigurationResponse' :: UpdateImageGenerationConfigurationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateImageGenerationConfigurationResponse
s@UpdateImageGenerationConfigurationResponse' {} Int
a -> UpdateImageGenerationConfigurationResponse
s {$sel:httpStatus:UpdateImageGenerationConfigurationResponse' :: Int
httpStatus = Int
a} :: UpdateImageGenerationConfigurationResponse)

instance
  Prelude.NFData
    UpdateImageGenerationConfigurationResponse
  where
  rnf :: UpdateImageGenerationConfigurationResponse -> ()
rnf UpdateImageGenerationConfigurationResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateImageGenerationConfigurationResponse' :: UpdateImageGenerationConfigurationResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus