{-# 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.Kinesis.DescribeStream
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the specified Kinesis data stream.
--
-- This API has been revised. It\'s highly recommended that you use the
-- DescribeStreamSummary API to get a summarized description of the
-- specified Kinesis data stream and the ListShards API to list the shards
-- in a specified data stream and obtain information about each shard.
--
-- When invoking this API, it is recommended you use the @StreamARN@ input
-- parameter rather than the @StreamName@ input parameter.
--
-- The information returned includes the stream name, Amazon Resource Name
-- (ARN), creation time, enhanced metric configuration, and shard map. The
-- shard map is an array of shard objects. For each shard object, there is
-- the hash key and sequence number ranges that the shard spans, and the
-- IDs of any earlier shards that played in a role in creating the shard.
-- Every record ingested in the stream is identified by a sequence number,
-- which is assigned when the record is put into the stream.
--
-- You can limit the number of shards returned by each call. For more
-- information, see
-- <https://docs.aws.amazon.com/kinesis/latest/dev/kinesis-using-sdk-java-retrieve-shards.html Retrieving Shards from a Stream>
-- in the /Amazon Kinesis Data Streams Developer Guide/.
--
-- There are no guarantees about the chronological order shards returned.
-- To process shards in chronological order, use the ID of the parent shard
-- to track the lineage to the oldest shard.
--
-- This operation has a limit of 10 transactions per second per account.
--
-- This operation returns paginated results.
module Amazonka.Kinesis.DescribeStream
  ( -- * Creating a Request
    DescribeStream (..),
    newDescribeStream,

    -- * Request Lenses
    describeStream_exclusiveStartShardId,
    describeStream_limit,
    describeStream_streamARN,
    describeStream_streamName,

    -- * Destructuring the Response
    DescribeStreamResponse (..),
    newDescribeStreamResponse,

    -- * Response Lenses
    describeStreamResponse_httpStatus,
    describeStreamResponse_streamDescription,
  )
where

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

-- | Represents the input for @DescribeStream@.
--
-- /See:/ 'newDescribeStream' smart constructor.
data DescribeStream = DescribeStream'
  { -- | The shard ID of the shard to start with.
    --
    -- Specify this parameter to indicate that you want to describe the stream
    -- starting with the shard whose ID immediately follows
    -- @ExclusiveStartShardId@.
    --
    -- If you don\'t specify this parameter, the default behavior for
    -- @DescribeStream@ is to describe the stream starting with the first shard
    -- in the stream.
    DescribeStream -> Maybe Text
exclusiveStartShardId :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of shards to return in a single call. The default
    -- value is 100. If you specify a value greater than 100, at most 100
    -- results are returned.
    DescribeStream -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | The ARN of the stream.
    DescribeStream -> Maybe Text
streamARN :: Prelude.Maybe Prelude.Text,
    -- | The name of the stream to describe.
    DescribeStream -> Maybe Text
streamName :: Prelude.Maybe Prelude.Text
  }
  deriving (DescribeStream -> DescribeStream -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeStream -> DescribeStream -> Bool
$c/= :: DescribeStream -> DescribeStream -> Bool
== :: DescribeStream -> DescribeStream -> Bool
$c== :: DescribeStream -> DescribeStream -> Bool
Prelude.Eq, ReadPrec [DescribeStream]
ReadPrec DescribeStream
Int -> ReadS DescribeStream
ReadS [DescribeStream]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeStream]
$creadListPrec :: ReadPrec [DescribeStream]
readPrec :: ReadPrec DescribeStream
$creadPrec :: ReadPrec DescribeStream
readList :: ReadS [DescribeStream]
$creadList :: ReadS [DescribeStream]
readsPrec :: Int -> ReadS DescribeStream
$creadsPrec :: Int -> ReadS DescribeStream
Prelude.Read, Int -> DescribeStream -> ShowS
[DescribeStream] -> ShowS
DescribeStream -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeStream] -> ShowS
$cshowList :: [DescribeStream] -> ShowS
show :: DescribeStream -> String
$cshow :: DescribeStream -> String
showsPrec :: Int -> DescribeStream -> ShowS
$cshowsPrec :: Int -> DescribeStream -> ShowS
Prelude.Show, forall x. Rep DescribeStream x -> DescribeStream
forall x. DescribeStream -> Rep DescribeStream x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeStream x -> DescribeStream
$cfrom :: forall x. DescribeStream -> Rep DescribeStream x
Prelude.Generic)

-- |
-- Create a value of 'DescribeStream' 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:
--
-- 'exclusiveStartShardId', 'describeStream_exclusiveStartShardId' - The shard ID of the shard to start with.
--
-- Specify this parameter to indicate that you want to describe the stream
-- starting with the shard whose ID immediately follows
-- @ExclusiveStartShardId@.
--
-- If you don\'t specify this parameter, the default behavior for
-- @DescribeStream@ is to describe the stream starting with the first shard
-- in the stream.
--
-- 'limit', 'describeStream_limit' - The maximum number of shards to return in a single call. The default
-- value is 100. If you specify a value greater than 100, at most 100
-- results are returned.
--
-- 'streamARN', 'describeStream_streamARN' - The ARN of the stream.
--
-- 'streamName', 'describeStream_streamName' - The name of the stream to describe.
newDescribeStream ::
  DescribeStream
newDescribeStream :: DescribeStream
newDescribeStream =
  DescribeStream'
    { $sel:exclusiveStartShardId:DescribeStream' :: Maybe Text
exclusiveStartShardId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:limit:DescribeStream' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:streamARN:DescribeStream' :: Maybe Text
streamARN = forall a. Maybe a
Prelude.Nothing,
      $sel:streamName:DescribeStream' :: Maybe Text
streamName = forall a. Maybe a
Prelude.Nothing
    }

-- | The shard ID of the shard to start with.
--
-- Specify this parameter to indicate that you want to describe the stream
-- starting with the shard whose ID immediately follows
-- @ExclusiveStartShardId@.
--
-- If you don\'t specify this parameter, the default behavior for
-- @DescribeStream@ is to describe the stream starting with the first shard
-- in the stream.
describeStream_exclusiveStartShardId :: Lens.Lens' DescribeStream (Prelude.Maybe Prelude.Text)
describeStream_exclusiveStartShardId :: Lens' DescribeStream (Maybe Text)
describeStream_exclusiveStartShardId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStream' {Maybe Text
exclusiveStartShardId :: Maybe Text
$sel:exclusiveStartShardId:DescribeStream' :: DescribeStream -> Maybe Text
exclusiveStartShardId} -> Maybe Text
exclusiveStartShardId) (\s :: DescribeStream
s@DescribeStream' {} Maybe Text
a -> DescribeStream
s {$sel:exclusiveStartShardId:DescribeStream' :: Maybe Text
exclusiveStartShardId = Maybe Text
a} :: DescribeStream)

-- | The maximum number of shards to return in a single call. The default
-- value is 100. If you specify a value greater than 100, at most 100
-- results are returned.
describeStream_limit :: Lens.Lens' DescribeStream (Prelude.Maybe Prelude.Natural)
describeStream_limit :: Lens' DescribeStream (Maybe Natural)
describeStream_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStream' {Maybe Natural
limit :: Maybe Natural
$sel:limit:DescribeStream' :: DescribeStream -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: DescribeStream
s@DescribeStream' {} Maybe Natural
a -> DescribeStream
s {$sel:limit:DescribeStream' :: Maybe Natural
limit = Maybe Natural
a} :: DescribeStream)

-- | The ARN of the stream.
describeStream_streamARN :: Lens.Lens' DescribeStream (Prelude.Maybe Prelude.Text)
describeStream_streamARN :: Lens' DescribeStream (Maybe Text)
describeStream_streamARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStream' {Maybe Text
streamARN :: Maybe Text
$sel:streamARN:DescribeStream' :: DescribeStream -> Maybe Text
streamARN} -> Maybe Text
streamARN) (\s :: DescribeStream
s@DescribeStream' {} Maybe Text
a -> DescribeStream
s {$sel:streamARN:DescribeStream' :: Maybe Text
streamARN = Maybe Text
a} :: DescribeStream)

-- | The name of the stream to describe.
describeStream_streamName :: Lens.Lens' DescribeStream (Prelude.Maybe Prelude.Text)
describeStream_streamName :: Lens' DescribeStream (Maybe Text)
describeStream_streamName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStream' {Maybe Text
streamName :: Maybe Text
$sel:streamName:DescribeStream' :: DescribeStream -> Maybe Text
streamName} -> Maybe Text
streamName) (\s :: DescribeStream
s@DescribeStream' {} Maybe Text
a -> DescribeStream
s {$sel:streamName:DescribeStream' :: Maybe Text
streamName = Maybe Text
a} :: DescribeStream)

instance Core.AWSPager DescribeStream where
  page :: DescribeStream
-> AWSResponse DescribeStream -> Maybe DescribeStream
page DescribeStream
rq AWSResponse DescribeStream
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeStream
rs
            forall s a. s -> Getting a s a -> a
Lens.^. Lens' DescribeStreamResponse StreamDescription
describeStreamResponse_streamDescription
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' StreamDescription Bool
streamDescription_hasMoreShards
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. Maybe a -> Bool
Prelude.isNothing
        ( AWSResponse DescribeStream
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeStreamResponse StreamDescription
describeStreamResponse_streamDescription
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' StreamDescription [Shard]
streamDescription_shards
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s a. Snoc s s a a => Traversal' s a
Lens._last
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' Shard Text
shard_shardId
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ DescribeStream
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeStream (Maybe Text)
describeStream_exclusiveStartShardId
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeStream
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeStreamResponse StreamDescription
describeStreamResponse_streamDescription
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' StreamDescription [Shard]
streamDescription_shards
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s a. Snoc s s a a => Traversal' s a
Lens._last
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Lens' Shard Text
shard_shardId

instance Core.AWSRequest DescribeStream where
  type
    AWSResponse DescribeStream =
      DescribeStreamResponse
  request :: (Service -> Service) -> DescribeStream -> Request DescribeStream
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 DescribeStream
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeStream)))
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 ->
          Int -> StreamDescription -> DescribeStreamResponse
DescribeStreamResponse'
            forall (f :: * -> *) a b. Functor 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 a
Data..:> Key
"StreamDescription")
      )

instance Prelude.Hashable DescribeStream where
  hashWithSalt :: Int -> DescribeStream -> Int
hashWithSalt Int
_salt DescribeStream' {Maybe Natural
Maybe Text
streamName :: Maybe Text
streamARN :: Maybe Text
limit :: Maybe Natural
exclusiveStartShardId :: Maybe Text
$sel:streamName:DescribeStream' :: DescribeStream -> Maybe Text
$sel:streamARN:DescribeStream' :: DescribeStream -> Maybe Text
$sel:limit:DescribeStream' :: DescribeStream -> Maybe Natural
$sel:exclusiveStartShardId:DescribeStream' :: DescribeStream -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
exclusiveStartShardId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
streamARN
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
streamName

instance Prelude.NFData DescribeStream where
  rnf :: DescribeStream -> ()
rnf DescribeStream' {Maybe Natural
Maybe Text
streamName :: Maybe Text
streamARN :: Maybe Text
limit :: Maybe Natural
exclusiveStartShardId :: Maybe Text
$sel:streamName:DescribeStream' :: DescribeStream -> Maybe Text
$sel:streamARN:DescribeStream' :: DescribeStream -> Maybe Text
$sel:limit:DescribeStream' :: DescribeStream -> Maybe Natural
$sel:exclusiveStartShardId:DescribeStream' :: DescribeStream -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
exclusiveStartShardId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
streamARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
streamName

instance Data.ToHeaders DescribeStream where
  toHeaders :: DescribeStream -> 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
"Kinesis_20131202.DescribeStream" ::
                          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 DescribeStream where
  toJSON :: DescribeStream -> Value
toJSON DescribeStream' {Maybe Natural
Maybe Text
streamName :: Maybe Text
streamARN :: Maybe Text
limit :: Maybe Natural
exclusiveStartShardId :: Maybe Text
$sel:streamName:DescribeStream' :: DescribeStream -> Maybe Text
$sel:streamARN:DescribeStream' :: DescribeStream -> Maybe Text
$sel:limit:DescribeStream' :: DescribeStream -> Maybe Natural
$sel:exclusiveStartShardId:DescribeStream' :: DescribeStream -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ExclusiveStartShardId" 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
exclusiveStartShardId,
            (Key
"Limit" 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
limit,
            (Key
"StreamARN" 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
streamARN,
            (Key
"StreamName" 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
streamName
          ]
      )

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

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

-- | Represents the output for @DescribeStream@.
--
-- /See:/ 'newDescribeStreamResponse' smart constructor.
data DescribeStreamResponse = DescribeStreamResponse'
  { -- | The response's http status code.
    DescribeStreamResponse -> Int
httpStatus :: Prelude.Int,
    -- | The current status of the stream, the stream Amazon Resource Name (ARN),
    -- an array of shard objects that comprise the stream, and whether there
    -- are more shards available.
    DescribeStreamResponse -> StreamDescription
streamDescription :: StreamDescription
  }
  deriving (DescribeStreamResponse -> DescribeStreamResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeStreamResponse -> DescribeStreamResponse -> Bool
$c/= :: DescribeStreamResponse -> DescribeStreamResponse -> Bool
== :: DescribeStreamResponse -> DescribeStreamResponse -> Bool
$c== :: DescribeStreamResponse -> DescribeStreamResponse -> Bool
Prelude.Eq, ReadPrec [DescribeStreamResponse]
ReadPrec DescribeStreamResponse
Int -> ReadS DescribeStreamResponse
ReadS [DescribeStreamResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeStreamResponse]
$creadListPrec :: ReadPrec [DescribeStreamResponse]
readPrec :: ReadPrec DescribeStreamResponse
$creadPrec :: ReadPrec DescribeStreamResponse
readList :: ReadS [DescribeStreamResponse]
$creadList :: ReadS [DescribeStreamResponse]
readsPrec :: Int -> ReadS DescribeStreamResponse
$creadsPrec :: Int -> ReadS DescribeStreamResponse
Prelude.Read, Int -> DescribeStreamResponse -> ShowS
[DescribeStreamResponse] -> ShowS
DescribeStreamResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeStreamResponse] -> ShowS
$cshowList :: [DescribeStreamResponse] -> ShowS
show :: DescribeStreamResponse -> String
$cshow :: DescribeStreamResponse -> String
showsPrec :: Int -> DescribeStreamResponse -> ShowS
$cshowsPrec :: Int -> DescribeStreamResponse -> ShowS
Prelude.Show, forall x. Rep DescribeStreamResponse x -> DescribeStreamResponse
forall x. DescribeStreamResponse -> Rep DescribeStreamResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeStreamResponse x -> DescribeStreamResponse
$cfrom :: forall x. DescribeStreamResponse -> Rep DescribeStreamResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeStreamResponse' 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:
--
-- 'httpStatus', 'describeStreamResponse_httpStatus' - The response's http status code.
--
-- 'streamDescription', 'describeStreamResponse_streamDescription' - The current status of the stream, the stream Amazon Resource Name (ARN),
-- an array of shard objects that comprise the stream, and whether there
-- are more shards available.
newDescribeStreamResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'streamDescription'
  StreamDescription ->
  DescribeStreamResponse
newDescribeStreamResponse :: Int -> StreamDescription -> DescribeStreamResponse
newDescribeStreamResponse
  Int
pHttpStatus_
  StreamDescription
pStreamDescription_ =
    DescribeStreamResponse'
      { $sel:httpStatus:DescribeStreamResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:streamDescription:DescribeStreamResponse' :: StreamDescription
streamDescription = StreamDescription
pStreamDescription_
      }

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

-- | The current status of the stream, the stream Amazon Resource Name (ARN),
-- an array of shard objects that comprise the stream, and whether there
-- are more shards available.
describeStreamResponse_streamDescription :: Lens.Lens' DescribeStreamResponse StreamDescription
describeStreamResponse_streamDescription :: Lens' DescribeStreamResponse StreamDescription
describeStreamResponse_streamDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeStreamResponse' {StreamDescription
streamDescription :: StreamDescription
$sel:streamDescription:DescribeStreamResponse' :: DescribeStreamResponse -> StreamDescription
streamDescription} -> StreamDescription
streamDescription) (\s :: DescribeStreamResponse
s@DescribeStreamResponse' {} StreamDescription
a -> DescribeStreamResponse
s {$sel:streamDescription:DescribeStreamResponse' :: StreamDescription
streamDescription = StreamDescription
a} :: DescribeStreamResponse)

instance Prelude.NFData DescribeStreamResponse where
  rnf :: DescribeStreamResponse -> ()
rnf DescribeStreamResponse' {Int
StreamDescription
streamDescription :: StreamDescription
httpStatus :: Int
$sel:streamDescription:DescribeStreamResponse' :: DescribeStreamResponse -> StreamDescription
$sel:httpStatus:DescribeStreamResponse' :: DescribeStreamResponse -> Int
..} =
    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 StreamDescription
streamDescription