{-# 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.DynamoDB.Types.SourceTableDetails
-- 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.DynamoDB.Types.SourceTableDetails where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DynamoDB.Types.AttributeValue
import Amazonka.DynamoDB.Types.BillingMode
import Amazonka.DynamoDB.Types.KeySchemaElement
import Amazonka.DynamoDB.Types.ProvisionedThroughput
import Amazonka.DynamoDB.Types.WriteRequest
import qualified Amazonka.Prelude as Prelude

-- | Contains the details of the table when the backup was created.
--
-- /See:/ 'newSourceTableDetails' smart constructor.
data SourceTableDetails = SourceTableDetails'
  { -- | Controls how you are charged for read and write throughput and how you
    -- manage capacity. This setting can be changed later.
    --
    -- -   @PROVISIONED@ - Sets the read\/write capacity mode to @PROVISIONED@.
    --     We recommend using @PROVISIONED@ for predictable workloads.
    --
    -- -   @PAY_PER_REQUEST@ - Sets the read\/write capacity mode to
    --     @PAY_PER_REQUEST@. We recommend using @PAY_PER_REQUEST@ for
    --     unpredictable workloads.
    SourceTableDetails -> Maybe BillingMode
billingMode :: Prelude.Maybe BillingMode,
    -- | Number of items in the table. Note that this is an approximate value.
    SourceTableDetails -> Maybe Natural
itemCount :: Prelude.Maybe Prelude.Natural,
    -- | ARN of the table for which backup was created.
    SourceTableDetails -> Maybe Text
tableArn :: Prelude.Maybe Prelude.Text,
    -- | Size of the table in bytes. Note that this is an approximate value.
    SourceTableDetails -> Maybe Integer
tableSizeBytes :: Prelude.Maybe Prelude.Integer,
    -- | The name of the table for which the backup was created.
    SourceTableDetails -> Text
tableName :: Prelude.Text,
    -- | Unique identifier for the table for which the backup was created.
    SourceTableDetails -> Text
tableId :: Prelude.Text,
    -- | Schema of the table.
    SourceTableDetails -> NonEmpty KeySchemaElement
keySchema :: Prelude.NonEmpty KeySchemaElement,
    -- | Time when the source table was created.
    SourceTableDetails -> POSIX
tableCreationDateTime :: Data.POSIX,
    -- | Read IOPs and Write IOPS on the table when the backup was created.
    SourceTableDetails -> ProvisionedThroughput
provisionedThroughput :: ProvisionedThroughput
  }
  deriving (SourceTableDetails -> SourceTableDetails -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SourceTableDetails -> SourceTableDetails -> Bool
$c/= :: SourceTableDetails -> SourceTableDetails -> Bool
== :: SourceTableDetails -> SourceTableDetails -> Bool
$c== :: SourceTableDetails -> SourceTableDetails -> Bool
Prelude.Eq, ReadPrec [SourceTableDetails]
ReadPrec SourceTableDetails
Int -> ReadS SourceTableDetails
ReadS [SourceTableDetails]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SourceTableDetails]
$creadListPrec :: ReadPrec [SourceTableDetails]
readPrec :: ReadPrec SourceTableDetails
$creadPrec :: ReadPrec SourceTableDetails
readList :: ReadS [SourceTableDetails]
$creadList :: ReadS [SourceTableDetails]
readsPrec :: Int -> ReadS SourceTableDetails
$creadsPrec :: Int -> ReadS SourceTableDetails
Prelude.Read, Int -> SourceTableDetails -> ShowS
[SourceTableDetails] -> ShowS
SourceTableDetails -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SourceTableDetails] -> ShowS
$cshowList :: [SourceTableDetails] -> ShowS
show :: SourceTableDetails -> String
$cshow :: SourceTableDetails -> String
showsPrec :: Int -> SourceTableDetails -> ShowS
$cshowsPrec :: Int -> SourceTableDetails -> ShowS
Prelude.Show, forall x. Rep SourceTableDetails x -> SourceTableDetails
forall x. SourceTableDetails -> Rep SourceTableDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SourceTableDetails x -> SourceTableDetails
$cfrom :: forall x. SourceTableDetails -> Rep SourceTableDetails x
Prelude.Generic)

-- |
-- Create a value of 'SourceTableDetails' 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:
--
-- 'billingMode', 'sourceTableDetails_billingMode' - Controls how you are charged for read and write throughput and how you
-- manage capacity. This setting can be changed later.
--
-- -   @PROVISIONED@ - Sets the read\/write capacity mode to @PROVISIONED@.
--     We recommend using @PROVISIONED@ for predictable workloads.
--
-- -   @PAY_PER_REQUEST@ - Sets the read\/write capacity mode to
--     @PAY_PER_REQUEST@. We recommend using @PAY_PER_REQUEST@ for
--     unpredictable workloads.
--
-- 'itemCount', 'sourceTableDetails_itemCount' - Number of items in the table. Note that this is an approximate value.
--
-- 'tableArn', 'sourceTableDetails_tableArn' - ARN of the table for which backup was created.
--
-- 'tableSizeBytes', 'sourceTableDetails_tableSizeBytes' - Size of the table in bytes. Note that this is an approximate value.
--
-- 'tableName', 'sourceTableDetails_tableName' - The name of the table for which the backup was created.
--
-- 'tableId', 'sourceTableDetails_tableId' - Unique identifier for the table for which the backup was created.
--
-- 'keySchema', 'sourceTableDetails_keySchema' - Schema of the table.
--
-- 'tableCreationDateTime', 'sourceTableDetails_tableCreationDateTime' - Time when the source table was created.
--
-- 'provisionedThroughput', 'sourceTableDetails_provisionedThroughput' - Read IOPs and Write IOPS on the table when the backup was created.
newSourceTableDetails ::
  -- | 'tableName'
  Prelude.Text ->
  -- | 'tableId'
  Prelude.Text ->
  -- | 'keySchema'
  Prelude.NonEmpty KeySchemaElement ->
  -- | 'tableCreationDateTime'
  Prelude.UTCTime ->
  -- | 'provisionedThroughput'
  ProvisionedThroughput ->
  SourceTableDetails
newSourceTableDetails :: Text
-> Text
-> NonEmpty KeySchemaElement
-> UTCTime
-> ProvisionedThroughput
-> SourceTableDetails
newSourceTableDetails
  Text
pTableName_
  Text
pTableId_
  NonEmpty KeySchemaElement
pKeySchema_
  UTCTime
pTableCreationDateTime_
  ProvisionedThroughput
pProvisionedThroughput_ =
    SourceTableDetails'
      { $sel:billingMode:SourceTableDetails' :: Maybe BillingMode
billingMode = forall a. Maybe a
Prelude.Nothing,
        $sel:itemCount:SourceTableDetails' :: Maybe Natural
itemCount = forall a. Maybe a
Prelude.Nothing,
        $sel:tableArn:SourceTableDetails' :: Maybe Text
tableArn = forall a. Maybe a
Prelude.Nothing,
        $sel:tableSizeBytes:SourceTableDetails' :: Maybe Integer
tableSizeBytes = forall a. Maybe a
Prelude.Nothing,
        $sel:tableName:SourceTableDetails' :: Text
tableName = Text
pTableName_,
        $sel:tableId:SourceTableDetails' :: Text
tableId = Text
pTableId_,
        $sel:keySchema:SourceTableDetails' :: NonEmpty KeySchemaElement
keySchema = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty KeySchemaElement
pKeySchema_,
        $sel:tableCreationDateTime:SourceTableDetails' :: POSIX
tableCreationDateTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pTableCreationDateTime_,
        $sel:provisionedThroughput:SourceTableDetails' :: ProvisionedThroughput
provisionedThroughput = ProvisionedThroughput
pProvisionedThroughput_
      }

-- | Controls how you are charged for read and write throughput and how you
-- manage capacity. This setting can be changed later.
--
-- -   @PROVISIONED@ - Sets the read\/write capacity mode to @PROVISIONED@.
--     We recommend using @PROVISIONED@ for predictable workloads.
--
-- -   @PAY_PER_REQUEST@ - Sets the read\/write capacity mode to
--     @PAY_PER_REQUEST@. We recommend using @PAY_PER_REQUEST@ for
--     unpredictable workloads.
sourceTableDetails_billingMode :: Lens.Lens' SourceTableDetails (Prelude.Maybe BillingMode)
sourceTableDetails_billingMode :: Lens' SourceTableDetails (Maybe BillingMode)
sourceTableDetails_billingMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SourceTableDetails' {Maybe BillingMode
billingMode :: Maybe BillingMode
$sel:billingMode:SourceTableDetails' :: SourceTableDetails -> Maybe BillingMode
billingMode} -> Maybe BillingMode
billingMode) (\s :: SourceTableDetails
s@SourceTableDetails' {} Maybe BillingMode
a -> SourceTableDetails
s {$sel:billingMode:SourceTableDetails' :: Maybe BillingMode
billingMode = Maybe BillingMode
a} :: SourceTableDetails)

-- | Number of items in the table. Note that this is an approximate value.
sourceTableDetails_itemCount :: Lens.Lens' SourceTableDetails (Prelude.Maybe Prelude.Natural)
sourceTableDetails_itemCount :: Lens' SourceTableDetails (Maybe Natural)
sourceTableDetails_itemCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SourceTableDetails' {Maybe Natural
itemCount :: Maybe Natural
$sel:itemCount:SourceTableDetails' :: SourceTableDetails -> Maybe Natural
itemCount} -> Maybe Natural
itemCount) (\s :: SourceTableDetails
s@SourceTableDetails' {} Maybe Natural
a -> SourceTableDetails
s {$sel:itemCount:SourceTableDetails' :: Maybe Natural
itemCount = Maybe Natural
a} :: SourceTableDetails)

-- | ARN of the table for which backup was created.
sourceTableDetails_tableArn :: Lens.Lens' SourceTableDetails (Prelude.Maybe Prelude.Text)
sourceTableDetails_tableArn :: Lens' SourceTableDetails (Maybe Text)
sourceTableDetails_tableArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SourceTableDetails' {Maybe Text
tableArn :: Maybe Text
$sel:tableArn:SourceTableDetails' :: SourceTableDetails -> Maybe Text
tableArn} -> Maybe Text
tableArn) (\s :: SourceTableDetails
s@SourceTableDetails' {} Maybe Text
a -> SourceTableDetails
s {$sel:tableArn:SourceTableDetails' :: Maybe Text
tableArn = Maybe Text
a} :: SourceTableDetails)

-- | Size of the table in bytes. Note that this is an approximate value.
sourceTableDetails_tableSizeBytes :: Lens.Lens' SourceTableDetails (Prelude.Maybe Prelude.Integer)
sourceTableDetails_tableSizeBytes :: Lens' SourceTableDetails (Maybe Integer)
sourceTableDetails_tableSizeBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SourceTableDetails' {Maybe Integer
tableSizeBytes :: Maybe Integer
$sel:tableSizeBytes:SourceTableDetails' :: SourceTableDetails -> Maybe Integer
tableSizeBytes} -> Maybe Integer
tableSizeBytes) (\s :: SourceTableDetails
s@SourceTableDetails' {} Maybe Integer
a -> SourceTableDetails
s {$sel:tableSizeBytes:SourceTableDetails' :: Maybe Integer
tableSizeBytes = Maybe Integer
a} :: SourceTableDetails)

-- | The name of the table for which the backup was created.
sourceTableDetails_tableName :: Lens.Lens' SourceTableDetails Prelude.Text
sourceTableDetails_tableName :: Lens' SourceTableDetails Text
sourceTableDetails_tableName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SourceTableDetails' {Text
tableName :: Text
$sel:tableName:SourceTableDetails' :: SourceTableDetails -> Text
tableName} -> Text
tableName) (\s :: SourceTableDetails
s@SourceTableDetails' {} Text
a -> SourceTableDetails
s {$sel:tableName:SourceTableDetails' :: Text
tableName = Text
a} :: SourceTableDetails)

-- | Unique identifier for the table for which the backup was created.
sourceTableDetails_tableId :: Lens.Lens' SourceTableDetails Prelude.Text
sourceTableDetails_tableId :: Lens' SourceTableDetails Text
sourceTableDetails_tableId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SourceTableDetails' {Text
tableId :: Text
$sel:tableId:SourceTableDetails' :: SourceTableDetails -> Text
tableId} -> Text
tableId) (\s :: SourceTableDetails
s@SourceTableDetails' {} Text
a -> SourceTableDetails
s {$sel:tableId:SourceTableDetails' :: Text
tableId = Text
a} :: SourceTableDetails)

-- | Schema of the table.
sourceTableDetails_keySchema :: Lens.Lens' SourceTableDetails (Prelude.NonEmpty KeySchemaElement)
sourceTableDetails_keySchema :: Lens' SourceTableDetails (NonEmpty KeySchemaElement)
sourceTableDetails_keySchema = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SourceTableDetails' {NonEmpty KeySchemaElement
keySchema :: NonEmpty KeySchemaElement
$sel:keySchema:SourceTableDetails' :: SourceTableDetails -> NonEmpty KeySchemaElement
keySchema} -> NonEmpty KeySchemaElement
keySchema) (\s :: SourceTableDetails
s@SourceTableDetails' {} NonEmpty KeySchemaElement
a -> SourceTableDetails
s {$sel:keySchema:SourceTableDetails' :: NonEmpty KeySchemaElement
keySchema = NonEmpty KeySchemaElement
a} :: SourceTableDetails) 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

-- | Time when the source table was created.
sourceTableDetails_tableCreationDateTime :: Lens.Lens' SourceTableDetails Prelude.UTCTime
sourceTableDetails_tableCreationDateTime :: Lens' SourceTableDetails UTCTime
sourceTableDetails_tableCreationDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SourceTableDetails' {POSIX
tableCreationDateTime :: POSIX
$sel:tableCreationDateTime:SourceTableDetails' :: SourceTableDetails -> POSIX
tableCreationDateTime} -> POSIX
tableCreationDateTime) (\s :: SourceTableDetails
s@SourceTableDetails' {} POSIX
a -> SourceTableDetails
s {$sel:tableCreationDateTime:SourceTableDetails' :: POSIX
tableCreationDateTime = POSIX
a} :: SourceTableDetails) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Read IOPs and Write IOPS on the table when the backup was created.
sourceTableDetails_provisionedThroughput :: Lens.Lens' SourceTableDetails ProvisionedThroughput
sourceTableDetails_provisionedThroughput :: Lens' SourceTableDetails ProvisionedThroughput
sourceTableDetails_provisionedThroughput = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SourceTableDetails' {ProvisionedThroughput
provisionedThroughput :: ProvisionedThroughput
$sel:provisionedThroughput:SourceTableDetails' :: SourceTableDetails -> ProvisionedThroughput
provisionedThroughput} -> ProvisionedThroughput
provisionedThroughput) (\s :: SourceTableDetails
s@SourceTableDetails' {} ProvisionedThroughput
a -> SourceTableDetails
s {$sel:provisionedThroughput:SourceTableDetails' :: ProvisionedThroughput
provisionedThroughput = ProvisionedThroughput
a} :: SourceTableDetails)

instance Data.FromJSON SourceTableDetails where
  parseJSON :: Value -> Parser SourceTableDetails
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"SourceTableDetails"
      ( \Object
x ->
          Maybe BillingMode
-> Maybe Natural
-> Maybe Text
-> Maybe Integer
-> Text
-> Text
-> NonEmpty KeySchemaElement
-> POSIX
-> ProvisionedThroughput
-> SourceTableDetails
SourceTableDetails'
            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
"BillingMode")
            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
"ItemCount")
            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
"TableArn")
            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
"TableSizeBytes")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"TableName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"TableId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser 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 a
Data..: Key
"TableCreationDateTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"ProvisionedThroughput")
      )

instance Prelude.Hashable SourceTableDetails where
  hashWithSalt :: Int -> SourceTableDetails -> Int
hashWithSalt Int
_salt SourceTableDetails' {Maybe Integer
Maybe Natural
Maybe Text
Maybe BillingMode
NonEmpty KeySchemaElement
Text
POSIX
ProvisionedThroughput
provisionedThroughput :: ProvisionedThroughput
tableCreationDateTime :: POSIX
keySchema :: NonEmpty KeySchemaElement
tableId :: Text
tableName :: Text
tableSizeBytes :: Maybe Integer
tableArn :: Maybe Text
itemCount :: Maybe Natural
billingMode :: Maybe BillingMode
$sel:provisionedThroughput:SourceTableDetails' :: SourceTableDetails -> ProvisionedThroughput
$sel:tableCreationDateTime:SourceTableDetails' :: SourceTableDetails -> POSIX
$sel:keySchema:SourceTableDetails' :: SourceTableDetails -> NonEmpty KeySchemaElement
$sel:tableId:SourceTableDetails' :: SourceTableDetails -> Text
$sel:tableName:SourceTableDetails' :: SourceTableDetails -> Text
$sel:tableSizeBytes:SourceTableDetails' :: SourceTableDetails -> Maybe Integer
$sel:tableArn:SourceTableDetails' :: SourceTableDetails -> Maybe Text
$sel:itemCount:SourceTableDetails' :: SourceTableDetails -> Maybe Natural
$sel:billingMode:SourceTableDetails' :: SourceTableDetails -> Maybe BillingMode
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BillingMode
billingMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
itemCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
tableArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
tableSizeBytes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
tableName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
tableId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty KeySchemaElement
keySchema
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
tableCreationDateTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ProvisionedThroughput
provisionedThroughput

instance Prelude.NFData SourceTableDetails where
  rnf :: SourceTableDetails -> ()
rnf SourceTableDetails' {Maybe Integer
Maybe Natural
Maybe Text
Maybe BillingMode
NonEmpty KeySchemaElement
Text
POSIX
ProvisionedThroughput
provisionedThroughput :: ProvisionedThroughput
tableCreationDateTime :: POSIX
keySchema :: NonEmpty KeySchemaElement
tableId :: Text
tableName :: Text
tableSizeBytes :: Maybe Integer
tableArn :: Maybe Text
itemCount :: Maybe Natural
billingMode :: Maybe BillingMode
$sel:provisionedThroughput:SourceTableDetails' :: SourceTableDetails -> ProvisionedThroughput
$sel:tableCreationDateTime:SourceTableDetails' :: SourceTableDetails -> POSIX
$sel:keySchema:SourceTableDetails' :: SourceTableDetails -> NonEmpty KeySchemaElement
$sel:tableId:SourceTableDetails' :: SourceTableDetails -> Text
$sel:tableName:SourceTableDetails' :: SourceTableDetails -> Text
$sel:tableSizeBytes:SourceTableDetails' :: SourceTableDetails -> Maybe Integer
$sel:tableArn:SourceTableDetails' :: SourceTableDetails -> Maybe Text
$sel:itemCount:SourceTableDetails' :: SourceTableDetails -> Maybe Natural
$sel:billingMode:SourceTableDetails' :: SourceTableDetails -> Maybe BillingMode
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe BillingMode
billingMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
itemCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
tableArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
tableSizeBytes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
tableName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
tableId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty KeySchemaElement
keySchema
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
tableCreationDateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ProvisionedThroughput
provisionedThroughput