{-# 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.UpdateSignalingChannel
-- 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 existing signaling channel. This is an asynchronous
-- operation and takes time to complete.
--
-- If the @MessageTtlSeconds@ value is updated (either increased or
-- reduced), it only applies to new messages sent via this channel after
-- it\'s been updated. Existing messages are still expired as per the
-- previous @MessageTtlSeconds@ value.
module Amazonka.KinesisVideo.UpdateSignalingChannel
  ( -- * Creating a Request
    UpdateSignalingChannel (..),
    newUpdateSignalingChannel,

    -- * Request Lenses
    updateSignalingChannel_singleMasterConfiguration,
    updateSignalingChannel_channelARN,
    updateSignalingChannel_currentVersion,

    -- * Destructuring the Response
    UpdateSignalingChannelResponse (..),
    newUpdateSignalingChannelResponse,

    -- * Response Lenses
    updateSignalingChannelResponse_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:/ 'newUpdateSignalingChannel' smart constructor.
data UpdateSignalingChannel = UpdateSignalingChannel'
  { -- | The structure containing the configuration for the @SINGLE_MASTER@ type
    -- of the signaling channel that you want to update.
    UpdateSignalingChannel -> Maybe SingleMasterConfiguration
singleMasterConfiguration :: Prelude.Maybe SingleMasterConfiguration,
    -- | The Amazon Resource Name (ARN) of the signaling channel that you want to
    -- update.
    UpdateSignalingChannel -> Text
channelARN :: Prelude.Text,
    -- | The current version of the signaling channel that you want to update.
    UpdateSignalingChannel -> Text
currentVersion :: Prelude.Text
  }
  deriving (UpdateSignalingChannel -> UpdateSignalingChannel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSignalingChannel -> UpdateSignalingChannel -> Bool
$c/= :: UpdateSignalingChannel -> UpdateSignalingChannel -> Bool
== :: UpdateSignalingChannel -> UpdateSignalingChannel -> Bool
$c== :: UpdateSignalingChannel -> UpdateSignalingChannel -> Bool
Prelude.Eq, ReadPrec [UpdateSignalingChannel]
ReadPrec UpdateSignalingChannel
Int -> ReadS UpdateSignalingChannel
ReadS [UpdateSignalingChannel]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateSignalingChannel]
$creadListPrec :: ReadPrec [UpdateSignalingChannel]
readPrec :: ReadPrec UpdateSignalingChannel
$creadPrec :: ReadPrec UpdateSignalingChannel
readList :: ReadS [UpdateSignalingChannel]
$creadList :: ReadS [UpdateSignalingChannel]
readsPrec :: Int -> ReadS UpdateSignalingChannel
$creadsPrec :: Int -> ReadS UpdateSignalingChannel
Prelude.Read, Int -> UpdateSignalingChannel -> ShowS
[UpdateSignalingChannel] -> ShowS
UpdateSignalingChannel -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSignalingChannel] -> ShowS
$cshowList :: [UpdateSignalingChannel] -> ShowS
show :: UpdateSignalingChannel -> String
$cshow :: UpdateSignalingChannel -> String
showsPrec :: Int -> UpdateSignalingChannel -> ShowS
$cshowsPrec :: Int -> UpdateSignalingChannel -> ShowS
Prelude.Show, forall x. Rep UpdateSignalingChannel x -> UpdateSignalingChannel
forall x. UpdateSignalingChannel -> Rep UpdateSignalingChannel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateSignalingChannel x -> UpdateSignalingChannel
$cfrom :: forall x. UpdateSignalingChannel -> Rep UpdateSignalingChannel x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSignalingChannel' 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:
--
-- 'singleMasterConfiguration', 'updateSignalingChannel_singleMasterConfiguration' - The structure containing the configuration for the @SINGLE_MASTER@ type
-- of the signaling channel that you want to update.
--
-- 'channelARN', 'updateSignalingChannel_channelARN' - The Amazon Resource Name (ARN) of the signaling channel that you want to
-- update.
--
-- 'currentVersion', 'updateSignalingChannel_currentVersion' - The current version of the signaling channel that you want to update.
newUpdateSignalingChannel ::
  -- | 'channelARN'
  Prelude.Text ->
  -- | 'currentVersion'
  Prelude.Text ->
  UpdateSignalingChannel
newUpdateSignalingChannel :: Text -> Text -> UpdateSignalingChannel
newUpdateSignalingChannel
  Text
pChannelARN_
  Text
pCurrentVersion_ =
    UpdateSignalingChannel'
      { $sel:singleMasterConfiguration:UpdateSignalingChannel' :: Maybe SingleMasterConfiguration
singleMasterConfiguration =
          forall a. Maybe a
Prelude.Nothing,
        $sel:channelARN:UpdateSignalingChannel' :: Text
channelARN = Text
pChannelARN_,
        $sel:currentVersion:UpdateSignalingChannel' :: Text
currentVersion = Text
pCurrentVersion_
      }

-- | The structure containing the configuration for the @SINGLE_MASTER@ type
-- of the signaling channel that you want to update.
updateSignalingChannel_singleMasterConfiguration :: Lens.Lens' UpdateSignalingChannel (Prelude.Maybe SingleMasterConfiguration)
updateSignalingChannel_singleMasterConfiguration :: Lens' UpdateSignalingChannel (Maybe SingleMasterConfiguration)
updateSignalingChannel_singleMasterConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSignalingChannel' {Maybe SingleMasterConfiguration
singleMasterConfiguration :: Maybe SingleMasterConfiguration
$sel:singleMasterConfiguration:UpdateSignalingChannel' :: UpdateSignalingChannel -> Maybe SingleMasterConfiguration
singleMasterConfiguration} -> Maybe SingleMasterConfiguration
singleMasterConfiguration) (\s :: UpdateSignalingChannel
s@UpdateSignalingChannel' {} Maybe SingleMasterConfiguration
a -> UpdateSignalingChannel
s {$sel:singleMasterConfiguration:UpdateSignalingChannel' :: Maybe SingleMasterConfiguration
singleMasterConfiguration = Maybe SingleMasterConfiguration
a} :: UpdateSignalingChannel)

-- | The Amazon Resource Name (ARN) of the signaling channel that you want to
-- update.
updateSignalingChannel_channelARN :: Lens.Lens' UpdateSignalingChannel Prelude.Text
updateSignalingChannel_channelARN :: Lens' UpdateSignalingChannel Text
updateSignalingChannel_channelARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSignalingChannel' {Text
channelARN :: Text
$sel:channelARN:UpdateSignalingChannel' :: UpdateSignalingChannel -> Text
channelARN} -> Text
channelARN) (\s :: UpdateSignalingChannel
s@UpdateSignalingChannel' {} Text
a -> UpdateSignalingChannel
s {$sel:channelARN:UpdateSignalingChannel' :: Text
channelARN = Text
a} :: UpdateSignalingChannel)

-- | The current version of the signaling channel that you want to update.
updateSignalingChannel_currentVersion :: Lens.Lens' UpdateSignalingChannel Prelude.Text
updateSignalingChannel_currentVersion :: Lens' UpdateSignalingChannel Text
updateSignalingChannel_currentVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSignalingChannel' {Text
currentVersion :: Text
$sel:currentVersion:UpdateSignalingChannel' :: UpdateSignalingChannel -> Text
currentVersion} -> Text
currentVersion) (\s :: UpdateSignalingChannel
s@UpdateSignalingChannel' {} Text
a -> UpdateSignalingChannel
s {$sel:currentVersion:UpdateSignalingChannel' :: Text
currentVersion = Text
a} :: UpdateSignalingChannel)

instance Core.AWSRequest UpdateSignalingChannel where
  type
    AWSResponse UpdateSignalingChannel =
      UpdateSignalingChannelResponse
  request :: (Service -> Service)
-> UpdateSignalingChannel -> Request UpdateSignalingChannel
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 UpdateSignalingChannel
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateSignalingChannel)))
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 -> UpdateSignalingChannelResponse
UpdateSignalingChannelResponse'
            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 UpdateSignalingChannel where
  hashWithSalt :: Int -> UpdateSignalingChannel -> Int
hashWithSalt Int
_salt UpdateSignalingChannel' {Maybe SingleMasterConfiguration
Text
currentVersion :: Text
channelARN :: Text
singleMasterConfiguration :: Maybe SingleMasterConfiguration
$sel:currentVersion:UpdateSignalingChannel' :: UpdateSignalingChannel -> Text
$sel:channelARN:UpdateSignalingChannel' :: UpdateSignalingChannel -> Text
$sel:singleMasterConfiguration:UpdateSignalingChannel' :: UpdateSignalingChannel -> Maybe SingleMasterConfiguration
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SingleMasterConfiguration
singleMasterConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
channelARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
currentVersion

instance Prelude.NFData UpdateSignalingChannel where
  rnf :: UpdateSignalingChannel -> ()
rnf UpdateSignalingChannel' {Maybe SingleMasterConfiguration
Text
currentVersion :: Text
channelARN :: Text
singleMasterConfiguration :: Maybe SingleMasterConfiguration
$sel:currentVersion:UpdateSignalingChannel' :: UpdateSignalingChannel -> Text
$sel:channelARN:UpdateSignalingChannel' :: UpdateSignalingChannel -> Text
$sel:singleMasterConfiguration:UpdateSignalingChannel' :: UpdateSignalingChannel -> Maybe SingleMasterConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe SingleMasterConfiguration
singleMasterConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
channelARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
currentVersion

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

instance Data.ToJSON UpdateSignalingChannel where
  toJSON :: UpdateSignalingChannel -> Value
toJSON UpdateSignalingChannel' {Maybe SingleMasterConfiguration
Text
currentVersion :: Text
channelARN :: Text
singleMasterConfiguration :: Maybe SingleMasterConfiguration
$sel:currentVersion:UpdateSignalingChannel' :: UpdateSignalingChannel -> Text
$sel:channelARN:UpdateSignalingChannel' :: UpdateSignalingChannel -> Text
$sel:singleMasterConfiguration:UpdateSignalingChannel' :: UpdateSignalingChannel -> Maybe SingleMasterConfiguration
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"SingleMasterConfiguration" 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 SingleMasterConfiguration
singleMasterConfiguration,
            forall a. a -> Maybe a
Prelude.Just (Key
"ChannelARN" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
channelARN),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"CurrentVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
currentVersion)
          ]
      )

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

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

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

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

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

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