{-# 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.IVS.ListStreamKeys
-- 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 summary information about stream keys for the specified channel.
--
-- This operation returns paginated results.
module Amazonka.IVS.ListStreamKeys
  ( -- * Creating a Request
    ListStreamKeys (..),
    newListStreamKeys,

    -- * Request Lenses
    listStreamKeys_maxResults,
    listStreamKeys_nextToken,
    listStreamKeys_channelArn,

    -- * Destructuring the Response
    ListStreamKeysResponse (..),
    newListStreamKeysResponse,

    -- * Response Lenses
    listStreamKeysResponse_nextToken,
    listStreamKeysResponse_httpStatus,
    listStreamKeysResponse_streamKeys,
  )
where

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

-- | /See:/ 'newListStreamKeys' smart constructor.
data ListStreamKeys = ListStreamKeys'
  { -- | Maximum number of streamKeys to return. Default: 1.
    ListStreamKeys -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The first stream key to retrieve. This is used for pagination; see the
    -- @nextToken@ response field.
    ListStreamKeys -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Channel ARN used to filter the list.
    ListStreamKeys -> Text
channelArn :: Prelude.Text
  }
  deriving (ListStreamKeys -> ListStreamKeys -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListStreamKeys -> ListStreamKeys -> Bool
$c/= :: ListStreamKeys -> ListStreamKeys -> Bool
== :: ListStreamKeys -> ListStreamKeys -> Bool
$c== :: ListStreamKeys -> ListStreamKeys -> Bool
Prelude.Eq, ReadPrec [ListStreamKeys]
ReadPrec ListStreamKeys
Int -> ReadS ListStreamKeys
ReadS [ListStreamKeys]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListStreamKeys]
$creadListPrec :: ReadPrec [ListStreamKeys]
readPrec :: ReadPrec ListStreamKeys
$creadPrec :: ReadPrec ListStreamKeys
readList :: ReadS [ListStreamKeys]
$creadList :: ReadS [ListStreamKeys]
readsPrec :: Int -> ReadS ListStreamKeys
$creadsPrec :: Int -> ReadS ListStreamKeys
Prelude.Read, Int -> ListStreamKeys -> ShowS
[ListStreamKeys] -> ShowS
ListStreamKeys -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListStreamKeys] -> ShowS
$cshowList :: [ListStreamKeys] -> ShowS
show :: ListStreamKeys -> String
$cshow :: ListStreamKeys -> String
showsPrec :: Int -> ListStreamKeys -> ShowS
$cshowsPrec :: Int -> ListStreamKeys -> ShowS
Prelude.Show, forall x. Rep ListStreamKeys x -> ListStreamKeys
forall x. ListStreamKeys -> Rep ListStreamKeys x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListStreamKeys x -> ListStreamKeys
$cfrom :: forall x. ListStreamKeys -> Rep ListStreamKeys x
Prelude.Generic)

-- |
-- Create a value of 'ListStreamKeys' 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', 'listStreamKeys_maxResults' - Maximum number of streamKeys to return. Default: 1.
--
-- 'nextToken', 'listStreamKeys_nextToken' - The first stream key to retrieve. This is used for pagination; see the
-- @nextToken@ response field.
--
-- 'channelArn', 'listStreamKeys_channelArn' - Channel ARN used to filter the list.
newListStreamKeys ::
  -- | 'channelArn'
  Prelude.Text ->
  ListStreamKeys
newListStreamKeys :: Text -> ListStreamKeys
newListStreamKeys Text
pChannelArn_ =
  ListStreamKeys'
    { $sel:maxResults:ListStreamKeys' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListStreamKeys' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:channelArn:ListStreamKeys' :: Text
channelArn = Text
pChannelArn_
    }

-- | Maximum number of streamKeys to return. Default: 1.
listStreamKeys_maxResults :: Lens.Lens' ListStreamKeys (Prelude.Maybe Prelude.Natural)
listStreamKeys_maxResults :: Lens' ListStreamKeys (Maybe Natural)
listStreamKeys_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStreamKeys' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListStreamKeys' :: ListStreamKeys -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListStreamKeys
s@ListStreamKeys' {} Maybe Natural
a -> ListStreamKeys
s {$sel:maxResults:ListStreamKeys' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListStreamKeys)

-- | The first stream key to retrieve. This is used for pagination; see the
-- @nextToken@ response field.
listStreamKeys_nextToken :: Lens.Lens' ListStreamKeys (Prelude.Maybe Prelude.Text)
listStreamKeys_nextToken :: Lens' ListStreamKeys (Maybe Text)
listStreamKeys_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStreamKeys' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListStreamKeys' :: ListStreamKeys -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListStreamKeys
s@ListStreamKeys' {} Maybe Text
a -> ListStreamKeys
s {$sel:nextToken:ListStreamKeys' :: Maybe Text
nextToken = Maybe Text
a} :: ListStreamKeys)

-- | Channel ARN used to filter the list.
listStreamKeys_channelArn :: Lens.Lens' ListStreamKeys Prelude.Text
listStreamKeys_channelArn :: Lens' ListStreamKeys Text
listStreamKeys_channelArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStreamKeys' {Text
channelArn :: Text
$sel:channelArn:ListStreamKeys' :: ListStreamKeys -> Text
channelArn} -> Text
channelArn) (\s :: ListStreamKeys
s@ListStreamKeys' {} Text
a -> ListStreamKeys
s {$sel:channelArn:ListStreamKeys' :: Text
channelArn = Text
a} :: ListStreamKeys)

instance Core.AWSPager ListStreamKeys where
  page :: ListStreamKeys
-> AWSResponse ListStreamKeys -> Maybe ListStreamKeys
page ListStreamKeys
rq AWSResponse ListStreamKeys
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListStreamKeys
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListStreamKeysResponse (Maybe Text)
listStreamKeysResponse_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 ListStreamKeys
rs forall s a. s -> Getting a s a -> a
Lens.^. Lens' ListStreamKeysResponse [StreamKeySummary]
listStreamKeysResponse_streamKeys) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListStreamKeys
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListStreamKeys (Maybe Text)
listStreamKeys_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListStreamKeys
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListStreamKeysResponse (Maybe Text)
listStreamKeysResponse_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 ListStreamKeys where
  type
    AWSResponse ListStreamKeys =
      ListStreamKeysResponse
  request :: (Service -> Service) -> ListStreamKeys -> Request ListStreamKeys
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 ListStreamKeys
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListStreamKeys)))
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 -> Int -> [StreamKeySummary] -> ListStreamKeysResponse
ListStreamKeysResponse'
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            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
"streamKeys" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable ListStreamKeys where
  hashWithSalt :: Int -> ListStreamKeys -> Int
hashWithSalt Int
_salt ListStreamKeys' {Maybe Natural
Maybe Text
Text
channelArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:channelArn:ListStreamKeys' :: ListStreamKeys -> Text
$sel:nextToken:ListStreamKeys' :: ListStreamKeys -> Maybe Text
$sel:maxResults:ListStreamKeys' :: ListStreamKeys -> 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
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
channelArn

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

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

instance Data.ToJSON ListStreamKeys where
  toJSON :: ListStreamKeys -> Value
toJSON ListStreamKeys' {Maybe Natural
Maybe Text
Text
channelArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:channelArn:ListStreamKeys' :: ListStreamKeys -> Text
$sel:nextToken:ListStreamKeys' :: ListStreamKeys -> Maybe Text
$sel:maxResults:ListStreamKeys' :: ListStreamKeys -> 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,
            forall a. a -> Maybe a
Prelude.Just (Key
"channelArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
channelArn)
          ]
      )

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

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

-- | /See:/ 'newListStreamKeysResponse' smart constructor.
data ListStreamKeysResponse = ListStreamKeysResponse'
  { -- | If there are more stream keys than @maxResults@, use @nextToken@ in the
    -- request to get the next set.
    ListStreamKeysResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListStreamKeysResponse -> Int
httpStatus :: Prelude.Int,
    -- | List of stream keys.
    ListStreamKeysResponse -> [StreamKeySummary]
streamKeys :: [StreamKeySummary]
  }
  deriving (ListStreamKeysResponse -> ListStreamKeysResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListStreamKeysResponse -> ListStreamKeysResponse -> Bool
$c/= :: ListStreamKeysResponse -> ListStreamKeysResponse -> Bool
== :: ListStreamKeysResponse -> ListStreamKeysResponse -> Bool
$c== :: ListStreamKeysResponse -> ListStreamKeysResponse -> Bool
Prelude.Eq, ReadPrec [ListStreamKeysResponse]
ReadPrec ListStreamKeysResponse
Int -> ReadS ListStreamKeysResponse
ReadS [ListStreamKeysResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListStreamKeysResponse]
$creadListPrec :: ReadPrec [ListStreamKeysResponse]
readPrec :: ReadPrec ListStreamKeysResponse
$creadPrec :: ReadPrec ListStreamKeysResponse
readList :: ReadS [ListStreamKeysResponse]
$creadList :: ReadS [ListStreamKeysResponse]
readsPrec :: Int -> ReadS ListStreamKeysResponse
$creadsPrec :: Int -> ReadS ListStreamKeysResponse
Prelude.Read, Int -> ListStreamKeysResponse -> ShowS
[ListStreamKeysResponse] -> ShowS
ListStreamKeysResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListStreamKeysResponse] -> ShowS
$cshowList :: [ListStreamKeysResponse] -> ShowS
show :: ListStreamKeysResponse -> String
$cshow :: ListStreamKeysResponse -> String
showsPrec :: Int -> ListStreamKeysResponse -> ShowS
$cshowsPrec :: Int -> ListStreamKeysResponse -> ShowS
Prelude.Show, forall x. Rep ListStreamKeysResponse x -> ListStreamKeysResponse
forall x. ListStreamKeysResponse -> Rep ListStreamKeysResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListStreamKeysResponse x -> ListStreamKeysResponse
$cfrom :: forall x. ListStreamKeysResponse -> Rep ListStreamKeysResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListStreamKeysResponse' 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', 'listStreamKeysResponse_nextToken' - If there are more stream keys than @maxResults@, use @nextToken@ in the
-- request to get the next set.
--
-- 'httpStatus', 'listStreamKeysResponse_httpStatus' - The response's http status code.
--
-- 'streamKeys', 'listStreamKeysResponse_streamKeys' - List of stream keys.
newListStreamKeysResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListStreamKeysResponse
newListStreamKeysResponse :: Int -> ListStreamKeysResponse
newListStreamKeysResponse Int
pHttpStatus_ =
  ListStreamKeysResponse'
    { $sel:nextToken:ListStreamKeysResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListStreamKeysResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:streamKeys:ListStreamKeysResponse' :: [StreamKeySummary]
streamKeys = forall a. Monoid a => a
Prelude.mempty
    }

-- | If there are more stream keys than @maxResults@, use @nextToken@ in the
-- request to get the next set.
listStreamKeysResponse_nextToken :: Lens.Lens' ListStreamKeysResponse (Prelude.Maybe Prelude.Text)
listStreamKeysResponse_nextToken :: Lens' ListStreamKeysResponse (Maybe Text)
listStreamKeysResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStreamKeysResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListStreamKeysResponse' :: ListStreamKeysResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListStreamKeysResponse
s@ListStreamKeysResponse' {} Maybe Text
a -> ListStreamKeysResponse
s {$sel:nextToken:ListStreamKeysResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListStreamKeysResponse)

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

-- | List of stream keys.
listStreamKeysResponse_streamKeys :: Lens.Lens' ListStreamKeysResponse [StreamKeySummary]
listStreamKeysResponse_streamKeys :: Lens' ListStreamKeysResponse [StreamKeySummary]
listStreamKeysResponse_streamKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListStreamKeysResponse' {[StreamKeySummary]
streamKeys :: [StreamKeySummary]
$sel:streamKeys:ListStreamKeysResponse' :: ListStreamKeysResponse -> [StreamKeySummary]
streamKeys} -> [StreamKeySummary]
streamKeys) (\s :: ListStreamKeysResponse
s@ListStreamKeysResponse' {} [StreamKeySummary]
a -> ListStreamKeysResponse
s {$sel:streamKeys:ListStreamKeysResponse' :: [StreamKeySummary]
streamKeys = [StreamKeySummary]
a} :: ListStreamKeysResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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