{-# 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.ListChannelsAssociatedWithChannelFlow
-- 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 associated with a specified channel flow. You can
-- associate a channel flow with multiple channels, but you can only
-- associate a channel with one channel flow. This is a developer API.
module Amazonka.ChimeSDKMessaging.ListChannelsAssociatedWithChannelFlow
  ( -- * Creating a Request
    ListChannelsAssociatedWithChannelFlow (..),
    newListChannelsAssociatedWithChannelFlow,

    -- * Request Lenses
    listChannelsAssociatedWithChannelFlow_maxResults,
    listChannelsAssociatedWithChannelFlow_nextToken,
    listChannelsAssociatedWithChannelFlow_channelFlowArn,

    -- * Destructuring the Response
    ListChannelsAssociatedWithChannelFlowResponse (..),
    newListChannelsAssociatedWithChannelFlowResponse,

    -- * Response Lenses
    listChannelsAssociatedWithChannelFlowResponse_channels,
    listChannelsAssociatedWithChannelFlowResponse_nextToken,
    listChannelsAssociatedWithChannelFlowResponse_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:/ 'newListChannelsAssociatedWithChannelFlow' smart constructor.
data ListChannelsAssociatedWithChannelFlow = ListChannelsAssociatedWithChannelFlow'
  { -- | The maximum number of channels that you want to return.
    ListChannelsAssociatedWithChannelFlow -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token passed by previous API calls until all requested channels are
    -- returned.
    ListChannelsAssociatedWithChannelFlow -> Maybe (Sensitive Text)
nextToken :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The ARN of the channel flow.
    ListChannelsAssociatedWithChannelFlow -> Text
channelFlowArn :: Prelude.Text
  }
  deriving (ListChannelsAssociatedWithChannelFlow
-> ListChannelsAssociatedWithChannelFlow -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListChannelsAssociatedWithChannelFlow
-> ListChannelsAssociatedWithChannelFlow -> Bool
$c/= :: ListChannelsAssociatedWithChannelFlow
-> ListChannelsAssociatedWithChannelFlow -> Bool
== :: ListChannelsAssociatedWithChannelFlow
-> ListChannelsAssociatedWithChannelFlow -> Bool
$c== :: ListChannelsAssociatedWithChannelFlow
-> ListChannelsAssociatedWithChannelFlow -> Bool
Prelude.Eq, Int -> ListChannelsAssociatedWithChannelFlow -> ShowS
[ListChannelsAssociatedWithChannelFlow] -> ShowS
ListChannelsAssociatedWithChannelFlow -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListChannelsAssociatedWithChannelFlow] -> ShowS
$cshowList :: [ListChannelsAssociatedWithChannelFlow] -> ShowS
show :: ListChannelsAssociatedWithChannelFlow -> String
$cshow :: ListChannelsAssociatedWithChannelFlow -> String
showsPrec :: Int -> ListChannelsAssociatedWithChannelFlow -> ShowS
$cshowsPrec :: Int -> ListChannelsAssociatedWithChannelFlow -> ShowS
Prelude.Show, forall x.
Rep ListChannelsAssociatedWithChannelFlow x
-> ListChannelsAssociatedWithChannelFlow
forall x.
ListChannelsAssociatedWithChannelFlow
-> Rep ListChannelsAssociatedWithChannelFlow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListChannelsAssociatedWithChannelFlow x
-> ListChannelsAssociatedWithChannelFlow
$cfrom :: forall x.
ListChannelsAssociatedWithChannelFlow
-> Rep ListChannelsAssociatedWithChannelFlow x
Prelude.Generic)

-- |
-- Create a value of 'ListChannelsAssociatedWithChannelFlow' 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:
--
-- 'maxResults', 'listChannelsAssociatedWithChannelFlow_maxResults' - The maximum number of channels that you want to return.
--
-- 'nextToken', 'listChannelsAssociatedWithChannelFlow_nextToken' - The token passed by previous API calls until all requested channels are
-- returned.
--
-- 'channelFlowArn', 'listChannelsAssociatedWithChannelFlow_channelFlowArn' - The ARN of the channel flow.
newListChannelsAssociatedWithChannelFlow ::
  -- | 'channelFlowArn'
  Prelude.Text ->
  ListChannelsAssociatedWithChannelFlow
newListChannelsAssociatedWithChannelFlow :: Text -> ListChannelsAssociatedWithChannelFlow
newListChannelsAssociatedWithChannelFlow
  Text
pChannelFlowArn_ =
    ListChannelsAssociatedWithChannelFlow'
      { $sel:maxResults:ListChannelsAssociatedWithChannelFlow' :: Maybe Natural
maxResults =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:ListChannelsAssociatedWithChannelFlow' :: Maybe (Sensitive Text)
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:channelFlowArn:ListChannelsAssociatedWithChannelFlow' :: Text
channelFlowArn = Text
pChannelFlowArn_
      }

-- | The maximum number of channels that you want to return.
listChannelsAssociatedWithChannelFlow_maxResults :: Lens.Lens' ListChannelsAssociatedWithChannelFlow (Prelude.Maybe Prelude.Natural)
listChannelsAssociatedWithChannelFlow_maxResults :: Lens' ListChannelsAssociatedWithChannelFlow (Maybe Natural)
listChannelsAssociatedWithChannelFlow_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChannelsAssociatedWithChannelFlow' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListChannelsAssociatedWithChannelFlow' :: ListChannelsAssociatedWithChannelFlow -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListChannelsAssociatedWithChannelFlow
s@ListChannelsAssociatedWithChannelFlow' {} Maybe Natural
a -> ListChannelsAssociatedWithChannelFlow
s {$sel:maxResults:ListChannelsAssociatedWithChannelFlow' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListChannelsAssociatedWithChannelFlow)

-- | The token passed by previous API calls until all requested channels are
-- returned.
listChannelsAssociatedWithChannelFlow_nextToken :: Lens.Lens' ListChannelsAssociatedWithChannelFlow (Prelude.Maybe Prelude.Text)
listChannelsAssociatedWithChannelFlow_nextToken :: Lens' ListChannelsAssociatedWithChannelFlow (Maybe Text)
listChannelsAssociatedWithChannelFlow_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChannelsAssociatedWithChannelFlow' {Maybe (Sensitive Text)
nextToken :: Maybe (Sensitive Text)
$sel:nextToken:ListChannelsAssociatedWithChannelFlow' :: ListChannelsAssociatedWithChannelFlow -> Maybe (Sensitive Text)
nextToken} -> Maybe (Sensitive Text)
nextToken) (\s :: ListChannelsAssociatedWithChannelFlow
s@ListChannelsAssociatedWithChannelFlow' {} Maybe (Sensitive Text)
a -> ListChannelsAssociatedWithChannelFlow
s {$sel:nextToken:ListChannelsAssociatedWithChannelFlow' :: Maybe (Sensitive Text)
nextToken = Maybe (Sensitive Text)
a} :: ListChannelsAssociatedWithChannelFlow) 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 ARN of the channel flow.
listChannelsAssociatedWithChannelFlow_channelFlowArn :: Lens.Lens' ListChannelsAssociatedWithChannelFlow Prelude.Text
listChannelsAssociatedWithChannelFlow_channelFlowArn :: Lens' ListChannelsAssociatedWithChannelFlow Text
listChannelsAssociatedWithChannelFlow_channelFlowArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChannelsAssociatedWithChannelFlow' {Text
channelFlowArn :: Text
$sel:channelFlowArn:ListChannelsAssociatedWithChannelFlow' :: ListChannelsAssociatedWithChannelFlow -> Text
channelFlowArn} -> Text
channelFlowArn) (\s :: ListChannelsAssociatedWithChannelFlow
s@ListChannelsAssociatedWithChannelFlow' {} Text
a -> ListChannelsAssociatedWithChannelFlow
s {$sel:channelFlowArn:ListChannelsAssociatedWithChannelFlow' :: Text
channelFlowArn = Text
a} :: ListChannelsAssociatedWithChannelFlow)

instance
  Core.AWSRequest
    ListChannelsAssociatedWithChannelFlow
  where
  type
    AWSResponse
      ListChannelsAssociatedWithChannelFlow =
      ListChannelsAssociatedWithChannelFlowResponse
  request :: (Service -> Service)
-> ListChannelsAssociatedWithChannelFlow
-> Request ListChannelsAssociatedWithChannelFlow
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 ListChannelsAssociatedWithChannelFlow
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse ListChannelsAssociatedWithChannelFlow)))
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 [ChannelAssociatedWithFlowSummary]
-> Maybe (Sensitive Text)
-> Int
-> ListChannelsAssociatedWithChannelFlowResponse
ListChannelsAssociatedWithChannelFlowResponse'
            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
"Channels" 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
    ListChannelsAssociatedWithChannelFlow
  where
  hashWithSalt :: Int -> ListChannelsAssociatedWithChannelFlow -> Int
hashWithSalt
    Int
_salt
    ListChannelsAssociatedWithChannelFlow' {Maybe Natural
Maybe (Sensitive Text)
Text
channelFlowArn :: Text
nextToken :: Maybe (Sensitive Text)
maxResults :: Maybe Natural
$sel:channelFlowArn:ListChannelsAssociatedWithChannelFlow' :: ListChannelsAssociatedWithChannelFlow -> Text
$sel:nextToken:ListChannelsAssociatedWithChannelFlow' :: ListChannelsAssociatedWithChannelFlow -> Maybe (Sensitive Text)
$sel:maxResults:ListChannelsAssociatedWithChannelFlow' :: ListChannelsAssociatedWithChannelFlow -> Maybe Natural
..} =
      Int
