{-# 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.CreateChannel
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates 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.CreateChannel
  ( -- * Creating a Request
    CreateChannel (..),
    newCreateChannel,

    -- * Request Lenses
    createChannel_fillerSlate,
    createChannel_tags,
    createChannel_tier,
    createChannel_channelName,
    createChannel_outputs,
    createChannel_playbackMode,

    -- * Destructuring the Response
    CreateChannelResponse (..),
    newCreateChannelResponse,

    -- * Response Lenses
    createChannelResponse_arn,
    createChannelResponse_channelName,
    createChannelResponse_channelState,
    createChannelResponse_creationTime,
    createChannelResponse_fillerSlate,
    createChannelResponse_lastModifiedTime,
    createChannelResponse_outputs,
    createChannelResponse_playbackMode,
    createChannelResponse_tags,
    createChannelResponse_tier,
    createChannelResponse_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:/ 'newCreateChannel' smart constructor.
data CreateChannel = CreateChannel'
  { -- | 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@.
    CreateChannel -> Maybe SlateSource
fillerSlate :: Prelude.Maybe SlateSource,
    -- | 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>.
    CreateChannel -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The tier of the channel.
    CreateChannel -> Maybe Tier
tier :: Prelude.Maybe Tier,
    -- | The name of the channel.
    CreateChannel -> Text
channelName :: Prelude.Text,
    -- | The channel\'s output properties.
    CreateChannel -> [RequestOutputItem]
outputs :: [RequestOutputItem],
    -- | The type of playback mode to use for this channel.
    --
    -- @LINEAR@ - The programs in the schedule play once back-to-back in the
    -- schedule.
    --
    -- @LOOP@ - The programs in the schedule play back-to-back in an endless
    -- loop. When the last program in the schedule stops playing, playback
    -- loops back to the first program in the schedule.
    CreateChannel -> PlaybackMode
playbackMode :: PlaybackMode
  }
  deriving (CreateChannel -> CreateChannel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateChannel -> CreateChannel -> Bool
$c/= :: CreateChannel -> CreateChannel -> Bool
== :: CreateChannel -> CreateChannel -> Bool
$c== :: CreateChannel -> CreateChannel -> Bool
Prelude.Eq, ReadPrec [CreateChannel]
ReadPrec CreateChannel
Int -> ReadS CreateChannel
ReadS [CreateChannel]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateChannel]
$creadListPrec :: ReadPrec [CreateChannel]
readPrec :: ReadPrec CreateChannel
$creadPrec :: ReadPrec CreateChannel
readList :: ReadS [CreateChannel]
$creadList :: ReadS [CreateChannel]
readsPrec :: Int -> ReadS CreateChannel
$creadsPrec :: Int -> ReadS CreateChannel
Prelude.Read, Int -> CreateChannel -> ShowS
[CreateChannel] -> ShowS
CreateChannel -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateChannel] -> ShowS
$cshowList :: [CreateChannel] -> ShowS
show :: CreateChannel -> String
$cshow :: CreateChannel -> String
showsPrec :: Int -> CreateChannel -> ShowS
$cshowsPrec :: Int -> CreateChannel -> ShowS
Prelude.Show, forall x. Rep CreateChannel x -> CreateChannel
forall x. CreateChannel -> Rep CreateChannel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateChannel x -> CreateChannel
$cfrom :: forall x. CreateChannel -> Rep CreateChannel x
Prelude.Generic)

-- |
-- Create a value of 'CreateChannel' 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', 'createChannel_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@.
--
-- 'tags', 'createChannel_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', 'createChannel_tier' - The tier of the channel.
--
-- 'channelName', 'createChannel_channelName' - The name of the channel.
--
-- 'outputs', 'createChannel_outputs' - The channel\'s output properties.
--
-- 'playbackMode', 'createChannel_playbackMode' - The type of playback mode to use for this channel.
--
-- @LINEAR@ - The programs in the schedule play once back-to-back in the
-- schedule.
--
-- @LOOP@ - The programs in the schedule play back-to-back in an endless
-- loop. When the last program in the schedule stops playing, playback
-- loops back to the first program in the schedule.
newCreateChannel ::
  -- | 'channelName'
  Prelude.Text ->
  -- | 'playbackMode'
  PlaybackMode ->
  CreateChannel
newCreateChannel :: Text -> PlaybackMode -> CreateChannel
newCreateChannel Text
pChannelName_ PlaybackMode
pPlaybackMode_ =
  CreateChannel'
    { $sel:fillerSlate:CreateChannel' :: Maybe SlateSource
fillerSlate = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateChannel' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:tier:CreateChannel' :: Maybe Tier
tier = forall a. Maybe a
Prelude.Nothing,
      $sel:channelName:CreateChannel' :: Text
channelName = Text
pChannelName_,
      $sel:outputs:CreateChannel' :: [RequestOutputItem]
outputs = forall a. Monoid a => a
Prelude.mempty,
      $sel:playbackMode:CreateChannel' :: PlaybackMode
playbackMode = PlaybackMode
pPlaybackMode_
    }

-- | 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@.
createChannel_fillerSlate :: Lens.Lens' CreateChannel (Prelude.Maybe SlateSource)
createChannel_fillerSlate :: Lens' CreateChannel (Maybe SlateSource)
createChannel_fillerSlate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {Maybe SlateSource
fillerSlate :: Maybe SlateSource
$sel:fillerSlate:CreateChannel' :: CreateChannel -> Maybe SlateSource
fillerSlate} -> Maybe SlateSource
fillerSlate) (\s :: CreateChannel
s@CreateChannel' {} Maybe SlateSource
a -> CreateChannel
s {$sel:fillerSlate:CreateChannel' :: Maybe SlateSource
fillerSlate = Maybe SlateSource
a} :: CreateChannel)

-- | 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>.
createChannel_tags :: Lens.Lens' CreateChannel (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createChannel_tags :: Lens' CreateChannel (Maybe (HashMap Text Text))
createChannel_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateChannel' :: CreateChannel -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateChannel
s@CreateChannel' {} Maybe (HashMap Text Text)
a -> CreateChannel
s {$sel:tags:CreateChannel' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateChannel) 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 of the channel.
createChannel_tier :: Lens.Lens' CreateChannel (Prelude.Maybe Tier)
createChannel_tier :: Lens' CreateChannel (Maybe Tier)
createChannel_tier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {Maybe Tier
tier :: Maybe Tier
$sel:tier:CreateChannel' :: CreateChannel -> Maybe Tier
tier} -> Maybe Tier
tier) (\s :: CreateChannel
s@CreateChannel' {} Maybe Tier
a -> CreateChannel
s {$sel:tier:CreateChannel' :: Maybe Tier
tier = Maybe Tier
a} :: CreateChannel)

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

-- | The channel\'s output properties.
createChannel_outputs :: Lens.Lens' CreateChannel [RequestOutputItem]
createChannel_outputs :: Lens' CreateChannel [RequestOutputItem]
createChannel_outputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {[RequestOutputItem]
outputs :: [RequestOutputItem]
$sel:outputs:CreateChannel' :: CreateChannel -> [RequestOutputItem]
outputs} -> [RequestOutputItem]
outputs) (\s :: CreateChannel
s@CreateChannel' {} [RequestOutputItem]
a -> CreateChannel
s {$sel:outputs:CreateChannel' :: [RequestOutputItem]
outputs = [RequestOutputItem]
a} :: CreateChannel) 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

-- | The type of playback mode to use for this channel.
--
-- @LINEAR@ - The programs in the schedule play once back-to-back in the
-- schedule.
--
-- @LOOP@ - The programs in the schedule play back-to-back in an endless
-- loop. When the last program in the schedule stops playing, playback
-- loops back to the first program in the schedule.
createChannel_playbackMode :: Lens.Lens' CreateChannel PlaybackMode
createChannel_playbackMode :: Lens' CreateChannel PlaybackMode
createChannel_playbackMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {PlaybackMode
playbackMode :: PlaybackMode
$sel:playbackMode:CreateChannel' :: CreateChannel -> PlaybackMode
playbackMode} -> PlaybackMode
playbackMode) (\s :: CreateChannel
s@CreateChannel' {} PlaybackMode
a -> CreateChannel
s {$sel:playbackMode:CreateChannel' :: PlaybackMode
playbackMode = PlaybackMode
a} :: CreateChannel)

instance Core.AWSRequest CreateChannel where
  type
    AWSResponse CreateChannel =
      CreateChannelResponse
  request :: (Service -> Service) -> CreateChannel -> Request CreateChannel
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 CreateChannel
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateChannel)))
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
-> CreateChannelResponse
CreateChannelResponse'
            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 CreateChannel where
  hashWithSalt :: Int -> CreateChannel -> Int
hashWithSalt Int
_salt CreateChannel' {[RequestOutputItem]
Maybe (HashMap Text Text)
Maybe SlateSource
Maybe Tier
Text
PlaybackMode
playbackMode :: PlaybackMode
outputs :: [RequestOutputItem]
channelName :: Text
tier :: Maybe Tier
tags :: Maybe (HashMap Text Text)
fillerSlate :: Maybe SlateSource
$sel:playbackMode:CreateChannel' :: CreateChannel -> PlaybackMode
$sel:outputs:CreateChannel' :: CreateChannel -> [RequestOutputItem]
$sel:channelName:CreateChannel' :: CreateChannel -> Text
$sel:tier:CreateChannel' :: CreateChannel -> Maybe Tier
$sel:tags:CreateChannel' :: CreateChannel -> Maybe (HashMap Text Text)
$sel:fillerSlate:CreateChannel' :: CreateChannel -> 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` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Tier
tier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
channelName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [RequestOutputItem]
outputs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` PlaybackMode
playbackMode

instance Prelude.NFData CreateChannel where
  rnf :: CreateChannel -> ()
rnf CreateChannel' {[RequestOutputItem]
Maybe (HashMap Text Text)
Maybe SlateSource
Maybe Tier
Text
PlaybackMode
playbackMode :: PlaybackMode
outputs :: [RequestOutputItem]
channelName :: Text
tier :: Maybe Tier
tags :: Maybe (HashMap Text Text)
fillerSlate :: Maybe SlateSource
$sel:playbackMode:CreateChannel' :: CreateChannel -> PlaybackMode
$sel:outputs:CreateChannel' :: CreateChannel -> [RequestOutputItem]
$sel:channelName:CreateChannel' :: CreateChannel -> Text
$sel:tier:CreateChannel' :: CreateChannel -> Maybe Tier
$sel:tags:CreateChannel' :: CreateChannel -> Maybe (HashMap Text Text)
$sel:fillerSlate:CreateChannel' :: CreateChannel -> 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 Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Tier
tier
      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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf PlaybackMode
playbackMode

instance Data.ToHeaders CreateChannel where
  toHeaders :: CreateChannel -> 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 CreateChannel where
  toJSON :: CreateChannel -> Value
toJSON CreateChannel' {[RequestOutputItem]
Maybe (HashMap Text Text)
Maybe SlateSource
Maybe Tier
Text
PlaybackMode
playbackMode :: PlaybackMode
outputs :: [RequestOutputItem]
channelName :: Text
tier :: Maybe Tier
tags :: Maybe (HashMap Text Text)
fillerSlate :: Maybe SlateSource
$sel:playbackMode:CreateChannel' :: CreateChannel -> PlaybackMode
$sel:outputs:CreateChannel' :: CreateChannel -> [RequestOutputItem]
$sel:channelName:CreateChannel' :: CreateChannel -> Text
$sel:tier:CreateChannel' :: CreateChannel -> Maybe Tier
$sel:tags:CreateChannel' :: CreateChannel -> Maybe (HashMap Text Text)
$sel:fillerSlate:CreateChannel' :: CreateChannel -> 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,
            (Key
"tags" 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 Text Text)
tags,
            (Key
"Tier" 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 Tier
tier,
            forall a. a -> Maybe a
Prelude.Just (Key
"Outputs" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [RequestOutputItem]
outputs),
            forall a. a -> Maybe a
Prelude.Just (Key
"PlaybackMode" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= PlaybackMode
playbackMode)
          ]
      )

instance Data.ToPath CreateChannel where
  toPath :: CreateChannel -> ByteString
toPath CreateChannel' {[RequestOutputItem]
Maybe (HashMap Text Text)
Maybe SlateSource
Maybe Tier
Text
PlaybackMode
playbackMode :: PlaybackMode
outputs :: [RequestOutputItem]
channelName :: Text
tier :: Maybe Tier
tags :: Maybe (HashMap Text Text)
fillerSlate :: Maybe SlateSource
$sel:playbackMode:CreateChannel' :: CreateChannel -> PlaybackMode
$sel:outputs:CreateChannel' :: CreateChannel -> [RequestOutputItem]
$sel:channelName:CreateChannel' :: CreateChannel -> Text
$sel:tier:CreateChannel' :: CreateChannel -> Maybe Tier
$sel:tags:CreateChannel' :: CreateChannel -> Maybe (HashMap Text Text)
$sel:fillerSlate:CreateChannel' :: CreateChannel -> 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 CreateChannel where
  toQuery :: CreateChannel -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newCreateChannelResponse' smart constructor.
data CreateChannelResponse = CreateChannelResponse'
  { -- | The Amazon Resource Name (ARN) to assign to the channel.
    CreateChannelResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The name to assign to the channel.
    CreateChannelResponse -> Maybe Text
channelName :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether the channel is in a running state or not.
    CreateChannelResponse -> Maybe ChannelState
channelState :: Prelude.Maybe ChannelState,
    -- | The timestamp of when the channel was created.
    CreateChannelResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | Contains information about the slate used to fill gaps between programs
    -- in the schedule.
    CreateChannelResponse -> Maybe SlateSource
fillerSlate :: Prelude.Maybe SlateSource,
    -- | The timestamp of when the channel was last modified.
    CreateChannelResponse -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | The output properties to assign to the channel.
    CreateChannelResponse -> Maybe [ResponseOutputItem]
outputs :: Prelude.Maybe [ResponseOutputItem],
    -- | The playback mode to assign to the channel.
    CreateChannelResponse -> 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>.
    CreateChannelResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The tier of the channel.
    CreateChannelResponse -> Maybe Text
tier :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateChannelResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateChannelResponse -> CreateChannelResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateChannelResponse -> CreateChannelResponse -> Bool
$c/= :: CreateChannelResponse -> CreateChannelResponse -> Bool
== :: CreateChannelResponse -> CreateChannelResponse -> Bool
$c== :: CreateChannelResponse -> CreateChannelResponse -> Bool
Prelude.Eq, ReadPrec [CreateChannelResponse]
ReadPrec CreateChannelResponse
Int -> ReadS CreateChannelResponse
ReadS [CreateChannelResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateChannelResponse]
$creadListPrec :: ReadPrec [CreateChannelResponse]
readPrec :: ReadPrec CreateChannelResponse
$creadPrec :: ReadPrec CreateChannelResponse
readList :: ReadS [CreateChannelResponse]
$creadList :: ReadS [CreateChannelResponse]
readsPrec :: Int -> ReadS CreateChannelResponse
$creadsPrec :: Int -> ReadS CreateChannelResponse
Prelude.Read, Int -> CreateChannelResponse -> ShowS
[CreateChannelResponse] -> ShowS
CreateChannelResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateChannelResponse] -> ShowS
$cshowList :: [CreateChannelResponse] -> ShowS
show :: CreateChannelResponse -> String
$cshow :: CreateChannelResponse -> String
showsPrec :: Int -> CreateChannelResponse -> ShowS
$cshowsPrec :: Int -> CreateChannelResponse -> ShowS
Prelude.Show, forall x. Rep CreateChannelResponse x -> CreateChannelResponse
forall x. CreateChannelResponse -> Rep CreateChannelResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateChannelResponse x -> CreateChannelResponse
$cfrom :: forall x. CreateChannelResponse -> Rep CreateChannelResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateChannelResponse' 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', 'createChannelResponse_arn' - The Amazon Resource Name (ARN) to assign to the channel.
--
-- 'channelName', 'createChannelResponse_channelName' - The name to assign to the channel.
--
-- 'channelState', 'createChannelResponse_channelState' - Indicates whether the channel is in a running state or not.
--
-- 'creationTime', 'createChannelResponse_creationTime' - The timestamp of when the channel was created.
--
-- 'fillerSlate', 'createChannelResponse_fillerSlate' - Contains information about the slate used to fill gaps between programs
-- in the schedule.
--
-- 'lastModifiedTime', 'createChannelResponse_lastModifiedTime' - The timestamp of when the channel was last modified.
--
-- 'outputs', 'createChannelResponse_outputs' - The output properties to assign to the channel.
--
-- 'playbackMode', 'createChannelResponse_playbackMode' - The playback mode to assign to the channel.
--
-- 'tags', 'createChannelResponse_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', 'createChannelResponse_tier' - The tier of the channel.
--
-- 'httpStatus', 'createChannelResponse_httpStatus' - The response's http status code.
newCreateChannelResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateChannelResponse
newCreateChannelResponse :: Int -> CreateChannelResponse
newCreateChannelResponse Int
pHttpStatus_ =
  CreateChannelResponse'
    { $sel:arn:CreateChannelResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:channelName:CreateChannelResponse' :: Maybe Text
channelName = forall a. Maybe a
Prelude.Nothing,
      $sel:channelState:CreateChannelResponse' :: Maybe ChannelState
channelState = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:CreateChannelResponse' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:fillerSlate:CreateChannelResponse' :: Maybe SlateSource
fillerSlate = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:CreateChannelResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:outputs:CreateChannelResponse' :: Maybe [ResponseOutputItem]
outputs = forall a. Maybe a
Prelude.Nothing,
      $sel:playbackMode:CreateChannelResponse' :: Maybe Text
playbackMode = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateChannelResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:tier:CreateChannelResponse' :: Maybe Text
tier = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateChannelResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

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

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

-- | Contains information about the slate used to fill gaps between programs
-- in the schedule.
createChannelResponse_fillerSlate :: Lens.Lens' CreateChannelResponse (Prelude.Maybe SlateSource)
createChannelResponse_fillerSlate :: Lens' CreateChannelResponse (Maybe SlateSource)
createChannelResponse_fillerSlate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannelResponse' {Maybe SlateSource
fillerSlate :: Maybe SlateSource
$sel:fillerSlate:CreateChannelResponse' :: CreateChannelResponse -> Maybe SlateSource
fillerSlate} -> Maybe SlateSource
fillerSlate) (\s :: CreateChannelResponse
s@CreateChannelResponse' {} Maybe SlateSource
a -> CreateChannelResponse
s {$sel:fillerSlate:CreateChannelResponse' :: Maybe SlateSource
fillerSlate = Maybe SlateSource
a} :: CreateChannelResponse)

-- | The timestamp of when the channel was last modified.
createChannelResponse_lastModifiedTime :: Lens.Lens' CreateChannelResponse (Prelude.Maybe Prelude.UTCTime)
createChannelResponse_lastModifiedTime :: Lens' CreateChannelResponse (Maybe UTCTime)
createChannelResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannelResponse' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:CreateChannelResponse' :: CreateChannelResponse -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: CreateChannelResponse
s@CreateChannelResponse' {} Maybe POSIX
a -> CreateChannelResponse
s {$sel:lastModifiedTime:CreateChannelResponse' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: CreateChannelResponse) 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 output properties to assign to the channel.
createChannelResponse_outputs :: Lens.Lens' CreateChannelResponse (Prelude.Maybe [ResponseOutputItem])
createChannelResponse_outputs :: Lens' CreateChannelResponse (Maybe [ResponseOutputItem])
createChannelResponse_outputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannelResponse' {Maybe [ResponseOutputItem]
outputs :: Maybe [ResponseOutputItem]
$sel:outputs:CreateChannelResponse' :: CreateChannelResponse -> Maybe [ResponseOutputItem]
outputs} -> Maybe [ResponseOutputItem]
outputs) (\s :: CreateChannelResponse
s@CreateChannelResponse' {} Maybe [ResponseOutputItem]
a -> CreateChannelResponse
s {$sel:outputs:CreateChannelResponse' :: Maybe [ResponseOutputItem]
outputs = Maybe [ResponseOutputItem]
a} :: CreateChannelResponse) 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 playback mode to assign to the channel.
createChannelResponse_playbackMode :: Lens.Lens' CreateChannelResponse (Prelude.Maybe Prelude.Text)
createChannelResponse_playbackMode :: Lens' CreateChannelResponse (Maybe Text)
createChannelResponse_playbackMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannelResponse' {Maybe Text
playbackMode :: Maybe Text
$sel:playbackMode:CreateChannelResponse' :: CreateChannelResponse -> Maybe Text
playbackMode} -> Maybe Text
playbackMode) (\s :: CreateChannelResponse
s@CreateChannelResponse' {} Maybe Text
a -> CreateChannelResponse
s {$sel:playbackMode:CreateChannelResponse' :: Maybe Text
playbackMode = Maybe Text
a} :: CreateChannelResponse)

-- | 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>.
createChannelResponse_tags :: Lens.Lens' CreateChannelResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createChannelResponse_tags :: Lens' CreateChannelResponse (Maybe (HashMap Text Text))
createChannelResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannelResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateChannelResponse' :: CreateChannelResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateChannelResponse
s@CreateChannelResponse' {} Maybe (HashMap Text Text)
a -> CreateChannelResponse
s {$sel:tags:CreateChannelResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateChannelResponse) 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 of the channel.
createChannelResponse_tier :: Lens.Lens' CreateChannelResponse (Prelude.Maybe Prelude.Text)
createChannelResponse_tier :: Lens' CreateChannelResponse (Maybe Text)
createChannelResponse_tier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannelResponse' {Maybe Text
tier :: Maybe Text
$sel:tier:CreateChannelResponse' :: CreateChannelResponse -> Maybe Text
tier} -> Maybe Text
tier) (\s :: CreateChannelResponse
s@CreateChannelResponse' {} Maybe Text
a -> CreateChannelResponse
s {$sel:tier:CreateChannelResponse' :: Maybe Text
tier = Maybe Text
a} :: CreateChannelResponse)

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

instance Prelude.NFData CreateChannelResponse where
  rnf :: CreateChannelResponse -> ()
rnf CreateChannelResponse' {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:CreateChannelResponse' :: CreateChannelResponse -> Int
$sel:tier:CreateChannelResponse' :: CreateChannelResponse -> Maybe Text
$sel:tags:CreateChannelResponse' :: CreateChannelResponse -> Maybe (HashMap Text Text)
$sel:playbackMode:CreateChannelResponse' :: CreateChannelResponse -> Maybe Text
$sel:outputs:CreateChannelResponse' :: CreateChannelResponse -> Maybe [ResponseOutputItem]
$sel:lastModifiedTime:CreateChannelResponse' :: CreateChannelResponse -> Maybe POSIX
$sel:fillerSlate:CreateChannelResponse' :: CreateChannelResponse -> Maybe SlateSource
$sel:creationTime:CreateChannelResponse' :: CreateChannelResponse -> Maybe POSIX
$sel:channelState:CreateChannelResponse' :: CreateChannelResponse -> Maybe ChannelState
$sel:channelName:CreateChannelResponse' :: CreateChannelResponse -> Maybe Text
$sel:arn:CreateChannelResponse' :: CreateChannelResponse -> 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