{-# 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.Rekognition.ListStreamProcessors
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets a list of stream processors that you have created with
-- CreateStreamProcessor.
--
-- This operation returns paginated results.
module Amazonka.Rekognition.ListStreamProcessors
  ( -- * Creating a Request
    ListStreamProcessors (..),
    newListStreamProcessors,

    -- * Request Lenses
    listStreamProcessors_maxResults,
    listStreamProcessors_nextToken,

    -- * Destructuring the Response
    ListStreamProcessorsResponse (..),
    newListStreamProcessorsResponse,

    -- * Response Lenses
    listStreamProcessorsResponse_nextToken,
    listStreamProcessorsResponse_streamProcessors,
    listStreamProcessorsResponse_httpStatus,
  )
where

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 Amazonka.Rekognition.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListStreamProcessors' smart constructor.
data ListStreamProcessors = ListStreamProcessors'
  { -- | Maximum number of stream processors you want Amazon Rekognition Video to
    -- return in the response. The default is 1000.
    ListStreamProcessors -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If the previous response was incomplete (because there are more stream
    -- processors to retrieve), Amazon Rekognition Video returns a pagination
    -- token in the response. You can use this pagination token to retrieve the
    -- next set of stream processors.
    ListStreamProcessors -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListStreamProcessors -> ListStreamProcessors -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListStreamProcessors -> ListStreamProcessors -> Bool
$c/= :: ListStreamProcessors -> ListStreamProcessors -> Bool
== :: ListStreamProcessors -> ListStreamProcessors -> Bool
$c== :: ListStreamProcessors -> ListStreamProcessors -> Bool
Prelude.Eq, ReadPrec [ListStreamProcessors]
ReadPrec ListStreamProcessors
Int -> ReadS ListStreamProcessors
ReadS [ListStreamProcessors]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListStreamProcessors]
$creadListPrec :: ReadPrec [ListStreamProcessors]
readPrec :: ReadPrec ListStreamProcessors
$creadPrec :: ReadPrec ListStreamProcessors
readList :: ReadS [ListStreamProcessors]
$creadList :: ReadS [ListStreamProcessors]
readsPrec :: Int -> ReadS ListStreamProcessors
$creadsPrec :: Int -> ReadS ListStreamProcessors
Prelude.Read, Int -> ListStreamProcessors -> ShowS
[ListStreamProcessors] -> ShowS
ListStreamProcessors -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListStreamProcessors] -> ShowS
$cshowList :: [ListStreamProcessors] -> ShowS
show :: ListStreamProcessors -> String
$cshow :: ListStreamProcessors -> String
showsPrec :: Int -> ListStreamProcessors -> ShowS
$cshowsPrec :: Int -> ListStreamProcessors -> ShowS
Prelude.Show, forall x. Rep ListStreamProcessors x -> ListStreamProcessors
forall x. ListStreamProcessors -> Rep ListStreamProcessors x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListStreamProcessors x -> ListStreamProcessors
$cfrom :: forall x. ListStreamProcessors -> Rep ListStreamProcessors x
Prelude.Generic)

-- |
-- Create a value of 'ListStreamProcessors' 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', 'listStreamProcessors_maxResults' - Maximum number of stream processors you want Amazon Rekognition Video to
-- return in the response. The default is 1000.
--
-- 'nextToken', 'listStreamProcessors_nextToken' - If the previous response was incomplete (because there are more stream
-- processors to retrieve), Amazon Rekognition Video returns a pagination
-- token in the response. You can use this pagination token to retrieve the
-- next set of stream processors.
newListStreamProcessors ::
  ListStreamProcessors
newListStreamProcessors :: ListStreamProcessors
newListStreamProcessors =
  ListStreamProcessors'
    { $sel:maxResults:ListStreamProcessors' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListStreamProcessors' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | Maximum number of stream processors you want Amazon Rekognition Video to
-- return in the response. The default is 1000.
listStreamProcessors_maxResults :: Lens.Lens' ListStreamProcessors (Prelude.Maybe Prelude.Natural)
listStreamProcessors_maxResults :: Lens' ListStreamProcessors (Maybe Natural)
listStreamProcessors_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStreamProcessors' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListStreamProcessors' :: ListStreamProcessors -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListStreamProcessors
s@ListStreamProcessors' {} Maybe Natural
a -> ListStreamProcessors
s {$sel:maxResults:ListStreamProcessors' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListStreamProcessors)

-- | If the previous response was incomplete (because there are more stream
-- processors to retrieve), Amazon Rekognition Video returns a pagination
-- token in the response. You can use this pagination token to retrieve the
-- next set of stream processors.
listStreamProcessors_nextToken :: Lens.Lens' ListStreamProcessors (Prelude.Maybe Prelude.Text)
listStreamProcessors_nextToken :: Lens' ListStreamProcessors (Maybe Text)
listStreamProcessors_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStreamProcessors' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListStreamProcessors' :: ListStreamProcessors -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListStreamProcessors
s@ListStreamProcessors' {} Maybe Text
a -> ListStreamProcessors
s {$sel:nextToken:ListStreamProcessors' :: Maybe Text
nextToken = Maybe Text
a} :: ListStreamProcessors)

instance Core.AWSPager ListStreamProcessors where
  page :: ListStreamProcessors
-> AWSResponse ListStreamProcessors -> Maybe ListStreamProcessors
page ListStreamProcessors
rq AWSResponse ListStreamProcessors
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListStreamProcessors
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListStreamProcessorsResponse (Maybe Text)
listStreamProcessorsResponse_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 ListStreamProcessors
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListStreamProcessorsResponse (Maybe [StreamProcessor])
listStreamProcessorsResponse_streamProcessors
            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.$ ListStreamProcessors
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListStreamProcessors (Maybe Text)
listStreamProcessors_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListStreamProcessors
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListStreamProcessorsResponse (Maybe Text)
listStreamProcessorsResponse_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 ListStreamProcessors where
  type
    AWSResponse ListStreamProcessors =
      ListStreamProcessorsResponse
  request :: (Service -> Service)
-> ListStreamProcessors -> Request ListStreamProcessors
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 ListStreamProcessors
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListStreamProcessors)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe [StreamProcessor] -> Int -> ListStreamProcessorsResponse
ListStreamProcessorsResponse'
            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
"NextToken")
            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
"StreamProcessors"
                            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ListStreamProcessors where
  hashWithSalt :: Int -> ListStreamProcessors -> Int
hashWithSalt Int
_salt ListStreamProcessors' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListStreamProcessors' :: ListStreamProcessors -> Maybe Text
$sel:maxResults:ListStreamProcessors' :: ListStreamProcessors -> 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 Text
nextToken

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

instance Data.ToHeaders ListStreamProcessors where
  toHeaders :: ListStreamProcessors -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"RekognitionService.ListStreamProcessors" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON ListStreamProcessors where
  toJSON :: ListStreamProcessors -> Value
toJSON ListStreamProcessors' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListStreamProcessors' :: ListStreamProcessors -> Maybe Text
$sel:maxResults:ListStreamProcessors' :: ListStreamProcessors -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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 ListStreamProcessors where
  toPath :: ListStreamProcessors -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newListStreamProcessorsResponse' smart constructor.
data ListStreamProcessorsResponse = ListStreamProcessorsResponse'
  { -- | If the response is truncated, Amazon Rekognition Video returns this
    -- token that you can use in the subsequent request to retrieve the next
    -- set of stream processors.
    ListStreamProcessorsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | List of stream processors that you have created.
    ListStreamProcessorsResponse -> Maybe [StreamProcessor]
streamProcessors :: Prelude.Maybe [StreamProcessor],
    -- | The response's http status code.
    ListStreamProcessorsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListStreamProcessorsResponse
-> ListStreamProcessorsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListStreamProcessorsResponse
-> ListStreamProcessorsResponse -> Bool
$c/= :: ListStreamProcessorsResponse
-> ListStreamProcessorsResponse -> Bool
== :: ListStreamProcessorsResponse
-> ListStreamProcessorsResponse -> Bool
$c== :: ListStreamProcessorsResponse
-> ListStreamProcessorsResponse -> Bool
Prelude.Eq, ReadPrec [ListStreamProcessorsResponse]
ReadPrec ListStreamProcessorsResponse
Int -> ReadS ListStreamProcessorsResponse
ReadS [ListStreamProcessorsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListStreamProcessorsResponse]
$creadListPrec :: ReadPrec [ListStreamProcessorsResponse]
readPrec :: ReadPrec ListStreamProcessorsResponse
$creadPrec :: ReadPrec ListStreamProcessorsResponse
readList :: ReadS [ListStreamProcessorsResponse]
$creadList :: ReadS [ListStreamProcessorsResponse]
readsPrec :: Int -> ReadS ListStreamProcessorsResponse
$creadsPrec :: Int -> ReadS ListStreamProcessorsResponse
Prelude.Read, Int -> ListStreamProcessorsResponse -> ShowS
[ListStreamProcessorsResponse] -> ShowS
ListStreamProcessorsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListStreamProcessorsResponse] -> ShowS
$cshowList :: [ListStreamProcessorsResponse] -> ShowS
show :: ListStreamProcessorsResponse -> String
$cshow :: ListStreamProcessorsResponse -> String
showsPrec :: Int -> ListStreamProcessorsResponse -> ShowS
$cshowsPrec :: Int -> ListStreamProcessorsResponse -> ShowS
Prelude.Show, forall x.
Rep ListStreamProcessorsResponse x -> ListStreamProcessorsResponse
forall x.
ListStreamProcessorsResponse -> Rep ListStreamProcessorsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListStreamProcessorsResponse x -> ListStreamProcessorsResponse
$cfrom :: forall x.
ListStreamProcessorsResponse -> Rep ListStreamProcessorsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListStreamProcessorsResponse' 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:
--
-- 'nextToken', 'listStreamProcessorsResponse_nextToken' - If the response is truncated, Amazon Rekognition Video returns this
-- token that you can use in the subsequent request to retrieve the next
-- set of stream processors.
--
-- 'streamProcessors', 'listStreamProcessorsResponse_streamProcessors' - List of stream processors that you have created.
--
-- 'httpStatus', 'listStreamProcessorsResponse_httpStatus' - The response's http status code.
newListStreamProcessorsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListStreamProcessorsResponse
newListStreamProcessorsResponse :: Int -> ListStreamProcessorsResponse
newListStreamProcessorsResponse Int
pHttpStatus_ =
  ListStreamProcessorsResponse'
    { $sel:nextToken:ListStreamProcessorsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:streamProcessors:ListStreamProcessorsResponse' :: Maybe [StreamProcessor]
streamProcessors = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListStreamProcessorsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | If the response is truncated, Amazon Rekognition Video returns this
-- token that you can use in the subsequent request to retrieve the next
-- set of stream processors.
listStreamProcessorsResponse_nextToken :: Lens.Lens' ListStreamProcessorsResponse (Prelude.Maybe Prelude.Text)
listStreamProcessorsResponse_nextToken :: Lens' ListStreamProcessorsResponse (Maybe Text)
listStreamProcessorsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStreamProcessorsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListStreamProcessorsResponse' :: ListStreamProcessorsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListStreamProcessorsResponse
s@ListStreamProcessorsResponse' {} Maybe Text
a -> ListStreamProcessorsResponse
s {$sel:nextToken:ListStreamProcessorsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListStreamProcessorsResponse)

-- | List of stream processors that you have created.
listStreamProcessorsResponse_streamProcessors :: Lens.Lens' ListStreamProcessorsResponse (Prelude.Maybe [StreamProcessor])
listStreamProcessorsResponse_streamProcessors :: Lens' ListStreamProcessorsResponse (Maybe [StreamProcessor])
listStreamProcessorsResponse_streamProcessors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStreamProcessorsResponse' {Maybe [StreamProcessor]
streamProcessors :: Maybe [StreamProcessor]
$sel:streamProcessors:ListStreamProcessorsResponse' :: ListStreamProcessorsResponse -> Maybe [StreamProcessor]
streamProcessors} -> Maybe [StreamProcessor]
streamProcessors) (\s :: ListStreamProcessorsResponse
s@ListStreamProcessorsResponse' {} Maybe [StreamProcessor]
a -> ListStreamProcessorsResponse
s {$sel:streamProcessors:ListStreamProcessorsResponse' :: Maybe [StreamProcessor]
streamProcessors = Maybe [StreamProcessor]
a} :: ListStreamProcessorsResponse) 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 response's http status code.
listStreamProcessorsResponse_httpStatus :: Lens.Lens' ListStreamProcessorsResponse Prelude.Int
listStreamProcessorsResponse_httpStatus :: Lens' ListStreamProcessorsResponse Int
listStreamProcessorsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStreamProcessorsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListStreamProcessorsResponse' :: ListStreamProcessorsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListStreamProcessorsResponse
s@ListStreamProcessorsResponse' {} Int
a -> ListStreamProcessorsResponse
s {$sel:httpStatus:ListStreamProcessorsResponse' :: Int
httpStatus = Int
a} :: ListStreamProcessorsResponse)

instance Prelude.NFData ListStreamProcessorsResponse where
  rnf :: ListStreamProcessorsResponse -> ()
rnf ListStreamProcessorsResponse' {Int
Maybe [StreamProcessor]
Maybe Text
httpStatus :: Int
streamProcessors :: Maybe [StreamProcessor]
nextToken :: Maybe Text
$sel:httpStatus:ListStreamProcessorsResponse' :: ListStreamProcessorsResponse -> Int
$sel:streamProcessors:ListStreamProcessorsResponse' :: ListStreamProcessorsResponse -> Maybe [StreamProcessor]
$sel:nextToken:ListStreamProcessorsResponse' :: ListStreamProcessorsResponse -> Maybe Text
..} =
    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 Maybe [StreamProcessor]
streamProcessors
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus