{-# 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.IVS.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 new channel and an associated stream key to start streaming.
module Amazonka.IVS.CreateChannel
  ( -- * Creating a Request
    CreateChannel (..),
    newCreateChannel,

    -- * Request Lenses
    createChannel_authorized,
    createChannel_latencyMode,
    createChannel_name,
    createChannel_recordingConfigurationArn,
    createChannel_tags,
    createChannel_type,

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

    -- * Response Lenses
    createChannelResponse_channel,
    createChannelResponse_streamKey,
    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.IVS.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'
  { -- | Whether the channel is private (enabled for playback authorization).
    -- Default: @false@.
    CreateChannel -> Maybe Bool
authorized :: Prelude.Maybe Prelude.Bool,
    -- | Channel latency mode. Use @NORMAL@ to broadcast and deliver live video
    -- up to Full HD. Use @LOW@ for near-real-time interaction with viewers.
    -- (Note: In the Amazon IVS console, @LOW@ and @NORMAL@ correspond to
    -- Ultra-low and Standard, respectively.) Default: @LOW@.
    CreateChannel -> Maybe ChannelLatencyMode
latencyMode :: Prelude.Maybe ChannelLatencyMode,
    -- | Channel name.
    CreateChannel -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | Recording-configuration ARN. Default: \"\" (empty string, recording is
    -- disabled).
    CreateChannel -> Maybe Text
recordingConfigurationArn :: Prelude.Maybe Prelude.Text,
    -- | Array of 1-50 maps, each of the form @string:string (key:value)@. See
    -- <https://docs.aws.amazon.com/general/latest/gr/aws_tagging.html Tagging Amazon Web Services Resources>
    -- for more information, including restrictions that apply to tags and
    -- \"Tag naming limits and requirements\"; Amazon IVS has no
    -- service-specific constraints beyond what is documented there.
    CreateChannel -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | Channel type, which determines the allowable resolution and bitrate. /If
    -- you exceed the allowable resolution or bitrate, the stream probably will
    -- disconnect immediately./ Default: @STANDARD@. Valid values:
    --
    -- -   @STANDARD@: Video is transcoded: multiple qualities are generated
    --     from the original input, to automatically give viewers the best
    --     experience for their devices and network conditions. Transcoding
    --     allows higher playback quality across a range of download speeds.
    --     Resolution can be up to 1080p and bitrate can be up to 8.5 Mbps.
    --     Audio is transcoded only for renditions 360p and below; above that,
    --     audio is passed through. This is the default.
    --
    -- -   @BASIC@: Video is transmuxed: Amazon IVS delivers the original input
    --     to viewers. The viewer’s video-quality choice is limited to the
    --     original input. Resolution can be up to 1080p and bitrate can be up
    --     to 1.5 Mbps for 480p and up to 3.5 Mbps for resolutions between 480p
    --     and 1080p.
    CreateChannel -> Maybe ChannelType
type' :: Prelude.Maybe ChannelType
  }
  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:
--
-- 'authorized', 'createChannel_authorized' - Whether the channel is private (enabled for playback authorization).
-- Default: @false@.
--
-- 'latencyMode', 'createChannel_latencyMode' - Channel latency mode. Use @NORMAL@ to broadcast and deliver live video
-- up to Full HD. Use @LOW@ for near-real-time interaction with viewers.
-- (Note: In the Amazon IVS console, @LOW@ and @NORMAL@ correspond to
-- Ultra-low and Standard, respectively.) Default: @LOW@.
--
-- 'name', 'createChannel_name' - Channel name.
--
-- 'recordingConfigurationArn', 'createChannel_recordingConfigurationArn' - Recording-configuration ARN. Default: \"\" (empty string, recording is
-- disabled).
--
-- 'tags', 'createChannel_tags' - Array of 1-50 maps, each of the form @string:string (key:value)@. See
-- <https://docs.aws.amazon.com/general/latest/gr/aws_tagging.html Tagging Amazon Web Services Resources>
-- for more information, including restrictions that apply to tags and
-- \"Tag naming limits and requirements\"; Amazon IVS has no
-- service-specific constraints beyond what is documented there.
--
-- 'type'', 'createChannel_type' - Channel type, which determines the allowable resolution and bitrate. /If
-- you exceed the allowable resolution or bitrate, the stream probably will
-- disconnect immediately./ Default: @STANDARD@. Valid values:
--
-- -   @STANDARD@: Video is transcoded: multiple qualities are generated
--     from the original input, to automatically give viewers the best
--     experience for their devices and network conditions. Transcoding
--     allows higher playback quality across a range of download speeds.
--     Resolution can be up to 1080p and bitrate can be up to 8.5 Mbps.
--     Audio is transcoded only for renditions 360p and below; above that,
--     audio is passed through. This is the default.
--
-- -   @BASIC@: Video is transmuxed: Amazon IVS delivers the original input
--     to viewers. The viewer’s video-quality choice is limited to the
--     original input. Resolution can be up to 1080p and bitrate can be up
--     to 1.5 Mbps for 480p and up to 3.5 Mbps for resolutions between 480p
--     and 1080p.
newCreateChannel ::
  CreateChannel
newCreateChannel :: CreateChannel
newCreateChannel =
  CreateChannel'
    { $sel:authorized:CreateChannel' :: Maybe Bool
authorized = forall a. Maybe a
Prelude.Nothing,
      $sel:latencyMode:CreateChannel' :: Maybe ChannelLatencyMode
latencyMode = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateChannel' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:recordingConfigurationArn:CreateChannel' :: Maybe Text
recordingConfigurationArn = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateChannel' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:type':CreateChannel' :: Maybe ChannelType
type' = forall a. Maybe a
Prelude.Nothing
    }

-- | Whether the channel is private (enabled for playback authorization).
-- Default: @false@.
createChannel_authorized :: Lens.Lens' CreateChannel (Prelude.Maybe Prelude.Bool)
createChannel_authorized :: Lens' CreateChannel (Maybe Bool)
createChannel_authorized = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {Maybe Bool
authorized :: Maybe Bool
$sel:authorized:CreateChannel' :: CreateChannel -> Maybe Bool
authorized} -> Maybe Bool
authorized) (\s :: CreateChannel
s@CreateChannel' {} Maybe Bool
a -> CreateChannel
s {$sel:authorized:CreateChannel' :: Maybe Bool
authorized = Maybe Bool
a} :: CreateChannel)

-- | Channel latency mode. Use @NORMAL@ to broadcast and deliver live video
-- up to Full HD. Use @LOW@ for near-real-time interaction with viewers.
-- (Note: In the Amazon IVS console, @LOW@ and @NORMAL@ correspond to
-- Ultra-low and Standard, respectively.) Default: @LOW@.
createChannel_latencyMode :: Lens.Lens' CreateChannel (Prelude.Maybe ChannelLatencyMode)
createChannel_latencyMode :: Lens' CreateChannel (Maybe ChannelLatencyMode)
createChannel_latencyMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {Maybe ChannelLatencyMode
latencyMode :: Maybe ChannelLatencyMode
$sel:latencyMode:CreateChannel' :: CreateChannel -> Maybe ChannelLatencyMode
latencyMode} -> Maybe ChannelLatencyMode
latencyMode) (\s :: CreateChannel
s@CreateChannel' {} Maybe ChannelLatencyMode
a -> CreateChannel
s {$sel:latencyMode:CreateChannel' :: Maybe ChannelLatencyMode
latencyMode = Maybe ChannelLatencyMode
a} :: CreateChannel)

-- | Channel name.
createChannel_name :: Lens.Lens' CreateChannel (Prelude.Maybe Prelude.Text)
createChannel_name :: Lens' CreateChannel (Maybe Text)
createChannel_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {Maybe Text
name :: Maybe Text
$sel:name:CreateChannel' :: CreateChannel -> Maybe Text
name} -> Maybe Text
name) (\s :: CreateChannel
s@CreateChannel' {} Maybe Text
a -> CreateChannel
s {$sel:name:CreateChannel' :: Maybe Text
name = Maybe Text
a} :: CreateChannel)

-- | Recording-configuration ARN. Default: \"\" (empty string, recording is
-- disabled).
createChannel_recordingConfigurationArn :: Lens.Lens' CreateChannel (Prelude.Maybe Prelude.Text)
createChannel_recordingConfigurationArn :: Lens' CreateChannel (Maybe Text)
createChannel_recordingConfigurationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {Maybe Text
recordingConfigurationArn :: Maybe Text
$sel:recordingConfigurationArn:CreateChannel' :: CreateChannel -> Maybe Text
recordingConfigurationArn} -> Maybe Text
recordingConfigurationArn) (\s :: CreateChannel
s@CreateChannel' {} Maybe Text
a -> CreateChannel
s {$sel:recordingConfigurationArn:CreateChannel' :: Maybe Text
recordingConfigurationArn = Maybe Text
a} :: CreateChannel)

-- | Array of 1-50 maps, each of the form @string:string (key:value)@. See
-- <https://docs.aws.amazon.com/general/latest/gr/aws_tagging.html Tagging Amazon Web Services Resources>
-- for more information, including restrictions that apply to tags and
-- \"Tag naming limits and requirements\"; Amazon IVS has no
-- service-specific constraints beyond what is documented there.
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

-- | Channel type, which determines the allowable resolution and bitrate. /If
-- you exceed the allowable resolution or bitrate, the stream probably will
-- disconnect immediately./ Default: @STANDARD@. Valid values:
--
-- -   @STANDARD@: Video is transcoded: multiple qualities are generated
--     from the original input, to automatically give viewers the best
--     experience for their devices and network conditions. Transcoding
--     allows higher playback quality across a range of download speeds.
--     Resolution can be up to 1080p and bitrate can be up to 8.5 Mbps.
--     Audio is transcoded only for renditions 360p and below; above that,
--     audio is passed through. This is the default.
--
-- -   @BASIC@: Video is transmuxed: Amazon IVS delivers the original input
--     to viewers. The viewer’s video-quality choice is limited to the
--     original input. Resolution can be up to 1080p and bitrate can be up
--     to 1.5 Mbps for 480p and up to 3.5 Mbps for resolutions between 480p
--     and 1080p.
createChannel_type :: Lens.Lens' CreateChannel (Prelude.Maybe ChannelType)
createChannel_type :: Lens' CreateChannel (Maybe ChannelType)
createChannel_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {Maybe ChannelType
type' :: Maybe ChannelType
$sel:type':CreateChannel' :: CreateChannel -> Maybe ChannelType
type'} -> Maybe ChannelType
type') (\s :: CreateChannel
s@CreateChannel' {} Maybe ChannelType
a -> CreateChannel
s {$sel:type':CreateChannel' :: Maybe ChannelType
type' = Maybe ChannelType
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 Channel -> Maybe StreamKey -> 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
"channel")
            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
"streamKey")
            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' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Maybe ChannelLatencyMode
Maybe ChannelType
type' :: Maybe ChannelType
tags :: Maybe (HashMap Text Text)
recordingConfigurationArn :: Maybe Text
name :: Maybe Text
latencyMode :: Maybe ChannelLatencyMode
authorized :: Maybe Bool
$sel:type':CreateChannel' :: CreateChannel -> Maybe ChannelType
$sel:tags:CreateChannel' :: CreateChannel -> Maybe (HashMap Text Text)
$sel:recordingConfigurationArn:CreateChannel' :: CreateChannel -> Maybe Text
$sel:name:CreateChannel' :: CreateChannel -> Maybe Text
$sel:latencyMode:CreateChannel' :: CreateChannel -> Maybe ChannelLatencyMode
$sel:authorized:CreateChannel' :: CreateChannel -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
authorized
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ChannelLatencyMode
latencyMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
recordingConfigurationArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ChannelType
type'

instance Prelude.NFData CreateChannel where
  rnf :: CreateChannel -> ()
rnf CreateChannel' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Maybe ChannelLatencyMode
Maybe ChannelType
type' :: Maybe ChannelType
tags :: Maybe (HashMap Text Text)
recordingConfigurationArn :: Maybe Text
name :: Maybe Text
latencyMode :: Maybe ChannelLatencyMode
authorized :: Maybe Bool
$sel:type':CreateChannel' :: CreateChannel -> Maybe ChannelType
$sel:tags:CreateChannel' :: CreateChannel -> Maybe (HashMap Text Text)
$sel:recordingConfigurationArn:CreateChannel' :: CreateChannel -> Maybe Text
$sel:name:CreateChannel' :: CreateChannel -> Maybe Text
$sel:latencyMode:CreateChannel' :: CreateChannel -> Maybe ChannelLatencyMode
$sel:authorized:CreateChannel' :: CreateChannel -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
authorized
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ChannelLatencyMode
latencyMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
recordingConfigurationArn
      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 ChannelType
type'

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' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Maybe ChannelLatencyMode
Maybe ChannelType
type' :: Maybe ChannelType
tags :: Maybe (HashMap Text Text)
recordingConfigurationArn :: Maybe Text
name :: Maybe Text
latencyMode :: Maybe ChannelLatencyMode
authorized :: Maybe Bool
$sel:type':CreateChannel' :: CreateChannel -> Maybe ChannelType
$sel:tags:CreateChannel' :: CreateChannel -> Maybe (HashMap Text Text)
$sel:recordingConfigurationArn:CreateChannel' :: CreateChannel -> Maybe Text
$sel:name:CreateChannel' :: CreateChannel -> Maybe Text
$sel:latencyMode:CreateChannel' :: CreateChannel -> Maybe ChannelLatencyMode
$sel:authorized:CreateChannel' :: CreateChannel -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"authorized" 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 Bool
authorized,
            (Key
"latencyMode" 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 ChannelLatencyMode
latencyMode,
            (Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
name,
            (Key
"recordingConfigurationArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
recordingConfigurationArn,
            (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
"type" 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 ChannelType
type'
          ]
      )

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

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'
  { CreateChannelResponse -> Maybe Channel
channel :: Prelude.Maybe Channel,
    CreateChannelResponse -> Maybe StreamKey
streamKey :: Prelude.Maybe StreamKey,
    -- | 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, 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:
--
-- 'channel', 'createChannelResponse_channel' -
--
-- 'streamKey', 'createChannelResponse_streamKey' -
--
-- 'httpStatus', 'createChannelResponse_httpStatus' - The response's http status code.
newCreateChannelResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateChannelResponse
newCreateChannelResponse :: Int -> CreateChannelResponse
newCreateChannelResponse Int
pHttpStatus_ =
  CreateChannelResponse'
    { $sel:channel:CreateChannelResponse' :: Maybe Channel
channel = forall a. Maybe a
Prelude.Nothing,
      $sel:streamKey:CreateChannelResponse' :: Maybe StreamKey
streamKey = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateChannelResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

createChannelResponse_channel :: Lens.Lens' CreateChannelResponse (Prelude.Maybe Channel)
createChannelResponse_channel :: Lens' CreateChannelResponse (Maybe Channel)
createChannelResponse_channel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannelResponse' {Maybe Channel
channel :: Maybe Channel
$sel:channel:CreateChannelResponse' :: CreateChannelResponse -> Maybe Channel
channel} -> Maybe Channel
channel) (\s :: CreateChannelResponse
s@CreateChannelResponse' {} Maybe Channel
a -> CreateChannelResponse
s {$sel:channel:CreateChannelResponse' :: Maybe Channel
channel = Maybe Channel
a} :: CreateChannelResponse)

createChannelResponse_streamKey :: Lens.Lens' CreateChannelResponse (Prelude.Maybe StreamKey)
createChannelResponse_streamKey :: Lens' CreateChannelResponse (Maybe StreamKey)
createChannelResponse_streamKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannelResponse' {Maybe StreamKey
streamKey :: Maybe StreamKey
$sel:streamKey:CreateChannelResponse' :: CreateChannelResponse -> Maybe StreamKey
streamKey} -> Maybe StreamKey
streamKey) (\s :: CreateChannelResponse
s@CreateChannelResponse' {} Maybe StreamKey
a -> CreateChannelResponse
s {$sel:streamKey:CreateChannelResponse' :: Maybe StreamKey
streamKey = Maybe StreamKey
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 Channel
Maybe StreamKey
httpStatus :: Int
streamKey :: Maybe StreamKey
channel :: Maybe Channel
$sel:httpStatus:CreateChannelResponse' :: CreateChannelResponse -> Int
$sel:streamKey:CreateChannelResponse' :: CreateChannelResponse -> Maybe StreamKey
$sel:channel:CreateChannelResponse' :: CreateChannelResponse -> Maybe Channel
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Channel
channel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StreamKey
streamKey
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus