{-# 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.MediaTailor.UpdateChannel
-- 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 a channel. For information about MediaTailor channels, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/channel-assembly-channels.html Working with channels>
-- in the /MediaTailor User Guide/.
module Amazonka.MediaTailor.UpdateChannel
  ( -- * Creating a Request
    UpdateChannel (..),
    newUpdateChannel,

    -- * Request Lenses
    updateChannel_fillerSlate,
    updateChannel_channelName,
    updateChannel_outputs,

    -- * Destructuring the Response
    UpdateChannelResponse (..),
    newUpdateChannelResponse,

    -- * Response Lenses
    updateChannelResponse_arn,
    updateChannelResponse_channelName,
    updateChannelResponse_channelState,
    updateChannelResponse_creationTime,
    updateChannelResponse_fillerSlate,
    updateChannelResponse_lastModifiedTime,
    updateChannelResponse_outputs,
    updateChannelResponse_playbackMode,
    updateChannelResponse_tags,
    updateChannelResponse_tier,
    updateChannelResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MediaTailor.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateChannel' smart constructor.
data UpdateChannel = UpdateChannel'
  { -- | The slate used to fill gaps between programs in the schedule. You must
    -- configure filler slate if your channel uses the @LINEAR@ @PlaybackMode@.
    -- MediaTailor doesn\'t support filler slate for channels using the @LOOP@
    -- @PlaybackMode@.
    UpdateChannel -> Maybe SlateSource
fillerSlate :: Prelude.Maybe SlateSource,
    -- | The name of the channel.
    UpdateChannel -> Text
channelName :: Prelude.Text,
    -- | The channel\'s output properties.
    UpdateChannel -> [RequestOutputItem]
outputs :: [RequestOutputItem]
  }
  deriving (UpdateChannel -> UpdateChannel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateChannel -> UpdateChannel -> Bool
$c/= :: UpdateChannel -> UpdateChannel -> Bool
== :: UpdateChannel -> UpdateChannel -> Bool
$c== :: UpdateChannel -> UpdateChannel -> Bool
Prelude.Eq, ReadPrec [UpdateChannel]
ReadPrec UpdateChannel
Int -> ReadS UpdateChannel
ReadS [UpdateChannel]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateChannel]
$creadListPrec :: ReadPrec [UpdateChannel]
readPrec :: ReadPrec UpdateChannel
$creadPrec :: ReadPrec UpdateChannel
readList :: ReadS [UpdateChannel]
$creadList :: ReadS [UpdateChannel]
readsPrec :: Int -> ReadS UpdateChannel
$creadsPrec :: Int -> ReadS UpdateChannel
Prelude.Read, Int -> UpdateChannel -> ShowS
[UpdateChannel] -> ShowS
UpdateChannel -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateChannel] -> ShowS
$cshowList :: [UpdateChannel] -> ShowS
show :: UpdateChannel -> String
$cshow :: UpdateChannel -> String
showsPrec :: Int -> UpdateChannel -> ShowS
$cshowsPrec :: Int -> UpdateChannel -> ShowS
Prelude.Show, forall x. Rep UpdateChannel x -> UpdateChannel
forall x. UpdateChannel -> Rep UpdateChannel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateChannel x -> UpdateChannel
$cfrom :: forall x. UpdateChannel -> Rep UpdateChannel x
Prelude.Generic)

-- |
-- Create a value of 'UpdateChannel' 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:
--
-- 'fillerSlate', 'updateChannel_fillerSlate' - The slate used to fill gaps between programs in the schedule. You must
-- configure filler slate if your channel uses the @LINEAR@ @PlaybackMode@.
-- MediaTailor doesn\'t support filler slate for channels using the @LOOP@
-- @PlaybackMode@.
--
-- 'channelName', 'updateChannel_channelName' - The name of the channel.
--
-- 'outputs', 'updateChannel_outputs' - The channel\'s output properties.
newUpdateChannel ::
  -- | 'channelName'
  Prelude.Text ->
  UpdateChannel
newUpdateChannel :: Text -> UpdateChannel
newUpdateChannel Text
pChannelName_ =
  UpdateChannel'
    { $sel:fillerSlate:UpdateChannel' :: Maybe SlateSource
fillerSlate = forall a. Maybe a
Prelude.Nothing,
      $sel:channelName:UpdateChannel' :: Text
channelName = Text
pChannelName_,
      $sel:outputs:UpdateChannel' :: [RequestOutputItem]
outputs = forall a. Monoid a => a
Prelude.mempty
    }