_salt
        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
channelFlowArn

instance
  Prelude.NFData
    ListChannelsAssociatedWithChannelFlow
  where
  rnf :: ListChannelsAssociatedWithChannelFlow -> ()
rnf ListChannelsAssociatedWithChannelFlow' {Maybe Natural
Maybe (Sensitive Text)
Text
channelFlowArn :: Text
nextToken :: Maybe (Sensitive Text)
maxResults :: Maybe Natural
$sel:channelFlowArn:ListChannelsAssociatedWithChannelFlow' :: ListChannelsAssociatedWithChannelFlow -> Text
$sel:nextToken:ListChannelsAssociatedWithChannelFlow' :: ListChannelsAssociatedWithChannelFlow -> Maybe (Sensitive Text)
$sel:maxResults:ListChannelsAssociatedWithChannelFlow' :: ListChannelsAssociatedWithChannelFlow -> Maybe Natural
..} =
    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
channelFlowArn

instance
  Data.ToHeaders
    ListChannelsAssociatedWithChannelFlow
  where
  toHeaders :: ListChannelsAssociatedWithChannelFlow -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance
  Data.ToQuery
    ListChannelsAssociatedWithChannelFlow
  where
  toQuery :: ListChannelsAssociatedWithChannelFlow -> QueryString
toQuery ListChannelsAssociatedWithChannelFlow' {Maybe Natural
Maybe (Sensitive Text)
Text
channelFlowArn :: Text
nextToken :: Maybe (Sensitive Text)
maxResults :: Maybe Natural
$sel:channelFlowArn:ListChannelsAssociatedWithChannelFlow' :: ListChannelsAssociatedWithChannelFlow -> Text
$sel:nextToken:ListChannelsAssociatedWithChannelFlow' :: ListChannelsAssociatedWithChannelFlow -> Maybe (Sensitive Text)
$sel:maxResults:ListChannelsAssociatedWithChannelFlow' :: ListChannelsAssociatedWithChannelFlow -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ 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,
        ByteString
"channel-flow-arn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
channelFlowArn,
        QueryString
"scope=channel-flow-associations"
      ]

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

-- |
-- Create a value of 'ListChannelsAssociatedWithChannelFlowResponse' 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:
--
-- 'channels', 'listChannelsAssociatedWithChannelFlowResponse_channels' - The information about each channel.
--
-- 'nextToken', 'listChannelsAssociatedWithChannelFlowResponse_nextToken' - The token passed by previous API calls until all requested channels are
-- returned.
--
-- 'httpStatus', 'listChannelsAssociatedWithChannelFlowResponse_httpStatus' - The response's http status code.
newListChannelsAssociatedWithChannelFlowResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListChannelsAssociatedWithChannelFlowResponse
newListChannelsAssociatedWithChannelFlowResponse :: Int -> ListChannelsAssociatedWithChannelFlowResponse
newListChannelsAssociatedWithChannelFlowResponse
  Int
pHttpStatus_ =
    ListChannelsAssociatedWithChannelFlowResponse'
      { $sel:channels:ListChannelsAssociatedWithChannelFlowResponse' :: Maybe [ChannelAssociatedWithFlowSummary]
channels =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:ListChannelsAssociatedWithChannelFlowResponse' :: Maybe (Sensitive Text)
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ListChannelsAssociatedWithChannelFlowResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The information about each channel.
listChannelsAssociatedWithChannelFlowResponse_channels :: Lens.Lens' ListChannelsAssociatedWithChannelFlowResponse (Prelude.Maybe [ChannelAssociatedWithFlowSummary])
listChannelsAssociatedWithChannelFlowResponse_channels :: Lens'
  ListChannelsAssociatedWithChannelFlowResponse
  (Maybe [ChannelAssociatedWithFlowSummary])
listChannelsAssociatedWithChannelFlowResponse_channels = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChannelsAssociatedWithChannelFlowResponse' {Maybe [ChannelAssociatedWithFlowSummary]
channels :: Maybe [ChannelAssociatedWithFlowSummary]
$sel:channels:ListChannelsAssociatedWithChannelFlowResponse' :: ListChannelsAssociatedWithChannelFlowResponse
-> Maybe [ChannelAssociatedWithFlowSummary]
channels} -> Maybe [ChannelAssociatedWithFlowSummary]
channels) (\s :: ListChannelsAssociatedWithChannelFlowResponse
s@ListChannelsAssociatedWithChannelFlowResponse' {} Maybe [ChannelAssociatedWithFlowSummary]
a -> ListChannelsAssociatedWithChannelFlowResponse
s {$sel:channels:ListChannelsAssociatedWithChannelFlowResponse' :: Maybe [ChannelAssociatedWithFlowSummary]
channels = Maybe [ChannelAssociatedWithFlowSummary]
a} :: ListChannelsAssociatedWithChannelFlowResponse) 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 channels are
-- returned.
listChannelsAssociatedWithChannelFlowResponse_nextToken :: Lens.Lens' ListChannelsAssociatedWithChannelFlowResponse (Prelude.Maybe Prelude.Text)
listChannelsAssociatedWithChannelFlowResponse_nextToken :: Lens' ListChannelsAssociatedWithChannelFlowResponse (Maybe Text)
listChannelsAssociatedWithChannelFlowResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChannelsAssociatedWithChannelFlowResponse' {Maybe (Sensitive Text)
nextToken :: Maybe (Sensitive Text)
$sel:nextToken:ListChannelsAssociatedWithChannelFlowResponse' :: ListChannelsAssociatedWithChannelFlowResponse
-> Maybe (Sensitive Text)
nextToken} -> Maybe (Sensitive Text)
nextToken) (\s :: ListChannelsAssociatedWithChannelFlowResponse
s@ListChannelsAssociatedWithChannelFlowResponse' {} Maybe (Sensitive Text)
a -> ListChannelsAssociatedWithChannelFlowResponse
s {$sel:nextToken:ListChannelsAssociatedWithChannelFlowResponse' :: Maybe (Sensitive Text)
nextToken = Maybe (Sensitive Text)
a} :: ListChannelsAssociatedWithChannelFlowResponse) 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.
listChannelsAssociatedWithChannelFlowResponse_httpStatus :: Lens.Lens' ListChannelsAssociatedWithChannelFlowResponse Prelude.Int
listChannelsAssociatedWithChannelFlowResponse_httpStatus :: Lens' ListChannelsAssociatedWithChannelFlowResponse Int
listChannelsAssociatedWithChannelFlowResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChannelsAssociatedWithChannelFlowResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListChannelsAssociatedWithChannelFlowResponse' :: ListChannelsAssociatedWithChannelFlowResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListChannelsAssociatedWithChannelFlowResponse
s@ListChannelsAssociatedWithChannelFlowResponse' {} Int
a -> ListChannelsAssociatedWithChannelFlowResponse
s {$sel:httpStatus:ListChannelsAssociatedWithChannelFlowResponse' :: Int
httpStatus = Int
a} :: ListChannelsAssociatedWithChannelFlowResponse)

instance
  Prelude.NFData
    ListChannelsAssociatedWithChannelFlowResponse
  where
  rnf :: ListChannelsAssociatedWithChannelFlowResponse -> ()
rnf
    ListChannelsAssociatedWithChannelFlowResponse' {Int
Maybe [ChannelAssociatedWithFlowSummary]
Maybe (Sensitive Text)
httpStatus :: Int
nextToken :: Maybe (Sensitive Text)
channels :: Maybe [ChannelAssociatedWithFlowSummary]
$sel:httpStatus:ListChannelsAssociatedWithChannelFlowResponse' :: ListChannelsAssociatedWithChannelFlowResponse -> Int
$sel:nextToken:ListChannelsAssociatedWithChannelFlowResponse' :: ListChannelsAssociatedWithChannelFlowResponse
-> Maybe (Sensitive Text)
$sel:channels:ListChannelsAssociatedWithChannelFlowResponse' :: ListChannelsAssociatedWithChannelFlowResponse
-> Maybe [ChannelAssociatedWithFlowSummary]
..} =
      forall a. NFData a => a -> ()
Prelude.rnf Maybe [ChannelAssociatedWithFlowSummary]
channels
        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