{-# 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.DescribeChannelMembershipForAppInstanceUser
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the details of a channel based on the membership of the
-- specified @AppInstanceUser@.
--
-- 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.DescribeChannelMembershipForAppInstanceUser
  ( -- * Creating a Request
    DescribeChannelMembershipForAppInstanceUser (..),
    newDescribeChannelMembershipForAppInstanceUser,

    -- * Request Lenses
    describeChannelMembershipForAppInstanceUser_chimeBearer,
    describeChannelMembershipForAppInstanceUser_channelArn,
    describeChannelMembershipForAppInstanceUser_appInstanceUserArn,

    -- * Destructuring the Response
    DescribeChannelMembershipForAppInstanceUserResponse (..),
    newDescribeChannelMembershipForAppInstanceUserResponse,

    -- * Response Lenses
    describeChannelMembershipForAppInstanceUserResponse_channelMembership,
    describeChannelMembershipForAppInstanceUserResponse_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:/ 'newDescribeChannelMembershipForAppInstanceUser' smart constructor.
data DescribeChannelMembershipForAppInstanceUser = DescribeChannelMembershipForAppInstanceUser'
  { -- | The @AppInstanceUserArn@ of the user that makes the API call.
    DescribeChannelMembershipForAppInstanceUser -> Maybe Text
chimeBearer :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the channel to which the user belongs.
    DescribeChannelMembershipForAppInstanceUser -> Text
channelArn :: Prelude.Text,
    -- | The ARN of the user in a channel.
    DescribeChannelMembershipForAppInstanceUser -> Text
appInstanceUserArn :: Prelude.Text
  }
  deriving (DescribeChannelMembershipForAppInstanceUser
-> DescribeChannelMembershipForAppInstanceUser -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeChannelMembershipForAppInstanceUser
-> DescribeChannelMembershipForAppInstanceUser -> Bool
$c/= :: DescribeChannelMembershipForAppInstanceUser
-> DescribeChannelMembershipForAppInstanceUser -> Bool
== :: DescribeChannelMembershipForAppInstanceUser
-> DescribeChannelMembershipForAppInstanceUser -> Bool
$c== :: DescribeChannelMembershipForAppInstanceUser
-> DescribeChannelMembershipForAppInstanceUser -> Bool
Prelude.Eq, ReadPrec [DescribeChannelMembershipForAppInstanceUser]
ReadPrec DescribeChannelMembershipForAppInstanceUser
Int -> ReadS DescribeChannelMembershipForAppInstanceUser
ReadS [DescribeChannelMembershipForAppInstanceUser]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeChannelMembershipForAppInstanceUser]
$creadListPrec :: ReadPrec [DescribeChannelMembershipForAppInstanceUser]
readPrec :: ReadPrec DescribeChannelMembershipForAppInstanceUser
$creadPrec :: ReadPrec DescribeChannelMembershipForAppInstanceUser
readList :: ReadS [DescribeChannelMembershipForAppInstanceUser]
$creadList :: ReadS [DescribeChannelMembershipForAppInstanceUser]
readsPrec :: Int -> ReadS DescribeChannelMembershipForAppInstanceUser
$creadsPrec :: Int -> ReadS DescribeChannelMembershipForAppInstanceUser
Prelude.Read, Int -> DescribeChannelMembershipForAppInstanceUser -> ShowS
[DescribeChannelMembershipForAppInstanceUser] -> ShowS
DescribeChannelMembershipForAppInstanceUser -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeChannelMembershipForAppInstanceUser] -> ShowS
$cshowList :: [DescribeChannelMembershipForAppInstanceUser] -> ShowS
show :: DescribeChannelMembershipForAppInstanceUser -> String
$cshow :: DescribeChannelMembershipForAppInstanceUser -> String
showsPrec :: Int -> DescribeChannelMembershipForAppInstanceUser -> ShowS
$cshowsPrec :: Int -> DescribeChannelMembershipForAppInstanceUser -> ShowS
Prelude.Show, forall x.
Rep DescribeChannelMembershipForAppInstanceUser x
-> DescribeChannelMembershipForAppInstanceUser
forall x.
DescribeChannelMembershipForAppInstanceUser
-> Rep DescribeChannelMembershipForAppInstanceUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeChannelMembershipForAppInstanceUser x
-> DescribeChannelMembershipForAppInstanceUser
$cfrom :: forall x.
DescribeChannelMembershipForAppInstanceUser
-> Rep DescribeChannelMembershipForAppInstanceUser x
Prelude.Generic)

-- |
-- Create a value of 'DescribeChannelMembershipForAppInstanceUser' 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', 'describeChannelMembershipForAppInstanceUser_chimeBearer' - The @AppInstanceUserArn@ of the user that makes the API call.
--
-- 'channelArn', 'describeChannelMembershipForAppInstanceUser_channelArn' - The ARN of the channel to which the user belongs.
--
-- 'appInstanceUserArn', 'describeChannelMembershipForAppInstanceUser_appInstanceUserArn' - The ARN of the user in a channel.
newDescribeChannelMembershipForAppInstanceUser ::
  -- | 'channelArn'
  Prelude.Text ->
  -- | 'appInstanceUserArn'
  Prelude.Text ->
  DescribeChannelMembershipForAppInstanceUser
newDescribeChannelMembershipForAppInstanceUser :: Text -> Text -> DescribeChannelMembershipForAppInstanceUser
newDescribeChannelMembershipForAppInstanceUser
  Text
pChannelArn_
  Text
pAppInstanceUserArn_ =
    DescribeChannelMembershipForAppInstanceUser'
      { $sel:chimeBearer:DescribeChannelMembershipForAppInstanceUser' :: Maybe Text
chimeBearer =
          forall a. Maybe a
Prelude.Nothing,
        $sel:channelArn:DescribeChannelMembershipForAppInstanceUser' :: Text
channelArn = Text
pChannelArn_,
        $sel:appInstanceUserArn:DescribeChannelMembershipForAppInstanceUser' :: Text
appInstanceUserArn =
          Text
pAppInstanceUserArn_
      }

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

-- | The ARN of the channel to which the user belongs.
describeChannelMembershipForAppInstanceUser_channelArn :: Lens.Lens' DescribeChannelMembershipForAppInstanceUser Prelude.Text
describeChannelMembershipForAppInstanceUser_channelArn :: Lens' DescribeChannelMembershipForAppInstanceUser Text
describeChannelMembershipForAppInstanceUser_channelArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeChannelMembershipForAppInstanceUser' {Text
channelArn :: Text
$sel:channelArn:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> Text
channelArn} -> Text
channelArn) (\s :: DescribeChannelMembershipForAppInstanceUser
s@DescribeChannelMembershipForAppInstanceUser' {} Text
a -> DescribeChannelMembershipForAppInstanceUser
s {$sel:channelArn:DescribeChannelMembershipForAppInstanceUser' :: Text
channelArn = Text
a} :: DescribeChannelMembershipForAppInstanceUser)

-- | The ARN of the user in a channel.
describeChannelMembershipForAppInstanceUser_appInstanceUserArn :: Lens.Lens' DescribeChannelMembershipForAppInstanceUser Prelude.Text
describeChannelMembershipForAppInstanceUser_appInstanceUserArn :: Lens' DescribeChannelMembershipForAppInstanceUser Text
describeChannelMembershipForAppInstanceUser_appInstanceUserArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeChannelMembershipForAppInstanceUser' {Text
appInstanceUserArn :: Text
$sel:appInstanceUserArn:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> Text
appInstanceUserArn} -> Text
appInstanceUserArn) (\s :: DescribeChannelMembershipForAppInstanceUser
s@DescribeChannelMembershipForAppInstanceUser' {} Text
a -> DescribeChannelMembershipForAppInstanceUser
s {$sel:appInstanceUserArn:DescribeChannelMembershipForAppInstanceUser' :: Text
appInstanceUserArn = Text
a} :: DescribeChannelMembershipForAppInstanceUser)

instance
  Core.AWSRequest
    DescribeChannelMembershipForAppInstanceUser
  where
  type
    AWSResponse
      DescribeChannelMembershipForAppInstanceUser =
      DescribeChannelMembershipForAppInstanceUserResponse
  request :: (Service -> Service)
-> DescribeChannelMembershipForAppInstanceUser
-> Request DescribeChannelMembershipForAppInstanceUser
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeChannelMembershipForAppInstanceUser
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse DescribeChannelMembershipForAppInstanceUser)))
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 ChannelMembershipForAppInstanceUserSummary
-> Int -> DescribeChannelMembershipForAppInstanceUserResponse
DescribeChannelMembershipForAppInstanceUserResponse'
            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
"ChannelMembership")
            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
    DescribeChannelMembershipForAppInstanceUser
  where
  hashWithSalt :: Int -> DescribeChannelMembershipForAppInstanceUser -> Int
hashWithSalt
    Int
_salt
    DescribeChannelMembershipForAppInstanceUser' {Maybe Text
Text
appInstanceUserArn :: Text
channelArn :: Text
chimeBearer :: Maybe Text
$sel:appInstanceUserArn:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> Text
$sel:channelArn:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> Text
$sel:chimeBearer:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> 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` Text
channelArn
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
appInstanceUserArn

instance
  Prelude.NFData
    DescribeChannelMembershipForAppInstanceUser
  where
  rnf :: DescribeChannelMembershipForAppInstanceUser -> ()
rnf DescribeChannelMembershipForAppInstanceUser' {Maybe Text
Text
appInstanceUserArn :: Text
channelArn :: Text
chimeBearer :: Maybe Text
$sel:appInstanceUserArn:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> Text
$sel:channelArn:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> Text
$sel:chimeBearer:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> 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 Text
channelArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
appInstanceUserArn

instance
  Data.ToHeaders
    DescribeChannelMembershipForAppInstanceUser
  where
  toHeaders :: DescribeChannelMembershipForAppInstanceUser -> ResponseHeaders
toHeaders
    DescribeChannelMembershipForAppInstanceUser' {Maybe Text
Text
appInstanceUserArn :: Text
channelArn :: Text
chimeBearer :: Maybe Text
$sel:appInstanceUserArn:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> Text
$sel:channelArn:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> Text
$sel:chimeBearer:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> 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.ToPath
    DescribeChannelMembershipForAppInstanceUser
  where
  toPath :: DescribeChannelMembershipForAppInstanceUser -> ByteString
toPath
    DescribeChannelMembershipForAppInstanceUser' {Maybe Text
Text
appInstanceUserArn :: Text
channelArn :: Text
chimeBearer :: Maybe Text
$sel:appInstanceUserArn:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> Text
$sel:channelArn:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> Text
$sel:chimeBearer:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> Maybe Text
..} =
      forall a. Monoid a => [a] -> a
Prelude.mconcat
        [ByteString
"/channels/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
channelArn]

instance
  Data.ToQuery
    DescribeChannelMembershipForAppInstanceUser
  where
  toQuery :: DescribeChannelMembershipForAppInstanceUser -> QueryString
toQuery
    DescribeChannelMembershipForAppInstanceUser' {Maybe Text
Text
appInstanceUserArn :: Text
channelArn :: Text
chimeBearer :: Maybe Text
$sel:appInstanceUserArn:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> Text
$sel:channelArn:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> Text
$sel:chimeBearer:DescribeChannelMembershipForAppInstanceUser' :: DescribeChannelMembershipForAppInstanceUser -> Maybe Text
..} =
      forall a. Monoid a => [a] -> a
Prelude.mconcat
        [ ByteString
"app-instance-user-arn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
appInstanceUserArn,
          QueryString
"scope=app-instance-user-membership"
        ]

-- | /See:/ 'newDescribeChannelMembershipForAppInstanceUserResponse' smart constructor.
data DescribeChannelMembershipForAppInstanceUserResponse = DescribeChannelMembershipForAppInstanceUserResponse'
  { -- | The channel to which a user belongs.
    DescribeChannelMembershipForAppInstanceUserResponse
-> Maybe ChannelMembershipForAppInstanceUserSummary
channelMembership :: Prelude.Maybe ChannelMembershipForAppInstanceUserSummary,
    -- | The response's http status code.
    DescribeChannelMembershipForAppInstanceUserResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeChannelMembershipForAppInstanceUserResponse
-> DescribeChannelMembershipForAppInstanceUserResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeChannelMembershipForAppInstanceUserResponse
-> DescribeChannelMembershipForAppInstanceUserResponse -> Bool
$c/= :: DescribeChannelMembershipForAppInstanceUserResponse
-> DescribeChannelMembershipForAppInstanceUserResponse -> Bool
== :: DescribeChannelMembershipForAppInstanceUserResponse
-> DescribeChannelMembershipForAppInstanceUserResponse -> Bool
$c== :: DescribeChannelMembershipForAppInstanceUserResponse
-> DescribeChannelMembershipForAppInstanceUserResponse -> Bool
Prelude.Eq, Int -> DescribeChannelMembershipForAppInstanceUserResponse -> ShowS
[DescribeChannelMembershipForAppInstanceUserResponse] -> ShowS
DescribeChannelMembershipForAppInstanceUserResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeChannelMembershipForAppInstanceUserResponse] -> ShowS
$cshowList :: [DescribeChannelMembershipForAppInstanceUserResponse] -> ShowS
show :: DescribeChannelMembershipForAppInstanceUserResponse -> String
$cshow :: DescribeChannelMembershipForAppInstanceUserResponse -> String
showsPrec :: Int -> DescribeChannelMembershipForAppInstanceUserResponse -> ShowS
$cshowsPrec :: Int -> DescribeChannelMembershipForAppInstanceUserResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeChannelMembershipForAppInstanceUserResponse x
-> DescribeChannelMembershipForAppInstanceUserResponse
forall x.
DescribeChannelMembershipForAppInstanceUserResponse
-> Rep DescribeChannelMembershipForAppInstanceUserResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeChannelMembershipForAppInstanceUserResponse x
-> DescribeChannelMembershipForAppInstanceUserResponse
$cfrom :: forall x.
DescribeChannelMembershipForAppInstanceUserResponse
-> Rep DescribeChannelMembershipForAppInstanceUserResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeChannelMembershipForAppInstanceUserResponse' 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:
--
-- 'channelMembership', 'describeChannelMembershipForAppInstanceUserResponse_channelMembership' - The channel to which a user belongs.
--
-- 'httpStatus', 'describeChannelMembershipForAppInstanceUserResponse_httpStatus' - The response's http status code.
newDescribeChannelMembershipForAppInstanceUserResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeChannelMembershipForAppInstanceUserResponse
newDescribeChannelMembershipForAppInstanceUserResponse :: Int -> DescribeChannelMembershipForAppInstanceUserResponse
newDescribeChannelMembershipForAppInstanceUserResponse
  Int
pHttpStatus_ =
    DescribeChannelMembershipForAppInstanceUserResponse'
      { $sel:channelMembership:DescribeChannelMembershipForAppInstanceUserResponse' :: Maybe ChannelMembershipForAppInstanceUserSummary
channelMembership =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeChannelMembershipForAppInstanceUserResponse' :: Int
httpStatus =
          Int
pHttpStatus_
      }

-- | The channel to which a user belongs.
describeChannelMembershipForAppInstanceUserResponse_channelMembership :: Lens.Lens' DescribeChannelMembershipForAppInstanceUserResponse (Prelude.Maybe ChannelMembershipForAppInstanceUserSummary)
describeChannelMembershipForAppInstanceUserResponse_channelMembership :: Lens'
  DescribeChannelMembershipForAppInstanceUserResponse
  (Maybe ChannelMembershipForAppInstanceUserSummary)
describeChannelMembershipForAppInstanceUserResponse_channelMembership = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeChannelMembershipForAppInstanceUserResponse' {Maybe ChannelMembershipForAppInstanceUserSummary
channelMembership :: Maybe ChannelMembershipForAppInstanceUserSummary
$sel:channelMembership:DescribeChannelMembershipForAppInstanceUserResponse' :: DescribeChannelMembershipForAppInstanceUserResponse
-> Maybe ChannelMembershipForAppInstanceUserSummary
channelMembership} -> Maybe ChannelMembershipForAppInstanceUserSummary
channelMembership) (\s :: DescribeChannelMembershipForAppInstanceUserResponse
s@DescribeChannelMembershipForAppInstanceUserResponse' {} Maybe ChannelMembershipForAppInstanceUserSummary
a -> DescribeChannelMembershipForAppInstanceUserResponse
s {$sel:channelMembership:DescribeChannelMembershipForAppInstanceUserResponse' :: Maybe ChannelMembershipForAppInstanceUserSummary
channelMembership = Maybe ChannelMembershipForAppInstanceUserSummary
a} :: DescribeChannelMembershipForAppInstanceUserResponse)

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

instance
  Prelude.NFData
    DescribeChannelMembershipForAppInstanceUserResponse
  where
  rnf :: DescribeChannelMembershipForAppInstanceUserResponse -> ()
rnf
    DescribeChannelMembershipForAppInstanceUserResponse' {Int
Maybe ChannelMembershipForAppInstanceUserSummary
httpStatus :: Int
channelMembership :: Maybe ChannelMembershipForAppInstanceUserSummary
$sel:httpStatus:DescribeChannelMembershipForAppInstanceUserResponse' :: DescribeChannelMembershipForAppInstanceUserResponse -> Int
$sel:channelMembership:DescribeChannelMembershipForAppInstanceUserResponse' :: DescribeChannelMembershipForAppInstanceUserResponse
-> Maybe ChannelMembershipForAppInstanceUserSummary
..} =
      forall a. NFData a => a -> ()
Prelude.rnf Maybe ChannelMembershipForAppInstanceUserSummary
channelMembership
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus