module Stratosphere.DynamoDB.GlobalTable (
        module Exports, GlobalTable(..), mkGlobalTable
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.DynamoDB.GlobalTable.AttributeDefinitionProperty as Exports
import {-# SOURCE #-} Stratosphere.DynamoDB.GlobalTable.GlobalSecondaryIndexProperty as Exports
import {-# SOURCE #-} Stratosphere.DynamoDB.GlobalTable.GlobalTableWitnessProperty as Exports
import {-# SOURCE #-} Stratosphere.DynamoDB.GlobalTable.KeySchemaProperty as Exports
import {-# SOURCE #-} Stratosphere.DynamoDB.GlobalTable.LocalSecondaryIndexProperty as Exports
import {-# SOURCE #-} Stratosphere.DynamoDB.GlobalTable.ReplicaSpecificationProperty as Exports
import {-# SOURCE #-} Stratosphere.DynamoDB.GlobalTable.SSESpecificationProperty as Exports
import {-# SOURCE #-} Stratosphere.DynamoDB.GlobalTable.StreamSpecificationProperty as Exports
import {-# SOURCE #-} Stratosphere.DynamoDB.GlobalTable.TimeToLiveSpecificationProperty as Exports
import {-# SOURCE #-} Stratosphere.DynamoDB.GlobalTable.WarmThroughputProperty as Exports
import {-# SOURCE #-} Stratosphere.DynamoDB.GlobalTable.WriteOnDemandThroughputSettingsProperty as Exports
import {-# SOURCE #-} Stratosphere.DynamoDB.GlobalTable.WriteProvisionedThroughputSettingsProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data GlobalTable
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-dynamodb-globaltable.html>
    GlobalTable {GlobalTable -> ()
haddock_workaround_ :: (),
                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-dynamodb-globaltable.html#cfn-dynamodb-globaltable-attributedefinitions>
                 GlobalTable -> [AttributeDefinitionProperty]
attributeDefinitions :: [AttributeDefinitionProperty],
                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-dynamodb-globaltable.html#cfn-dynamodb-globaltable-billingmode>
                 GlobalTable -> Maybe (Value Text)
billingMode :: (Prelude.Maybe (Value Prelude.Text)),
                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-dynamodb-globaltable.html#cfn-dynamodb-globaltable-globalsecondaryindexes>
                 GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalSecondaryIndexes :: (Prelude.Maybe [GlobalSecondaryIndexProperty]),
                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-dynamodb-globaltable.html#cfn-dynamodb-globaltable-globaltablewitnesses>
                 GlobalTable -> Maybe [GlobalTableWitnessProperty]
globalTableWitnesses :: (Prelude.Maybe [GlobalTableWitnessProperty]),
                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-dynamodb-globaltable.html#cfn-dynamodb-globaltable-keyschema>
                 GlobalTable -> [KeySchemaProperty]
keySchema :: [KeySchemaProperty],
                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-dynamodb-globaltable.html#cfn-dynamodb-globaltable-localsecondaryindexes>
                 GlobalTable -> Maybe [LocalSecondaryIndexProperty]
localSecondaryIndexes :: (Prelude.Maybe [LocalSecondaryIndexProperty]),
                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-dynamodb-globaltable.html#cfn-dynamodb-globaltable-multiregionconsistency>
                 GlobalTable -> Maybe (Value Text)
multiRegionConsistency :: (Prelude.Maybe (Value Prelude.Text)),
                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-dynamodb-globaltable.html#cfn-dynamodb-globaltable-replicas>
                 GlobalTable -> [ReplicaSpecificationProperty]
replicas :: [ReplicaSpecificationProperty],
                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-dynamodb-globaltable.html#cfn-dynamodb-globaltable-ssespecification>
                 GlobalTable -> Maybe SSESpecificationProperty
sSESpecification :: (Prelude.Maybe SSESpecificationProperty),
                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-dynamodb-globaltable.html#cfn-dynamodb-globaltable-streamspecification>
                 GlobalTable -> Maybe StreamSpecificationProperty
streamSpecification :: (Prelude.Maybe StreamSpecificationProperty),
                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-dynamodb-globaltable.html#cfn-dynamodb-globaltable-tablename>
                 GlobalTable -> Maybe (Value Text)
tableName :: (Prelude.Maybe (Value Prelude.Text)),
                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-dynamodb-globaltable.html#cfn-dynamodb-globaltable-timetolivespecification>
                 GlobalTable -> Maybe TimeToLiveSpecificationProperty
timeToLiveSpecification :: (Prelude.Maybe TimeToLiveSpecificationProperty),
                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-dynamodb-globaltable.html#cfn-dynamodb-globaltable-warmthroughput>
                 GlobalTable -> Maybe WarmThroughputProperty
warmThroughput :: (Prelude.Maybe WarmThroughputProperty),
                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-dynamodb-globaltable.html#cfn-dynamodb-globaltable-writeondemandthroughputsettings>
                 GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeOnDemandThroughputSettings :: (Prelude.Maybe WriteOnDemandThroughputSettingsProperty),
                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-dynamodb-globaltable.html#cfn-dynamodb-globaltable-writeprovisionedthroughputsettings>
                 GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
writeProvisionedThroughputSettings :: (Prelude.Maybe WriteProvisionedThroughputSettingsProperty)}
  deriving stock (GlobalTable -> GlobalTable -> Bool
(GlobalTable -> GlobalTable -> Bool)
-> (GlobalTable -> GlobalTable -> Bool) -> Eq GlobalTable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GlobalTable -> GlobalTable -> Bool
== :: GlobalTable -> GlobalTable -> Bool
$c/= :: GlobalTable -> GlobalTable -> Bool
/= :: GlobalTable -> GlobalTable -> Bool
Prelude.Eq, Int -> GlobalTable -> ShowS
[GlobalTable] -> ShowS
GlobalTable -> String
(Int -> GlobalTable -> ShowS)
-> (GlobalTable -> String)
-> ([GlobalTable] -> ShowS)
-> Show GlobalTable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GlobalTable -> ShowS
showsPrec :: Int -> GlobalTable -> ShowS
$cshow :: GlobalTable -> String
show :: GlobalTable -> String
$cshowList :: [GlobalTable] -> ShowS
showList :: [GlobalTable] -> ShowS
Prelude.Show)
mkGlobalTable ::
  [AttributeDefinitionProperty]
  -> [KeySchemaProperty]
     -> [ReplicaSpecificationProperty] -> GlobalTable
mkGlobalTable :: [AttributeDefinitionProperty]
-> [KeySchemaProperty]
-> [ReplicaSpecificationProperty]
-> GlobalTable
mkGlobalTable [AttributeDefinitionProperty]
attributeDefinitions [KeySchemaProperty]
keySchema [ReplicaSpecificationProperty]
replicas
  = GlobalTable
      {haddock_workaround_ :: ()
haddock_workaround_ = (),
       attributeDefinitions :: [AttributeDefinitionProperty]
attributeDefinitions = [AttributeDefinitionProperty]
attributeDefinitions, keySchema :: [KeySchemaProperty]
keySchema = [KeySchemaProperty]
keySchema,
       replicas :: [ReplicaSpecificationProperty]
replicas = [ReplicaSpecificationProperty]
replicas, billingMode :: Maybe (Value Text)
billingMode = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalSecondaryIndexes = Maybe [GlobalSecondaryIndexProperty]
forall a. Maybe a
Prelude.Nothing,
       globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
globalTableWitnesses = Maybe [GlobalTableWitnessProperty]
forall a. Maybe a
Prelude.Nothing,
       localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
localSecondaryIndexes = Maybe [LocalSecondaryIndexProperty]
forall a. Maybe a
Prelude.Nothing,
       multiRegionConsistency :: Maybe (Value Text)
multiRegionConsistency = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       sSESpecification :: Maybe SSESpecificationProperty
sSESpecification = Maybe SSESpecificationProperty
forall a. Maybe a
Prelude.Nothing,
       streamSpecification :: Maybe StreamSpecificationProperty
streamSpecification = Maybe StreamSpecificationProperty
forall a. Maybe a
Prelude.Nothing, tableName :: Maybe (Value Text)
tableName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
timeToLiveSpecification = Maybe TimeToLiveSpecificationProperty
forall a. Maybe a
Prelude.Nothing,
       warmThroughput :: Maybe WarmThroughputProperty
warmThroughput = Maybe WarmThroughputProperty
forall a. Maybe a
Prelude.Nothing,
       writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeOnDemandThroughputSettings = Maybe WriteOnDemandThroughputSettingsProperty
forall a. Maybe a
Prelude.Nothing,
       writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
writeProvisionedThroughputSettings = Maybe WriteProvisionedThroughputSettingsProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties GlobalTable where
  toResourceProperties :: GlobalTable -> ResourceProperties
toResourceProperties GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::DynamoDB::GlobalTable",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
                        ([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
                           [Key
"AttributeDefinitions" Key -> [AttributeDefinitionProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [AttributeDefinitionProperty]
attributeDefinitions,
                            Key
"KeySchema" Key -> [KeySchemaProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [KeySchemaProperty]
keySchema, Key
"Replicas" Key -> [ReplicaSpecificationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [ReplicaSpecificationProperty]
replicas]
                           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                              [Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"BillingMode" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
billingMode,
                               Key -> [GlobalSecondaryIndexProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"GlobalSecondaryIndexes"
                                 ([GlobalSecondaryIndexProperty] -> (Key, Value))
-> Maybe [GlobalSecondaryIndexProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [GlobalSecondaryIndexProperty]
globalSecondaryIndexes,
                               Key -> [GlobalTableWitnessProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"GlobalTableWitnesses" ([GlobalTableWitnessProperty] -> (Key, Value))
-> Maybe [GlobalTableWitnessProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [GlobalTableWitnessProperty]
globalTableWitnesses,
                               Key -> [LocalSecondaryIndexProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LocalSecondaryIndexes"
                                 ([LocalSecondaryIndexProperty] -> (Key, Value))
-> Maybe [LocalSecondaryIndexProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [LocalSecondaryIndexProperty]
localSecondaryIndexes,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MultiRegionConsistency"
                                 (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
multiRegionConsistency,
                               Key -> SSESpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SSESpecification" (SSESpecificationProperty -> (Key, Value))
-> Maybe SSESpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SSESpecificationProperty
sSESpecification,
                               Key -> StreamSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"StreamSpecification" (StreamSpecificationProperty -> (Key, Value))
-> Maybe StreamSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe StreamSpecificationProperty
streamSpecification,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TableName" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
tableName,
                               Key -> TimeToLiveSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TimeToLiveSpecification"
                                 (TimeToLiveSpecificationProperty -> (Key, Value))
-> Maybe TimeToLiveSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TimeToLiveSpecificationProperty
timeToLiveSpecification,
                               Key -> WarmThroughputProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"WarmThroughput" (WarmThroughputProperty -> (Key, Value))
-> Maybe WarmThroughputProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe WarmThroughputProperty
warmThroughput,
                               Key -> WriteOnDemandThroughputSettingsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"WriteOnDemandThroughputSettings"
                                 (WriteOnDemandThroughputSettingsProperty -> (Key, Value))
-> Maybe WriteOnDemandThroughputSettingsProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe WriteOnDemandThroughputSettingsProperty
writeOnDemandThroughputSettings,
                               Key -> WriteProvisionedThroughputSettingsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"WriteProvisionedThroughputSettings"
                                 (WriteProvisionedThroughputSettingsProperty -> (Key, Value))
-> Maybe WriteProvisionedThroughputSettingsProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe WriteProvisionedThroughputSettingsProperty
writeProvisionedThroughputSettings]))}
instance JSON.ToJSON GlobalTable where
  toJSON :: GlobalTable -> Value
toJSON GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = [(Key, Value)] -> Value
JSON.object
        ([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
           ([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
              [Key
"AttributeDefinitions" Key -> [AttributeDefinitionProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [AttributeDefinitionProperty]
attributeDefinitions,
               Key
"KeySchema" Key -> [KeySchemaProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [KeySchemaProperty]
keySchema, Key
"Replicas" Key -> [ReplicaSpecificationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [ReplicaSpecificationProperty]
replicas]
              ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                 [Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"BillingMode" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
billingMode,
                  Key -> [GlobalSecondaryIndexProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"GlobalSecondaryIndexes"
                    ([GlobalSecondaryIndexProperty] -> (Key, Value))
-> Maybe [GlobalSecondaryIndexProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [GlobalSecondaryIndexProperty]
globalSecondaryIndexes,
                  Key -> [GlobalTableWitnessProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"GlobalTableWitnesses" ([GlobalTableWitnessProperty] -> (Key, Value))
-> Maybe [GlobalTableWitnessProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [GlobalTableWitnessProperty]
globalTableWitnesses,
                  Key -> [LocalSecondaryIndexProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LocalSecondaryIndexes"
                    ([LocalSecondaryIndexProperty] -> (Key, Value))
-> Maybe [LocalSecondaryIndexProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [LocalSecondaryIndexProperty]
localSecondaryIndexes,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MultiRegionConsistency"
                    (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
multiRegionConsistency,
                  Key -> SSESpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SSESpecification" (SSESpecificationProperty -> (Key, Value))
-> Maybe SSESpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SSESpecificationProperty
sSESpecification,
                  Key -> StreamSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"StreamSpecification" (StreamSpecificationProperty -> (Key, Value))
-> Maybe StreamSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe StreamSpecificationProperty
streamSpecification,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TableName" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
tableName,
                  Key -> TimeToLiveSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TimeToLiveSpecification"
                    (TimeToLiveSpecificationProperty -> (Key, Value))
-> Maybe TimeToLiveSpecificationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TimeToLiveSpecificationProperty
timeToLiveSpecification,
                  Key -> WarmThroughputProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"WarmThroughput" (WarmThroughputProperty -> (Key, Value))
-> Maybe WarmThroughputProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe WarmThroughputProperty
warmThroughput,
                  Key -> WriteOnDemandThroughputSettingsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"WriteOnDemandThroughputSettings"
                    (WriteOnDemandThroughputSettingsProperty -> (Key, Value))
-> Maybe WriteOnDemandThroughputSettingsProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe WriteOnDemandThroughputSettingsProperty
writeOnDemandThroughputSettings,
                  Key -> WriteProvisionedThroughputSettingsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"WriteProvisionedThroughputSettings"
                    (WriteProvisionedThroughputSettingsProperty -> (Key, Value))
-> Maybe WriteProvisionedThroughputSettingsProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe WriteProvisionedThroughputSettingsProperty
writeProvisionedThroughputSettings])))
instance Property "AttributeDefinitions" GlobalTable where
  type PropertyType "AttributeDefinitions" GlobalTable = [AttributeDefinitionProperty]
  set :: PropertyType "AttributeDefinitions" GlobalTable
-> GlobalTable -> GlobalTable
set PropertyType "AttributeDefinitions" GlobalTable
newValue GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = GlobalTable {attributeDefinitions :: [AttributeDefinitionProperty]
attributeDefinitions = [AttributeDefinitionProperty]
PropertyType "AttributeDefinitions" GlobalTable
newValue, [KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: ()
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
instance Property "BillingMode" GlobalTable where
  type PropertyType "BillingMode" GlobalTable = Value Prelude.Text
  set :: PropertyType "BillingMode" GlobalTable
-> GlobalTable -> GlobalTable
set PropertyType "BillingMode" GlobalTable
newValue GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = GlobalTable {billingMode :: Maybe (Value Text)
billingMode = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "BillingMode" GlobalTable
Value Text
newValue, [AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
instance Property "GlobalSecondaryIndexes" GlobalTable where
  type PropertyType "GlobalSecondaryIndexes" GlobalTable = [GlobalSecondaryIndexProperty]
  set :: PropertyType "GlobalSecondaryIndexes" GlobalTable
-> GlobalTable -> GlobalTable
set PropertyType "GlobalSecondaryIndexes" GlobalTable
newValue GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = GlobalTable {globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalSecondaryIndexes = [GlobalSecondaryIndexProperty]
-> Maybe [GlobalSecondaryIndexProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [GlobalSecondaryIndexProperty]
PropertyType "GlobalSecondaryIndexes" GlobalTable
newValue, [AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
instance Property "GlobalTableWitnesses" GlobalTable where
  type PropertyType "GlobalTableWitnesses" GlobalTable = [GlobalTableWitnessProperty]
  set :: PropertyType "GlobalTableWitnesses" GlobalTable
-> GlobalTable -> GlobalTable
set PropertyType "GlobalTableWitnesses" GlobalTable
newValue GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = GlobalTable {globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
globalTableWitnesses = [GlobalTableWitnessProperty] -> Maybe [GlobalTableWitnessProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [GlobalTableWitnessProperty]
PropertyType "GlobalTableWitnesses" GlobalTable
newValue, [AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
instance Property "KeySchema" GlobalTable where
  type PropertyType "KeySchema" GlobalTable = [KeySchemaProperty]
  set :: PropertyType "KeySchema" GlobalTable -> GlobalTable -> GlobalTable
set PropertyType "KeySchema" GlobalTable
newValue GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = GlobalTable {keySchema :: [KeySchemaProperty]
keySchema = [KeySchemaProperty]
PropertyType "KeySchema" GlobalTable
newValue, [AttributeDefinitionProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
instance Property "LocalSecondaryIndexes" GlobalTable where
  type PropertyType "LocalSecondaryIndexes" GlobalTable = [LocalSecondaryIndexProperty]
  set :: PropertyType "LocalSecondaryIndexes" GlobalTable
-> GlobalTable -> GlobalTable
set PropertyType "LocalSecondaryIndexes" GlobalTable
newValue GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = GlobalTable {localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
localSecondaryIndexes = [LocalSecondaryIndexProperty]
-> Maybe [LocalSecondaryIndexProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [LocalSecondaryIndexProperty]
PropertyType "LocalSecondaryIndexes" GlobalTable
newValue, [AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
instance Property "MultiRegionConsistency" GlobalTable where
  type PropertyType "MultiRegionConsistency" GlobalTable = Value Prelude.Text
  set :: PropertyType "MultiRegionConsistency" GlobalTable
-> GlobalTable -> GlobalTable
set PropertyType "MultiRegionConsistency" GlobalTable
newValue GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = GlobalTable {multiRegionConsistency :: Maybe (Value Text)
multiRegionConsistency = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MultiRegionConsistency" GlobalTable
Value Text
newValue, [AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
instance Property "Replicas" GlobalTable where
  type PropertyType "Replicas" GlobalTable = [ReplicaSpecificationProperty]
  set :: PropertyType "Replicas" GlobalTable -> GlobalTable -> GlobalTable
set PropertyType "Replicas" GlobalTable
newValue GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = GlobalTable {replicas :: [ReplicaSpecificationProperty]
replicas = [ReplicaSpecificationProperty]
PropertyType "Replicas" GlobalTable
newValue, [AttributeDefinitionProperty]
[KeySchemaProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
instance Property "SSESpecification" GlobalTable where
  type PropertyType "SSESpecification" GlobalTable = SSESpecificationProperty
  set :: PropertyType "SSESpecification" GlobalTable
-> GlobalTable -> GlobalTable
set PropertyType "SSESpecification" GlobalTable
newValue GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = GlobalTable {sSESpecification :: Maybe SSESpecificationProperty
sSESpecification = SSESpecificationProperty -> Maybe SSESpecificationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SSESpecification" GlobalTable
SSESpecificationProperty
newValue, [AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
instance Property "StreamSpecification" GlobalTable where
  type PropertyType "StreamSpecification" GlobalTable = StreamSpecificationProperty
  set :: PropertyType "StreamSpecification" GlobalTable
-> GlobalTable -> GlobalTable
set PropertyType "StreamSpecification" GlobalTable
newValue GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = GlobalTable {streamSpecification :: Maybe StreamSpecificationProperty
streamSpecification = StreamSpecificationProperty -> Maybe StreamSpecificationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "StreamSpecification" GlobalTable
StreamSpecificationProperty
newValue, [AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
instance Property "TableName" GlobalTable where
  type PropertyType "TableName" GlobalTable = Value Prelude.Text
  set :: PropertyType "TableName" GlobalTable -> GlobalTable -> GlobalTable
set PropertyType "TableName" GlobalTable
newValue GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = GlobalTable {tableName :: Maybe (Value Text)
tableName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "TableName" GlobalTable
Value Text
newValue, [AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
instance Property "TimeToLiveSpecification" GlobalTable where
  type PropertyType "TimeToLiveSpecification" GlobalTable = TimeToLiveSpecificationProperty
  set :: PropertyType "TimeToLiveSpecification" GlobalTable
-> GlobalTable -> GlobalTable
set PropertyType "TimeToLiveSpecification" GlobalTable
newValue GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = GlobalTable {timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
timeToLiveSpecification = TimeToLiveSpecificationProperty
-> Maybe TimeToLiveSpecificationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "TimeToLiveSpecification" GlobalTable
TimeToLiveSpecificationProperty
newValue, [AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
instance Property "WarmThroughput" GlobalTable where
  type PropertyType "WarmThroughput" GlobalTable = WarmThroughputProperty
  set :: PropertyType "WarmThroughput" GlobalTable
-> GlobalTable -> GlobalTable
set PropertyType "WarmThroughput" GlobalTable
newValue GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = GlobalTable {warmThroughput :: Maybe WarmThroughputProperty
warmThroughput = WarmThroughputProperty -> Maybe WarmThroughputProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "WarmThroughput" GlobalTable
WarmThroughputProperty
newValue, [AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
instance Property "WriteOnDemandThroughputSettings" GlobalTable where
  type PropertyType "WriteOnDemandThroughputSettings" GlobalTable = WriteOnDemandThroughputSettingsProperty
  set :: PropertyType "WriteOnDemandThroughputSettings" GlobalTable
-> GlobalTable -> GlobalTable
set PropertyType "WriteOnDemandThroughputSettings" GlobalTable
newValue GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = GlobalTable
        {writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeOnDemandThroughputSettings = WriteOnDemandThroughputSettingsProperty
-> Maybe WriteOnDemandThroughputSettingsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "WriteOnDemandThroughputSettings" GlobalTable
WriteOnDemandThroughputSettingsProperty
newValue, [AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
instance Property "WriteProvisionedThroughputSettings" GlobalTable where
  type PropertyType "WriteProvisionedThroughputSettings" GlobalTable = WriteProvisionedThroughputSettingsProperty
  set :: PropertyType "WriteProvisionedThroughputSettings" GlobalTable
-> GlobalTable -> GlobalTable
set PropertyType "WriteProvisionedThroughputSettings" GlobalTable
newValue GlobalTable {[AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
Maybe WriteProvisionedThroughputSettingsProperty
()
haddock_workaround_ :: GlobalTable -> ()
attributeDefinitions :: GlobalTable -> [AttributeDefinitionProperty]
billingMode :: GlobalTable -> Maybe (Value Text)
globalSecondaryIndexes :: GlobalTable -> Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: GlobalTable -> Maybe [GlobalTableWitnessProperty]
keySchema :: GlobalTable -> [KeySchemaProperty]
localSecondaryIndexes :: GlobalTable -> Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: GlobalTable -> Maybe (Value Text)
replicas :: GlobalTable -> [ReplicaSpecificationProperty]
sSESpecification :: GlobalTable -> Maybe SSESpecificationProperty
streamSpecification :: GlobalTable -> Maybe StreamSpecificationProperty
tableName :: GlobalTable -> Maybe (Value Text)
timeToLiveSpecification :: GlobalTable -> Maybe TimeToLiveSpecificationProperty
warmThroughput :: GlobalTable -> Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: GlobalTable -> Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: GlobalTable -> Maybe WriteProvisionedThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
..}
    = GlobalTable
        {writeProvisionedThroughputSettings :: Maybe WriteProvisionedThroughputSettingsProperty
writeProvisionedThroughputSettings = WriteProvisionedThroughputSettingsProperty
-> Maybe WriteProvisionedThroughputSettingsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "WriteProvisionedThroughputSettings" GlobalTable
WriteProvisionedThroughputSettingsProperty
newValue, [AttributeDefinitionProperty]
[KeySchemaProperty]
[ReplicaSpecificationProperty]
Maybe [GlobalTableWitnessProperty]
Maybe [LocalSecondaryIndexProperty]
Maybe [GlobalSecondaryIndexProperty]
Maybe (Value Text)
Maybe SSESpecificationProperty
Maybe StreamSpecificationProperty
Maybe TimeToLiveSpecificationProperty
Maybe WarmThroughputProperty
Maybe WriteOnDemandThroughputSettingsProperty
()
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
haddock_workaround_ :: ()
attributeDefinitions :: [AttributeDefinitionProperty]
billingMode :: Maybe (Value Text)
globalSecondaryIndexes :: Maybe [GlobalSecondaryIndexProperty]
globalTableWitnesses :: Maybe [GlobalTableWitnessProperty]
keySchema :: [KeySchemaProperty]
localSecondaryIndexes :: Maybe [LocalSecondaryIndexProperty]
multiRegionConsistency :: Maybe (Value Text)
replicas :: [ReplicaSpecificationProperty]
sSESpecification :: Maybe SSESpecificationProperty
streamSpecification :: Maybe StreamSpecificationProperty
tableName :: Maybe (Value Text)
timeToLiveSpecification :: Maybe TimeToLiveSpecificationProperty
warmThroughput :: Maybe WarmThroughputProperty
writeOnDemandThroughputSettings :: Maybe WriteOnDemandThroughputSettingsProperty
..}