{-# 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.KinesisVideo.ListSignalingChannels
-- 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 an array of @ChannelInfo@ objects. Each object describes a
-- signaling channel. To retrieve only those channels that satisfy a
-- specific condition, you can specify a @ChannelNameCondition@.
--
-- This operation returns paginated results.
module Amazonka.KinesisVideo.ListSignalingChannels
  ( -- * Creating a Request
    ListSignalingChannels (..),
    newListSignalingChannels,

    -- * Request Lenses
    listSignalingChannels_channelNameCondition,
    listSignalingChannels_maxResults,
    listSignalingChannels_nextToken,

    -- * Destructuring the Response
    ListSignalingChannelsResponse (..),
    newListSignalingChannelsResponse,

    -- * Response Lenses
    listSignalingChannelsResponse_channelInfoList,
    listSignalingChannelsResponse_nextToken,
    listSignalingChannelsResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.KinesisVideo.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListSignalingChannels' smart constructor.
data ListSignalingChannels = ListSignalingChannels'
  { -- | Optional: Returns only the channels that satisfy a specific condition.
    ListSignalingChannels -> Maybe ChannelNameCondition
channelNameCondition :: Prelude.Maybe ChannelNameCondition,
    -- | The maximum number of channels to return in the response. The default is
    -- 500.
    ListSignalingChannels -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If you specify this parameter, when the result of a
    -- @ListSignalingChannels@ operation is truncated, the call returns the
    -- @NextToken@ in the response. To get another batch of channels, provide
    -- this token in your next request.
    ListSignalingChannels -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListSignalingChannels -> ListSignalingChannels -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListSignalingChannels -> ListSignalingChannels -> Bool
$c/= :: ListSignalingChannels -> ListSignalingChannels -> Bool
== :: ListSignalingChannels -> ListSignalingChannels -> Bool
$c== :: ListSignalingChannels -> ListSignalingChannels -> Bool
Prelude.Eq, ReadPrec [ListSignalingChannels]
ReadPrec ListSignalingChannels
Int -> ReadS ListSignalingChannels
ReadS [ListSignalingChannels]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListSignalingChannels]
$creadListPrec :: ReadPrec [ListSignalingChannels]
readPrec :: ReadPrec ListSignalingChannels
$creadPrec :: ReadPrec ListSignalingChannels
readList :: ReadS [ListSignalingChannels]
$creadList :: ReadS [ListSignalingChannels]
readsPrec :: Int -> ReadS ListSignalingChannels
$creadsPrec :: Int -> ReadS ListSignalingChannels
Prelude.Read, Int -> ListSignalingChannels -> ShowS
[ListSignalingChannels] -> ShowS
ListSignalingChannels -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListSignalingChannels] -> ShowS
$cshowList :: [ListSignalingChannels] -> ShowS
show :: ListSignalingChannels -> String
$cshow :: ListSignalingChannels -> String
showsPrec :: Int -> ListSignalingChannels -> ShowS
$cshowsPrec :: Int -> ListSignalingChannels -> ShowS
Prelude.Show, forall x. Rep ListSignalingChannels x -> ListSignalingChannels
forall x. ListSignalingChannels -> Rep ListSignalingChannels x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListSignalingChannels x -> ListSignalingChannels
$cfrom :: forall x. ListSignalingChannels -> Rep ListSignalingChannels x
Prelude.Generic)

-- |
-- Create a value of 'ListSignalingChannels' 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:
--
-- 'channelNameCondition', 'listSignalingChannels_channelNameCondition' - Optional: Returns only the channels that satisfy a specific condition.
--
-- 'maxResults', 'listSignalingChannels_maxResults' - The maximum number of channels to return in the response. The default is
-- 500.
--
-- 'nextToken', 'listSignalingChannels_nextToken' - If you specify this parameter, when the result of a
-- @ListSignalingChannels@ operation is truncated, the call returns the
-- @NextToken@ in the response. To get another batch of channels, provide
-- this token in your next request.
newListSignalingChannels ::
  ListSignalingChannels
newListSignalingChannels :: ListSignalingChannels
newListSignalingChannels =
  ListSignalingChannels'
    { $sel:channelNameCondition:ListSignalingChannels' :: Maybe ChannelNameCondition
channelNameCondition =
        forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListSignalingChannels' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListSignalingChannels' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | Optional: Returns only the channels that satisfy a specific condition.
listSignalingChannels_channelNameCondition :: Lens.Lens' ListSignalingChannels (Prelude.Maybe ChannelNameCondition)
listSignalingChannels_channelNameCondition :: Lens' ListSignalingChannels (Maybe ChannelNameCondition)
listSignalingChannels_channelNameCondition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSignalingChannels' {Maybe ChannelNameCondition
channelNameCondition :: Maybe ChannelNameCondition
$sel:channelNameCondition:ListSignalingChannels' :: ListSignalingChannels -> Maybe ChannelNameCondition
channelNameCondition} -> Maybe ChannelNameCondition
channelNameCondition) (\s :: ListSignalingChannels
s@ListSignalingChannels' {} Maybe ChannelNameCondition
a -> ListSignalingChannels
s {$sel:channelNameCondition:ListSignalingChannels' :: Maybe ChannelNameCondition
channelNameCondition = Maybe ChannelNameCondition
a} :: ListSignalingChannels)

-- | The maximum number of channels to return in the response. The default is
-- 500.
listSignalingChannels_maxResults :: Lens.Lens' ListSignalingChannels (Prelude.Maybe Prelude.Natural)
listSignalingChannels_maxResults :: Lens' ListSignalingChannels (Maybe Natural)
listSignalingChannels_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSignalingChannels' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListSignalingChannels' :: ListSignalingChannels -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListSignalingChannels
s@ListSignalingChannels' {} Maybe Natural
a -> ListSignalingChannels
s {$sel:maxResults:ListSignalingChannels' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListSignalingChannels)

-- | If you specify this parameter, when the result of a
-- @ListSignalingChannels@ operation is truncated, the call returns the
-- @NextToken@ in the response. To get another batch of channels, provide
-- this token in your next request.
listSignalingChannels_nextToken :: Lens.Lens' ListSignalingChannels (Prelude.Maybe Prelude.Text)
listSignalingChannels_nextToken :: Lens' ListSignalingChannels (Maybe Text)
listSignalingChannels_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSignalingChannels' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListSignalingChannels' :: ListSignalingChannels -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListSignalingChannels
s@ListSignalingChannels' {} Maybe Text
a -> ListSignalingChannels
s {$sel:nextToken:ListSignalingChannels' :: Maybe Text
nextToken = Maybe Text
a} :: ListSignalingChannels)

instance Core.AWSPager ListSignalingChannels where
  page :: ListSignalingChannels
-> AWSResponse ListSignalingChannels -> Maybe ListSignalingChannels
page ListSignalingChannels
rq AWSResponse ListSignalingChannels
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListSignalingChannels
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListSignalingChannelsResponse (Maybe Text)
listSignalingChannelsResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListSignalingChannels
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListSignalingChannelsResponse (Maybe [ChannelInfo])
listSignalingChannelsResponse_channelInfoList
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListSignalingChannels
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListSignalingChannels (Maybe Text)
listSignalingChannels_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListSignalingChannels
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListSignalingChannelsResponse (Maybe Text)
listSignalingChannelsResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest ListSignalingChannels where
  type
    AWSResponse ListSignalingChannels =
      ListSignalingChannelsResponse
  request :: (Service -> Service)
-> ListSignalingChannels -> Request ListSignalingChannels
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 ListSignalingChannels
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListSignalingChannels)))
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 [ChannelInfo]
-> Maybe Text -> Int -> ListSignalingChannelsResponse
ListSignalingChannelsResponse'
            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
"ChannelInfoList"
                            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 ListSignalingChannels where
  hashWithSalt :: Int -> ListSignalingChannels -> Int
hashWithSalt Int
_salt ListSignalingChannels' {Maybe Natural
Maybe Text
Maybe ChannelNameCondition
nextToken :: Maybe Text
maxResults :: Maybe Natural
channelNameCondition :: Maybe ChannelNameCondition
$sel:nextToken:ListSignalingChannels' :: ListSignalingChannels -> Maybe Text
$sel:maxResults:ListSignalingChannels' :: ListSignalingChannels -> Maybe Natural
$sel:channelNameCondition:ListSignalingChannels' :: ListSignalingChannels -> Maybe ChannelNameCondition
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ChannelNameCondition
channelNameCondition
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListSignalingChannels where
  rnf :: ListSignalingChannels -> ()
rnf ListSignalingChannels' {Maybe Natural
Maybe Text
Maybe ChannelNameCondition
nextToken :: Maybe Text
maxResults :: Maybe Natural
channelNameCondition :: Maybe ChannelNameCondition
$sel:nextToken:ListSignalingChannels' :: ListSignalingChannels -> Maybe Text
$sel:maxResults:ListSignalingChannels' :: ListSignalingChannels -> Maybe Natural
$sel:channelNameCondition:ListSignalingChannels' :: ListSignalingChannels -> Maybe ChannelNameCondition
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ChannelNameCondition
channelNameCondition
      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 Text
nextToken

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

instance Data.ToJSON ListSignalingChannels where
  toJSON :: ListSignalingChannels -> Value
toJSON ListSignalingChannels' {Maybe Natural
Maybe Text
Maybe ChannelNameCondition
nextToken :: Maybe Text
maxResults :: Maybe Natural
channelNameCondition :: Maybe ChannelNameCondition
$sel:nextToken:ListSignalingChannels' :: ListSignalingChannels -> Maybe Text
$sel:maxResults:ListSignalingChannels' :: ListSignalingChannels -> Maybe Natural
$sel:channelNameCondition:ListSignalingChannels' :: ListSignalingChannels -> Maybe ChannelNameCondition
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ChannelNameCondition" 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 ChannelNameCondition
channelNameCondition,
            (Key
"MaxResults" 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 Natural
maxResults,
            (Key
"NextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken
          ]
      )

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

instance Data.ToQuery ListSignalingChannels where
  toQuery :: ListSignalingChannels -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newListSignalingChannelsResponse' smart constructor.
data ListSignalingChannelsResponse = ListSignalingChannelsResponse'
  { -- | An array of @ChannelInfo@ objects.
    ListSignalingChannelsResponse -> Maybe [ChannelInfo]
channelInfoList :: Prelude.Maybe [ChannelInfo],
    -- | If the response is truncated, the call returns this element with a
    -- token. To get the next batch of streams, use this token in your next
    -- request.
    ListSignalingChannelsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListSignalingChannelsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListSignalingChannelsResponse
-> ListSignalingChannelsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListSignalingChannelsResponse
-> ListSignalingChannelsResponse -> Bool
$c/= :: ListSignalingChannelsResponse
-> ListSignalingChannelsResponse -> Bool
== :: ListSignalingChannelsResponse
-> ListSignalingChannelsResponse -> Bool
$c== :: ListSignalingChannelsResponse
-> ListSignalingChannelsResponse -> Bool
Prelude.Eq, ReadPrec [ListSignalingChannelsResponse]
ReadPrec ListSignalingChannelsResponse
Int -> ReadS ListSignalingChannelsResponse
ReadS [ListSignalingChannelsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListSignalingChannelsResponse]
$creadListPrec :: ReadPrec [ListSignalingChannelsResponse]
readPrec :: ReadPrec ListSignalingChannelsResponse
$creadPrec :: ReadPrec ListSignalingChannelsResponse
readList :: ReadS [ListSignalingChannelsResponse]
$creadList :: ReadS [ListSignalingChannelsResponse]
readsPrec :: Int -> ReadS ListSignalingChannelsResponse
$creadsPrec :: Int -> ReadS ListSignalingChannelsResponse
Prelude.Read, Int -> ListSignalingChannelsResponse -> ShowS
[ListSignalingChannelsResponse] -> ShowS
ListSignalingChannelsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListSignalingChannelsResponse] -> ShowS
$cshowList :: [ListSignalingChannelsResponse] -> ShowS
show :: ListSignalingChannelsResponse -> String
$cshow :: ListSignalingChannelsResponse -> String
showsPrec :: Int -> ListSignalingChannelsResponse -> ShowS
$cshowsPrec :: Int -> ListSignalingChannelsResponse -> ShowS
Prelude.Show, forall x.
Rep ListSignalingChannelsResponse x
-> ListSignalingChannelsResponse
forall x.
ListSignalingChannelsResponse
-> Rep ListSignalingChannelsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListSignalingChannelsResponse x
-> ListSignalingChannelsResponse
$cfrom :: forall x.
ListSignalingChannelsResponse
-> Rep ListSignalingChannelsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListSignalingChannelsResponse' 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:
--
-- 'channelInfoList', 'listSignalingChannelsResponse_channelInfoList' - An array of @ChannelInfo@ objects.
--
-- 'nextToken', 'listSignalingChannelsResponse_nextToken' - If the response is truncated, the call returns this element with a
-- token. To get the next batch of streams, use this token in your next
-- request.
--
-- 'httpStatus', 'listSignalingChannelsResponse_httpStatus' - The response's http status code.
newListSignalingChannelsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListSignalingChannelsResponse
newListSignalingChannelsResponse :: Int -> ListSignalingChannelsResponse
newListSignalingChannelsResponse Int
pHttpStatus_ =
  ListSignalingChannelsResponse'
    { $sel:channelInfoList:ListSignalingChannelsResponse' :: Maybe [ChannelInfo]
channelInfoList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListSignalingChannelsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListSignalingChannelsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of @ChannelInfo@ objects.
listSignalingChannelsResponse_channelInfoList :: Lens.Lens' ListSignalingChannelsResponse (Prelude.Maybe [ChannelInfo])
listSignalingChannelsResponse_channelInfoList :: Lens' ListSignalingChannelsResponse (Maybe [ChannelInfo])
listSignalingChannelsResponse_channelInfoList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSignalingChannelsResponse' {Maybe [ChannelInfo]
channelInfoList :: Maybe [ChannelInfo]
$sel:channelInfoList:ListSignalingChannelsResponse' :: ListSignalingChannelsResponse -> Maybe [ChannelInfo]
channelInfoList} -> Maybe [ChannelInfo]
channelInfoList) (\s :: ListSignalingChannelsResponse
s@ListSignalingChannelsResponse' {} Maybe [ChannelInfo]
a -> ListSignalingChannelsResponse
s {$sel:channelInfoList:ListSignalingChannelsResponse' :: Maybe [ChannelInfo]
channelInfoList = Maybe [ChannelInfo]
a} :: ListSignalingChannelsResponse) 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

-- | If the response is truncated, the call returns this element with a
-- token. To get the next batch of streams, use this token in your next
-- request.
listSignalingChannelsResponse_nextToken :: Lens.Lens' ListSignalingChannelsResponse (Prelude.Maybe Prelude.Text)
listSignalingChannelsResponse_nextToken :: Lens' ListSignalingChannelsResponse (Maybe Text)
listSignalingChannelsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListSignalingChannelsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListSignalingChannelsResponse' :: ListSignalingChannelsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListSignalingChannelsResponse
s@ListSignalingChannelsResponse' {} Maybe Text
a -> ListSignalingChannelsResponse
s {$sel:nextToken:ListSignalingChannelsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListSignalingChannelsResponse)

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

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