{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.DynamoDBStreams.Types.StreamDescription
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.DynamoDBStreams.Types.StreamDescription where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DynamoDBStreams.Internal
import Amazonka.DynamoDBStreams.Types.KeySchemaElement
import Amazonka.DynamoDBStreams.Types.Shard
import Amazonka.DynamoDBStreams.Types.StreamStatus
import Amazonka.DynamoDBStreams.Types.StreamViewType
import qualified Amazonka.Prelude as Prelude

-- | Represents all of the data describing a particular stream.
--
-- /See:/ 'newStreamDescription' smart constructor.
data StreamDescription = StreamDescription'
  { -- | The date and time when the request to create this stream was issued.
    StreamDescription -> Maybe POSIX
creationRequestDateTime :: Prelude.Maybe Data.POSIX,
    -- | The key attribute(s) of the stream\'s DynamoDB table.
    StreamDescription -> Maybe (NonEmpty KeySchemaElement)
keySchema :: Prelude.Maybe (Prelude.NonEmpty KeySchemaElement),
    -- | The shard ID of the item where the operation stopped, inclusive of the
    -- previous result set. Use this value to start a new operation, excluding
    -- this value in the new request.
    --
    -- If @LastEvaluatedShardId@ is empty, then the \"last page\" of results
    -- has been processed and there is currently no more data to be retrieved.
    --
    -- If @LastEvaluatedShardId@ is not empty, it does not necessarily mean
    -- that there is more data in the result set. The only way to know when you
    -- have reached the end of the result set is when @LastEvaluatedShardId@ is
    -- empty.
    StreamDescription -> Maybe Text
lastEvaluatedShardId :: Prelude.Maybe Prelude.Text,
    -- | The shards that comprise the stream.
    StreamDescription -> Maybe [Shard]
shards :: Prelude.Maybe [Shard],
    -- | The Amazon Resource Name (ARN) for the stream.
    StreamDescription -> Maybe Text
streamArn :: Prelude.Maybe Prelude.Text,
    -- | A timestamp, in ISO 8601 format, for this stream.
    --
    -- Note that @LatestStreamLabel@ is not a unique identifier for the stream,
    -- because it is possible that a stream from another table might have the
    -- same timestamp. However, the combination of the following three elements
    -- is guaranteed to be unique:
    --
    -- -   the AWS customer ID.
    --
    -- -   the table name
    --
    -- -   the @StreamLabel@
    StreamDescription -> Maybe Text
streamLabel :: Prelude.Maybe Prelude.Text,
    -- | Indicates the current status of the stream:
    --
    -- -   @ENABLING@ - Streams is currently being enabled on the DynamoDB
    --     table.
    --
    -- -   @ENABLED@ - the stream is enabled.
    --
    -- -   @DISABLING@ - Streams is currently being disabled on the DynamoDB
    --     table.
    --
    -- -   @DISABLED@ - the stream is disabled.
    StreamDescription -> Maybe StreamStatus
streamStatus :: Prelude.Maybe StreamStatus,
    -- | Indicates the format of the records within this stream:
    --
    -- -   @KEYS_ONLY@ - only the key attributes of items that were modified in
    --     the DynamoDB table.
    --
    -- -   @NEW_IMAGE@ - entire items from the table, as they appeared after
    --     they were modified.
    --
    -- -   @OLD_IMAGE@ - entire items from the table, as they appeared before
    --     they were modified.
    --
    -- -   @NEW_AND_OLD_IMAGES@ - both the new and the old images of the items
    --     from the table.
    StreamDescription -> Maybe StreamViewType
streamViewType :: Prelude.Maybe StreamViewType,
    -- | The DynamoDB table with which the stream is associated.
    StreamDescription -> Maybe Text
tableName :: Prelude.Maybe Prelude.Text
  }
  deriving (StreamDescription -> StreamDescription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StreamDescription -> StreamDescription -> Bool
$c/= :: StreamDescription -> StreamDescription -> Bool
== :: StreamDescription -> StreamDescription -> Bool
$c== :: StreamDescription -> StreamDescription -> Bool
Prelude.Eq, ReadPrec [StreamDescription]
ReadPrec StreamDescription
Int -> ReadS StreamDescription
ReadS [StreamDescription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StreamDescription]
$creadListPrec :: ReadPrec [StreamDescription]
readPrec :: ReadPrec StreamDescription
$creadPrec :: ReadPrec StreamDescription
readList :: ReadS [StreamDescription]
$creadList :: ReadS [StreamDescription]
readsPrec :: Int -> ReadS StreamDescription
$creadsPrec :: Int -> ReadS StreamDescription
Prelude.Read, Int -> StreamDescription -> ShowS
[StreamDescription] -> ShowS
StreamDescription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StreamDescription] -> ShowS
$cshowList :: [StreamDescription] -> ShowS
show :: StreamDescription -> String
$cshow :: StreamDescription -> String
showsPrec :: Int -> StreamDescription -> ShowS
$cshowsPrec :: Int -> StreamDescription -> ShowS
Prelude.Show, forall x. Rep StreamDescription x -> StreamDescription
forall x. StreamDescription -> Rep StreamDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StreamDescription x -> StreamDescription
$cfrom :: forall x. StreamDescription -> Rep StreamDescription x
Prelude.Generic)

-- |
-- Create a value of 'StreamDescription' 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:
--
-- 'creationRequestDateTime', 'streamDescription_creationRequestDateTime' - The date and time when the request to create this stream was issued.
--
-- 'keySchema', 'streamDescription_keySchema' - The key attribute(s) of the stream\'s DynamoDB table.
--
-- 'lastEvaluatedShardId', 'streamDescription_lastEvaluatedShardId' - The shard ID of the item where the operation stopped, inclusive of the
-- previous result set. Use this value to start a new operation, excluding
-- this value in the new request.
--
-- If @LastEvaluatedShardId@ is empty, then the \"last page\" of results
-- has been processed and there is currently no more data to be retrieved.
--
-- If @LastEvaluatedShardId@ is not empty, it does not necessarily mean
-- that there is more data in the result set. The only way to know when you
-- have reached the end of the result set is when @LastEvaluatedShardId@ is
-- empty.
--
-- 'shards', 'streamDescription_shards' - The shards that comprise the stream.
--
-- 'streamArn', 'streamDescription_streamArn' - The Amazon Resource Name (ARN) for the stream.
--
-- 'streamLabel', 'streamDescription_streamLabel' - A timestamp, in ISO 8601 format, for this stream.
--
-- Note that @LatestStreamLabel@ is not a unique identifier for the stream,
-- because it is possible that a stream from another table might have the
-- same timestamp. However, the combination of the following three elements
-- is guaranteed to be unique:
--
-- -   the AWS customer ID.
--
-- -   the table name
--
-- -   the @StreamLabel@
--
-- 'streamStatus', 'streamDescription_streamStatus' - Indicates the current status of the stream:
--
-- -   @ENABLING@ - Streams is currently being enabled on the DynamoDB
--     table.
--
-- -   @ENABLED@ - the stream is enabled.
--
-- -   @DISABLING@ - Streams is currently being disabled on the DynamoDB
--     table.
--
-- -   @DISABLED@ - the stream is disabled.
--
-- 'streamViewType', 'streamDescription_streamViewType' - Indicates the format of the records within this stream:
--
-- -   @KEYS_ONLY@ - only the key attributes of items that were modified in
--     the DynamoDB table.
--
-- -   @NEW_IMAGE@ - entire items from the table, as they appeared after
--     they were modified.
--
-- -   @OLD_IMAGE@ - entire items from the table, as they appeared before
--     they were modified.
--
-- -   @NEW_AND_OLD_IMAGES@ - both the new and the old images of the items
--     from the table.
--
-- 'tableName', 'streamDescription_tableName' - The DynamoDB table with which the stream is associated.
newStreamDescription ::
  StreamDescription
newStreamDescription :: StreamDescription
newStreamDescription =
  StreamDescription'
    { $sel:creationRequestDateTime:StreamDescription' :: Maybe POSIX
creationRequestDateTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:keySchema:StreamDescription' :: Maybe (NonEmpty KeySchemaElement)
keySchema = forall a. Maybe a
Prelude.Nothing,
      $sel:lastEvaluatedShardId:StreamDescription' :: Maybe Text
lastEvaluatedShardId = forall a. Maybe a
Prelude.Nothing,
      $sel:shards:StreamDescription' :: Maybe [Shard]
shards = forall a. Maybe a
Prelude.Nothing,
      $sel:streamArn:StreamDescription' :: Maybe Text
streamArn = forall a. Maybe a
Prelude.Nothing,
      $sel:streamLabel:StreamDescription' :: Maybe Text
streamLabel = forall a. Maybe a
Prelude.Nothing,
      $sel:streamStatus:StreamDescription' :: Maybe StreamStatus
streamStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:streamViewType:StreamDescription' :: Maybe StreamViewType
streamViewType = forall a. Maybe a
Prelude.Nothing,
      $sel:tableName:StreamDescription' :: Maybe Text
tableName = forall a. Maybe a
Prelude.Nothing
    }

-- | The date and time when the request to create this stream was issued.
streamDescription_creationRequestDateTime :: Lens.Lens' StreamDescription (Prelude.Maybe Prelude.UTCTime)
streamDescription_creationRequestDateTime :: Lens' StreamDescription (Maybe UTCTime)
streamDescription_creationRequestDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StreamDescription' {Maybe POSIX
creationRequestDateTime :: Maybe POSIX
$sel:creationRequestDateTime:StreamDescription' :: StreamDescription -> Maybe POSIX
creationRequestDateTime} -> Maybe POSIX
creationRequestDateTime) (\s :: StreamDescription
s@StreamDescription' {} Maybe POSIX
a -> StreamDescription
s {$sel:creationRequestDateTime:StreamDescription' :: Maybe POSIX
creationRequestDateTime = Maybe POSIX
a} :: StreamDescription) 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 :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The key attribute(s) of the stream\'s DynamoDB table.
streamDescription_keySchema :: Lens.Lens' StreamDescription (Prelude.Maybe (Prelude.NonEmpty KeySchemaElement))
streamDescription_keySchema :: Lens' StreamDescription (Maybe (NonEmpty KeySchemaElement))
streamDescription_keySchema = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StreamDescription' {Maybe (NonEmpty KeySchemaElement)
keySchema :: Maybe (NonEmpty KeySchemaElement)
$sel:keySchema:StreamDescription' :: StreamDescription -> Maybe (NonEmpty KeySchemaElement)
keySchema} -> Maybe (NonEmpty KeySchemaElement)
keySchema) (\s :: StreamDescription
s@StreamDescription' {} Maybe (NonEmpty KeySchemaElement)
a -> StreamDescription
s {$sel:keySchema:StreamDescription' :: Maybe (NonEmpty KeySchemaElement)
keySchema = Maybe (NonEmpty KeySchemaElement)
a} :: StreamDescription) 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 shard ID of the item where the operation stopped, inclusive of the
-- previous result set. Use this value to start a new operation, excluding
-- this value in the new request.
--
-- If @LastEvaluatedShardId@ is empty, then the \"last page\" of results
-- has been processed and there is currently no more data to be retrieved.
--
-- If @LastEvaluatedShardId@ is not empty, it does not necessarily mean
-- that there is more data in the result set. The only way to know when you
-- have reached the end of the result set is when @LastEvaluatedShardId@ is
-- empty.
streamDescription_lastEvaluatedShardId :: Lens.Lens' StreamDescription (Prelude.Maybe Prelude.Text)
streamDescription_lastEvaluatedShardId :: Lens' StreamDescription (Maybe Text)
streamDescription_lastEvaluatedShardId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StreamDescription' {Maybe Text
lastEvaluatedShardId :: Maybe Text
$sel:lastEvaluatedShardId:StreamDescription' :: StreamDescription -> Maybe Text
lastEvaluatedShardId} -> Maybe Text
lastEvaluatedShardId) (\s :: StreamDescription
s@StreamDescription' {} Maybe Text
a -> StreamDescription
s {$sel:lastEvaluatedShardId:StreamDescription' :: Maybe Text
lastEvaluatedShardId = Maybe Text
a} :: StreamDescription)

-- | The shards that comprise the stream.
streamDescription_shards :: Lens.Lens' StreamDescription (Prelude.Maybe [Shard])
streamDescription_shards :: Lens' StreamDescription (Maybe [Shard])
streamDescription_shards = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StreamDescription' {Maybe [Shard]
shards :: Maybe [Shard]
$sel:shards:StreamDescription' :: StreamDescription -> Maybe [Shard]
shards} -> Maybe [Shard]
shards) (\s :: StreamDescription
s@StreamDescription' {} Maybe [Shard]
a -> StreamDescription
s {$sel:shards:StreamDescription' :: Maybe [Shard]
shards = Maybe [Shard]
a} :: StreamDescription) 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 Amazon Resource Name (ARN) for the stream.
streamDescription_streamArn :: Lens.Lens' StreamDescription (Prelude.Maybe Prelude.Text)
streamDescription_streamArn :: Lens' StreamDescription (Maybe Text)
streamDescription_streamArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StreamDescription' {Maybe Text
streamArn :: Maybe Text
$sel:streamArn:StreamDescription' :: StreamDescription -> Maybe Text
streamArn} -> Maybe Text
streamArn) (\s :: StreamDescription
s@StreamDescription' {} Maybe Text
a -> StreamDescription
s {$sel:streamArn:StreamDescription' :: Maybe Text
streamArn = Maybe Text
a} :: StreamDescription)

-- | A timestamp, in ISO 8601 format, for this stream.
--
-- Note that @LatestStreamLabel@ is not a unique identifier for the stream,
-- because it is possible that a stream from another table might have the
-- same timestamp. However, the combination of the following three elements
-- is guaranteed to be unique:
--
-- -   the AWS customer ID.
--
-- -   the table name
--
-- -   the @StreamLabel@
streamDescription_streamLabel :: Lens.Lens' StreamDescription (Prelude.Maybe Prelude.Text)
streamDescription_streamLabel :: Lens' StreamDescription (Maybe Text)
streamDescription_streamLabel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StreamDescription' {Maybe Text
streamLabel :: Maybe Text
$sel:streamLabel:StreamDescription' :: StreamDescription -> Maybe Text
streamLabel} -> Maybe Text
streamLabel) (\s :: StreamDescription
s@StreamDescription' {} Maybe Text
a -> StreamDescription
s {$sel:streamLabel:StreamDescription' :: Maybe Text
streamLabel = Maybe Text
a} :: StreamDescription)

-- | Indicates the current status of the stream:
--
-- -   @ENABLING@ - Streams is currently being enabled on the DynamoDB
--     table.
--
-- -   @ENABLED@ - the stream is enabled.
--
-- -   @DISABLING@ - Streams is currently being disabled on the DynamoDB
--     table.
--
-- -   @DISABLED@ - the stream is disabled.
streamDescription_streamStatus :: Lens.Lens' StreamDescription (Prelude.Maybe StreamStatus)
streamDescription_streamStatus :: Lens' StreamDescription (Maybe StreamStatus)
streamDescription_streamStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StreamDescription' {Maybe StreamStatus
streamStatus :: Maybe StreamStatus
$sel:streamStatus:StreamDescription' :: StreamDescription -> Maybe StreamStatus
streamStatus} -> Maybe StreamStatus
streamStatus) (\s :: StreamDescription
s@StreamDescription' {} Maybe StreamStatus
a -> StreamDescription
s {$sel:streamStatus:StreamDescription' :: Maybe StreamStatus
streamStatus = Maybe StreamStatus
a} :: StreamDescription)

-- | Indicates the format of the records within this stream:
--
-- -   @KEYS_ONLY@ - only the key attributes of items that were modified in
--     the DynamoDB table.
--
-- -   @NEW_IMAGE@ - entire items from the table, as they appeared after
--     they were modified.
--
-- -   @OLD_IMAGE@ - entire items from the table, as they appeared before
--     they were modified.
--
-- -   @NEW_AND_OLD_IMAGES@ - both the new and the old images of the items
--     from the table.
streamDescription_streamViewType :: Lens.Lens' StreamDescription (Prelude.Maybe StreamViewType)
streamDescription_streamViewType :: Lens' StreamDescription (Maybe StreamViewType)
streamDescription_streamViewType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StreamDescription' {Maybe StreamViewType
streamViewType :: Maybe StreamViewType
$sel:streamViewType:StreamDescription' :: StreamDescription -> Maybe StreamViewType
streamViewType} -> Maybe StreamViewType
streamViewType) (\s :: StreamDescription
s@StreamDescription' {} Maybe StreamViewType
a -> StreamDescription
s {$sel:streamViewType:StreamDescription' :: Maybe StreamViewType
streamViewType = Maybe StreamViewType
a} :: StreamDescription)

-- | The DynamoDB table with which the stream is associated.
streamDescription_tableName :: Lens.Lens' StreamDescription (Prelude.Maybe Prelude.Text)
streamDescription_tableName :: Lens' StreamDescription (Maybe Text)
streamDescription_tableName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StreamDescription' {Maybe Text
tableName :: Maybe Text
$sel:tableName:StreamDescription' :: StreamDescription -> Maybe Text
tableName} -> Maybe Text
tableName) (\s :: StreamDescription
s@StreamDescription' {} Maybe Text
a -> StreamDescription
s {$sel:tableName:StreamDescription' :: Maybe Text
tableName = Maybe Text
a} :: StreamDescription)

instance Data.FromJSON StreamDescription where
  parseJSON :: Value -> Parser StreamDescription
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"StreamDescription"
      ( \Object
x ->
          Maybe POSIX
-> Maybe (NonEmpty KeySchemaElement)
-> Maybe Text
-> Maybe [Shard]
-> Maybe Text
-> Maybe Text
-> Maybe StreamStatus
-> Maybe StreamViewType
-> Maybe Text
-> StreamDescription
StreamDescription'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CreationRequestDateTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"KeySchema")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"LastEvaluatedShardId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Shards" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"StreamArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"StreamLabel")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"StreamStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"StreamViewType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"TableName")
      )

instance Prelude.Hashable StreamDescription where
  hashWithSalt :: Int -> StreamDescription -> Int
hashWithSalt Int
_salt StreamDescription' {Maybe [Shard]
Maybe (NonEmpty KeySchemaElement)
Maybe Text
Maybe POSIX
Maybe StreamStatus
Maybe StreamViewType
tableName :: Maybe Text
streamViewType :: Maybe StreamViewType
streamStatus :: Maybe StreamStatus
streamLabel :: Maybe Text
streamArn :: Maybe Text
shards :: Maybe [Shard]
lastEvaluatedShardId :: Maybe Text
keySchema :: Maybe (NonEmpty KeySchemaElement)
creationRequestDateTime :: Maybe POSIX
$sel:tableName:StreamDescription' :: StreamDescription -> Maybe Text
$sel:streamViewType:StreamDescription' :: StreamDescription -> Maybe StreamViewType
$sel:streamStatus:StreamDescription' :: StreamDescription -> Maybe StreamStatus
$sel:streamLabel:StreamDescription' :: StreamDescription -> Maybe Text
$sel:streamArn:StreamDescription' :: StreamDescription -> Maybe Text
$sel:shards:StreamDescription' :: StreamDescription -> Maybe [Shard]
$sel:lastEvaluatedShardId:StreamDescription' :: StreamDescription -> Maybe Text
$sel:keySchema:StreamDescription' :: StreamDescription -> Maybe (NonEmpty KeySchemaElement)
$sel:creationRequestDateTime:StreamDescription' :: StreamDescription -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationRequestDateTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty KeySchemaElement)
keySchema
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
lastEvaluatedShardId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Shard]
shards
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
streamArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
streamLabel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StreamStatus
streamStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StreamViewType
streamViewType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
tableName

instance Prelude.NFData StreamDescription where
  rnf :: StreamDescription -> ()
rnf StreamDescription' {Maybe [Shard]
Maybe (NonEmpty KeySchemaElement)
Maybe Text
Maybe POSIX
Maybe StreamStatus
Maybe StreamViewType
tableName :: Maybe Text
streamViewType :: Maybe StreamViewType
streamStatus :: Maybe StreamStatus
streamLabel :: Maybe Text
streamArn :: Maybe Text
shards :: Maybe [Shard]
lastEvaluatedShardId :: Maybe Text
keySchema :: Maybe (NonEmpty KeySchemaElement)
creationRequestDateTime :: Maybe POSIX
$sel:tableName:StreamDescription' :: StreamDescription -> Maybe Text
$sel:streamViewType:StreamDescription' :: StreamDescription -> Maybe StreamViewType
$sel:streamStatus:StreamDescription' :: StreamDescription -> Maybe StreamStatus
$sel:streamLabel:StreamDescription' :: StreamDescription -> Maybe Text
$sel:streamArn:StreamDescription' :: StreamDescription -> Maybe Text
$sel:shards:StreamDescription' :: StreamDescription -> Maybe [Shard]
$sel:lastEvaluatedShardId:StreamDescription' :: StreamDescription -> Maybe Text
$sel:keySchema:StreamDescription' :: StreamDescription -> Maybe (NonEmpty KeySchemaElement)
$sel:creationRequestDateTime:StreamDescription' :: StreamDescription -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationRequestDateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty KeySchemaElement)
keySchema
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
lastEvaluatedShardId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Shard]
shards
      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
streamLabel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StreamStatus
streamStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StreamViewType
streamViewType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
tableName