-- | The slate used to fill gaps between programs in the schedule. You must
-- configure filler slate if your channel uses the @LINEAR@ @PlaybackMode@.
-- MediaTailor doesn\'t support filler slate for channels using the @LOOP@
-- @PlaybackMode@.
updateChannel_fillerSlate :: Lens.Lens' UpdateChannel (Prelude.Maybe SlateSource)
updateChannel_fillerSlate :: Lens' UpdateChannel (Maybe SlateSource)
updateChannel_fillerSlate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChannel' {Maybe SlateSource
fillerSlate :: Maybe SlateSource
$sel:fillerSlate:UpdateChannel' :: UpdateChannel -> Maybe SlateSource
fillerSlate} -> Maybe SlateSource
fillerSlate) (\s :: UpdateChannel
s@UpdateChannel' {} Maybe SlateSource
a -> UpdateChannel
s {$sel:fillerSlate:UpdateChannel' :: Maybe SlateSource
fillerSlate = Maybe SlateSource
a} :: UpdateChannel)

-- | The name of the channel.
updateChannel_channelName :: Lens.Lens' UpdateChannel Prelude.Text
updateChannel_channelName :: Lens' UpdateChannel Text
updateChannel_channelName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChannel' {Text
channelName :: Text
$sel:channelName:UpdateChannel' :: UpdateChannel -> Text
channelName} -> Text
channelName) (\s :: UpdateChannel
s@UpdateChannel' {} Text
a -> UpdateChannel
s {$sel:channelName:UpdateChannel' :: Text
channelName = Text
a} :: UpdateChannel)

-- | The channel\'s output properties.
updateChannel_outputs :: Lens.Lens' UpdateChannel [RequestOutputItem]
updateChannel_outputs :: Lens' UpdateChannel [RequestOutputItem]
updateChannel_outputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChannel' {[RequestOutputItem]
outputs :: [RequestOutputItem]
$sel:outputs:UpdateChannel' :: UpdateChannel -> [RequestOutputItem]
outputs} -> [RequestOutputItem]
outputs) (\s :: UpdateChannel
s@UpdateChannel' {} [RequestOutputItem]
a -> UpdateChannel
s {$sel:outputs:UpdateChannel' :: [RequestOutputItem]
outputs = [RequestOutputItem]
a} :: UpdateChannel) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest UpdateChannel where
  type
    AWSResponse UpdateChannel =
      UpdateChannelResponse
  request :: (Service -> Service) -> UpdateChannel -> Request UpdateChannel
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateChannel
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateChannel)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe ChannelState
-> Maybe POSIX
-> Maybe SlateSource
-> Maybe POSIX
-> Maybe [ResponseOutputItem]
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Maybe Text
-> Int
-> UpdateChannelResponse
UpdateChannelResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ChannelName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ChannelState")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CreationTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"FillerSlate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LastModifiedTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Outputs" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (Maybe a)
Data..?> Key
"PlaybackMode")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (Maybe a)
Data..?> Key
"Tier")
            forall (f :: * -> *) a b. Applicative f => 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 UpdateChannel where
  hashWithSalt :: Int -> UpdateChannel -> Int
hashWithSalt Int
_salt UpdateChannel' {[RequestOutputItem]
Maybe SlateSource
Text
outputs :: [RequestOutputItem]
channelName :: Text
fillerSlate :: Maybe SlateSource
$sel:outputs:UpdateChannel' :: UpdateChannel -> [RequestOutputItem]
$sel:channelName:UpdateChannel' :: UpdateChannel -> Text
$sel:fillerSlate:UpdateChannel' :: UpdateChannel -> Maybe SlateSource
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SlateSource
fillerSlate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
channelName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [RequestOutputItem]
outputs

instance Prelude.NFData UpdateChannel where
  rnf :: UpdateChannel -> ()
rnf UpdateChannel' {[RequestOutputItem]
Maybe SlateSource
Text
outputs :: [RequestOutputItem]
channelName :: Text
fillerSlate :: Maybe SlateSource
$sel:outputs:UpdateChannel' :: UpdateChannel -> [RequestOutputItem]
$sel:channelName:UpdateChannel' :: UpdateChannel -> Text
$sel:fillerSlate:UpdateChannel' :: UpdateChannel -> Maybe SlateSource
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe SlateSource
fillerSlate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
channelName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [RequestOutputItem]
outputs

instance Data.ToHeaders UpdateChannel where
  toHeaders :: UpdateChannel -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateChannel where
  toJSON :: UpdateChannel -> Value
toJSON UpdateChannel' {[RequestOutputItem]
Maybe SlateSource
Text
outputs :: [RequestOutputItem]
channelName :: Text
fillerSlate :: Maybe SlateSource
$sel:outputs:UpdateChannel' :: UpdateChannel -> [RequestOutputItem]
$sel:channelName:UpdateChannel' :: UpdateChannel -> Text
$sel:fillerSlate:UpdateChannel' :: UpdateChannel -> Maybe SlateSource
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"FillerSlate" 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 SlateSource
fillerSlate,
            forall a. a -> Maybe a
Prelude.Just (Key
"Outputs" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [RequestOutputItem]
outputs)
          ]
      )

instance Data.ToPath UpdateChannel where
  toPath :: UpdateChannel -> ByteString
toPath UpdateChannel' {[RequestOutputItem]
Maybe SlateSource
Text
outputs :: [RequestOutputItem]
channelName :: Text
fillerSlate :: Maybe SlateSource
$sel:outputs:UpdateChannel' :: UpdateChannel -> [RequestOutputItem]
$sel:channelName:UpdateChannel' :: UpdateChannel -> Text
$sel:fillerSlate:UpdateChannel' :: UpdateChannel -> Maybe SlateSource
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/channel/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
channelName]

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

-- | /See:/ 'newUpdateChannelResponse' smart constructor.
data UpdateChannelResponse = UpdateChannelResponse'
  { -- | The Amazon Resource Name (ARN) associated with the channel.
    UpdateChannelResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The name of the channel.
    UpdateChannelResponse -> Maybe Text
channelName :: Prelude.Maybe Prelude.Text,
    -- | Returns the state whether the channel is running or not.
    UpdateChannelResponse -> Maybe ChannelState
channelState :: Prelude.Maybe ChannelState,
    -- | The timestamp of when the channel was created.
    UpdateChannelResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The slate used to fill gaps between programs in the schedule. You must
    -- configure filler slate if your channel uses the @LINEAR@ @PlaybackMode@.
    -- MediaTailor doesn\'t support filler slate for channels using the @LOOP@
    -- @PlaybackMode@.
    UpdateChannelResponse -> Maybe SlateSource
fillerSlate :: Prelude.Maybe SlateSource,
    -- | The timestamp that indicates when the channel was last modified.
    UpdateChannelResponse -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | The channel\'s output properties.
    UpdateChannelResponse -> Maybe [ResponseOutputItem]
outputs :: Prelude.Maybe [ResponseOutputItem],
    -- | The type of playback mode for this channel.
    --
    -- @LINEAR@ - Programs play back-to-back only once.
    --
    -- @LOOP@ - Programs play back-to-back in an endless loop. When the last
    -- program in the schedule plays, playback loops back to the first program
    -- in the schedule.
    UpdateChannelResponse -> Maybe Text
playbackMode :: Prelude.Maybe Prelude.Text,
    -- | The tags to assign to the channel. Tags are key-value pairs that you can
    -- associate with Amazon resources to help with organization, access
    -- control, and cost tracking. For more information, see
    -- <https://docs.aws.amazon.com/mediatailor/latest/ug/tagging.html Tagging AWS Elemental MediaTailor Resources>.
    UpdateChannelResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The tier associated with this Channel.
    UpdateChannelResponse -> Maybe Text
tier :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateChannelResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateChannelResponse -> UpdateChannelResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateChannelResponse -> UpdateChannelResponse -> Bool
$c/= :: UpdateChannelResponse -> UpdateChannelResponse -> Bool
== :: UpdateChannelResponse -> UpdateChannelResponse -> Bool
$c== :: UpdateChannelResponse -> UpdateChannelResponse -> Bool
Prelude.Eq, ReadPrec [UpdateChannelResponse]
ReadPrec UpdateChannelResponse
Int -> ReadS UpdateChannelResponse
ReadS [UpdateChannelResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateChannelResponse]
$creadListPrec :: ReadPrec [UpdateChannelResponse]
readPrec :: ReadPrec UpdateChannelResponse
$creadPrec :: ReadPrec UpdateChannelResponse
readList :: ReadS [UpdateChannelResponse]
$creadList :: ReadS [UpdateChannelResponse]
readsPrec :: Int -> ReadS UpdateChannelResponse
$creadsPrec :: Int -> ReadS UpdateChannelResponse
Prelude.Read, Int -> UpdateChannelResponse -> ShowS
[UpdateChannelResponse] -> ShowS
UpdateChannelResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateChannelResponse] -> ShowS
$cshowList :: [UpdateChannelResponse] -> ShowS
show :: UpdateChannelResponse -> String
$cshow :: UpdateChannelResponse -> String
showsPrec :: Int -> UpdateChannelResponse -> ShowS
$cshowsPrec :: Int -> UpdateChannelResponse -> ShowS
Prelude.Show, forall x. Rep UpdateChannelResponse x -> UpdateChannelResponse
forall x. UpdateChannelResponse -> Rep UpdateChannelResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateChannelResponse x -> UpdateChannelResponse
$cfrom :: forall x. UpdateChannelResponse -> Rep UpdateChannelResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateChannelResponse' 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:
--
-- 'arn', 'updateChannelResponse_arn' - The Amazon Resource Name (ARN) associated with the channel.
--
-- 'channelName', 'updateChannelResponse_channelName' - The name of the channel.
--
-- 'channelState', 'updateChannelResponse_channelState' - Returns the state whether the channel is running or not.
--
-- 'creationTime', 'updateChannelResponse_creationTime' - The timestamp of when the channel was created.
--
-- 'fillerSlate', 'updateChannelResponse_fillerSlate' - The slate used to fill gaps between programs in the schedule. You must
-- configure filler slate if your channel uses the @LINEAR@ @PlaybackMode@.
-- MediaTailor doesn\'t support filler slate for channels using the @LOOP@
-- @PlaybackMode@.
--
-- 'lastModifiedTime', 'updateChannelResponse_lastModifiedTime' - The timestamp that indicates when the channel was last modified.
--
-- 'outputs', 'updateChannelResponse_outputs' - The channel\'s output properties.
--
-- 'playbackMode', 'updateChannelResponse_playbackMode' - The type of playback mode for this channel.
--
-- @LINEAR@ - Programs play back-to-back only once.
--
-- @LOOP@ - Programs play back-to-back in an endless loop. When the last
-- program in the schedule plays, playback loops back to the first program
-- in the schedule.
--
-- 'tags', 'updateChannelResponse_tags' - The tags to assign to the channel. Tags are key-value pairs that you can
-- associate with Amazon resources to help with organization, access
-- control, and cost tracking. For more information, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/tagging.html Tagging AWS Elemental MediaTailor Resources>.
--
-- 'tier', 'updateChannelResponse_tier' - The tier associated with this Channel.
--
-- 'httpStatus', 'updateChannelResponse_httpStatus' - The response's http status code.
newUpdateChannelResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateChannelResponse
newUpdateChannelResponse :: Int -> UpdateChannelResponse
newUpdateChannelResponse Int
pHttpStatus_ =
  UpdateChannelResponse'
    { $sel:arn:UpdateChannelResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:channelName:UpdateChannelResponse' :: Maybe Text
channelName = forall a. Maybe a
Prelude.Nothing,
      $sel:channelState:UpdateChannelResponse' :: Maybe ChannelState
channelState = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:UpdateChannelResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:fillerSlate:UpdateChannelResponse' :: Maybe SlateSource
fillerSlate = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:UpdateChannelResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:outputs:UpdateChannelResponse' :: Maybe [ResponseOutputItem]
outputs = forall a. Maybe a
Prelude.Nothing,
      $sel:playbackMode:UpdateChannelResponse' :: Maybe Text
playbackMode = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:UpdateChannelResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:tier:UpdateChannelResponse' :: Maybe Text
tier = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateChannelResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) associated with the channel.
updateChannelResponse_arn :: Lens.Lens' UpdateChannelResponse (Prelude.Maybe Prelude.Text)
updateChannelResponse_arn :: Lens' UpdateChannelResponse (Maybe Text)
updateChannelResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChannelResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: UpdateChannelResponse
s@UpdateChannelResponse' {} Maybe Text
a -> UpdateChannelResponse
s {$sel:arn:UpdateChannelResponse' :: Maybe Text
arn = Maybe Text
a} :: UpdateChannelResponse)

-- | The name of the channel.
updateChannelResponse_channelName :: Lens.Lens' UpdateChannelResponse (Prelude.Maybe Prelude.Text)
updateChannelResponse_channelName :: Lens' UpdateChannelResponse (Maybe Text)
updateChannelResponse_channelName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChannelResponse' {Maybe Text
channelName :: Maybe Text
$sel:channelName:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe Text
channelName} -> Maybe Text
channelName) (\s :: UpdateChannelResponse
s@UpdateChannelResponse' {} Maybe Text
a -> UpdateChannelResponse
s {$sel:channelName:UpdateChannelResponse' :: Maybe Text
channelName = Maybe Text
a} :: UpdateChannelResponse)

-- | Returns the state whether the channel is running or not.
updateChannelResponse_channelState :: Lens.Lens' UpdateChannelResponse (Prelude.Maybe ChannelState)
updateChannelResponse_channelState :: Lens' UpdateChannelResponse (Maybe ChannelState)
updateChannelResponse_channelState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChannelResponse' {Maybe ChannelState
channelState :: Maybe ChannelState
$sel:channelState:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe ChannelState
channelState} -> Maybe ChannelState
channelState) (\s :: UpdateChannelResponse
s@UpdateChannelResponse' {} Maybe ChannelState
a -> UpdateChannelResponse
s {$sel:channelState:UpdateChannelResponse' :: Maybe ChannelState
channelState = Maybe ChannelState
a} :: UpdateChannelResponse)

-- | The timestamp of when the channel was created.
updateChannelResponse_creationTime :: Lens.Lens' UpdateChannelResponse (Prelude.Maybe Prelude.UTCTime)
updateChannelResponse_creationTime :: Lens' UpdateChannelResponse (Maybe UTCTime)
updateChannelResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChannelResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: UpdateChannelResponse
s@UpdateChannelResponse' {} Maybe POSIX
a -> UpdateChannelResponse
s {$sel:creationTime:UpdateChannelResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: UpdateChannelResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The slate used to fill gaps between programs in the schedule. You must
-- configure filler slate if your channel uses the @LINEAR@ @PlaybackMode@.
-- MediaTailor doesn\'t support filler slate for channels using the @LOOP@
-- @PlaybackMode@.
updateChannelResponse_fillerSlate :: Lens.Lens' UpdateChannelResponse (Prelude.Maybe SlateSource)
updateChannelResponse_fillerSlate :: Lens' UpdateChannelResponse (Maybe SlateSource)
updateChannelResponse_fillerSlate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChannelResponse' {Maybe SlateSource
fillerSlate :: Maybe SlateSource
$sel:fillerSlate:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe SlateSource
fillerSlate} -> Maybe SlateSource
fillerSlate) (\s :: UpdateChannelResponse
s@UpdateChannelResponse' {} Maybe SlateSource
a -> UpdateChannelResponse
s {$sel:fillerSlate:UpdateChannelResponse' :: Maybe SlateSource
fillerSlate = Maybe SlateSource
a} :: UpdateChannelResponse)

-- | The timestamp that indicates when the channel was last modified.
updateChannelResponse_lastModifiedTime :: Lens.Lens' UpdateChannelResponse (Prelude.Maybe Prelude.UTCTime)
updateChannelResponse_lastModifiedTime :: Lens' UpdateChannelResponse (Maybe UTCTime)
updateChannelResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChannelResponse' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: UpdateChannelResponse
s@UpdateChannelResponse' {} Maybe POSIX
a -> UpdateChannelResponse
s {$sel:lastModifiedTime:UpdateChannelResponse' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: UpdateChannelResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The channel\'s output properties.
updateChannelResponse_outputs :: Lens.Lens' UpdateChannelResponse (Prelude.Maybe [ResponseOutputItem])
updateChannelResponse_outputs :: Lens' UpdateChannelResponse (Maybe [ResponseOutputItem])
updateChannelResponse_outputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChannelResponse' {Maybe [ResponseOutputItem]
outputs :: Maybe [ResponseOutputItem]
$sel:outputs:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe [ResponseOutputItem]
outputs} -> Maybe [ResponseOutputItem]
outputs) (\s :: UpdateChannelResponse
s@UpdateChannelResponse' {} Maybe [ResponseOutputItem]
a -> UpdateChannelResponse
s {$sel:outputs:UpdateChannelResponse' :: Maybe [ResponseOutputItem]
outputs = Maybe [ResponseOutputItem]
a} :: UpdateChannelResponse) 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 type of playback mode for this channel.
--
-- @LINEAR@ - Programs play back-to-back only once.
--
-- @LOOP@ - Programs play back-to-back in an endless loop. When the last
-- program in the schedule plays, playback loops back to the first program
-- in the schedule.
updateChannelResponse_playbackMode :: Lens.Lens' UpdateChannelResponse (Prelude.Maybe Prelude.Text)
updateChannelResponse_playbackMode :: Lens' UpdateChannelResponse (Maybe Text)
updateChannelResponse_playbackMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChannelResponse' {Maybe Text
playbackMode :: Maybe Text
$sel:playbackMode:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe Text
playbackMode} -> Maybe Text
playbackMode) (\s :: UpdateChannelResponse
s@UpdateChannelResponse' {} Maybe Text
a -> UpdateChannelResponse
s {$sel:playbackMode:UpdateChannelResponse' :: Maybe Text
playbackMode = Maybe Text
a} :: UpdateChannelResponse)

-- | The tags to assign to the channel. Tags are key-value pairs that you can
-- associate with Amazon resources to help with organization, access
-- control, and cost tracking. For more information, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/tagging.html Tagging AWS Elemental MediaTailor Resources>.
updateChannelResponse_tags :: Lens.Lens' UpdateChannelResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
updateChannelResponse_tags :: Lens' UpdateChannelResponse (Maybe (HashMap Text Text))
updateChannelResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChannelResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: UpdateChannelResponse
s@UpdateChannelResponse' {} Maybe (HashMap Text Text)
a -> UpdateChannelResponse
s {$sel:tags:UpdateChannelResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: UpdateChannelResponse) 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 tier associated with this Channel.
updateChannelResponse_tier :: Lens.Lens' UpdateChannelResponse (Prelude.Maybe Prelude.Text)
updateChannelResponse_tier :: Lens' UpdateChannelResponse (Maybe Text)
updateChannelResponse_tier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateChannelResponse' {Maybe Text
tier :: Maybe Text
$sel:tier:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe Text
tier} -> Maybe Text
tier) (\s :: UpdateChannelResponse
s@UpdateChannelResponse' {} Maybe Text
a -> UpdateChannelResponse
s {$sel:tier:UpdateChannelResponse' :: Maybe Text
tier = Maybe Text
a} :: UpdateChannelResponse)

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

instance Prelude.NFData UpdateChannelResponse where
  rnf :: UpdateChannelResponse -> ()
rnf UpdateChannelResponse' {Int
Maybe [ResponseOutputItem]
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe ChannelState
Maybe SlateSource
httpStatus :: Int
tier :: Maybe Text
tags :: Maybe (HashMap Text Text)
playbackMode :: Maybe Text
outputs :: Maybe [ResponseOutputItem]
lastModifiedTime :: Maybe POSIX
fillerSlate :: Maybe SlateSource
creationTime :: Maybe POSIX
channelState :: Maybe ChannelState
channelName :: Maybe Text
arn :: Maybe Text
$sel:httpStatus:UpdateChannelResponse' :: UpdateChannelResponse -> Int
$sel:tier:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe Text
$sel:tags:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe (HashMap Text Text)
$sel:playbackMode:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe Text
$sel:outputs:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe [ResponseOutputItem]
$sel:lastModifiedTime:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe POSIX
$sel:fillerSlate:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe SlateSource
$sel:creationTime:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe POSIX
$sel:channelState:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe ChannelState
$sel:channelName:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe Text
$sel:arn:UpdateChannelResponse' :: UpdateChannelResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
channelName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ChannelState
channelState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SlateSource
fillerSlate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ResponseOutputItem]
outputs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
playbackMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
tier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus