{-# 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.ChimeSDKMessaging.ListChannelMembershipsForAppInstanceUser
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists all channels that a particular @AppInstanceUser@ is a part of.
-- Only an @AppInstanceAdmin@ can call the API with a user ARN that is not
-- their own.
--
-- 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.ChimeSDKMessaging.ListChannelMembershipsForAppInstanceUser
  ( -- * Creating a Request
    ListChannelMembershipsForAppInstanceUser (..),
    newListChannelMembershipsForAppInstanceUser,

    -- * Request Lenses
    listChannelMembershipsForAppInstanceUser_appInstanceUserArn,
    listChannelMembershipsForAppInstanceUser_maxResults,
    listChannelMembershipsForAppInstanceUser_nextToken,
    listChannelMembershipsForAppInstanceUser_chimeBearer,

    -- * Destructuring the Response
    ListChannelMembershipsForAppInstanceUserResponse (..),
    newListChannelMembershipsForAppInstanceUserResponse,

    -- * Response Lenses
    listChannelMembershipsForAppInstanceUserResponse_channelMemberships,
    listChannelMembershipsForAppInstanceUserResponse_nextToken,
    listChannelMembershipsForAppInstanceUserResponse_httpStatus,
  )
where

import Amazonka.ChimeSDKMessaging.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:/ 'newListChannelMembershipsForAppInstanceUser' smart constructor.
data ListChannelMembershipsForAppInstanceUser = ListChannelMembershipsForAppInstanceUser'
  { -- | The ARN of the @AppInstanceUser@s
    ListChannelMembershipsForAppInstanceUser -> Maybe Text
appInstanceUserArn :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of users that you want returned.
    ListChannelMembershipsForAppInstanceUser -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token returned from previous API requests until the number of
    -- channel memberships is reached.
    ListChannelMembershipsForAppInstanceUser -> Maybe (Sensitive Text)
nextToken :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The @AppInstanceUserArn@ of the user that makes the API call.
    ListChannelMembershipsForAppInstanceUser -> Text
chimeBearer :: Prelude.Text
  }
  deriving (ListChannelMembershipsForAppInstanceUser
-> ListChannelMembershipsForAppInstanceUser -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListChannelMembershipsForAppInstanceUser
-> ListChannelMembershipsForAppInstanceUser -> Bool
$c/= :: ListChannelMembershipsForAppInstanceUser
-> ListChannelMembershipsForAppInstanceUser -> Bool
== :: ListChannelMembershipsForAppInstanceUser
-> ListChannelMembershipsForAppInstanceUser -> Bool
$c== :: ListChannelMembershipsForAppInstanceUser
-> ListChannelMembershipsForAppInstanceUser -> Bool
Prelude.Eq, Int -> ListChannelMembershipsForAppInstanceUser -> ShowS
[ListChannelMembershipsForAppInstanceUser] -> ShowS
ListChannelMembershipsForAppInstanceUser -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListChannelMembershipsForAppInstanceUser] -> ShowS
$cshowList :: [ListChannelMembershipsForAppInstanceUser] -> ShowS
show :: ListChannelMembershipsForAppInstanceUser -> String
$cshow :: ListChannelMembershipsForAppInstanceUser -> String
showsPrec :: Int -> ListChannelMembershipsForAppInstanceUser -> ShowS
$cshowsPrec :: Int -> ListChannelMembershipsForAppInstanceUser -> ShowS
Prelude.Show, forall x.
Rep ListChannelMembershipsForAppInstanceUser x
-> ListChannelMembershipsForAppInstanceUser
forall x.
ListChannelMembershipsForAppInstanceUser
-> Rep ListChannelMembershipsForAppInstanceUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListChannelMembershipsForAppInstanceUser x
-> ListChannelMembershipsForAppInstanceUser
$cfrom :: forall x.
ListChannelMembershipsForAppInstanceUser
-> Rep ListChannelMembershipsForAppInstanceUser x
Prelude.Generic)

-- |
-- Create a value of 'ListChannelMembershipsForAppInstanceUser' 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:
--
-- 'appInstanceUserArn', 'listChannelMembershipsForAppInstanceUser_appInstanceUserArn' - The ARN of the @AppInstanceUser@s
--
-- 'maxResults', 'listChannelMembershipsForAppInstanceUser_maxResults' - The maximum number of users that you want returned.
--
-- 'nextToken', 'listChannelMembershipsForAppInstanceUser_nextToken' - The token returned from previous API requests until the number of
-- channel memberships is reached.
--
-- 'chimeBearer', 'listChannelMembershipsForAppInstanceUser_chimeBearer' - The @AppInstanceUserArn@ of the user that makes the API call.
newListChannelMembershipsForAppInstanceUser ::
  -- | 'chimeBearer'
  Prelude.Text ->
  ListChannelMembershipsForAppInstanceUser
newListChannelMembershipsForAppInstanceUser :: Text -> ListChannelMembershipsForAppInstanceUser
newListChannelMembershipsForAppInstanceUser
  Text
pChimeBearer_ =
    ListChannelMembershipsForAppInstanceUser'
      { $sel:appInstanceUserArn:ListChannelMembershipsForAppInstanceUser' :: Maybe Text
appInstanceUserArn =
          forall a. Maybe a
Prelude.Nothing,
        $sel:maxResults:ListChannelMembershipsForAppInstanceUser' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:ListChannelMembershipsForAppInstanceUser' :: Maybe (Sensitive Text)
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:chimeBearer:ListChannelMembershipsForAppInstanceUser' :: Text
chimeBearer = Text
pChimeBearer_
      }

-- | The ARN of the @AppInstanceUser@s
listChannelMembershipsForAppInstanceUser_appInstanceUserArn :: Lens.Lens' ListChannelMembershipsForAppInstanceUser (Prelude.Maybe Prelude.Text)
listChannelMembershipsForAppInstanceUser_appInstanceUserArn :: Lens' ListChannelMembershipsForAppInstanceUser (Maybe Text)
listChannelMembershipsForAppInstanceUser_appInstanceUserArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChannelMembershipsForAppInstanceUser' {Maybe Text
appInstanceUserArn :: Maybe Text
$sel:appInstanceUserArn:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Maybe Text
appInstanceUserArn} -> Maybe Text
appInstanceUserArn) (\s :: ListChannelMembershipsForAppInstanceUser
s@ListChannelMembershipsForAppInstanceUser' {} Maybe Text
a -> ListChannelMembershipsForAppInstanceUser
s {$sel:appInstanceUserArn:ListChannelMembershipsForAppInstanceUser' :: Maybe Text
appInstanceUserArn = Maybe Text
a} :: ListChannelMembershipsForAppInstanceUser)

-- | The maximum number of users that you want returned.
listChannelMembershipsForAppInstanceUser_maxResults :: Lens.Lens' ListChannelMembershipsForAppInstanceUser (Prelude.Maybe Prelude.Natural)
listChannelMembershipsForAppInstanceUser_maxResults :: Lens' ListChannelMembershipsForAppInstanceUser (Maybe Natural)
listChannelMembershipsForAppInstanceUser_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChannelMembershipsForAppInstanceUser' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListChannelMembershipsForAppInstanceUser
s@ListChannelMembershipsForAppInstanceUser' {} Maybe Natural
a -> ListChannelMembershipsForAppInstanceUser
s {$sel:maxResults:ListChannelMembershipsForAppInstanceUser' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListChannelMembershipsForAppInstanceUser)

-- | The token returned from previous API requests until the number of
-- channel memberships is reached.
listChannelMembershipsForAppInstanceUser_nextToken :: Lens.Lens' ListChannelMembershipsForAppInstanceUser (Prelude.Maybe Prelude.Text)
listChannelMembershipsForAppInstanceUser_nextToken :: Lens' ListChannelMembershipsForAppInstanceUser (Maybe Text)
listChannelMembershipsForAppInstanceUser_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChannelMembershipsForAppInstanceUser' {Maybe (Sensitive Text)
nextToken :: Maybe (Sensitive Text)
$sel:nextToken:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Maybe (Sensitive Text)
nextToken} -> Maybe (Sensitive Text)
nextToken) (\s :: ListChannelMembershipsForAppInstanceUser
s@ListChannelMembershipsForAppInstanceUser' {} Maybe (Sensitive Text)
a -> ListChannelMembershipsForAppInstanceUser
s {$sel:nextToken:ListChannelMembershipsForAppInstanceUser' :: Maybe (Sensitive Text)
nextToken = Maybe (Sensitive Text)
a} :: ListChannelMembershipsForAppInstanceUser) 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 @AppInstanceUserArn@ of the user that makes the API call.
listChannelMembershipsForAppInstanceUser_chimeBearer :: Lens.Lens' ListChannelMembershipsForAppInstanceUser Prelude.Text
listChannelMembershipsForAppInstanceUser_chimeBearer :: Lens' ListChannelMembershipsForAppInstanceUser Text
listChannelMembershipsForAppInstanceUser_chimeBearer = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChannelMembershipsForAppInstanceUser' {Text
chimeBearer :: Text
$sel:chimeBearer:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Text
chimeBearer} -> Text
chimeBearer) (\s :: ListChannelMembershipsForAppInstanceUser
s@ListChannelMembershipsForAppInstanceUser' {} Text
a -> ListChannelMembershipsForAppInstanceUser
s {$sel:chimeBearer:ListChannelMembershipsForAppInstanceUser' :: Text
chimeBearer = Text
a} :: ListChannelMembershipsForAppInstanceUser)

instance
  Core.AWSRequest
    ListChannelMembershipsForAppInstanceUser
  where
  type
    AWSResponse
      ListChannelMembershipsForAppInstanceUser =
      ListChannelMembershipsForAppInstanceUserResponse
  request :: (Service -> Service)
-> ListChannelMembershipsForAppInstanceUser
-> Request ListChannelMembershipsForAppInstanceUser
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 ListChannelMembershipsForAppInstanceUser
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse ListChannelMembershipsForAppInstanceUser)))
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]
-> Maybe (Sensitive Text)
-> Int
-> ListChannelMembershipsForAppInstanceUserResponse
ListChannelMembershipsForAppInstanceUserResponse'
            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
"ChannelMemberships"
                            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
"NextToken")
            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
    ListChannelMembershipsForAppInstanceUser
  where
  hashWithSalt :: Int -> ListChannelMembershipsForAppInstanceUser -> Int
hashWithSalt
    Int
_salt
    ListChannelMembershipsForAppInstanceUser' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Text
chimeBearer :: Text
nextToken :: Maybe (Sensitive Text)
maxResults :: Maybe Natural
appInstanceUserArn :: Maybe Text
$sel:chimeBearer:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Text
$sel:nextToken:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Maybe (Sensitive Text)
$sel:maxResults:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Maybe Natural
$sel:appInstanceUserArn:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Maybe Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
appInstanceUserArn
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
nextToken
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
chimeBearer

instance
  Prelude.NFData
    ListChannelMembershipsForAppInstanceUser
  where
  rnf :: ListChannelMembershipsForAppInstanceUser -> ()
rnf ListChannelMembershipsForAppInstanceUser' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Text
chimeBearer :: Text
nextToken :: Maybe (Sensitive Text)
maxResults :: Maybe Natural
appInstanceUserArn :: Maybe Text
$sel:chimeBearer:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Text
$sel:nextToken:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Maybe (Sensitive Text)
$sel:maxResults:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Maybe Natural
$sel:appInstanceUserArn:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
appInstanceUserArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
chimeBearer

instance
  Data.ToHeaders
    ListChannelMembershipsForAppInstanceUser
  where
  toHeaders :: ListChannelMembershipsForAppInstanceUser -> ResponseHeaders
toHeaders
    ListChannelMembershipsForAppInstanceUser' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Text
chimeBearer :: Text
nextToken :: Maybe (Sensitive Text)
maxResults :: Maybe Natural
appInstanceUserArn :: Maybe Text
$sel:chimeBearer:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Text
$sel:nextToken:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Maybe (Sensitive Text)
$sel:maxResults:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Maybe Natural
$sel:appInstanceUserArn:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Maybe Text
..} =
      forall a. Monoid a => [a] -> a
Prelude.mconcat
        [HeaderName
"x-amz-chime-bearer" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Text
chimeBearer]

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

instance
  Data.ToQuery
    ListChannelMembershipsForAppInstanceUser
  where
  toQuery :: ListChannelMembershipsForAppInstanceUser -> QueryString
toQuery ListChannelMembershipsForAppInstanceUser' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Text
chimeBearer :: Text
nextToken :: Maybe (Sensitive Text)
maxResults :: Maybe Natural
appInstanceUserArn :: Maybe Text
$sel:chimeBearer:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Text
$sel:nextToken:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Maybe (Sensitive Text)
$sel:maxResults:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Maybe Natural
$sel:appInstanceUserArn:ListChannelMembershipsForAppInstanceUser' :: ListChannelMembershipsForAppInstanceUser -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"app-instance-user-arn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
appInstanceUserArn,
        ByteString
"max-results" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"next-token" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe (Sensitive Text)
nextToken,
        QueryString
"scope=app-instance-user-memberships"
      ]

-- | /See:/ 'newListChannelMembershipsForAppInstanceUserResponse' smart constructor.
data ListChannelMembershipsForAppInstanceUserResponse = ListChannelMembershipsForAppInstanceUserResponse'
  { -- | The information for the requested channel memberships.
    ListChannelMembershipsForAppInstanceUserResponse
-> Maybe [ChannelMembershipForAppInstanceUserSummary]
channelMemberships :: Prelude.Maybe [ChannelMembershipForAppInstanceUserSummary],
    -- | The token passed by previous API calls until all requested users are
    -- returned.
    ListChannelMembershipsForAppInstanceUserResponse
-> Maybe (Sensitive Text)
nextToken :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The response's http status code.
    ListChannelMembershipsForAppInstanceUserResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListChannelMembershipsForAppInstanceUserResponse
-> ListChannelMembershipsForAppInstanceUserResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListChannelMembershipsForAppInstanceUserResponse
-> ListChannelMembershipsForAppInstanceUserResponse -> Bool
$c/= :: ListChannelMembershipsForAppInstanceUserResponse
-> ListChannelMembershipsForAppInstanceUserResponse -> Bool
== :: ListChannelMembershipsForAppInstanceUserResponse
-> ListChannelMembershipsForAppInstanceUserResponse -> Bool
$c== :: ListChannelMembershipsForAppInstanceUserResponse
-> ListChannelMembershipsForAppInstanceUserResponse -> Bool
Prelude.Eq, Int -> ListChannelMembershipsForAppInstanceUserResponse -> ShowS
[ListChannelMembershipsForAppInstanceUserResponse] -> ShowS
ListChannelMembershipsForAppInstanceUserResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListChannelMembershipsForAppInstanceUserResponse] -> ShowS
$cshowList :: [ListChannelMembershipsForAppInstanceUserResponse] -> ShowS
show :: ListChannelMembershipsForAppInstanceUserResponse -> String
$cshow :: ListChannelMembershipsForAppInstanceUserResponse -> String
showsPrec :: Int -> ListChannelMembershipsForAppInstanceUserResponse -> ShowS
$cshowsPrec :: Int -> ListChannelMembershipsForAppInstanceUserResponse -> ShowS
Prelude.Show, forall x.
Rep ListChannelMembershipsForAppInstanceUserResponse x
-> ListChannelMembershipsForAppInstanceUserResponse
forall x.
ListChannelMembershipsForAppInstanceUserResponse
-> Rep ListChannelMembershipsForAppInstanceUserResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListChannelMembershipsForAppInstanceUserResponse x
-> ListChannelMembershipsForAppInstanceUserResponse
$cfrom :: forall x.
ListChannelMembershipsForAppInstanceUserResponse
-> Rep ListChannelMembershipsForAppInstanceUserResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListChannelMembershipsForAppInstanceUserResponse' 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:
--
-- 'channelMemberships', 'listChannelMembershipsForAppInstanceUserResponse_channelMemberships' - The information for the requested channel memberships.
--
-- 'nextToken', 'listChannelMembershipsForAppInstanceUserResponse_nextToken' - The token passed by previous API calls until all requested users are
-- returned.
--
-- 'httpStatus', 'listChannelMembershipsForAppInstanceUserResponse_httpStatus' - The response's http status code.
newListChannelMembershipsForAppInstanceUserResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListChannelMembershipsForAppInstanceUserResponse
newListChannelMembershipsForAppInstanceUserResponse :: Int -> ListChannelMembershipsForAppInstanceUserResponse
newListChannelMembershipsForAppInstanceUserResponse
  Int
pHttpStatus_ =
    ListChannelMembershipsForAppInstanceUserResponse'
      { $sel:channelMemberships:ListChannelMembershipsForAppInstanceUserResponse' :: Maybe [ChannelMembershipForAppInstanceUserSummary]
channelMemberships =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:ListChannelMembershipsForAppInstanceUserResponse' :: Maybe (Sensitive Text)
nextToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ListChannelMembershipsForAppInstanceUserResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The information for the requested channel memberships.
listChannelMembershipsForAppInstanceUserResponse_channelMemberships :: Lens.Lens' ListChannelMembershipsForAppInstanceUserResponse (Prelude.Maybe [ChannelMembershipForAppInstanceUserSummary])
listChannelMembershipsForAppInstanceUserResponse_channelMemberships :: Lens'
  ListChannelMembershipsForAppInstanceUserResponse
  (Maybe [ChannelMembershipForAppInstanceUserSummary])
listChannelMembershipsForAppInstanceUserResponse_channelMemberships = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChannelMembershipsForAppInstanceUserResponse' {Maybe [ChannelMembershipForAppInstanceUserSummary]
channelMemberships :: Maybe [ChannelMembershipForAppInstanceUserSummary]
$sel:channelMemberships:ListChannelMembershipsForAppInstanceUserResponse' :: ListChannelMembershipsForAppInstanceUserResponse
-> Maybe [ChannelMembershipForAppInstanceUserSummary]
channelMemberships} -> Maybe [ChannelMembershipForAppInstanceUserSummary]
channelMemberships) (\s :: ListChannelMembershipsForAppInstanceUserResponse
s@ListChannelMembershipsForAppInstanceUserResponse' {} Maybe [ChannelMembershipForAppInstanceUserSummary]
a -> ListChannelMembershipsForAppInstanceUserResponse
s {$sel:channelMemberships:ListChannelMembershipsForAppInstanceUserResponse' :: Maybe [ChannelMembershipForAppInstanceUserSummary]
channelMemberships = Maybe [ChannelMembershipForAppInstanceUserSummary]
a} :: ListChannelMembershipsForAppInstanceUserResponse) 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 token passed by previous API calls until all requested users are
-- returned.
listChannelMembershipsForAppInstanceUserResponse_nextToken :: Lens.Lens' ListChannelMembershipsForAppInstanceUserResponse (Prelude.Maybe Prelude.Text)
listChannelMembershipsForAppInstanceUserResponse_nextToken :: Lens' ListChannelMembershipsForAppInstanceUserResponse (Maybe Text)
listChannelMembershipsForAppInstanceUserResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChannelMembershipsForAppInstanceUserResponse' {Maybe (Sensitive Text)
nextToken :: Maybe (Sensitive Text)
$sel:nextToken:ListChannelMembershipsForAppInstanceUserResponse' :: ListChannelMembershipsForAppInstanceUserResponse
-> Maybe (Sensitive Text)
nextToken} -> Maybe (Sensitive Text)
nextToken) (\s :: ListChannelMembershipsForAppInstanceUserResponse
s@ListChannelMembershipsForAppInstanceUserResponse' {} Maybe (Sensitive Text)
a -> ListChannelMembershipsForAppInstanceUserResponse
s {$sel:nextToken:ListChannelMembershipsForAppInstanceUserResponse' :: Maybe (Sensitive Text)
nextToken = Maybe (Sensitive Text)
a} :: ListChannelMembershipsForAppInstanceUserResponse) 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 response's http status code.
listChannelMembershipsForAppInstanceUserResponse_httpStatus :: Lens.Lens' ListChannelMembershipsForAppInstanceUserResponse Prelude.Int
listChannelMembershipsForAppInstanceUserResponse_httpStatus :: Lens' ListChannelMembershipsForAppInstanceUserResponse Int
listChannelMembershipsForAppInstanceUserResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChannelMembershipsForAppInstanceUserResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListChannelMembershipsForAppInstanceUserResponse' :: ListChannelMembershipsForAppInstanceUserResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListChannelMembershipsForAppInstanceUserResponse
s@ListChannelMembershipsForAppInstanceUserResponse' {} Int
a -> ListChannelMembershipsForAppInstanceUserResponse
s {$sel:httpStatus:ListChannelMembershipsForAppInstanceUserResponse' :: Int
httpStatus = Int
a} :: ListChannelMembershipsForAppInstanceUserResponse)

instance
  Prelude.NFData
    ListChannelMembershipsForAppInstanceUserResponse
  where
  rnf :: ListChannelMembershipsForAppInstanceUserResponse -> ()
rnf
    ListChannelMembershipsForAppInstanceUserResponse' {Int
Maybe [ChannelMembershipForAppInstanceUserSummary]
Maybe (Sensitive Text)
httpStatus :: Int
nextToken :: Maybe (Sensitive Text)
channelMemberships :: Maybe [ChannelMembershipForAppInstanceUserSummary]
$sel:httpStatus:ListChannelMembershipsForAppInstanceUserResponse' :: ListChannelMembershipsForAppInstanceUserResponse -> Int
$sel:nextToken:ListChannelMembershipsForAppInstanceUserResponse' :: ListChannelMembershipsForAppInstanceUserResponse
-> Maybe (Sensitive Text)
$sel:channelMemberships:ListChannelMembershipsForAppInstanceUserResponse' :: ListChannelMembershipsForAppInstanceUserResponse
-> Maybe [ChannelMembershipForAppInstanceUserSummary]
..} =
      forall a. NFData a => a -> ()
Prelude.rnf Maybe [ChannelMembershipForAppInstanceUserSummary]
channelMemberships
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
nextToken
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus