{-# 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.Chime.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 to which you can add users and send messages.
--
-- __Restriction__: You can\'t change a channel\'s privacy.
--
-- The @x-amz-chime-bearer@ request header is mandatory. Use the
-- @AppInstanceUserArn@ of the user that makes the API call as the value in
-- the header.
module Amazonka.Chime.CreateChannel
  ( -- * Creating a Request
    CreateChannel (..),
    newCreateChannel,

    -- * Request Lenses
    createChannel_chimeBearer,
    createChannel_metadata,
    createChannel_mode,
    createChannel_privacy,
    createChannel_tags,
    createChannel_appInstanceArn,
    createChannel_name,
    createChannel_clientRequestToken,

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

    -- * Response Lenses
    createChannelResponse_channelArn,
    createChannelResponse_httpStatus,
  )
where

import Amazonka.Chime.Types
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
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 @AppInstanceUserArn@ of the user that makes the API call.
    CreateChannel -> Maybe Text
chimeBearer :: Prelude.Maybe Prelude.Text,
    -- | The metadata of the creation request. Limited to 1KB and UTF-8.
    CreateChannel -> Maybe (Sensitive Text)
metadata :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The channel mode: @UNRESTRICTED@ or @RESTRICTED@. Administrators,
    -- moderators, and channel members can add themselves and other members to
    -- unrestricted channels. Only administrators and moderators can add
    -- members to restricted channels.
    CreateChannel -> Maybe ChannelMode
mode :: Prelude.Maybe ChannelMode,
    -- | The channel\'s privacy level: @PUBLIC@ or @PRIVATE@. Private channels
    -- aren\'t discoverable by users outside the channel. Public channels are
    -- discoverable by anyone in the @AppInstance@.
    CreateChannel -> Maybe ChannelPrivacy
privacy :: Prelude.Maybe ChannelPrivacy,
    -- | The tags for the creation request.
    CreateChannel -> Maybe (NonEmpty Tag)
tags :: Prelude.Maybe (Prelude.NonEmpty Tag),
    -- | The ARN of the channel request.
    CreateChannel -> Text
appInstanceArn :: Prelude.Text,
    -- | The name of the channel.
    CreateChannel -> Sensitive Text
name :: Data.Sensitive Prelude.Text,
    -- | The client token for the request. An @Idempotency@ token.
    CreateChannel -> Sensitive Text
clientRequestToken :: Data.Sensitive Prelude.Text
  }
  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, 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:
--
-- 'chimeBearer', 'createChannel_chimeBearer' - The @AppInstanceUserArn@ of the user that makes the API call.
--
-- 'metadata', 'createChannel_metadata' - The metadata of the creation request. Limited to 1KB and UTF-8.
--
-- 'mode', 'createChannel_mode' - The channel mode: @UNRESTRICTED@ or @RESTRICTED@. Administrators,
-- moderators, and channel members can add themselves and other members to
-- unrestricted channels. Only administrators and moderators can add
-- members to restricted channels.
--
-- 'privacy', 'createChannel_privacy' - The channel\'s privacy level: @PUBLIC@ or @PRIVATE@. Private channels
-- aren\'t discoverable by users outside the channel. Public channels are
-- discoverable by anyone in the @AppInstance@.
--
-- 'tags', 'createChannel_tags' - The tags for the creation request.
--
-- 'appInstanceArn', 'createChannel_appInstanceArn' - The ARN of the channel request.
--
-- 'name', 'createChannel_name' - The name of the channel.
--
-- 'clientRequestToken', 'createChannel_clientRequestToken' - The client token for the request. An @Idempotency@ token.
newCreateChannel ::
  -- | 'appInstanceArn'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  -- | 'clientRequestToken'
  Prelude.Text ->
  CreateChannel
newCreateChannel :: Text -> Text -> Text -> CreateChannel
newCreateChannel
  Text
pAppInstanceArn_
  Text
pName_
  Text
pClientRequestToken_ =
    CreateChannel'
      { $sel:chimeBearer:CreateChannel' :: Maybe Text
chimeBearer = forall a. Maybe a
Prelude.Nothing,
        $sel:metadata:CreateChannel' :: Maybe (Sensitive Text)
metadata = forall a. Maybe a
Prelude.Nothing,
        $sel:mode:CreateChannel' :: Maybe ChannelMode
mode = forall a. Maybe a
Prelude.Nothing,
        $sel:privacy:CreateChannel' :: Maybe ChannelPrivacy
privacy = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateChannel' :: Maybe (NonEmpty Tag)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:appInstanceArn:CreateChannel' :: Text
appInstanceArn = Text
pAppInstanceArn_,
        $sel:name:CreateChannel' :: Sensitive Text
name = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pName_,
        $sel:clientRequestToken:CreateChannel' :: Sensitive Text
clientRequestToken =
          forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pClientRequestToken_
      }

-- | The @AppInstanceUserArn@ of the user that makes the API call.
createChannel_chimeBearer :: Lens.Lens' CreateChannel (Prelude.Maybe Prelude.Text)
createChannel_chimeBearer :: Lens' CreateChannel (Maybe Text)
createChannel_chimeBearer = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {Maybe Text
chimeBearer :: Maybe Text
$sel:chimeBearer:CreateChannel' :: CreateChannel -> Maybe Text
chimeBearer} -> Maybe Text
chimeBearer) (\s :: CreateChannel
s@CreateChannel' {} Maybe Text
a -> CreateChannel
s {$sel:chimeBearer:CreateChannel' :: Maybe Text
chimeBearer = Maybe Text
a} :: CreateChannel)

-- | The metadata of the creation request. Limited to 1KB and UTF-8.
createChannel_metadata :: Lens.Lens' CreateChannel (Prelude.Maybe Prelude.Text)
createChannel_metadata :: Lens' CreateChannel (Maybe Text)
createChannel_metadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {Maybe (Sensitive Text)
metadata :: Maybe (Sensitive Text)
$sel:metadata:CreateChannel' :: CreateChannel -> Maybe (Sensitive Text)
metadata} -> Maybe (Sensitive Text)
metadata) (\s :: CreateChannel
s@CreateChannel' {} Maybe (Sensitive Text)
a -> CreateChannel
s {$sel:metadata:CreateChannel' :: Maybe (Sensitive Text)
metadata = Maybe (Sensitive 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 a. Iso' (Sensitive a) a
Data._Sensitive

-- | The channel mode: @UNRESTRICTED@ or @RESTRICTED@. Administrators,
-- moderators, and channel members can add themselves and other members to
-- unrestricted channels. Only administrators and moderators can add
-- members to restricted channels.
createChannel_mode :: Lens.Lens' CreateChannel (Prelude.Maybe ChannelMode)
createChannel_mode :: Lens' CreateChannel (Maybe ChannelMode)
createChannel_mode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {Maybe ChannelMode
mode :: Maybe ChannelMode
$sel:mode:CreateChannel' :: CreateChannel -> Maybe ChannelMode
mode} -> Maybe ChannelMode
mode) (\s :: CreateChannel
s@CreateChannel' {} Maybe ChannelMode
a -> CreateChannel
s {$sel:mode:CreateChannel' :: Maybe ChannelMode
mode = Maybe ChannelMode
a} :: CreateChannel)

-- | The channel\'s privacy level: @PUBLIC@ or @PRIVATE@. Private channels
-- aren\'t discoverable by users outside the channel. Public channels are
-- discoverable by anyone in the @AppInstance@.
createChannel_privacy :: Lens.Lens' CreateChannel (Prelude.Maybe ChannelPrivacy)
createChannel_privacy :: Lens' CreateChannel (Maybe ChannelPrivacy)
createChannel_privacy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {Maybe ChannelPrivacy
privacy :: Maybe ChannelPrivacy
$sel:privacy:CreateChannel' :: CreateChannel -> Maybe ChannelPrivacy
privacy} -> Maybe ChannelPrivacy
privacy) (\s :: CreateChannel
s@CreateChannel' {} Maybe ChannelPrivacy
a -> CreateChannel
s {$sel:privacy:CreateChannel' :: Maybe ChannelPrivacy
privacy = Maybe ChannelPrivacy
a} :: CreateChannel)

-- | The tags for the creation request.
createChannel_tags :: Lens.Lens' CreateChannel (Prelude.Maybe (Prelude.NonEmpty Tag))
createChannel_tags :: Lens' CreateChannel (Maybe (NonEmpty Tag))
createChannel_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {Maybe (NonEmpty Tag)
tags :: Maybe (NonEmpty Tag)
$sel:tags:CreateChannel' :: CreateChannel -> Maybe (NonEmpty Tag)
tags} -> Maybe (NonEmpty Tag)
tags) (\s :: CreateChannel
s@CreateChannel' {} Maybe (NonEmpty Tag)
a -> CreateChannel
s {$sel:tags:CreateChannel' :: Maybe (NonEmpty Tag)
tags = Maybe (NonEmpty Tag)
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 ARN of the channel request.
createChannel_appInstanceArn :: Lens.Lens' CreateChannel Prelude.Text
createChannel_appInstanceArn :: Lens' CreateChannel Text
createChannel_appInstanceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {Text
appInstanceArn :: Text
$sel:appInstanceArn:CreateChannel' :: CreateChannel -> Text
appInstanceArn} -> Text
appInstanceArn) (\s :: CreateChannel
s@CreateChannel' {} Text
a -> CreateChannel
s {$sel:appInstanceArn:CreateChannel' :: Text
appInstanceArn = Text
a} :: CreateChannel)

-- | The name of the channel.
createChannel_name :: Lens.Lens' CreateChannel Prelude.Text
createChannel_name :: Lens' CreateChannel Text
createChannel_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {Sensitive Text
name :: Sensitive Text
$sel:name:CreateChannel' :: CreateChannel -> Sensitive Text
name} -> Sensitive Text
name) (\s :: CreateChannel
s@CreateChannel' {} Sensitive Text
a -> CreateChannel
s {$sel:name:CreateChannel' :: Sensitive Text
name = Sensitive Text
a} :: CreateChannel) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | The client token for the request. An @Idempotency@ token.
createChannel_clientRequestToken :: Lens.Lens' CreateChannel Prelude.Text
createChannel_clientRequestToken :: Lens' CreateChannel Text
createChannel_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannel' {Sensitive Text
clientRequestToken :: Sensitive Text
$sel:clientRequestToken:CreateChannel' :: CreateChannel -> Sensitive Text
clientRequestToken} -> Sensitive Text
clientRequestToken) (\s :: CreateChannel
s@CreateChannel' {} Sensitive Text
a -> CreateChannel
s {$sel:clientRequestToken:CreateChannel' :: Sensitive Text
clientRequestToken = Sensitive Text
a} :: CreateChannel) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

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 -> 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
"ChannelArn")
            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 (NonEmpty Tag)
Maybe Text
Maybe (Sensitive Text)
Maybe ChannelMode
Maybe ChannelPrivacy
Text
Sensitive Text
clientRequestToken :: Sensitive Text
name :: Sensitive Text
appInstanceArn :: Text
tags :: Maybe (NonEmpty Tag)
privacy :: Maybe ChannelPrivacy
mode :: Maybe ChannelMode
metadata :: Maybe (Sensitive Text)
chimeBearer :: Maybe Text
$sel:clientRequestToken:CreateChannel' :: CreateChannel -> Sensitive Text
$sel:name:CreateChannel' :: CreateChannel -> Sensitive Text
$sel:appInstanceArn:CreateChannel' :: CreateChannel -> Text
$sel:tags:CreateChannel' :: CreateChannel -> Maybe (NonEmpty Tag)
$sel:privacy:CreateChannel' :: CreateChannel -> Maybe ChannelPrivacy
$sel:mode:CreateChannel' :: CreateChannel -> Maybe ChannelMode
$sel:metadata:CreateChannel' :: CreateChannel -> Maybe (Sensitive Text)
$sel:chimeBearer:CreateChannel' :: CreateChannel -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
chimeBearer
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
metadata
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ChannelMode
mode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ChannelPrivacy
privacy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Tag)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
appInstanceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
clientRequestToken

instance Prelude.NFData CreateChannel where
  rnf :: CreateChannel -> ()
rnf CreateChannel' {Maybe (NonEmpty Tag)
Maybe Text
Maybe (Sensitive Text)
Maybe ChannelMode
Maybe ChannelPrivacy
Text
Sensitive Text
clientRequestToken :: Sensitive Text
name :: Sensitive Text
appInstanceArn :: Text
tags :: Maybe (NonEmpty Tag)
privacy :: Maybe ChannelPrivacy
mode :: Maybe ChannelMode
metadata :: Maybe (Sensitive Text)
chimeBearer :: Maybe Text
$sel:clientRequestToken:CreateChannel' :: CreateChannel -> Sensitive Text
$sel:name:CreateChannel' :: CreateChannel -> Sensitive Text
$sel:appInstanceArn:CreateChannel' :: CreateChannel -> Text
$sel:tags:CreateChannel' :: CreateChannel -> Maybe (NonEmpty Tag)
$sel:privacy:CreateChannel' :: CreateChannel -> Maybe ChannelPrivacy
$sel:mode:CreateChannel' :: CreateChannel -> Maybe ChannelMode
$sel:metadata:CreateChannel' :: CreateChannel -> Maybe (Sensitive Text)
$sel:chimeBearer:CreateChannel' :: CreateChannel -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
chimeBearer
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
metadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ChannelMode
mode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ChannelPrivacy
privacy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Tag)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
appInstanceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Text
clientRequestToken

instance Data.ToHeaders CreateChannel where
  toHeaders :: CreateChannel -> ResponseHeaders
toHeaders CreateChannel' {Maybe (NonEmpty Tag)
Maybe Text
Maybe (Sensitive Text)
Maybe ChannelMode
Maybe ChannelPrivacy
Text
Sensitive Text
clientRequestToken :: Sensitive Text
name :: Sensitive Text
appInstanceArn :: Text
tags :: Maybe (NonEmpty Tag)
privacy :: Maybe ChannelPrivacy
mode :: Maybe ChannelMode
metadata :: Maybe (Sensitive Text)
chimeBearer :: Maybe Text
$sel:clientRequestToken:CreateChannel' :: CreateChannel -> Sensitive Text
$sel:name:CreateChannel' :: CreateChannel -> Sensitive Text
$sel:appInstanceArn:CreateChannel' :: CreateChannel -> Text
$sel:tags:CreateChannel' :: CreateChannel -> Maybe (NonEmpty Tag)
$sel:privacy:CreateChannel' :: CreateChannel -> Maybe ChannelPrivacy
$sel:mode:CreateChannel' :: CreateChannel -> Maybe ChannelMode
$sel:metadata:CreateChannel' :: CreateChannel -> Maybe (Sensitive Text)
$sel:chimeBearer:CreateChannel' :: CreateChannel -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [HeaderName
"x-amz-chime-bearer" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
chimeBearer]

instance Data.ToJSON CreateChannel where
  toJSON :: CreateChannel -> Value
toJSON CreateChannel' {Maybe (NonEmpty Tag)
Maybe Text
Maybe (Sensitive Text)
Maybe ChannelMode
Maybe ChannelPrivacy
Text
Sensitive Text
clientRequestToken :: Sensitive Text
name :: Sensitive Text
appInstanceArn :: Text
tags :: Maybe (NonEmpty Tag)
privacy :: Maybe ChannelPrivacy
mode :: Maybe ChannelMode
metadata :: Maybe (Sensitive Text)
chimeBearer :: Maybe Text
$sel:clientRequestToken:CreateChannel' :: CreateChannel -> Sensitive Text
$sel:name:CreateChannel' :: CreateChannel -> Sensitive Text
$sel:appInstanceArn:CreateChannel' :: CreateChannel -> Text
$sel:tags:CreateChannel' :: CreateChannel -> Maybe (NonEmpty Tag)
$sel:privacy:CreateChannel' :: CreateChannel -> Maybe ChannelPrivacy
$sel:mode:CreateChannel' :: CreateChannel -> Maybe ChannelMode
$sel:metadata:CreateChannel' :: CreateChannel -> Maybe (Sensitive Text)
$sel:chimeBearer:CreateChannel' :: CreateChannel -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Metadata" 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 (Sensitive Text)
metadata,
            (Key
"Mode" 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 ChannelMode
mode,
            (Key
"Privacy" 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 ChannelPrivacy
privacy,
            (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 (NonEmpty Tag)
tags,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"AppInstanceArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
appInstanceArn),
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
name),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ClientRequestToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
clientRequestToken)
          ]
      )

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

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 ARN of the channel.
    CreateChannelResponse -> Maybe Text
channelArn :: 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:
--
-- 'channelArn', 'createChannelResponse_channelArn' - The ARN 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:channelArn:CreateChannelResponse' :: Maybe Text
channelArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateChannelResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the channel.
createChannelResponse_channelArn :: Lens.Lens' CreateChannelResponse (Prelude.Maybe Prelude.Text)
createChannelResponse_channelArn :: Lens' CreateChannelResponse (Maybe Text)
createChannelResponse_channelArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateChannelResponse' {Maybe Text
channelArn :: Maybe Text
$sel:channelArn:CreateChannelResponse' :: CreateChannelResponse -> Maybe Text
channelArn} -> Maybe Text
channelArn) (\s :: CreateChannelResponse
s@CreateChannelResponse' {} Maybe Text
a -> CreateChannelResponse
s {$sel:channelArn:CreateChannelResponse' :: Maybe Text
channelArn = 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 Text
httpStatus :: Int
channelArn :: Maybe Text
$sel:httpStatus:CreateChannelResponse' :: CreateChannelResponse -> Int
$sel:channelArn:CreateChannelResponse' :: CreateChannelResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
channelArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus