amazonka-dynamodb-1.6.0: Amazon DynamoDB SDK.

Copyright(c) 2013-2018 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay+amazonka@gmail.com>
Stabilityauto-generated
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.AWS.DynamoDB.Types

Contents

Description

 

Synopsis

Service Configuration

dynamoDB :: Service Source #

API version 2012-08-10 of the Amazon DynamoDB SDK configuration.

Errors

_BackupNotFoundException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Backup not found for the given BackupARN.

_TableInUseException :: AsError a => Getting (First ServiceError) a ServiceError Source #

A target table with the specified name is either being created or deleted.

_ContinuousBackupsUnavailableException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Backups have not yet been enabled for this table.

_ProvisionedThroughputExceededException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Your request rate is too high. The AWS SDKs for DynamoDB automatically retry requests that receive this exception. Your request is eventually successful, unless your retry queue is too large to finish. Reduce the frequency of requests and use exponential backoff. For more information, go to Error Retries and Exponential Backoff in the Amazon DynamoDB Developer Guide .

_GlobalTableNotFoundException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The specified global table does not exist.

_ConditionalCheckFailedException :: AsError a => Getting (First ServiceError) a ServiceError Source #

A condition specified in the operation could not be evaluated.

_GlobalTableAlreadyExistsException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The specified global table already exists.

_ReplicaNotFoundException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The specified replica is no longer part of the global table.

_TableAlreadyExistsException :: AsError a => Getting (First ServiceError) a ServiceError Source #

A target table with the specified name already exists.

_ItemCollectionSizeLimitExceededException :: AsError a => Getting (First ServiceError) a ServiceError Source #

An item collection is too large. This exception is only returned for tables that have one or more local secondary indexes.

_InternalServerError :: AsError a => Getting (First ServiceError) a ServiceError Source #

An error occurred on the server side.

_TableNotFoundException :: AsError a => Getting (First ServiceError) a ServiceError Source #

A source table with the name TableName does not currently exist within the subscriber's account.

_IndexNotFoundException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The operation tried to access a nonexistent index.

_BackupInUseException :: AsError a => Getting (First ServiceError) a ServiceError Source #

There is another ongoing conflicting backup control plane operation on the table. The backups is either being created, deleted or restored to a table.

_PointInTimeRecoveryUnavailableException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Point in time recovery has not yet been enabled for this source table.

_InvalidRestoreTimeException :: AsError a => Getting (First ServiceError) a ServiceError Source #

An invalid restore time was specified. RestoreDateTime must be between EarliestRestorableDateTime and LatestRestorableDateTime.

_ResourceNotFoundException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The operation tried to access a nonexistent table or index. The resource might not be specified correctly, or its status might not be ACTIVE .

_ReplicaAlreadyExistsException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The specified replica is already part of the global table.

_LimitExceededException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Up to 50 CreateBackup operations are allowed per second, per account. There is no limit to the number of daily on-demand backups that can be taken.

Up to 10 simultaneous table operations are allowed per account. These operations include CreateTable , UpdateTable , DeleteTable ,UpdateTimeToLive , RestoreTableFromBackup , and RestoreTableToPointInTime .

For tables with secondary indexes, only one of those tables can be in the CREATING state at any point in time. Do not attempt to create more than one such table simultaneously.

The total limit of tables in the ACTIVE state is 250.

_ResourceInUseException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The operation conflicts with the resource's availability. For example, you attempted to recreate an existing table, or tried to delete a table currently in the CREATING state.

AttributeAction

data AttributeAction Source #

Constructors

Add 
Delete 
Put 

Instances

Bounded AttributeAction Source # 
Enum AttributeAction Source # 
Eq AttributeAction Source # 
Data AttributeAction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AttributeAction -> c AttributeAction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AttributeAction #

toConstr :: AttributeAction -> Constr #

dataTypeOf :: AttributeAction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AttributeAction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AttributeAction) #

gmapT :: (forall b. Data b => b -> b) -> AttributeAction -> AttributeAction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AttributeAction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AttributeAction -> r #

gmapQ :: (forall d. Data d => d -> u) -> AttributeAction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AttributeAction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AttributeAction -> m AttributeAction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeAction -> m AttributeAction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeAction -> m AttributeAction #

Ord AttributeAction Source # 
Read AttributeAction Source # 
Show AttributeAction Source # 
Generic AttributeAction Source # 
Hashable AttributeAction Source # 
ToJSON AttributeAction Source # 
NFData AttributeAction Source # 

Methods

rnf :: AttributeAction -> () #

ToHeader AttributeAction Source # 
ToQuery AttributeAction Source # 
ToByteString AttributeAction Source # 
FromText AttributeAction Source # 
ToText AttributeAction Source # 
type Rep AttributeAction Source # 
type Rep AttributeAction = D1 * (MetaData "AttributeAction" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * (C1 * (MetaCons "Add" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Delete" PrefixI False) (U1 *)) (C1 * (MetaCons "Put" PrefixI False) (U1 *))))

BackupStatus

data BackupStatus Source #

Constructors

Available 
Creating 
Deleted 

Instances

Bounded BackupStatus Source # 
Enum BackupStatus Source # 
Eq BackupStatus Source # 
Data BackupStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BackupStatus -> c BackupStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BackupStatus #

toConstr :: BackupStatus -> Constr #

dataTypeOf :: BackupStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BackupStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BackupStatus) #

gmapT :: (forall b. Data b => b -> b) -> BackupStatus -> BackupStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BackupStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BackupStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> BackupStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BackupStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BackupStatus -> m BackupStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BackupStatus -> m BackupStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BackupStatus -> m BackupStatus #

Ord BackupStatus Source # 
Read BackupStatus Source # 
Show BackupStatus Source # 
Generic BackupStatus Source # 

Associated Types

type Rep BackupStatus :: * -> * #

Hashable BackupStatus Source # 
FromJSON BackupStatus Source # 
NFData BackupStatus Source # 

Methods

rnf :: BackupStatus -> () #

ToHeader BackupStatus Source # 
ToQuery BackupStatus Source # 
ToByteString BackupStatus Source # 
FromText BackupStatus Source # 
ToText BackupStatus Source # 

Methods

toText :: BackupStatus -> Text #

type Rep BackupStatus Source # 
type Rep BackupStatus = D1 * (MetaData "BackupStatus" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * (C1 * (MetaCons "Available" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Creating" PrefixI False) (U1 *)) (C1 * (MetaCons "Deleted" PrefixI False) (U1 *))))

ComparisonOperator

data ComparisonOperator Source #

Instances

Bounded ComparisonOperator Source # 
Enum ComparisonOperator Source # 
Eq ComparisonOperator Source # 
Data ComparisonOperator Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ComparisonOperator -> c ComparisonOperator #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ComparisonOperator #

toConstr :: ComparisonOperator -> Constr #

dataTypeOf :: ComparisonOperator -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ComparisonOperator) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ComparisonOperator) #

gmapT :: (forall b. Data b => b -> b) -> ComparisonOperator -> ComparisonOperator #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ComparisonOperator -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ComparisonOperator -> r #

gmapQ :: (forall d. Data d => d -> u) -> ComparisonOperator -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ComparisonOperator -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ComparisonOperator -> m ComparisonOperator #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ComparisonOperator -> m ComparisonOperator #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ComparisonOperator -> m ComparisonOperator #

Ord ComparisonOperator Source # 
Read ComparisonOperator Source # 
Show ComparisonOperator Source # 
Generic ComparisonOperator Source # 
Hashable ComparisonOperator Source # 
ToJSON ComparisonOperator Source # 
NFData ComparisonOperator Source # 

Methods

rnf :: ComparisonOperator -> () #

ToHeader ComparisonOperator Source # 
ToQuery ComparisonOperator Source # 
ToByteString ComparisonOperator Source # 
FromText ComparisonOperator Source # 
ToText ComparisonOperator Source # 
type Rep ComparisonOperator Source # 
type Rep ComparisonOperator = D1 * (MetaData "ComparisonOperator" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "BeginsWith" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Between" PrefixI False) (U1 *)) (C1 * (MetaCons "Contains" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "EQ'" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "GE" PrefixI False) (U1 *)) (C1 * (MetaCons "GT'" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "IN" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "LE" PrefixI False) (U1 *)) (C1 * (MetaCons "LT'" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "NE" PrefixI False) (U1 *)) (C1 * (MetaCons "NotContains" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NotNull" PrefixI False) (U1 *)) (C1 * (MetaCons "Null" PrefixI False) (U1 *))))))

ConditionalOperator

data ConditionalOperator Source #

Constructors

And 
OR 

Instances

Bounded ConditionalOperator Source # 
Enum ConditionalOperator Source # 
Eq ConditionalOperator Source # 
Data ConditionalOperator Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConditionalOperator -> c ConditionalOperator #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConditionalOperator #

toConstr :: ConditionalOperator -> Constr #

dataTypeOf :: ConditionalOperator -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConditionalOperator) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConditionalOperator) #

gmapT :: (forall b. Data b => b -> b) -> ConditionalOperator -> ConditionalOperator #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConditionalOperator -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConditionalOperator -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConditionalOperator -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConditionalOperator -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConditionalOperator -> m ConditionalOperator #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConditionalOperator -> m ConditionalOperator #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConditionalOperator -> m ConditionalOperator #

Ord ConditionalOperator Source # 
Read ConditionalOperator Source # 
Show ConditionalOperator Source # 
Generic ConditionalOperator Source # 
Hashable ConditionalOperator Source # 
ToJSON ConditionalOperator Source # 
NFData ConditionalOperator Source # 

Methods

rnf :: ConditionalOperator -> () #

ToHeader ConditionalOperator Source # 
ToQuery ConditionalOperator Source # 
ToByteString ConditionalOperator Source # 
FromText ConditionalOperator Source # 
ToText ConditionalOperator Source # 
type Rep ConditionalOperator Source # 
type Rep ConditionalOperator = D1 * (MetaData "ConditionalOperator" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * (C1 * (MetaCons "And" PrefixI False) (U1 *)) (C1 * (MetaCons "OR" PrefixI False) (U1 *)))

ContinuousBackupsStatus

data ContinuousBackupsStatus Source #

Constructors

CBSDisabled 
CBSEnabled 

Instances

Bounded ContinuousBackupsStatus Source # 
Enum ContinuousBackupsStatus Source # 
Eq ContinuousBackupsStatus Source # 
Data ContinuousBackupsStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ContinuousBackupsStatus -> c ContinuousBackupsStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ContinuousBackupsStatus #

toConstr :: ContinuousBackupsStatus -> Constr #

dataTypeOf :: ContinuousBackupsStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ContinuousBackupsStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ContinuousBackupsStatus) #

gmapT :: (forall b. Data b => b -> b) -> ContinuousBackupsStatus -> ContinuousBackupsStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ContinuousBackupsStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ContinuousBackupsStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> ContinuousBackupsStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ContinuousBackupsStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ContinuousBackupsStatus -> m ContinuousBackupsStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ContinuousBackupsStatus -> m ContinuousBackupsStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ContinuousBackupsStatus -> m ContinuousBackupsStatus #

Ord ContinuousBackupsStatus Source # 
Read ContinuousBackupsStatus Source # 
Show ContinuousBackupsStatus Source # 
Generic ContinuousBackupsStatus Source # 
Hashable ContinuousBackupsStatus Source # 
FromJSON ContinuousBackupsStatus Source # 
NFData ContinuousBackupsStatus Source # 

Methods

rnf :: ContinuousBackupsStatus -> () #

ToHeader ContinuousBackupsStatus Source # 
ToQuery ContinuousBackupsStatus Source # 
ToByteString ContinuousBackupsStatus Source # 
FromText ContinuousBackupsStatus Source # 
ToText ContinuousBackupsStatus Source # 
type Rep ContinuousBackupsStatus Source # 
type Rep ContinuousBackupsStatus = D1 * (MetaData "ContinuousBackupsStatus" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * (C1 * (MetaCons "CBSDisabled" PrefixI False) (U1 *)) (C1 * (MetaCons "CBSEnabled" PrefixI False) (U1 *)))

GlobalTableStatus

data GlobalTableStatus Source #

Instances

Bounded GlobalTableStatus Source # 
Enum GlobalTableStatus Source # 
Eq GlobalTableStatus Source # 
Data GlobalTableStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GlobalTableStatus -> c GlobalTableStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GlobalTableStatus #

toConstr :: GlobalTableStatus -> Constr #

dataTypeOf :: GlobalTableStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GlobalTableStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GlobalTableStatus) #

gmapT :: (forall b. Data b => b -> b) -> GlobalTableStatus -> GlobalTableStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlobalTableStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlobalTableStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> GlobalTableStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GlobalTableStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlobalTableStatus -> m GlobalTableStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalTableStatus -> m GlobalTableStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalTableStatus -> m GlobalTableStatus #

Ord GlobalTableStatus Source # 
Read GlobalTableStatus Source # 
Show GlobalTableStatus Source # 
Generic GlobalTableStatus Source # 
Hashable GlobalTableStatus Source # 
FromJSON GlobalTableStatus Source # 
NFData GlobalTableStatus Source # 

Methods

rnf :: GlobalTableStatus -> () #

ToHeader GlobalTableStatus Source # 
ToQuery GlobalTableStatus Source # 
ToByteString GlobalTableStatus Source # 
FromText GlobalTableStatus Source # 
ToText GlobalTableStatus Source # 
type Rep GlobalTableStatus Source # 
type Rep GlobalTableStatus = D1 * (MetaData "GlobalTableStatus" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * ((:+:) * (C1 * (MetaCons "GTSActive" PrefixI False) (U1 *)) (C1 * (MetaCons "GTSCreating" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "GTSDeleting" PrefixI False) (U1 *)) (C1 * (MetaCons "GTSUpdating" PrefixI False) (U1 *))))

IndexStatus

data IndexStatus Source #

Instances

Bounded IndexStatus Source # 
Enum IndexStatus Source # 
Eq IndexStatus Source # 
Data IndexStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IndexStatus -> c IndexStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IndexStatus #

toConstr :: IndexStatus -> Constr #

dataTypeOf :: IndexStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c IndexStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IndexStatus) #

gmapT :: (forall b. Data b => b -> b) -> IndexStatus -> IndexStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IndexStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IndexStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> IndexStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IndexStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IndexStatus -> m IndexStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IndexStatus -> m IndexStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IndexStatus -> m IndexStatus #

Ord IndexStatus Source # 
Read IndexStatus Source # 
Show IndexStatus Source # 
Generic IndexStatus Source # 

Associated Types

type Rep IndexStatus :: * -> * #

Hashable IndexStatus Source # 
FromJSON IndexStatus Source # 
NFData IndexStatus Source # 

Methods

rnf :: IndexStatus -> () #

ToHeader IndexStatus Source # 
ToQuery IndexStatus Source # 
ToByteString IndexStatus Source # 
FromText IndexStatus Source # 
ToText IndexStatus Source # 

Methods

toText :: IndexStatus -> Text #

type Rep IndexStatus Source # 
type Rep IndexStatus = D1 * (MetaData "IndexStatus" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ISActive" PrefixI False) (U1 *)) (C1 * (MetaCons "ISCreating" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ISDeleting" PrefixI False) (U1 *)) (C1 * (MetaCons "ISUpdating" PrefixI False) (U1 *))))

KeyType

data KeyType Source #

Constructors

Hash 
Range 

Instances

Bounded KeyType Source # 
Enum KeyType Source # 
Eq KeyType Source # 

Methods

(==) :: KeyType -> KeyType -> Bool #

(/=) :: KeyType -> KeyType -> Bool #

Data KeyType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KeyType -> c KeyType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KeyType #

toConstr :: KeyType -> Constr #

dataTypeOf :: KeyType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c KeyType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KeyType) #

gmapT :: (forall b. Data b => b -> b) -> KeyType -> KeyType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KeyType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KeyType -> r #

gmapQ :: (forall d. Data d => d -> u) -> KeyType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> KeyType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> KeyType -> m KeyType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyType -> m KeyType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyType -> m KeyType #

Ord KeyType Source # 
Read KeyType Source # 
Show KeyType Source # 
Generic KeyType Source # 

Associated Types

type Rep KeyType :: * -> * #

Methods

from :: KeyType -> Rep KeyType x #

to :: Rep KeyType x -> KeyType #

Hashable KeyType Source # 

Methods

hashWithSalt :: Int -> KeyType -> Int #

hash :: KeyType -> Int #

ToJSON KeyType Source # 
FromJSON KeyType Source # 
NFData KeyType Source # 

Methods

rnf :: KeyType -> () #

ToHeader KeyType Source # 

Methods

toHeader :: HeaderName -> KeyType -> [Header] #

ToQuery KeyType Source # 
ToByteString KeyType Source # 

Methods

toBS :: KeyType -> ByteString #

FromText KeyType Source # 
ToText KeyType Source # 

Methods

toText :: KeyType -> Text #

type Rep KeyType Source # 
type Rep KeyType = D1 * (MetaData "KeyType" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * (C1 * (MetaCons "Hash" PrefixI False) (U1 *)) (C1 * (MetaCons "Range" PrefixI False) (U1 *)))

PointInTimeRecoveryStatus

data PointInTimeRecoveryStatus Source #

Instances

Bounded PointInTimeRecoveryStatus Source # 
Enum PointInTimeRecoveryStatus Source # 
Eq PointInTimeRecoveryStatus Source # 
Data PointInTimeRecoveryStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PointInTimeRecoveryStatus -> c PointInTimeRecoveryStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PointInTimeRecoveryStatus #

toConstr :: PointInTimeRecoveryStatus -> Constr #

dataTypeOf :: PointInTimeRecoveryStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PointInTimeRecoveryStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PointInTimeRecoveryStatus) #

gmapT :: (forall b. Data b => b -> b) -> PointInTimeRecoveryStatus -> PointInTimeRecoveryStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PointInTimeRecoveryStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PointInTimeRecoveryStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> PointInTimeRecoveryStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PointInTimeRecoveryStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PointInTimeRecoveryStatus -> m PointInTimeRecoveryStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PointInTimeRecoveryStatus -> m PointInTimeRecoveryStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PointInTimeRecoveryStatus -> m PointInTimeRecoveryStatus #

Ord PointInTimeRecoveryStatus Source # 
Read PointInTimeRecoveryStatus Source # 
Show PointInTimeRecoveryStatus Source # 
Generic PointInTimeRecoveryStatus Source # 
Hashable PointInTimeRecoveryStatus Source # 
FromJSON PointInTimeRecoveryStatus Source # 
NFData PointInTimeRecoveryStatus Source # 
ToHeader PointInTimeRecoveryStatus Source # 
ToQuery PointInTimeRecoveryStatus Source # 
ToByteString PointInTimeRecoveryStatus Source # 
FromText PointInTimeRecoveryStatus Source # 
ToText PointInTimeRecoveryStatus Source # 
type Rep PointInTimeRecoveryStatus Source # 
type Rep PointInTimeRecoveryStatus = D1 * (MetaData "PointInTimeRecoveryStatus" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * (C1 * (MetaCons "PITRSDisabled" PrefixI False) (U1 *)) (C1 * (MetaCons "PITRSEnabled" PrefixI False) (U1 *)))

ProjectionType

data ProjectionType Source #

Constructors

PTAll 
PTInclude 
PTKeysOnly 

Instances

Bounded ProjectionType Source # 
Enum ProjectionType Source # 
Eq ProjectionType Source # 
Data ProjectionType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProjectionType -> c ProjectionType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProjectionType #

toConstr :: ProjectionType -> Constr #

dataTypeOf :: ProjectionType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ProjectionType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProjectionType) #

gmapT :: (forall b. Data b => b -> b) -> ProjectionType -> ProjectionType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProjectionType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProjectionType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProjectionType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProjectionType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProjectionType -> m ProjectionType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProjectionType -> m ProjectionType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProjectionType -> m ProjectionType #

Ord ProjectionType Source # 
Read ProjectionType Source # 
Show ProjectionType Source # 
Generic ProjectionType Source # 

Associated Types

type Rep ProjectionType :: * -> * #

Hashable ProjectionType Source # 
ToJSON ProjectionType Source # 
FromJSON ProjectionType Source # 
NFData ProjectionType Source # 

Methods

rnf :: ProjectionType -> () #

ToHeader ProjectionType Source # 
ToQuery ProjectionType Source # 
ToByteString ProjectionType Source # 
FromText ProjectionType Source # 
ToText ProjectionType Source # 
type Rep ProjectionType Source # 
type Rep ProjectionType = D1 * (MetaData "ProjectionType" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * (C1 * (MetaCons "PTAll" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PTInclude" PrefixI False) (U1 *)) (C1 * (MetaCons "PTKeysOnly" PrefixI False) (U1 *))))

ReplicaStatus

data ReplicaStatus Source #

Instances

Bounded ReplicaStatus Source # 
Enum ReplicaStatus Source # 
Eq ReplicaStatus Source # 
Data ReplicaStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReplicaStatus -> c ReplicaStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReplicaStatus #

toConstr :: ReplicaStatus -> Constr #

dataTypeOf :: ReplicaStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReplicaStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReplicaStatus) #

gmapT :: (forall b. Data b => b -> b) -> ReplicaStatus -> ReplicaStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReplicaStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReplicaStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReplicaStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReplicaStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReplicaStatus -> m ReplicaStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicaStatus -> m ReplicaStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicaStatus -> m ReplicaStatus #

Ord ReplicaStatus Source # 
Read ReplicaStatus Source # 
Show ReplicaStatus Source # 
Generic ReplicaStatus Source # 

Associated Types

type Rep ReplicaStatus :: * -> * #

Hashable ReplicaStatus Source # 
FromJSON ReplicaStatus Source # 
NFData ReplicaStatus Source # 

Methods

rnf :: ReplicaStatus -> () #

ToHeader ReplicaStatus Source # 
ToQuery ReplicaStatus Source # 
ToByteString ReplicaStatus Source # 
FromText ReplicaStatus Source # 
ToText ReplicaStatus Source # 

Methods

toText :: ReplicaStatus -> Text #

type Rep ReplicaStatus Source # 
type Rep ReplicaStatus = D1 * (MetaData "ReplicaStatus" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * ((:+:) * (C1 * (MetaCons "RSActive" PrefixI False) (U1 *)) (C1 * (MetaCons "RSCreating" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "RSDeleting" PrefixI False) (U1 *)) (C1 * (MetaCons "RSUpdating" PrefixI False) (U1 *))))

ReturnConsumedCapacity

data ReturnConsumedCapacity Source #

Determines the level of detail about provisioned throughput consumption that is returned in the response:

  • INDEXES - The response includes the aggregate ConsumedCapacity for the operation, together with ConsumedCapacity for each table and secondary index that was accessed.

Note that some operations, such as GetItem and BatchGetItem , do not access any indexes at all. In these cases, specifying INDEXES will only return ConsumedCapacity information for table(s).

  • TOTAL - The response includes only the aggregate ConsumedCapacity for the operation.
  • NONE - No ConsumedCapacity details are included in the response.

Constructors

RCCIndexes 
RCCNone 
RCCTotal 

Instances

Bounded ReturnConsumedCapacity Source # 
Enum ReturnConsumedCapacity Source # 
Eq ReturnConsumedCapacity Source # 
Data ReturnConsumedCapacity Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReturnConsumedCapacity -> c ReturnConsumedCapacity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReturnConsumedCapacity #

toConstr :: ReturnConsumedCapacity -> Constr #

dataTypeOf :: ReturnConsumedCapacity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReturnConsumedCapacity) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReturnConsumedCapacity) #

gmapT :: (forall b. Data b => b -> b) -> ReturnConsumedCapacity -> ReturnConsumedCapacity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReturnConsumedCapacity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReturnConsumedCapacity -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReturnConsumedCapacity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReturnConsumedCapacity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReturnConsumedCapacity -> m ReturnConsumedCapacity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReturnConsumedCapacity -> m ReturnConsumedCapacity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReturnConsumedCapacity -> m ReturnConsumedCapacity #

Ord ReturnConsumedCapacity Source # 
Read ReturnConsumedCapacity Source # 
Show ReturnConsumedCapacity Source # 
Generic ReturnConsumedCapacity Source # 
Hashable ReturnConsumedCapacity Source # 
ToJSON ReturnConsumedCapacity Source # 
NFData ReturnConsumedCapacity Source # 

Methods

rnf :: ReturnConsumedCapacity -> () #

ToHeader ReturnConsumedCapacity Source # 
ToQuery ReturnConsumedCapacity Source # 
ToByteString ReturnConsumedCapacity Source # 
FromText ReturnConsumedCapacity Source # 
ToText ReturnConsumedCapacity Source # 
type Rep ReturnConsumedCapacity Source # 
type Rep ReturnConsumedCapacity = D1 * (MetaData "ReturnConsumedCapacity" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * (C1 * (MetaCons "RCCIndexes" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "RCCNone" PrefixI False) (U1 *)) (C1 * (MetaCons "RCCTotal" PrefixI False) (U1 *))))

ReturnItemCollectionMetrics

data ReturnItemCollectionMetrics Source #

Constructors

RICMNone 
RICMSize 

Instances

Bounded ReturnItemCollectionMetrics Source # 
Enum ReturnItemCollectionMetrics Source # 
Eq ReturnItemCollectionMetrics Source # 
Data ReturnItemCollectionMetrics Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReturnItemCollectionMetrics -> c ReturnItemCollectionMetrics #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReturnItemCollectionMetrics #

toConstr :: ReturnItemCollectionMetrics -> Constr #

dataTypeOf :: ReturnItemCollectionMetrics -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReturnItemCollectionMetrics) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReturnItemCollectionMetrics) #

gmapT :: (forall b. Data b => b -> b) -> ReturnItemCollectionMetrics -> ReturnItemCollectionMetrics #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReturnItemCollectionMetrics -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReturnItemCollectionMetrics -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReturnItemCollectionMetrics -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReturnItemCollectionMetrics -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReturnItemCollectionMetrics -> m ReturnItemCollectionMetrics #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReturnItemCollectionMetrics -> m ReturnItemCollectionMetrics #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReturnItemCollectionMetrics -> m ReturnItemCollectionMetrics #

Ord ReturnItemCollectionMetrics Source # 
Read ReturnItemCollectionMetrics Source # 
Show ReturnItemCollectionMetrics Source # 
Generic ReturnItemCollectionMetrics Source # 
Hashable ReturnItemCollectionMetrics Source # 
ToJSON ReturnItemCollectionMetrics Source # 
NFData ReturnItemCollectionMetrics Source # 
ToHeader ReturnItemCollectionMetrics Source # 
ToQuery ReturnItemCollectionMetrics Source # 
ToByteString ReturnItemCollectionMetrics Source # 
FromText ReturnItemCollectionMetrics Source # 
ToText ReturnItemCollectionMetrics Source # 
type Rep ReturnItemCollectionMetrics Source # 
type Rep ReturnItemCollectionMetrics = D1 * (MetaData "ReturnItemCollectionMetrics" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * (C1 * (MetaCons "RICMNone" PrefixI False) (U1 *)) (C1 * (MetaCons "RICMSize" PrefixI False) (U1 *)))

ReturnValue

data ReturnValue Source #

Instances

Bounded ReturnValue Source # 
Enum ReturnValue Source # 
Eq ReturnValue Source # 
Data ReturnValue Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReturnValue -> c ReturnValue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReturnValue #

toConstr :: ReturnValue -> Constr #

dataTypeOf :: ReturnValue -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReturnValue) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReturnValue) #

gmapT :: (forall b. Data b => b -> b) -> ReturnValue -> ReturnValue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReturnValue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReturnValue -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReturnValue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReturnValue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReturnValue -> m ReturnValue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReturnValue -> m ReturnValue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReturnValue -> m ReturnValue #

Ord ReturnValue Source # 
Read ReturnValue Source # 
Show ReturnValue Source # 
Generic ReturnValue Source # 

Associated Types

type Rep ReturnValue :: * -> * #

Hashable ReturnValue Source # 
ToJSON ReturnValue Source # 
NFData ReturnValue Source # 

Methods

rnf :: ReturnValue -> () #

ToHeader ReturnValue Source # 
ToQuery ReturnValue Source # 
ToByteString ReturnValue Source # 
FromText ReturnValue Source # 
ToText ReturnValue Source # 

Methods

toText :: ReturnValue -> Text #

type Rep ReturnValue Source # 
type Rep ReturnValue = D1 * (MetaData "ReturnValue" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * ((:+:) * (C1 * (MetaCons "AllNew" PrefixI False) (U1 *)) (C1 * (MetaCons "AllOld" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "None" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "UpdatedNew" PrefixI False) (U1 *)) (C1 * (MetaCons "UpdatedOld" PrefixI False) (U1 *)))))

SSEStatus

data SSEStatus Source #

Instances

Bounded SSEStatus Source # 
Enum SSEStatus Source # 
Eq SSEStatus Source # 
Data SSEStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SSEStatus -> c SSEStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SSEStatus #

toConstr :: SSEStatus -> Constr #

dataTypeOf :: SSEStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SSEStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SSEStatus) #

gmapT :: (forall b. Data b => b -> b) -> SSEStatus -> SSEStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SSEStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SSEStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> SSEStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SSEStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SSEStatus -> m SSEStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SSEStatus -> m SSEStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SSEStatus -> m SSEStatus #

Ord SSEStatus Source # 
Read SSEStatus Source # 
Show SSEStatus Source # 
Generic SSEStatus Source # 

Associated Types

type Rep SSEStatus :: * -> * #

Hashable SSEStatus Source # 
FromJSON SSEStatus Source # 
NFData SSEStatus Source # 

Methods

rnf :: SSEStatus -> () #

ToHeader SSEStatus Source # 
ToQuery SSEStatus Source # 
ToByteString SSEStatus Source # 

Methods

toBS :: SSEStatus -> ByteString #

FromText SSEStatus Source # 
ToText SSEStatus Source # 

Methods

toText :: SSEStatus -> Text #

type Rep SSEStatus Source # 
type Rep SSEStatus = D1 * (MetaData "SSEStatus" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * ((:+:) * (C1 * (MetaCons "SSESDisabled" PrefixI False) (U1 *)) (C1 * (MetaCons "SSESDisabling" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "SSESEnabled" PrefixI False) (U1 *)) (C1 * (MetaCons "SSESEnabling" PrefixI False) (U1 *))))

ScalarAttributeType

data ScalarAttributeType Source #

Constructors

B 
N 
S 

Instances

Bounded ScalarAttributeType Source # 
Enum ScalarAttributeType Source # 
Eq ScalarAttributeType Source # 
Data ScalarAttributeType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScalarAttributeType -> c ScalarAttributeType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScalarAttributeType #

toConstr :: ScalarAttributeType -> Constr #

dataTypeOf :: ScalarAttributeType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ScalarAttributeType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScalarAttributeType) #

gmapT :: (forall b. Data b => b -> b) -> ScalarAttributeType -> ScalarAttributeType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScalarAttributeType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScalarAttributeType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ScalarAttributeType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ScalarAttributeType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScalarAttributeType -> m ScalarAttributeType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScalarAttributeType -> m ScalarAttributeType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScalarAttributeType -> m ScalarAttributeType #

Ord ScalarAttributeType Source # 
Read ScalarAttributeType Source # 
Show ScalarAttributeType Source # 
Generic ScalarAttributeType Source # 
Hashable ScalarAttributeType Source # 
ToJSON ScalarAttributeType Source # 
FromJSON ScalarAttributeType Source # 
NFData ScalarAttributeType Source # 

Methods

rnf :: ScalarAttributeType -> () #

ToHeader ScalarAttributeType Source # 
ToQuery ScalarAttributeType Source # 
ToByteString ScalarAttributeType Source # 
FromText ScalarAttributeType Source # 
ToText ScalarAttributeType Source # 
type Rep ScalarAttributeType Source # 
type Rep ScalarAttributeType = D1 * (MetaData "ScalarAttributeType" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * (C1 * (MetaCons "B" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "N" PrefixI False) (U1 *)) (C1 * (MetaCons "S" PrefixI False) (U1 *))))

Select

data Select Source #

Instances

Bounded Select Source # 
Enum Select Source # 
Eq Select Source # 

Methods

(==) :: Select -> Select -> Bool #

(/=) :: Select -> Select -> Bool #

Data Select Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Select -> c Select #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Select #

toConstr :: Select -> Constr #

dataTypeOf :: Select -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Select) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Select) #

gmapT :: (forall b. Data b => b -> b) -> Select -> Select #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Select -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Select -> r #

gmapQ :: (forall d. Data d => d -> u) -> Select -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Select -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Select -> m Select #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Select -> m Select #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Select -> m Select #

Ord Select Source # 
Read Select Source # 
Show Select Source # 
Generic Select Source # 

Associated Types

type Rep Select :: * -> * #

Methods

from :: Select -> Rep Select x #

to :: Rep Select x -> Select #

Hashable Select Source # 

Methods

hashWithSalt :: Int -> Select -> Int #

hash :: Select -> Int #

ToJSON Select Source # 
NFData Select Source # 

Methods

rnf :: Select -> () #

ToHeader Select Source # 

Methods

toHeader :: HeaderName -> Select -> [Header] #

ToQuery Select Source # 
ToByteString Select Source # 

Methods

toBS :: Select -> ByteString #

FromText Select Source # 

Methods

parser :: Parser Select #

ToText Select Source # 

Methods

toText :: Select -> Text #

type Rep Select Source # 
type Rep Select = D1 * (MetaData "Select" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * ((:+:) * (C1 * (MetaCons "AllAttributes" PrefixI False) (U1 *)) (C1 * (MetaCons "AllProjectedAttributes" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Count" PrefixI False) (U1 *)) (C1 * (MetaCons "SpecificAttributes" PrefixI False) (U1 *))))

StreamViewType

data StreamViewType Source #

Instances

Bounded StreamViewType Source # 
Enum StreamViewType Source # 
Eq StreamViewType Source # 
Data StreamViewType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StreamViewType -> c StreamViewType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StreamViewType #

toConstr :: StreamViewType -> Constr #

dataTypeOf :: StreamViewType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StreamViewType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StreamViewType) #

gmapT :: (forall b. Data b => b -> b) -> StreamViewType -> StreamViewType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StreamViewType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StreamViewType -> r #

gmapQ :: (forall d. Data d => d -> u) -> StreamViewType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StreamViewType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StreamViewType -> m StreamViewType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StreamViewType -> m StreamViewType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StreamViewType -> m StreamViewType #

Ord StreamViewType Source # 
Read StreamViewType Source # 
Show StreamViewType Source # 
Generic StreamViewType Source # 

Associated Types

type Rep StreamViewType :: * -> * #

Hashable StreamViewType Source # 
ToJSON StreamViewType Source # 
FromJSON StreamViewType Source # 
NFData StreamViewType Source # 

Methods

rnf :: StreamViewType -> () #

ToHeader StreamViewType Source # 
ToQuery StreamViewType Source # 
ToByteString StreamViewType Source # 
FromText StreamViewType Source # 
ToText StreamViewType Source # 
type Rep StreamViewType Source # 
type Rep StreamViewType = D1 * (MetaData "StreamViewType" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * ((:+:) * (C1 * (MetaCons "KeysOnly" PrefixI False) (U1 *)) (C1 * (MetaCons "NewAndOldImages" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "NewImage" PrefixI False) (U1 *)) (C1 * (MetaCons "OldImage" PrefixI False) (U1 *))))

TableStatus

data TableStatus Source #

Instances

Bounded TableStatus Source # 
Enum TableStatus Source # 
Eq TableStatus Source # 
Data TableStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableStatus -> c TableStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableStatus #

toConstr :: TableStatus -> Constr #

dataTypeOf :: TableStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TableStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableStatus) #

gmapT :: (forall b. Data b => b -> b) -> TableStatus -> TableStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> TableStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TableStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableStatus -> m TableStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableStatus -> m TableStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableStatus -> m TableStatus #

Ord TableStatus Source # 
Read TableStatus Source # 
Show TableStatus Source # 
Generic TableStatus Source # 

Associated Types

type Rep TableStatus :: * -> * #

Hashable TableStatus Source # 
FromJSON TableStatus Source # 
NFData TableStatus Source # 

Methods

rnf :: TableStatus -> () #

ToHeader TableStatus Source # 
ToQuery TableStatus Source # 
ToByteString TableStatus Source # 
FromText TableStatus Source # 
ToText TableStatus Source # 

Methods

toText :: TableStatus -> Text #

type Rep TableStatus Source # 
type Rep TableStatus = D1 * (MetaData "TableStatus" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * ((:+:) * (C1 * (MetaCons "TSActive" PrefixI False) (U1 *)) (C1 * (MetaCons "TSCreating" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "TSDeleting" PrefixI False) (U1 *)) (C1 * (MetaCons "TSUpdating" PrefixI False) (U1 *))))

TimeToLiveStatus

data TimeToLiveStatus Source #

Instances

Bounded TimeToLiveStatus Source # 
Enum TimeToLiveStatus Source # 
Eq TimeToLiveStatus Source # 
Data TimeToLiveStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeToLiveStatus -> c TimeToLiveStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeToLiveStatus #

toConstr :: TimeToLiveStatus -> Constr #

dataTypeOf :: TimeToLiveStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TimeToLiveStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeToLiveStatus) #

gmapT :: (forall b. Data b => b -> b) -> TimeToLiveStatus -> TimeToLiveStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeToLiveStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeToLiveStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> TimeToLiveStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeToLiveStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeToLiveStatus -> m TimeToLiveStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeToLiveStatus -> m TimeToLiveStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeToLiveStatus -> m TimeToLiveStatus #

Ord TimeToLiveStatus Source # 
Read TimeToLiveStatus Source # 
Show TimeToLiveStatus Source # 
Generic TimeToLiveStatus Source # 
Hashable TimeToLiveStatus Source # 
FromJSON TimeToLiveStatus Source # 
NFData TimeToLiveStatus Source # 

Methods

rnf :: TimeToLiveStatus -> () #

ToHeader TimeToLiveStatus Source # 
ToQuery TimeToLiveStatus Source # 
ToByteString TimeToLiveStatus Source # 
FromText TimeToLiveStatus Source # 
ToText TimeToLiveStatus Source # 
type Rep TimeToLiveStatus Source # 
type Rep TimeToLiveStatus = D1 * (MetaData "TimeToLiveStatus" "Network.AWS.DynamoDB.Types.Sum" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Disabled" PrefixI False) (U1 *)) (C1 * (MetaCons "Disabling" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Enabled" PrefixI False) (U1 *)) (C1 * (MetaCons "Enabling" PrefixI False) (U1 *))))

AttributeDefinition

data AttributeDefinition Source #

Represents an attribute for describing the key schema for the table and indexes.

See: attributeDefinition smart constructor.

Instances

Eq AttributeDefinition Source # 
Data AttributeDefinition Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AttributeDefinition -> c AttributeDefinition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AttributeDefinition #

toConstr :: AttributeDefinition -> Constr #

dataTypeOf :: AttributeDefinition -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AttributeDefinition) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AttributeDefinition) #

gmapT :: (forall b. Data b => b -> b) -> AttributeDefinition -> AttributeDefinition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AttributeDefinition -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AttributeDefinition -> r #

gmapQ :: (forall d. Data d => d -> u) -> AttributeDefinition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AttributeDefinition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AttributeDefinition -> m AttributeDefinition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeDefinition -> m AttributeDefinition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeDefinition -> m AttributeDefinition #

Read AttributeDefinition Source # 
Show AttributeDefinition Source # 
Generic AttributeDefinition Source # 
Hashable AttributeDefinition Source # 
ToJSON AttributeDefinition Source # 
FromJSON AttributeDefinition Source # 
NFData AttributeDefinition Source # 

Methods

rnf :: AttributeDefinition -> () #

type Rep AttributeDefinition Source # 
type Rep AttributeDefinition = D1 * (MetaData "AttributeDefinition" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "AttributeDefinition'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_adAttributeName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_adAttributeType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ScalarAttributeType))))

attributeDefinition Source #

Creates a value of AttributeDefinition with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • adAttributeName - A name for the attribute.
  • adAttributeType - The data type for the attribute, where: * S - the attribute is of type String * N - the attribute is of type Number * B - the attribute is of type Binary

adAttributeType :: Lens' AttributeDefinition ScalarAttributeType Source #

The data type for the attribute, where: * S - the attribute is of type String * N - the attribute is of type Number * B - the attribute is of type Binary

AttributeValue

data AttributeValue Source #

Represents the data for an attribute.

Each attribute value is described as a name-value pair. The name is the data type, and the value is the data itself.

For more information, see Data Types in the Amazon DynamoDB Developer Guide .

See: attributeValue smart constructor.

Instances

Eq AttributeValue Source # 
Data AttributeValue Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AttributeValue -> c AttributeValue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AttributeValue #

toConstr :: AttributeValue -> Constr #

dataTypeOf :: AttributeValue -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AttributeValue) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AttributeValue) #

gmapT :: (forall b. Data b => b -> b) -> AttributeValue -> AttributeValue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AttributeValue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AttributeValue -> r #

gmapQ :: (forall d. Data d => d -> u) -> AttributeValue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AttributeValue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AttributeValue -> m AttributeValue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeValue -> m AttributeValue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeValue -> m AttributeValue #

Read AttributeValue Source # 
Show AttributeValue Source # 
Generic AttributeValue Source # 

Associated Types

type Rep AttributeValue :: * -> * #

Hashable AttributeValue Source # 
ToJSON AttributeValue Source # 
FromJSON AttributeValue Source # 
NFData AttributeValue Source # 

Methods

rnf :: AttributeValue -> () #

type Rep AttributeValue Source # 

attributeValue :: AttributeValue Source #

Creates a value of AttributeValue with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • avL - An attribute of type List. For example: L: [Cookies, Coffee, 3.14159]
  • avNS - An attribute of type Number Set. For example: NS: ["42.2", "-19", "7.5", "3.14"] Numbers are sent across the network to DynamoDB as strings, to maximize compatibility across languages and libraries. However, DynamoDB treats them as number type attributes for mathematical operations.
  • avM - An attribute of type Map. For example: M: {Name: {S: Joe}, Age: {N: "35"}}
  • avNULL - An attribute of type Null. For example: NULL: true
  • avN - An attribute of type Number. For example: N: "123.45" Numbers are sent across the network to DynamoDB as strings, to maximize compatibility across languages and libraries. However, DynamoDB treats them as number type attributes for mathematical operations.
  • avBS - An attribute of type Binary Set. For example: BS: ["U3Vubnk=", "UmFpbnk=", "U25vd3k="]
  • avB - An attribute of type Binary. For example: B: "dGhpcyB0ZXh0IGlzIGJhc2U2NC1lbmNvZGVk" -- Note: This Lens automatically encodes and decodes Base64 data. The underlying isomorphism will encode to Base64 representation during serialisation, and decode from Base64 representation during deserialisation. This Lens accepts and returns only raw unencoded data.
  • avSS - An attribute of type String Set. For example: SS: [Giraffe, Hippo ,Zebra]
  • avS - An attribute of type String. For example: S: Hello
  • avBOOL - An attribute of type Boolean. For example: BOOL: true

avL :: Lens' AttributeValue [AttributeValue] Source #

An attribute of type List. For example: L: [Cookies, Coffee, 3.14159]

avNS :: Lens' AttributeValue [Text] Source #

An attribute of type Number Set. For example: NS: ["42.2", "-19", "7.5", "3.14"] Numbers are sent across the network to DynamoDB as strings, to maximize compatibility across languages and libraries. However, DynamoDB treats them as number type attributes for mathematical operations.

avM :: Lens' AttributeValue (HashMap Text AttributeValue) Source #

An attribute of type Map. For example: M: {Name: {S: Joe}, Age: {N: "35"}}

avNULL :: Lens' AttributeValue (Maybe Bool) Source #

An attribute of type Null. For example: NULL: true

avN :: Lens' AttributeValue (Maybe Text) Source #

An attribute of type Number. For example: N: "123.45" Numbers are sent across the network to DynamoDB as strings, to maximize compatibility across languages and libraries. However, DynamoDB treats them as number type attributes for mathematical operations.

avBS :: Lens' AttributeValue [ByteString] Source #

An attribute of type Binary Set. For example: BS: ["U3Vubnk=", "UmFpbnk=", "U25vd3k="]

avB :: Lens' AttributeValue (Maybe ByteString) Source #

An attribute of type Binary. For example: B: "dGhpcyB0ZXh0IGlzIGJhc2U2NC1lbmNvZGVk" -- Note: This Lens automatically encodes and decodes Base64 data. The underlying isomorphism will encode to Base64 representation during serialisation, and decode from Base64 representation during deserialisation. This Lens accepts and returns only raw unencoded data.

avSS :: Lens' AttributeValue [Text] Source #

An attribute of type String Set. For example: SS: [Giraffe, Hippo ,Zebra]

avS :: Lens' AttributeValue (Maybe Text) Source #

An attribute of type String. For example: S: Hello

avBOOL :: Lens' AttributeValue (Maybe Bool) Source #

An attribute of type Boolean. For example: BOOL: true

AttributeValueUpdate

data AttributeValueUpdate Source #

For the UpdateItem operation, represents the attributes to be modified, the action to perform on each, and the new value for each.

Attribute values cannot be null; string and binary type attributes must have lengths greater than zero; and set type attributes must not be empty. Requests with empty values will be rejected with a ValidationException exception.

See: attributeValueUpdate smart constructor.

Instances

Eq AttributeValueUpdate Source # 
Data AttributeValueUpdate Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AttributeValueUpdate -> c AttributeValueUpdate #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AttributeValueUpdate #

toConstr :: AttributeValueUpdate -> Constr #

dataTypeOf :: AttributeValueUpdate -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AttributeValueUpdate) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AttributeValueUpdate) #

gmapT :: (forall b. Data b => b -> b) -> AttributeValueUpdate -> AttributeValueUpdate #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AttributeValueUpdate -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AttributeValueUpdate -> r #

gmapQ :: (forall d. Data d => d -> u) -> AttributeValueUpdate -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AttributeValueUpdate -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AttributeValueUpdate -> m AttributeValueUpdate #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeValueUpdate -> m AttributeValueUpdate #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeValueUpdate -> m AttributeValueUpdate #

Read AttributeValueUpdate Source # 
Show AttributeValueUpdate Source # 
Generic AttributeValueUpdate Source # 
Hashable AttributeValueUpdate Source # 
ToJSON AttributeValueUpdate Source # 
NFData AttributeValueUpdate Source # 

Methods

rnf :: AttributeValueUpdate -> () #

type Rep AttributeValueUpdate Source # 
type Rep AttributeValueUpdate = D1 * (MetaData "AttributeValueUpdate" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "AttributeValueUpdate'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_avuValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AttributeValue))) (S1 * (MetaSel (Just Symbol "_avuAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AttributeAction)))))

attributeValueUpdate :: AttributeValueUpdate Source #

Creates a value of AttributeValueUpdate with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • avuValue - Represents the data for an attribute. Each attribute value is described as a name-value pair. The name is the data type, and the value is the data itself. For more information, see Data Types in the Amazon DynamoDB Developer Guide .
  • avuAction - Specifies how to perform the update. Valid values are PUT (default), DELETE , and ADD . The behavior depends on whether the specified primary key already exists in the table. If an item with the specified Key is found in the table: * PUT - Adds the specified attribute to the item. If the attribute already exists, it is replaced by the new value. * DELETE - If no value is specified, the attribute and its value are removed from the item. The data type of the specified value must match the existing value's data type. If a set of values is specified, then those values are subtracted from the old set. For example, if the attribute value was the set [a,b,c] and the DELETE action specified [a,c] , then the final attribute value would be [b] . Specifying an empty set is an error. * ADD - If the attribute does not already exist, then the attribute and its values are added to the item. If the attribute does exist, then the behavior of ADD depends on the data type of the attribute: * If the existing attribute is a number, and if Value is also a number, then the Value is mathematically added to the existing attribute. If Value is a negative number, then it is subtracted from the existing attribute. * If the existing data type is a set, and if the Value is also a set, then the Value is added to the existing set. (This is a set operation, not mathematical addition.) For example, if the attribute value was the set [1,2] , and the ADD action specified [3] , then the final attribute value would be [1,2,3] . An error occurs if an Add action is specified for a set attribute and the attribute type specified does not match the existing set type. Both sets must have the same primitive data type. For example, if the existing data type is a set of strings, the Value must also be a set of strings. The same holds true for number sets and binary sets. This action is only valid for an existing attribute whose data type is number or is a set. Do not use ADD for any other data types. If no item with the specified Key is found: * PUT - DynamoDB creates a new item with the specified primary key, and then adds the attribute. * DELETE - Nothing happens; there is no attribute to delete. * ADD - DynamoDB creates an item with the supplied primary key and number (or set of numbers) for the attribute value. The only data types allowed are number and number set; no other data types can be specified.

avuValue :: Lens' AttributeValueUpdate (Maybe AttributeValue) Source #

Represents the data for an attribute. Each attribute value is described as a name-value pair. The name is the data type, and the value is the data itself. For more information, see Data Types in the Amazon DynamoDB Developer Guide .

avuAction :: Lens' AttributeValueUpdate (Maybe AttributeAction) Source #

Specifies how to perform the update. Valid values are PUT (default), DELETE , and ADD . The behavior depends on whether the specified primary key already exists in the table. If an item with the specified Key is found in the table: * PUT - Adds the specified attribute to the item. If the attribute already exists, it is replaced by the new value. * DELETE - If no value is specified, the attribute and its value are removed from the item. The data type of the specified value must match the existing value's data type. If a set of values is specified, then those values are subtracted from the old set. For example, if the attribute value was the set [a,b,c] and the DELETE action specified [a,c] , then the final attribute value would be [b] . Specifying an empty set is an error. * ADD - If the attribute does not already exist, then the attribute and its values are added to the item. If the attribute does exist, then the behavior of ADD depends on the data type of the attribute: * If the existing attribute is a number, and if Value is also a number, then the Value is mathematically added to the existing attribute. If Value is a negative number, then it is subtracted from the existing attribute. * If the existing data type is a set, and if the Value is also a set, then the Value is added to the existing set. (This is a set operation, not mathematical addition.) For example, if the attribute value was the set [1,2] , and the ADD action specified [3] , then the final attribute value would be [1,2,3] . An error occurs if an Add action is specified for a set attribute and the attribute type specified does not match the existing set type. Both sets must have the same primitive data type. For example, if the existing data type is a set of strings, the Value must also be a set of strings. The same holds true for number sets and binary sets. This action is only valid for an existing attribute whose data type is number or is a set. Do not use ADD for any other data types. If no item with the specified Key is found: * PUT - DynamoDB creates a new item with the specified primary key, and then adds the attribute. * DELETE - Nothing happens; there is no attribute to delete. * ADD - DynamoDB creates an item with the supplied primary key and number (or set of numbers) for the attribute value. The only data types allowed are number and number set; no other data types can be specified.

BackupDescription

data BackupDescription Source #

Contains the description of the backup created for the table.

See: backupDescription smart constructor.

Instances

Eq BackupDescription Source # 
Data BackupDescription Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BackupDescription -> c BackupDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BackupDescription #

toConstr :: BackupDescription -> Constr #

dataTypeOf :: BackupDescription -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BackupDescription) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BackupDescription) #

gmapT :: (forall b. Data b => b -> b) -> BackupDescription -> BackupDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BackupDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BackupDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> BackupDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BackupDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BackupDescription -> m BackupDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BackupDescription -> m BackupDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BackupDescription -> m BackupDescription #

Read BackupDescription Source # 
Show BackupDescription Source # 
Generic BackupDescription Source # 
Hashable BackupDescription Source # 
FromJSON BackupDescription Source # 
NFData BackupDescription Source # 

Methods

rnf :: BackupDescription -> () #

type Rep BackupDescription Source # 
type Rep BackupDescription = D1 * (MetaData "BackupDescription" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "BackupDescription'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_bdBackupDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe BackupDetails))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bdSourceTableDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe SourceTableDetails))) (S1 * (MetaSel (Just Symbol "_bdSourceTableFeatureDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe SourceTableFeatureDetails))))))

backupDescription :: BackupDescription Source #

Creates a value of BackupDescription with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • bdBackupDetails - Contains the details of the backup created for the table.
  • bdSourceTableDetails - Contains the details of the table when the backup was created.
  • bdSourceTableFeatureDetails - Contains the details of the features enabled on the table when the backup was created. For example, LSIs, GSIs, streams, TTL.

bdBackupDetails :: Lens' BackupDescription (Maybe BackupDetails) Source #

Contains the details of the backup created for the table.

bdSourceTableDetails :: Lens' BackupDescription (Maybe SourceTableDetails) Source #

Contains the details of the table when the backup was created.

bdSourceTableFeatureDetails :: Lens' BackupDescription (Maybe SourceTableFeatureDetails) Source #

Contains the details of the features enabled on the table when the backup was created. For example, LSIs, GSIs, streams, TTL.

BackupDetails

data BackupDetails Source #

Contains the details of the backup created for the table.

See: backupDetails smart constructor.

Instances

Eq BackupDetails Source # 
Data BackupDetails Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BackupDetails -> c BackupDetails #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BackupDetails #

toConstr :: BackupDetails -> Constr #

dataTypeOf :: BackupDetails -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BackupDetails) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BackupDetails) #

gmapT :: (forall b. Data b => b -> b) -> BackupDetails -> BackupDetails #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BackupDetails -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BackupDetails -> r #

gmapQ :: (forall d. Data d => d -> u) -> BackupDetails -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BackupDetails -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BackupDetails -> m BackupDetails #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BackupDetails -> m BackupDetails #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BackupDetails -> m BackupDetails #

Read BackupDetails Source # 
Show BackupDetails Source # 
Generic BackupDetails Source # 

Associated Types

type Rep BackupDetails :: * -> * #

Hashable BackupDetails Source # 
FromJSON BackupDetails Source # 
NFData BackupDetails Source # 

Methods

rnf :: BackupDetails -> () #

type Rep BackupDetails Source # 
type Rep BackupDetails = D1 * (MetaData "BackupDetails" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "BackupDetails'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_bdBackupSizeBytes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_bdBackupARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_bdBackupName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "_bdBackupStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * BackupStatus)) (S1 * (MetaSel (Just Symbol "_bdBackupCreationDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * POSIX))))))

backupDetails Source #

Creates a value of BackupDetails with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

bdBackupSizeBytes :: Lens' BackupDetails (Maybe Natural) Source #

Size of the backup in bytes.

bdBackupARN :: Lens' BackupDetails Text Source #

ARN associated with the backup.

bdBackupName :: Lens' BackupDetails Text Source #

Name of the requested backup.

bdBackupStatus :: Lens' BackupDetails BackupStatus Source #

Backup can be in one of the following states: CREATING, ACTIVE, DELETED.

bdBackupCreationDateTime :: Lens' BackupDetails UTCTime Source #

Time at which the backup was created. This is the request time of the backup.

BackupSummary

data BackupSummary Source #

Contains details for the backup.

See: backupSummary smart constructor.

Instances

Eq BackupSummary Source # 
Data BackupSummary Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BackupSummary -> c BackupSummary #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BackupSummary #

toConstr :: BackupSummary -> Constr #

dataTypeOf :: BackupSummary -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BackupSummary) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BackupSummary) #

gmapT :: (forall b. Data b => b -> b) -> BackupSummary -> BackupSummary #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BackupSummary -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BackupSummary -> r #

gmapQ :: (forall d. Data d => d -> u) -> BackupSummary -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BackupSummary -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BackupSummary -> m BackupSummary #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BackupSummary -> m BackupSummary #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BackupSummary -> m BackupSummary #

Read BackupSummary Source # 
Show BackupSummary Source # 
Generic BackupSummary Source # 

Associated Types

type Rep BackupSummary :: * -> * #

Hashable BackupSummary Source # 
FromJSON BackupSummary Source # 
NFData BackupSummary Source # 

Methods

rnf :: BackupSummary -> () #

type Rep BackupSummary Source # 

backupSummary :: BackupSummary Source #

Creates a value of BackupSummary with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

bsTableARN :: Lens' BackupSummary (Maybe Text) Source #

ARN associated with the table.

bsBackupName :: Lens' BackupSummary (Maybe Text) Source #

Name of the specified backup.

bsBackupStatus :: Lens' BackupSummary (Maybe BackupStatus) Source #

Backup can be in one of the following states: CREATING, ACTIVE, DELETED.

bsBackupSizeBytes :: Lens' BackupSummary (Maybe Natural) Source #

Size of the backup in bytes.

bsBackupARN :: Lens' BackupSummary (Maybe Text) Source #

ARN associated with the backup.

bsTableId :: Lens' BackupSummary (Maybe Text) Source #

Unique identifier for the table.

bsBackupCreationDateTime :: Lens' BackupSummary (Maybe UTCTime) Source #

Time at which the backup was created.

Capacity

data Capacity Source #

Represents the amount of provisioned throughput capacity consumed on a table or an index.

See: capacity smart constructor.

Instances

Eq Capacity Source # 
Data Capacity Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Capacity -> c Capacity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Capacity #

toConstr :: Capacity -> Constr #

dataTypeOf :: Capacity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Capacity) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Capacity) #

gmapT :: (forall b. Data b => b -> b) -> Capacity -> Capacity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Capacity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Capacity -> r #

gmapQ :: (forall d. Data d => d -> u) -> Capacity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Capacity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Capacity -> m Capacity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Capacity -> m Capacity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Capacity -> m Capacity #

Read Capacity Source # 
Show Capacity Source # 
Generic Capacity Source # 

Associated Types

type Rep Capacity :: * -> * #

Methods

from :: Capacity -> Rep Capacity x #

to :: Rep Capacity x -> Capacity #

Hashable Capacity Source # 

Methods

hashWithSalt :: Int -> Capacity -> Int #

hash :: Capacity -> Int #

FromJSON Capacity Source # 
NFData Capacity Source # 

Methods

rnf :: Capacity -> () #

type Rep Capacity Source # 
type Rep Capacity = D1 * (MetaData "Capacity" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" True) (C1 * (MetaCons "Capacity'" PrefixI True) (S1 * (MetaSel (Just Symbol "_cCapacityUnits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Double))))

capacity :: Capacity Source #

Creates a value of Capacity with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • cCapacityUnits - The total number of capacity units consumed on a table or an index.

cCapacityUnits :: Lens' Capacity (Maybe Double) Source #

The total number of capacity units consumed on a table or an index.

Condition

data Condition Source #

Represents the selection criteria for a Query or Scan operation:

  • For a Query operation, Condition is used for specifying the KeyConditions to use when querying a table or an index. For KeyConditions , only the following comparison operators are supported:
EQ | LE | LT | GE | GT | BEGINS_WITH | BETWEEN

Condition is also used in a QueryFilter , which evaluates the query results and returns only the desired values.

  • For a Scan operation, Condition is used in a ScanFilter , which evaluates the scan results and returns only the desired values.

See: condition smart constructor.

Instances

Eq Condition Source # 
Data Condition Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Condition -> c Condition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Condition #

toConstr :: Condition -> Constr #

dataTypeOf :: Condition -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Condition) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Condition) #

gmapT :: (forall b. Data b => b -> b) -> Condition -> Condition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Condition -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Condition -> r #

gmapQ :: (forall d. Data d => d -> u) -> Condition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Condition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Condition -> m Condition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Condition -> m Condition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Condition -> m Condition #

Read Condition Source # 
Show Condition Source # 
Generic Condition Source # 

Associated Types

type Rep Condition :: * -> * #

Hashable Condition Source # 
ToJSON Condition Source # 
NFData Condition Source # 

Methods

rnf :: Condition -> () #

type Rep Condition Source # 
type Rep Condition = D1 * (MetaData "Condition" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "Condition'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cAttributeValueList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [AttributeValue]))) (S1 * (MetaSel (Just Symbol "_cComparisonOperator") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ComparisonOperator))))

condition Source #

Creates a value of Condition with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • cAttributeValueList - One or more values to evaluate against the supplied attribute. The number of values in the list depends on the ComparisonOperator being used. For type Number, value comparisons are numeric. String value comparisons for greater than, equals, or less than are based on ASCII character code values. For example, a is greater than A , and a is greater than B . For a list of code values, see http://en.wikipedia.org/wiki/ASCII#ASCII_printable_characters . For Binary, DynamoDB treats each byte of the binary data as unsigned when it compares binary values.
  • cComparisonOperator - A comparator for evaluating attributes. For example, equals, greater than, less than, etc. The following comparison operators are available: EQ | NE | LE | LT | GE | GT | NOT_NULL | NULL | CONTAINS | NOT_CONTAINS | BEGINS_WITH | IN | BETWEEN The following are descriptions of each comparison operator. * EQ : Equal. EQ is supported for all data types, including lists and maps. AttributeValueList can contain only one AttributeValue element of type String, Number, Binary, String Set, Number Set, or Binary Set. If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not equal {NS:["6", "2", "1"]} . * NE : Not equal. NE is supported for all data types, including lists and maps. AttributeValueList can contain only one AttributeValue of type String, Number, Binary, String Set, Number Set, or Binary Set. If an item contains an AttributeValue of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not equal {NS:["6", "2", "1"]} . * LE : Less than or equal. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} . * LT : Less than. AttributeValueList can contain only one AttributeValue of type String, Number, or Binary (not a set type). If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} . * GE : Greater than or equal. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} . * GT : Greater than. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} . * NOT_NULL : The attribute exists. NOT_NULL is supported for all data types, including lists and maps. * NULL : The attribute does not exist. NULL is supported for all data types, including lists and maps. * CONTAINS : Checks for a subsequence, or value in a set. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If the target attribute of the comparison is of type String, then the operator checks for a substring match. If the target attribute of the comparison is of type Binary, then the operator looks for a subsequence of the target that matches the input. If the target attribute of the comparison is a set ("SS ", "NS ", or "BS "), then the operator evaluates to true if it finds an exact match with any member of the set. CONTAINS is supported for lists: When evaluating "a CONTAINS b ", "a " can be a list; however, "b " cannot be a set, a map, or a list. * NOT_CONTAINS : Checks for absence of a subsequence, or absence of a value in a set. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If the target attribute of the comparison is a String, then the operator checks for the absence of a substring match. If the target attribute of the comparison is Binary, then the operator checks for the absence of a subsequence of the target that matches the input. If the target attribute of the comparison is a set ("SS ", "NS ", or "BS "), then the operator evaluates to true if it does not find an exact match with any member of the set. NOT_CONTAINS is supported for lists: When evaluating "a NOT CONTAINS b ", "a " can be a list; however, "b " cannot be a set, a map, or a list. * BEGINS_WITH : Checks for a prefix. AttributeValueList can contain only one AttributeValue of type String or Binary (not a Number or a set type). The target attribute of the comparison must be of type String or Binary (not a Number or a set type). * IN : Checks for matching elements in a list. AttributeValueList can contain one or more AttributeValue elements of type String, Number, or Binary. These attributes are compared against an existing attribute of an item. If any elements of the input are equal to the item attribute, the expression evaluates to true. * BETWEEN : Greater than or equal to the first value, and less than or equal to the second value. AttributeValueList must contain two AttributeValue elements of the same type, either String, Number, or Binary (not a set type). A target attribute matches if the target value is greater than, or equal to, the first element and less than, or equal to, the second element. If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not compare to {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} For usage examples of AttributeValueList and ComparisonOperator , see Legacy Conditional Parameters in the Amazon DynamoDB Developer Guide .

cAttributeValueList :: Lens' Condition [AttributeValue] Source #

One or more values to evaluate against the supplied attribute. The number of values in the list depends on the ComparisonOperator being used. For type Number, value comparisons are numeric. String value comparisons for greater than, equals, or less than are based on ASCII character code values. For example, a is greater than A , and a is greater than B . For a list of code values, see http://en.wikipedia.org/wiki/ASCII#ASCII_printable_characters . For Binary, DynamoDB treats each byte of the binary data as unsigned when it compares binary values.

cComparisonOperator :: Lens' Condition ComparisonOperator Source #

A comparator for evaluating attributes. For example, equals, greater than, less than, etc. The following comparison operators are available: EQ | NE | LE | LT | GE | GT | NOT_NULL | NULL | CONTAINS | NOT_CONTAINS | BEGINS_WITH | IN | BETWEEN The following are descriptions of each comparison operator. * EQ : Equal. EQ is supported for all data types, including lists and maps. AttributeValueList can contain only one AttributeValue element of type String, Number, Binary, String Set, Number Set, or Binary Set. If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not equal {NS:["6", "2", "1"]} . * NE : Not equal. NE is supported for all data types, including lists and maps. AttributeValueList can contain only one AttributeValue of type String, Number, Binary, String Set, Number Set, or Binary Set. If an item contains an AttributeValue of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not equal {NS:["6", "2", "1"]} . * LE : Less than or equal. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} . * LT : Less than. AttributeValueList can contain only one AttributeValue of type String, Number, or Binary (not a set type). If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} . * GE : Greater than or equal. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} . * GT : Greater than. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} . * NOT_NULL : The attribute exists. NOT_NULL is supported for all data types, including lists and maps. * NULL : The attribute does not exist. NULL is supported for all data types, including lists and maps. * CONTAINS : Checks for a subsequence, or value in a set. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If the target attribute of the comparison is of type String, then the operator checks for a substring match. If the target attribute of the comparison is of type Binary, then the operator looks for a subsequence of the target that matches the input. If the target attribute of the comparison is a set ("SS ", "NS ", or "BS "), then the operator evaluates to true if it finds an exact match with any member of the set. CONTAINS is supported for lists: When evaluating "a CONTAINS b ", "a " can be a list; however, "b " cannot be a set, a map, or a list. * NOT_CONTAINS : Checks for absence of a subsequence, or absence of a value in a set. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If the target attribute of the comparison is a String, then the operator checks for the absence of a substring match. If the target attribute of the comparison is Binary, then the operator checks for the absence of a subsequence of the target that matches the input. If the target attribute of the comparison is a set ("SS ", "NS ", or "BS "), then the operator evaluates to true if it does not find an exact match with any member of the set. NOT_CONTAINS is supported for lists: When evaluating "a NOT CONTAINS b ", "a " can be a list; however, "b " cannot be a set, a map, or a list. * BEGINS_WITH : Checks for a prefix. AttributeValueList can contain only one AttributeValue of type String or Binary (not a Number or a set type). The target attribute of the comparison must be of type String or Binary (not a Number or a set type). * IN : Checks for matching elements in a list. AttributeValueList can contain one or more AttributeValue elements of type String, Number, or Binary. These attributes are compared against an existing attribute of an item. If any elements of the input are equal to the item attribute, the expression evaluates to true. * BETWEEN : Greater than or equal to the first value, and less than or equal to the second value. AttributeValueList must contain two AttributeValue elements of the same type, either String, Number, or Binary (not a set type). A target attribute matches if the target value is greater than, or equal to, the first element and less than, or equal to, the second element. If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not compare to {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} For usage examples of AttributeValueList and ComparisonOperator , see Legacy Conditional Parameters in the Amazon DynamoDB Developer Guide .

ConsumedCapacity

data ConsumedCapacity Source #

The capacity units consumed by an operation. The data returned includes the total provisioned throughput consumed, along with statistics for the table and any indexes involved in the operation. ConsumedCapacity is only returned if the request asked for it. For more information, see Provisioned Throughput in the Amazon DynamoDB Developer Guide .

See: consumedCapacity smart constructor.

Instances

Eq ConsumedCapacity Source # 
Data ConsumedCapacity Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConsumedCapacity -> c ConsumedCapacity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConsumedCapacity #

toConstr :: ConsumedCapacity -> Constr #

dataTypeOf :: ConsumedCapacity -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConsumedCapacity) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConsumedCapacity) #

gmapT :: (forall b. Data b => b -> b) -> ConsumedCapacity -> ConsumedCapacity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConsumedCapacity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConsumedCapacity -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConsumedCapacity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConsumedCapacity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConsumedCapacity -> m ConsumedCapacity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConsumedCapacity -> m ConsumedCapacity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConsumedCapacity -> m ConsumedCapacity #

Read ConsumedCapacity Source # 
Show ConsumedCapacity Source # 
Generic ConsumedCapacity Source # 
Hashable ConsumedCapacity Source # 
FromJSON ConsumedCapacity Source # 
NFData ConsumedCapacity Source # 

Methods

rnf :: ConsumedCapacity -> () #

type Rep ConsumedCapacity Source # 
type Rep ConsumedCapacity = D1 * (MetaData "ConsumedCapacity" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "ConsumedCapacity'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ccGlobalSecondaryIndexes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Capacity)))) (S1 * (MetaSel (Just Symbol "_ccCapacityUnits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Double)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ccLocalSecondaryIndexes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Capacity)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ccTable") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Capacity))) (S1 * (MetaSel (Just Symbol "_ccTableName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

consumedCapacity :: ConsumedCapacity Source #

Creates a value of ConsumedCapacity with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ccGlobalSecondaryIndexes - The amount of throughput consumed on each global index affected by the operation.
  • ccCapacityUnits - The total number of capacity units consumed by the operation.
  • ccLocalSecondaryIndexes - The amount of throughput consumed on each local index affected by the operation.
  • ccTable - The amount of throughput consumed on the table affected by the operation.
  • ccTableName - The name of the table that was affected by the operation.

ccGlobalSecondaryIndexes :: Lens' ConsumedCapacity (HashMap Text Capacity) Source #

The amount of throughput consumed on each global index affected by the operation.

ccCapacityUnits :: Lens' ConsumedCapacity (Maybe Double) Source #

The total number of capacity units consumed by the operation.

ccLocalSecondaryIndexes :: Lens' ConsumedCapacity (HashMap Text Capacity) Source #

The amount of throughput consumed on each local index affected by the operation.

ccTable :: Lens' ConsumedCapacity (Maybe Capacity) Source #

The amount of throughput consumed on the table affected by the operation.

ccTableName :: Lens' ConsumedCapacity (Maybe Text) Source #

The name of the table that was affected by the operation.

ContinuousBackupsDescription

data ContinuousBackupsDescription Source #

Represents the continuous backups and point in time recovery settings on the table.

See: continuousBackupsDescription smart constructor.

Instances

Eq ContinuousBackupsDescription Source # 
Data ContinuousBackupsDescription Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ContinuousBackupsDescription -> c ContinuousBackupsDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ContinuousBackupsDescription #

toConstr :: ContinuousBackupsDescription -> Constr #

dataTypeOf :: ContinuousBackupsDescription -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ContinuousBackupsDescription) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ContinuousBackupsDescription) #

gmapT :: (forall b. Data b => b -> b) -> ContinuousBackupsDescription -> ContinuousBackupsDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ContinuousBackupsDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ContinuousBackupsDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> ContinuousBackupsDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ContinuousBackupsDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ContinuousBackupsDescription -> m ContinuousBackupsDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ContinuousBackupsDescription -> m ContinuousBackupsDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ContinuousBackupsDescription -> m ContinuousBackupsDescription #

Read ContinuousBackupsDescription Source # 
Show ContinuousBackupsDescription Source # 
Generic ContinuousBackupsDescription Source # 
Hashable ContinuousBackupsDescription Source # 
FromJSON ContinuousBackupsDescription Source # 
NFData ContinuousBackupsDescription Source # 
type Rep ContinuousBackupsDescription Source # 
type Rep ContinuousBackupsDescription = D1 * (MetaData "ContinuousBackupsDescription" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "ContinuousBackupsDescription'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_cbdPointInTimeRecoveryDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe PointInTimeRecoveryDescription))) (S1 * (MetaSel (Just Symbol "_cbdContinuousBackupsStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ContinuousBackupsStatus))))

continuousBackupsDescription Source #

Creates a value of ContinuousBackupsDescription with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cbdPointInTimeRecoveryDescription :: Lens' ContinuousBackupsDescription (Maybe PointInTimeRecoveryDescription) Source #

The description of the point in time recovery settings applied to the table.

cbdContinuousBackupsStatus :: Lens' ContinuousBackupsDescription ContinuousBackupsStatus Source #

ContinuousBackupsStatus can be one of the following states : ENABLED, DISABLED

CreateGlobalSecondaryIndexAction

data CreateGlobalSecondaryIndexAction Source #

Represents a new global secondary index to be added to an existing table.

See: createGlobalSecondaryIndexAction smart constructor.

Instances

Eq CreateGlobalSecondaryIndexAction Source # 
Data CreateGlobalSecondaryIndexAction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreateGlobalSecondaryIndexAction -> c CreateGlobalSecondaryIndexAction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreateGlobalSecondaryIndexAction #

toConstr :: CreateGlobalSecondaryIndexAction -> Constr #

dataTypeOf :: CreateGlobalSecondaryIndexAction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreateGlobalSecondaryIndexAction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreateGlobalSecondaryIndexAction) #

gmapT :: (forall b. Data b => b -> b) -> CreateGlobalSecondaryIndexAction -> CreateGlobalSecondaryIndexAction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreateGlobalSecondaryIndexAction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreateGlobalSecondaryIndexAction -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreateGlobalSecondaryIndexAction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreateGlobalSecondaryIndexAction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreateGlobalSecondaryIndexAction -> m CreateGlobalSecondaryIndexAction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreateGlobalSecondaryIndexAction -> m CreateGlobalSecondaryIndexAction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreateGlobalSecondaryIndexAction -> m CreateGlobalSecondaryIndexAction #

Read CreateGlobalSecondaryIndexAction Source # 
Show CreateGlobalSecondaryIndexAction Source # 
Generic CreateGlobalSecondaryIndexAction Source # 
Hashable CreateGlobalSecondaryIndexAction Source # 
ToJSON CreateGlobalSecondaryIndexAction Source # 
NFData CreateGlobalSecondaryIndexAction Source # 
type Rep CreateGlobalSecondaryIndexAction Source # 
type Rep CreateGlobalSecondaryIndexAction = D1 * (MetaData "CreateGlobalSecondaryIndexAction" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "CreateGlobalSecondaryIndexAction'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_cgsiaIndexName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_cgsiaKeySchema") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (List1 KeySchemaElement)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_cgsiaProjection") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Projection)) (S1 * (MetaSel (Just Symbol "_cgsiaProvisionedThroughput") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProvisionedThroughput)))))

createGlobalSecondaryIndexAction Source #

Creates a value of CreateGlobalSecondaryIndexAction with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • cgsiaIndexName - The name of the global secondary index to be created.
  • cgsiaKeySchema - The key schema for the global secondary index.
  • cgsiaProjection - Represents attributes that are copied (projected) from the table into an index. These are in addition to the primary key attributes and index key attributes, which are automatically projected.
  • cgsiaProvisionedThroughput - Represents the provisioned throughput settings for the specified global secondary index. For current minimum and maximum provisioned throughput values, see Limits in the Amazon DynamoDB Developer Guide .

cgsiaIndexName :: Lens' CreateGlobalSecondaryIndexAction Text Source #

The name of the global secondary index to be created.

cgsiaKeySchema :: Lens' CreateGlobalSecondaryIndexAction (NonEmpty KeySchemaElement) Source #

The key schema for the global secondary index.

cgsiaProjection :: Lens' CreateGlobalSecondaryIndexAction Projection Source #

Represents attributes that are copied (projected) from the table into an index. These are in addition to the primary key attributes and index key attributes, which are automatically projected.

cgsiaProvisionedThroughput :: Lens' CreateGlobalSecondaryIndexAction ProvisionedThroughput Source #

Represents the provisioned throughput settings for the specified global secondary index. For current minimum and maximum provisioned throughput values, see Limits in the Amazon DynamoDB Developer Guide .

CreateReplicaAction

data CreateReplicaAction Source #

Represents a replica to be added.

See: createReplicaAction smart constructor.

Instances

Eq CreateReplicaAction Source # 
Data CreateReplicaAction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CreateReplicaAction -> c CreateReplicaAction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CreateReplicaAction #

toConstr :: CreateReplicaAction -> Constr #

dataTypeOf :: CreateReplicaAction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CreateReplicaAction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CreateReplicaAction) #

gmapT :: (forall b. Data b => b -> b) -> CreateReplicaAction -> CreateReplicaAction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CreateReplicaAction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CreateReplicaAction -> r #

gmapQ :: (forall d. Data d => d -> u) -> CreateReplicaAction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CreateReplicaAction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CreateReplicaAction -> m CreateReplicaAction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CreateReplicaAction -> m CreateReplicaAction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CreateReplicaAction -> m CreateReplicaAction #

Read CreateReplicaAction Source # 
Show CreateReplicaAction Source # 
Generic CreateReplicaAction Source # 
Hashable CreateReplicaAction Source # 
ToJSON CreateReplicaAction Source # 
NFData CreateReplicaAction Source # 

Methods

rnf :: CreateReplicaAction -> () #

type Rep CreateReplicaAction Source # 
type Rep CreateReplicaAction = D1 * (MetaData "CreateReplicaAction" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" True) (C1 * (MetaCons "CreateReplicaAction'" PrefixI True) (S1 * (MetaSel (Just Symbol "_craRegionName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

createReplicaAction Source #

Creates a value of CreateReplicaAction with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

craRegionName :: Lens' CreateReplicaAction Text Source #

The region of the replica to be added.

DeleteGlobalSecondaryIndexAction

data DeleteGlobalSecondaryIndexAction Source #

Represents a global secondary index to be deleted from an existing table.

See: deleteGlobalSecondaryIndexAction smart constructor.

Instances

Eq DeleteGlobalSecondaryIndexAction Source # 
Data DeleteGlobalSecondaryIndexAction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeleteGlobalSecondaryIndexAction -> c DeleteGlobalSecondaryIndexAction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeleteGlobalSecondaryIndexAction #

toConstr :: DeleteGlobalSecondaryIndexAction -> Constr #

dataTypeOf :: DeleteGlobalSecondaryIndexAction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeleteGlobalSecondaryIndexAction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeleteGlobalSecondaryIndexAction) #

gmapT :: (forall b. Data b => b -> b) -> DeleteGlobalSecondaryIndexAction -> DeleteGlobalSecondaryIndexAction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeleteGlobalSecondaryIndexAction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeleteGlobalSecondaryIndexAction -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeleteGlobalSecondaryIndexAction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeleteGlobalSecondaryIndexAction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeleteGlobalSecondaryIndexAction -> m DeleteGlobalSecondaryIndexAction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteGlobalSecondaryIndexAction -> m DeleteGlobalSecondaryIndexAction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteGlobalSecondaryIndexAction -> m DeleteGlobalSecondaryIndexAction #

Read DeleteGlobalSecondaryIndexAction Source # 
Show DeleteGlobalSecondaryIndexAction Source # 
Generic DeleteGlobalSecondaryIndexAction Source # 
Hashable DeleteGlobalSecondaryIndexAction Source # 
ToJSON DeleteGlobalSecondaryIndexAction Source # 
NFData DeleteGlobalSecondaryIndexAction Source # 
type Rep DeleteGlobalSecondaryIndexAction Source # 
type Rep DeleteGlobalSecondaryIndexAction = D1 * (MetaData "DeleteGlobalSecondaryIndexAction" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" True) (C1 * (MetaCons "DeleteGlobalSecondaryIndexAction'" PrefixI True) (S1 * (MetaSel (Just Symbol "_dgsiaIndexName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

deleteGlobalSecondaryIndexAction Source #

Creates a value of DeleteGlobalSecondaryIndexAction with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • dgsiaIndexName - The name of the global secondary index to be deleted.

dgsiaIndexName :: Lens' DeleteGlobalSecondaryIndexAction Text Source #

The name of the global secondary index to be deleted.

DeleteReplicaAction

data DeleteReplicaAction Source #

Represents a replica to be removed.

See: deleteReplicaAction smart constructor.

Instances

Eq DeleteReplicaAction Source # 
Data DeleteReplicaAction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeleteReplicaAction -> c DeleteReplicaAction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeleteReplicaAction #

toConstr :: DeleteReplicaAction -> Constr #

dataTypeOf :: DeleteReplicaAction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeleteReplicaAction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeleteReplicaAction) #

gmapT :: (forall b. Data b => b -> b) -> DeleteReplicaAction -> DeleteReplicaAction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeleteReplicaAction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeleteReplicaAction -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeleteReplicaAction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeleteReplicaAction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeleteReplicaAction -> m DeleteReplicaAction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteReplicaAction -> m DeleteReplicaAction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteReplicaAction -> m DeleteReplicaAction #

Read DeleteReplicaAction Source # 
Show DeleteReplicaAction Source # 
Generic DeleteReplicaAction Source # 
Hashable DeleteReplicaAction Source # 
ToJSON DeleteReplicaAction Source # 
NFData DeleteReplicaAction Source # 

Methods

rnf :: DeleteReplicaAction -> () #

type Rep DeleteReplicaAction Source # 
type Rep DeleteReplicaAction = D1 * (MetaData "DeleteReplicaAction" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" True) (C1 * (MetaCons "DeleteReplicaAction'" PrefixI True) (S1 * (MetaSel (Just Symbol "_draRegionName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

deleteReplicaAction Source #

Creates a value of DeleteReplicaAction with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

draRegionName :: Lens' DeleteReplicaAction Text Source #

The region of the replica to be removed.

DeleteRequest

data DeleteRequest Source #

Represents a request to perform a DeleteItem operation on an item.

See: deleteRequest smart constructor.

Instances

Eq DeleteRequest Source # 
Data DeleteRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeleteRequest -> c DeleteRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeleteRequest #

toConstr :: DeleteRequest -> Constr #

dataTypeOf :: DeleteRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DeleteRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeleteRequest) #

gmapT :: (forall b. Data b => b -> b) -> DeleteRequest -> DeleteRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeleteRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeleteRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeleteRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeleteRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeleteRequest -> m DeleteRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteRequest -> m DeleteRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeleteRequest -> m DeleteRequest #

Read DeleteRequest Source # 
Show DeleteRequest Source # 
Generic DeleteRequest Source # 

Associated Types

type Rep DeleteRequest :: * -> * #

Hashable DeleteRequest Source # 
ToJSON DeleteRequest Source # 
FromJSON DeleteRequest Source # 
NFData DeleteRequest Source # 

Methods

rnf :: DeleteRequest -> () #

type Rep DeleteRequest Source # 
type Rep DeleteRequest = D1 * (MetaData "DeleteRequest" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" True) (C1 * (MetaCons "DeleteRequest'" PrefixI True) (S1 * (MetaSel (Just Symbol "_drKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Map Text AttributeValue))))

deleteRequest :: DeleteRequest Source #

Creates a value of DeleteRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • drKey - A map of attribute name to attribute values, representing the primary key of the item to delete. All of the table's primary key attributes must be specified, and their data types must match those of the table's key schema.

drKey :: Lens' DeleteRequest (HashMap Text AttributeValue) Source #

A map of attribute name to attribute values, representing the primary key of the item to delete. All of the table's primary key attributes must be specified, and their data types must match those of the table's key schema.

ExpectedAttributeValue

data ExpectedAttributeValue Source #

Represents a condition to be compared with an attribute value. This condition can be used with DeleteItem , PutItem or UpdateItem operations; if the comparison evaluates to true, the operation succeeds; if not, the operation fails. You can use ExpectedAttributeValue in one of two different ways:

  • Use AttributeValueList to specify one or more values to compare against an attribute. Use ComparisonOperator to specify how you want to perform the comparison. If the comparison evaluates to true, then the conditional operation succeeds.
  • Use Value to specify a value that DynamoDB will compare against an attribute. If the values match, then ExpectedAttributeValue evaluates to true and the conditional operation succeeds. Optionally, you can also set Exists to false, indicating that you do not expect to find the attribute value in the table. In this case, the conditional operation succeeds only if the comparison evaluates to false.

Value and Exists are incompatible with AttributeValueList and ComparisonOperator . Note that if you use both sets of parameters at once, DynamoDB will return a ValidationException exception.

See: expectedAttributeValue smart constructor.

Instances

Eq ExpectedAttributeValue Source # 
Data ExpectedAttributeValue Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExpectedAttributeValue -> c ExpectedAttributeValue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExpectedAttributeValue #

toConstr :: ExpectedAttributeValue -> Constr #

dataTypeOf :: ExpectedAttributeValue -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ExpectedAttributeValue) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExpectedAttributeValue) #

gmapT :: (forall b. Data b => b -> b) -> ExpectedAttributeValue -> ExpectedAttributeValue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExpectedAttributeValue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExpectedAttributeValue -> r #

gmapQ :: (forall d. Data d => d -> u) -> ExpectedAttributeValue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExpectedAttributeValue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExpectedAttributeValue -> m ExpectedAttributeValue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpectedAttributeValue -> m ExpectedAttributeValue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpectedAttributeValue -> m ExpectedAttributeValue #

Read ExpectedAttributeValue Source # 
Show ExpectedAttributeValue Source # 
Generic ExpectedAttributeValue Source # 
Hashable ExpectedAttributeValue Source # 
ToJSON ExpectedAttributeValue Source # 
NFData ExpectedAttributeValue Source # 

Methods

rnf :: ExpectedAttributeValue -> () #

type Rep ExpectedAttributeValue Source # 
type Rep ExpectedAttributeValue = D1 * (MetaData "ExpectedAttributeValue" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "ExpectedAttributeValue'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_eavAttributeValueList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [AttributeValue]))) (S1 * (MetaSel (Just Symbol "_eavExists") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_eavValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe AttributeValue))) (S1 * (MetaSel (Just Symbol "_eavComparisonOperator") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ComparisonOperator))))))

expectedAttributeValue :: ExpectedAttributeValue Source #

Creates a value of ExpectedAttributeValue with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • eavAttributeValueList - One or more values to evaluate against the supplied attribute. The number of values in the list depends on the ComparisonOperator being used. For type Number, value comparisons are numeric. String value comparisons for greater than, equals, or less than are based on ASCII character code values. For example, a is greater than A , and a is greater than B . For a list of code values, see http://en.wikipedia.org/wiki/ASCII#ASCII_printable_characters . For Binary, DynamoDB treats each byte of the binary data as unsigned when it compares binary values. For information on specifying data types in JSON, see JSON Data Format in the Amazon DynamoDB Developer Guide .
  • eavExists - Causes DynamoDB to evaluate the value before attempting a conditional operation: * If Exists is true , DynamoDB will check to see if that attribute value already exists in the table. If it is found, then the operation succeeds. If it is not found, the operation fails with a ConditionalCheckFailedException . * If Exists is false , DynamoDB assumes that the attribute value does not exist in the table. If in fact the value does not exist, then the assumption is valid and the operation succeeds. If the value is found, despite the assumption that it does not exist, the operation fails with a ConditionalCheckFailedException . The default setting for Exists is true . If you supply a Value all by itself, DynamoDB assumes the attribute exists: You don't have to set Exists to true , because it is implied. DynamoDB returns a ValidationException if: * Exists is true but there is no Value to check. (You expect a value to exist, but don't specify what that value is.) * Exists is false but you also provide a Value . (You cannot expect an attribute to have a value, while also expecting it not to exist.)
  • eavValue - Represents the data for the expected attribute. Each attribute value is described as a name-value pair. The name is the data type, and the value is the data itself. For more information, see Data Types in the Amazon DynamoDB Developer Guide .
  • eavComparisonOperator - A comparator for evaluating attributes in the AttributeValueList . For example, equals, greater than, less than, etc. The following comparison operators are available: EQ | NE | LE | LT | GE | GT | NOT_NULL | NULL | CONTAINS | NOT_CONTAINS | BEGINS_WITH | IN | BETWEEN The following are descriptions of each comparison operator. * EQ : Equal. EQ is supported for all data types, including lists and maps. AttributeValueList can contain only one AttributeValue element of type String, Number, Binary, String Set, Number Set, or Binary Set. If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not equal {NS:["6", "2", "1"]} . * NE : Not equal. NE is supported for all data types, including lists and maps. AttributeValueList can contain only one AttributeValue of type String, Number, Binary, String Set, Number Set, or Binary Set. If an item contains an AttributeValue of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not equal {NS:["6", "2", "1"]} . * LE : Less than or equal. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} . * LT : Less than. AttributeValueList can contain only one AttributeValue of type String, Number, or Binary (not a set type). If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} . * GE : Greater than or equal. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} . * GT : Greater than. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} . * NOT_NULL : The attribute exists. NOT_NULL is supported for all data types, including lists and maps. * NULL : The attribute does not exist. NULL is supported for all data types, including lists and maps. * CONTAINS : Checks for a subsequence, or value in a set. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If the target attribute of the comparison is of type String, then the operator checks for a substring match. If the target attribute of the comparison is of type Binary, then the operator looks for a subsequence of the target that matches the input. If the target attribute of the comparison is a set ("SS ", "NS ", or "BS "), then the operator evaluates to true if it finds an exact match with any member of the set. CONTAINS is supported for lists: When evaluating "a CONTAINS b ", "a " can be a list; however, "b " cannot be a set, a map, or a list. * NOT_CONTAINS : Checks for absence of a subsequence, or absence of a value in a set. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If the target attribute of the comparison is a String, then the operator checks for the absence of a substring match. If the target attribute of the comparison is Binary, then the operator checks for the absence of a subsequence of the target that matches the input. If the target attribute of the comparison is a set ("SS ", "NS ", or "BS "), then the operator evaluates to true if it does not find an exact match with any member of the set. NOT_CONTAINS is supported for lists: When evaluating "a NOT CONTAINS b ", "a " can be a list; however, "b " cannot be a set, a map, or a list. * BEGINS_WITH : Checks for a prefix. AttributeValueList can contain only one AttributeValue of type String or Binary (not a Number or a set type). The target attribute of the comparison must be of type String or Binary (not a Number or a set type). * IN : Checks for matching elements in a list. AttributeValueList can contain one or more AttributeValue elements of type String, Number, or Binary. These attributes are compared against an existing attribute of an item. If any elements of the input are equal to the item attribute, the expression evaluates to true. * BETWEEN : Greater than or equal to the first value, and less than or equal to the second value. AttributeValueList must contain two AttributeValue elements of the same type, either String, Number, or Binary (not a set type). A target attribute matches if the target value is greater than, or equal to, the first element and less than, or equal to, the second element. If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not compare to {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]}

eavAttributeValueList :: Lens' ExpectedAttributeValue [AttributeValue] Source #

One or more values to evaluate against the supplied attribute. The number of values in the list depends on the ComparisonOperator being used. For type Number, value comparisons are numeric. String value comparisons for greater than, equals, or less than are based on ASCII character code values. For example, a is greater than A , and a is greater than B . For a list of code values, see http://en.wikipedia.org/wiki/ASCII#ASCII_printable_characters . For Binary, DynamoDB treats each byte of the binary data as unsigned when it compares binary values. For information on specifying data types in JSON, see JSON Data Format in the Amazon DynamoDB Developer Guide .

eavExists :: Lens' ExpectedAttributeValue (Maybe Bool) Source #

Causes DynamoDB to evaluate the value before attempting a conditional operation: * If Exists is true , DynamoDB will check to see if that attribute value already exists in the table. If it is found, then the operation succeeds. If it is not found, the operation fails with a ConditionalCheckFailedException . * If Exists is false , DynamoDB assumes that the attribute value does not exist in the table. If in fact the value does not exist, then the assumption is valid and the operation succeeds. If the value is found, despite the assumption that it does not exist, the operation fails with a ConditionalCheckFailedException . The default setting for Exists is true . If you supply a Value all by itself, DynamoDB assumes the attribute exists: You don't have to set Exists to true , because it is implied. DynamoDB returns a ValidationException if: * Exists is true but there is no Value to check. (You expect a value to exist, but don't specify what that value is.) * Exists is false but you also provide a Value . (You cannot expect an attribute to have a value, while also expecting it not to exist.)

eavValue :: Lens' ExpectedAttributeValue (Maybe AttributeValue) Source #

Represents the data for the expected attribute. Each attribute value is described as a name-value pair. The name is the data type, and the value is the data itself. For more information, see Data Types in the Amazon DynamoDB Developer Guide .

eavComparisonOperator :: Lens' ExpectedAttributeValue (Maybe ComparisonOperator) Source #

A comparator for evaluating attributes in the AttributeValueList . For example, equals, greater than, less than, etc. The following comparison operators are available: EQ | NE | LE | LT | GE | GT | NOT_NULL | NULL | CONTAINS | NOT_CONTAINS | BEGINS_WITH | IN | BETWEEN The following are descriptions of each comparison operator. * EQ : Equal. EQ is supported for all data types, including lists and maps. AttributeValueList can contain only one AttributeValue element of type String, Number, Binary, String Set, Number Set, or Binary Set. If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not equal {NS:["6", "2", "1"]} . * NE : Not equal. NE is supported for all data types, including lists and maps. AttributeValueList can contain only one AttributeValue of type String, Number, Binary, String Set, Number Set, or Binary Set. If an item contains an AttributeValue of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not equal {NS:["6", "2", "1"]} . * LE : Less than or equal. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} . * LT : Less than. AttributeValueList can contain only one AttributeValue of type String, Number, or Binary (not a set type). If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} . * GE : Greater than or equal. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} . * GT : Greater than. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not equal {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]} . * NOT_NULL : The attribute exists. NOT_NULL is supported for all data types, including lists and maps. * NULL : The attribute does not exist. NULL is supported for all data types, including lists and maps. * CONTAINS : Checks for a subsequence, or value in a set. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If the target attribute of the comparison is of type String, then the operator checks for a substring match. If the target attribute of the comparison is of type Binary, then the operator looks for a subsequence of the target that matches the input. If the target attribute of the comparison is a set ("SS ", "NS ", or "BS "), then the operator evaluates to true if it finds an exact match with any member of the set. CONTAINS is supported for lists: When evaluating "a CONTAINS b ", "a " can be a list; however, "b " cannot be a set, a map, or a list. * NOT_CONTAINS : Checks for absence of a subsequence, or absence of a value in a set. AttributeValueList can contain only one AttributeValue element of type String, Number, or Binary (not a set type). If the target attribute of the comparison is a String, then the operator checks for the absence of a substring match. If the target attribute of the comparison is Binary, then the operator checks for the absence of a subsequence of the target that matches the input. If the target attribute of the comparison is a set ("SS ", "NS ", or "BS "), then the operator evaluates to true if it does not find an exact match with any member of the set. NOT_CONTAINS is supported for lists: When evaluating "a NOT CONTAINS b ", "a " can be a list; however, "b " cannot be a set, a map, or a list. * BEGINS_WITH : Checks for a prefix. AttributeValueList can contain only one AttributeValue of type String or Binary (not a Number or a set type). The target attribute of the comparison must be of type String or Binary (not a Number or a set type). * IN : Checks for matching elements in a list. AttributeValueList can contain one or more AttributeValue elements of type String, Number, or Binary. These attributes are compared against an existing attribute of an item. If any elements of the input are equal to the item attribute, the expression evaluates to true. * BETWEEN : Greater than or equal to the first value, and less than or equal to the second value. AttributeValueList must contain two AttributeValue elements of the same type, either String, Number, or Binary (not a set type). A target attribute matches if the target value is greater than, or equal to, the first element and less than, or equal to, the second element. If an item contains an AttributeValue element of a different type than the one provided in the request, the value does not match. For example, {S:"6"} does not compare to {N:"6"} . Also, {N:"6"} does not compare to {NS:["6", "2", "1"]}

GlobalSecondaryIndex

data GlobalSecondaryIndex Source #

Represents the properties of a global secondary index.

See: globalSecondaryIndex smart constructor.

Instances

Eq GlobalSecondaryIndex Source # 
Data GlobalSecondaryIndex Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GlobalSecondaryIndex -> c GlobalSecondaryIndex #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GlobalSecondaryIndex #

toConstr :: GlobalSecondaryIndex -> Constr #

dataTypeOf :: GlobalSecondaryIndex -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GlobalSecondaryIndex) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GlobalSecondaryIndex) #

gmapT :: (forall b. Data b => b -> b) -> GlobalSecondaryIndex -> GlobalSecondaryIndex #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlobalSecondaryIndex -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlobalSecondaryIndex -> r #

gmapQ :: (forall d. Data d => d -> u) -> GlobalSecondaryIndex -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GlobalSecondaryIndex -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlobalSecondaryIndex -> m GlobalSecondaryIndex #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalSecondaryIndex -> m GlobalSecondaryIndex #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalSecondaryIndex -> m GlobalSecondaryIndex #

Read GlobalSecondaryIndex Source # 
Show GlobalSecondaryIndex Source # 
Generic GlobalSecondaryIndex Source # 
Hashable GlobalSecondaryIndex Source # 
ToJSON GlobalSecondaryIndex Source # 
NFData GlobalSecondaryIndex Source # 

Methods

rnf :: GlobalSecondaryIndex -> () #

type Rep GlobalSecondaryIndex Source # 
type Rep GlobalSecondaryIndex = D1 * (MetaData "GlobalSecondaryIndex" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "GlobalSecondaryIndex'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_gsiIndexName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_gsiKeySchema") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (List1 KeySchemaElement)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_gsiProjection") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Projection)) (S1 * (MetaSel (Just Symbol "_gsiProvisionedThroughput") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProvisionedThroughput)))))

globalSecondaryIndex Source #

Creates a value of GlobalSecondaryIndex with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • gsiIndexName - The name of the global secondary index. The name must be unique among all other indexes on this table.
  • gsiKeySchema - The complete key schema for a global secondary index, which consists of one or more pairs of attribute names and key types: * HASH - partition key * RANGE - sort key
  • gsiProjection - Represents attributes that are copied (projected) from the table into the global secondary index. These are in addition to the primary key attributes and index key attributes, which are automatically projected.
  • gsiProvisionedThroughput - Represents the provisioned throughput settings for the specified global secondary index. For current minimum and maximum provisioned throughput values, see Limits in the Amazon DynamoDB Developer Guide .

gsiIndexName :: Lens' GlobalSecondaryIndex Text Source #

The name of the global secondary index. The name must be unique among all other indexes on this table.

gsiKeySchema :: Lens' GlobalSecondaryIndex (NonEmpty KeySchemaElement) Source #

The complete key schema for a global secondary index, which consists of one or more pairs of attribute names and key types: * HASH - partition key * RANGE - sort key

gsiProjection :: Lens' GlobalSecondaryIndex Projection Source #

Represents attributes that are copied (projected) from the table into the global secondary index. These are in addition to the primary key attributes and index key attributes, which are automatically projected.

gsiProvisionedThroughput :: Lens' GlobalSecondaryIndex ProvisionedThroughput Source #

Represents the provisioned throughput settings for the specified global secondary index. For current minimum and maximum provisioned throughput values, see Limits in the Amazon DynamoDB Developer Guide .

GlobalSecondaryIndexDescription

data GlobalSecondaryIndexDescription Source #

Represents the properties of a global secondary index.

See: globalSecondaryIndexDescription smart constructor.

Instances

Eq GlobalSecondaryIndexDescription Source # 
Data GlobalSecondaryIndexDescription Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GlobalSecondaryIndexDescription -> c GlobalSecondaryIndexDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GlobalSecondaryIndexDescription #

toConstr :: GlobalSecondaryIndexDescription -> Constr #

dataTypeOf :: GlobalSecondaryIndexDescription -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GlobalSecondaryIndexDescription) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GlobalSecondaryIndexDescription) #

gmapT :: (forall b. Data b => b -> b) -> GlobalSecondaryIndexDescription -> GlobalSecondaryIndexDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlobalSecondaryIndexDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlobalSecondaryIndexDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> GlobalSecondaryIndexDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GlobalSecondaryIndexDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlobalSecondaryIndexDescription -> m GlobalSecondaryIndexDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalSecondaryIndexDescription -> m GlobalSecondaryIndexDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalSecondaryIndexDescription -> m GlobalSecondaryIndexDescription #

Read GlobalSecondaryIndexDescription Source # 
Show GlobalSecondaryIndexDescription Source # 
Generic GlobalSecondaryIndexDescription Source # 
Hashable GlobalSecondaryIndexDescription Source # 
FromJSON GlobalSecondaryIndexDescription Source # 
NFData GlobalSecondaryIndexDescription Source # 
type Rep GlobalSecondaryIndexDescription Source # 

globalSecondaryIndexDescription :: GlobalSecondaryIndexDescription Source #

Creates a value of GlobalSecondaryIndexDescription with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • gsidBackfilling - Indicates whether the index is currently backfilling. Backfilling is the process of reading items from the table and determining whether they can be added to the index. (Not all items will qualify: For example, a partition key cannot have any duplicate values.) If an item can be added to the index, DynamoDB will do so. After all items have been processed, the backfilling operation is complete and Backfilling is false.
  • gsidIndexSizeBytes - The total size of the specified index, in bytes. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value.
  • gsidIndexStatus - The current state of the global secondary index: * CREATING - The index is being created. * UPDATING - The index is being updated. * DELETING - The index is being deleted. * ACTIVE - The index is ready for use.
  • gsidProvisionedThroughput - Represents the provisioned throughput settings for the specified global secondary index. For current minimum and maximum provisioned throughput values, see Limits in the Amazon DynamoDB Developer Guide .
  • gsidIndexARN - The Amazon Resource Name (ARN) that uniquely identifies the index.
  • gsidKeySchema - The complete key schema for a global secondary index, which consists of one or more pairs of attribute names and key types: * HASH - partition key * RANGE - sort key
  • gsidProjection - Represents attributes that are copied (projected) from the table into the global secondary index. These are in addition to the primary key attributes and index key attributes, which are automatically projected.
  • gsidItemCount - The number of items in the specified index. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value.
  • gsidIndexName - The name of the global secondary index.

gsidBackfilling :: Lens' GlobalSecondaryIndexDescription (Maybe Bool) Source #

Indicates whether the index is currently backfilling. Backfilling is the process of reading items from the table and determining whether they can be added to the index. (Not all items will qualify: For example, a partition key cannot have any duplicate values.) If an item can be added to the index, DynamoDB will do so. After all items have been processed, the backfilling operation is complete and Backfilling is false.

gsidIndexSizeBytes :: Lens' GlobalSecondaryIndexDescription (Maybe Integer) Source #

The total size of the specified index, in bytes. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value.

gsidIndexStatus :: Lens' GlobalSecondaryIndexDescription (Maybe IndexStatus) Source #

The current state of the global secondary index: * CREATING - The index is being created. * UPDATING - The index is being updated. * DELETING - The index is being deleted. * ACTIVE - The index is ready for use.

gsidProvisionedThroughput :: Lens' GlobalSecondaryIndexDescription (Maybe ProvisionedThroughputDescription) Source #

Represents the provisioned throughput settings for the specified global secondary index. For current minimum and maximum provisioned throughput values, see Limits in the Amazon DynamoDB Developer Guide .

gsidIndexARN :: Lens' GlobalSecondaryIndexDescription (Maybe Text) Source #

The Amazon Resource Name (ARN) that uniquely identifies the index.

gsidKeySchema :: Lens' GlobalSecondaryIndexDescription (Maybe (NonEmpty KeySchemaElement)) Source #

The complete key schema for a global secondary index, which consists of one or more pairs of attribute names and key types: * HASH - partition key * RANGE - sort key

gsidProjection :: Lens' GlobalSecondaryIndexDescription (Maybe Projection) Source #

Represents attributes that are copied (projected) from the table into the global secondary index. These are in addition to the primary key attributes and index key attributes, which are automatically projected.

gsidItemCount :: Lens' GlobalSecondaryIndexDescription (Maybe Integer) Source #

The number of items in the specified index. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value.

gsidIndexName :: Lens' GlobalSecondaryIndexDescription (Maybe Text) Source #

The name of the global secondary index.

GlobalSecondaryIndexInfo

data GlobalSecondaryIndexInfo Source #

Represents the properties of a global secondary index for the table when the backup was created.

See: globalSecondaryIndexInfo smart constructor.

Instances

Eq GlobalSecondaryIndexInfo Source # 
Data GlobalSecondaryIndexInfo Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GlobalSecondaryIndexInfo -> c GlobalSecondaryIndexInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GlobalSecondaryIndexInfo #

toConstr :: GlobalSecondaryIndexInfo -> Constr #

dataTypeOf :: GlobalSecondaryIndexInfo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GlobalSecondaryIndexInfo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GlobalSecondaryIndexInfo) #

gmapT :: (forall b. Data b => b -> b) -> GlobalSecondaryIndexInfo -> GlobalSecondaryIndexInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlobalSecondaryIndexInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlobalSecondaryIndexInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> GlobalSecondaryIndexInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GlobalSecondaryIndexInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlobalSecondaryIndexInfo -> m GlobalSecondaryIndexInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalSecondaryIndexInfo -> m GlobalSecondaryIndexInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalSecondaryIndexInfo -> m GlobalSecondaryIndexInfo #

Read GlobalSecondaryIndexInfo Source # 
Show GlobalSecondaryIndexInfo Source # 
Generic GlobalSecondaryIndexInfo Source # 
Hashable GlobalSecondaryIndexInfo Source # 
FromJSON GlobalSecondaryIndexInfo Source # 
NFData GlobalSecondaryIndexInfo Source # 
type Rep GlobalSecondaryIndexInfo Source # 
type Rep GlobalSecondaryIndexInfo = D1 * (MetaData "GlobalSecondaryIndexInfo" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "GlobalSecondaryIndexInfo'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_gsiiProvisionedThroughput") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ProvisionedThroughput))) (S1 * (MetaSel (Just Symbol "_gsiiKeySchema") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (List1 KeySchemaElement))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_gsiiProjection") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Projection))) (S1 * (MetaSel (Just Symbol "_gsiiIndexName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

globalSecondaryIndexInfo :: GlobalSecondaryIndexInfo Source #

Creates a value of GlobalSecondaryIndexInfo with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • gsiiProvisionedThroughput - Represents the provisioned throughput settings for the specified global secondary index.
  • gsiiKeySchema - The complete key schema for a global secondary index, which consists of one or more pairs of attribute names and key types: * HASH - partition key * RANGE - sort key
  • gsiiProjection - Represents attributes that are copied (projected) from the table into the global secondary index. These are in addition to the primary key attributes and index key attributes, which are automatically projected.
  • gsiiIndexName - The name of the global secondary index.

gsiiProvisionedThroughput :: Lens' GlobalSecondaryIndexInfo (Maybe ProvisionedThroughput) Source #

Represents the provisioned throughput settings for the specified global secondary index.

gsiiKeySchema :: Lens' GlobalSecondaryIndexInfo (Maybe (NonEmpty KeySchemaElement)) Source #

The complete key schema for a global secondary index, which consists of one or more pairs of attribute names and key types: * HASH - partition key * RANGE - sort key

gsiiProjection :: Lens' GlobalSecondaryIndexInfo (Maybe Projection) Source #

Represents attributes that are copied (projected) from the table into the global secondary index. These are in addition to the primary key attributes and index key attributes, which are automatically projected.

gsiiIndexName :: Lens' GlobalSecondaryIndexInfo (Maybe Text) Source #

The name of the global secondary index.

GlobalSecondaryIndexUpdate

data GlobalSecondaryIndexUpdate Source #

Represents one of the following:

  • A new global secondary index to be added to an existing table.
  • New provisioned throughput parameters for an existing global secondary index.
  • An existing global secondary index to be removed from an existing table.

See: globalSecondaryIndexUpdate smart constructor.

Instances

Eq GlobalSecondaryIndexUpdate Source # 
Data GlobalSecondaryIndexUpdate Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GlobalSecondaryIndexUpdate -> c GlobalSecondaryIndexUpdate #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GlobalSecondaryIndexUpdate #

toConstr :: GlobalSecondaryIndexUpdate -> Constr #

dataTypeOf :: GlobalSecondaryIndexUpdate -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GlobalSecondaryIndexUpdate) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GlobalSecondaryIndexUpdate) #

gmapT :: (forall b. Data b => b -> b) -> GlobalSecondaryIndexUpdate -> GlobalSecondaryIndexUpdate #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlobalSecondaryIndexUpdate -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlobalSecondaryIndexUpdate -> r #

gmapQ :: (forall d. Data d => d -> u) -> GlobalSecondaryIndexUpdate -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GlobalSecondaryIndexUpdate -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlobalSecondaryIndexUpdate -> m GlobalSecondaryIndexUpdate #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalSecondaryIndexUpdate -> m GlobalSecondaryIndexUpdate #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalSecondaryIndexUpdate -> m GlobalSecondaryIndexUpdate #

Read GlobalSecondaryIndexUpdate Source # 
Show GlobalSecondaryIndexUpdate Source # 
Generic GlobalSecondaryIndexUpdate Source # 
Hashable GlobalSecondaryIndexUpdate Source # 
ToJSON GlobalSecondaryIndexUpdate Source # 
NFData GlobalSecondaryIndexUpdate Source # 
type Rep GlobalSecondaryIndexUpdate Source # 
type Rep GlobalSecondaryIndexUpdate = D1 * (MetaData "GlobalSecondaryIndexUpdate" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "GlobalSecondaryIndexUpdate'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_gsiuCreate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe CreateGlobalSecondaryIndexAction))) ((:*:) * (S1 * (MetaSel (Just Symbol "_gsiuDelete") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DeleteGlobalSecondaryIndexAction))) (S1 * (MetaSel (Just Symbol "_gsiuUpdate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe UpdateGlobalSecondaryIndexAction))))))

globalSecondaryIndexUpdate :: GlobalSecondaryIndexUpdate Source #

Creates a value of GlobalSecondaryIndexUpdate with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • gsiuCreate - The parameters required for creating a global secondary index on an existing table: * IndexName * KeySchema * AttributeDefinitions * Projection * ProvisionedThroughput
  • gsiuDelete - The name of an existing global secondary index to be removed.
  • gsiuUpdate - The name of an existing global secondary index, along with new provisioned throughput settings to be applied to that index.

gsiuCreate :: Lens' GlobalSecondaryIndexUpdate (Maybe CreateGlobalSecondaryIndexAction) Source #

The parameters required for creating a global secondary index on an existing table: * IndexName * KeySchema * AttributeDefinitions * Projection * ProvisionedThroughput

gsiuDelete :: Lens' GlobalSecondaryIndexUpdate (Maybe DeleteGlobalSecondaryIndexAction) Source #

The name of an existing global secondary index to be removed.

gsiuUpdate :: Lens' GlobalSecondaryIndexUpdate (Maybe UpdateGlobalSecondaryIndexAction) Source #

The name of an existing global secondary index, along with new provisioned throughput settings to be applied to that index.

GlobalTable

data GlobalTable Source #

Represents the properties of a global table.

See: globalTable smart constructor.

Instances

Eq GlobalTable Source # 
Data GlobalTable Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GlobalTable -> c GlobalTable #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GlobalTable #

toConstr :: GlobalTable -> Constr #

dataTypeOf :: GlobalTable -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GlobalTable) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GlobalTable) #

gmapT :: (forall b. Data b => b -> b) -> GlobalTable -> GlobalTable #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlobalTable -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlobalTable -> r #

gmapQ :: (forall d. Data d => d -> u) -> GlobalTable -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GlobalTable -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlobalTable -> m GlobalTable #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalTable -> m GlobalTable #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalTable -> m GlobalTable #

Read GlobalTable Source # 
Show GlobalTable Source # 
Generic GlobalTable Source # 

Associated Types

type Rep GlobalTable :: * -> * #

Hashable GlobalTable Source # 
FromJSON GlobalTable Source # 
NFData GlobalTable Source # 

Methods

rnf :: GlobalTable -> () #

type Rep GlobalTable Source # 
type Rep GlobalTable = D1 * (MetaData "GlobalTable" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "GlobalTable'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_gtGlobalTableName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_gtReplicationGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Replica])))))

globalTable :: GlobalTable Source #

Creates a value of GlobalTable with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

gtGlobalTableName :: Lens' GlobalTable (Maybe Text) Source #

The global table name.

gtReplicationGroup :: Lens' GlobalTable [Replica] Source #

The regions where the global table has replicas.

GlobalTableDescription

data GlobalTableDescription Source #

Contains details about the global table.

See: globalTableDescription smart constructor.

Instances

Eq GlobalTableDescription Source # 
Data GlobalTableDescription Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GlobalTableDescription -> c GlobalTableDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GlobalTableDescription #

toConstr :: GlobalTableDescription -> Constr #

dataTypeOf :: GlobalTableDescription -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GlobalTableDescription) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GlobalTableDescription) #

gmapT :: (forall b. Data b => b -> b) -> GlobalTableDescription -> GlobalTableDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlobalTableDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlobalTableDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> GlobalTableDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GlobalTableDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlobalTableDescription -> m GlobalTableDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalTableDescription -> m GlobalTableDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalTableDescription -> m GlobalTableDescription #

Read GlobalTableDescription Source # 
Show GlobalTableDescription Source # 
Generic GlobalTableDescription Source # 
Hashable GlobalTableDescription Source # 
FromJSON GlobalTableDescription Source # 
NFData GlobalTableDescription Source # 

Methods

rnf :: GlobalTableDescription -> () #

type Rep GlobalTableDescription Source # 
type Rep GlobalTableDescription = D1 * (MetaData "GlobalTableDescription" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "GlobalTableDescription'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_gtdGlobalTableStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe GlobalTableStatus))) (S1 * (MetaSel (Just Symbol "_gtdGlobalTableName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_gtdGlobalTableARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "_gtdCreationDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_gtdReplicationGroup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [ReplicaDescription])))))))

globalTableDescription :: GlobalTableDescription Source #

Creates a value of GlobalTableDescription with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • gtdGlobalTableStatus - The current state of the global table: * CREATING - The global table is being created. * UPDATING - The global table is being updated. * DELETING - The global table is being deleted. * ACTIVE - The global table is ready for use.
  • gtdGlobalTableName - The global table name.
  • gtdGlobalTableARN - The unique identifier of the global table.
  • gtdCreationDateTime - The creation time of the global table.
  • gtdReplicationGroup - The regions where the global table has replicas.

gtdGlobalTableStatus :: Lens' GlobalTableDescription (Maybe GlobalTableStatus) Source #

The current state of the global table: * CREATING - The global table is being created. * UPDATING - The global table is being updated. * DELETING - The global table is being deleted. * ACTIVE - The global table is ready for use.

gtdGlobalTableARN :: Lens' GlobalTableDescription (Maybe Text) Source #

The unique identifier of the global table.

gtdCreationDateTime :: Lens' GlobalTableDescription (Maybe UTCTime) Source #

The creation time of the global table.

gtdReplicationGroup :: Lens' GlobalTableDescription [ReplicaDescription] Source #

The regions where the global table has replicas.

GlobalTableGlobalSecondaryIndexSettingsUpdate

data GlobalTableGlobalSecondaryIndexSettingsUpdate Source #

Represents the settings of a global secondary index for a global table that will be modified.

See: globalTableGlobalSecondaryIndexSettingsUpdate smart constructor.

Instances

Eq GlobalTableGlobalSecondaryIndexSettingsUpdate Source # 
Data GlobalTableGlobalSecondaryIndexSettingsUpdate Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GlobalTableGlobalSecondaryIndexSettingsUpdate -> c GlobalTableGlobalSecondaryIndexSettingsUpdate #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GlobalTableGlobalSecondaryIndexSettingsUpdate #

toConstr :: GlobalTableGlobalSecondaryIndexSettingsUpdate -> Constr #

dataTypeOf :: GlobalTableGlobalSecondaryIndexSettingsUpdate -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GlobalTableGlobalSecondaryIndexSettingsUpdate) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GlobalTableGlobalSecondaryIndexSettingsUpdate) #

gmapT :: (forall b. Data b => b -> b) -> GlobalTableGlobalSecondaryIndexSettingsUpdate -> GlobalTableGlobalSecondaryIndexSettingsUpdate #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GlobalTableGlobalSecondaryIndexSettingsUpdate -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GlobalTableGlobalSecondaryIndexSettingsUpdate -> r #

gmapQ :: (forall d. Data d => d -> u) -> GlobalTableGlobalSecondaryIndexSettingsUpdate -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GlobalTableGlobalSecondaryIndexSettingsUpdate -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GlobalTableGlobalSecondaryIndexSettingsUpdate -> m GlobalTableGlobalSecondaryIndexSettingsUpdate #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalTableGlobalSecondaryIndexSettingsUpdate -> m GlobalTableGlobalSecondaryIndexSettingsUpdate #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GlobalTableGlobalSecondaryIndexSettingsUpdate -> m GlobalTableGlobalSecondaryIndexSettingsUpdate #

Read GlobalTableGlobalSecondaryIndexSettingsUpdate Source # 
Show GlobalTableGlobalSecondaryIndexSettingsUpdate Source # 
Generic GlobalTableGlobalSecondaryIndexSettingsUpdate Source # 
Hashable GlobalTableGlobalSecondaryIndexSettingsUpdate Source # 
ToJSON GlobalTableGlobalSecondaryIndexSettingsUpdate Source # 
NFData GlobalTableGlobalSecondaryIndexSettingsUpdate Source # 
type Rep GlobalTableGlobalSecondaryIndexSettingsUpdate Source # 
type Rep GlobalTableGlobalSecondaryIndexSettingsUpdate = D1 * (MetaData "GlobalTableGlobalSecondaryIndexSettingsUpdate" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "GlobalTableGlobalSecondaryIndexSettingsUpdate'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_gtgsisuProvisionedWriteCapacityUnits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_gtgsisuIndexName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

globalTableGlobalSecondaryIndexSettingsUpdate Source #

Creates a value of GlobalTableGlobalSecondaryIndexSettingsUpdate with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

gtgsisuProvisionedWriteCapacityUnits :: Lens' GlobalTableGlobalSecondaryIndexSettingsUpdate (Maybe Natural) Source #

The maximum number of writes consumed per second before DynamoDB returns a ThrottlingException.

gtgsisuIndexName :: Lens' GlobalTableGlobalSecondaryIndexSettingsUpdate Text Source #

The name of the global secondary index. The name must be unique among all other indexes on this table.

ItemCollectionMetrics

data ItemCollectionMetrics Source #

Information about item collections, if any, that were affected by the operation. ItemCollectionMetrics is only returned if the request asked for it. If the table does not have any local secondary indexes, this information is not returned in the response.

See: itemCollectionMetrics smart constructor.

Instances

Eq ItemCollectionMetrics Source # 
Data ItemCollectionMetrics Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ItemCollectionMetrics -> c ItemCollectionMetrics #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ItemCollectionMetrics #

toConstr :: ItemCollectionMetrics -> Constr #

dataTypeOf :: ItemCollectionMetrics -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ItemCollectionMetrics) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ItemCollectionMetrics) #

gmapT :: (forall b. Data b => b -> b) -> ItemCollectionMetrics -> ItemCollectionMetrics #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ItemCollectionMetrics -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ItemCollectionMetrics -> r #

gmapQ :: (forall d. Data d => d -> u) -> ItemCollectionMetrics -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ItemCollectionMetrics -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ItemCollectionMetrics -> m ItemCollectionMetrics #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ItemCollectionMetrics -> m ItemCollectionMetrics #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ItemCollectionMetrics -> m ItemCollectionMetrics #

Read ItemCollectionMetrics Source # 
Show ItemCollectionMetrics Source # 
Generic ItemCollectionMetrics Source # 
Hashable ItemCollectionMetrics Source # 
FromJSON ItemCollectionMetrics Source # 
NFData ItemCollectionMetrics Source # 

Methods

rnf :: ItemCollectionMetrics -> () #

type Rep ItemCollectionMetrics Source # 
type Rep ItemCollectionMetrics = D1 * (MetaData "ItemCollectionMetrics" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "ItemCollectionMetrics'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_icmItemCollectionKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text AttributeValue)))) (S1 * (MetaSel (Just Symbol "_icmSizeEstimateRangeGB") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [Double])))))

itemCollectionMetrics :: ItemCollectionMetrics Source #

Creates a value of ItemCollectionMetrics with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • icmItemCollectionKey - The partition key value of the item collection. This value is the same as the partition key value of the item.
  • icmSizeEstimateRangeGB - An estimate of item collection size, in gigabytes. This value is a two-element array containing a lower bound and an upper bound for the estimate. The estimate includes the size of all the items in the table, plus the size of all attributes projected into all of the local secondary indexes on that table. Use this estimate to measure whether a local secondary index is approaching its size limit. The estimate is subject to change over time; therefore, do not rely on the precision or accuracy of the estimate.

icmItemCollectionKey :: Lens' ItemCollectionMetrics (HashMap Text AttributeValue) Source #

The partition key value of the item collection. This value is the same as the partition key value of the item.

icmSizeEstimateRangeGB :: Lens' ItemCollectionMetrics [Double] Source #

An estimate of item collection size, in gigabytes. This value is a two-element array containing a lower bound and an upper bound for the estimate. The estimate includes the size of all the items in the table, plus the size of all attributes projected into all of the local secondary indexes on that table. Use this estimate to measure whether a local secondary index is approaching its size limit. The estimate is subject to change over time; therefore, do not rely on the precision or accuracy of the estimate.

KeySchemaElement

data KeySchemaElement Source #

Represents a single element of a key schema. A key schema specifies the attributes that make up the primary key of a table, or the key attributes of an index.

A KeySchemaElement represents exactly one attribute of the primary key. For example, a simple primary key would be represented by one KeySchemaElement (for the partition key). A composite primary key would require one KeySchemaElement for the partition key, and another KeySchemaElement for the sort key.

A KeySchemaElement must be a scalar, top-level attribute (not a nested attribute). The data type must be one of String, Number, or Binary. The attribute cannot be nested within a List or a Map.

See: keySchemaElement smart constructor.

Instances

Eq KeySchemaElement Source # 
Data KeySchemaElement Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KeySchemaElement -> c KeySchemaElement #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KeySchemaElement #

toConstr :: KeySchemaElement -> Constr #

dataTypeOf :: KeySchemaElement -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c KeySchemaElement) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KeySchemaElement) #

gmapT :: (forall b. Data b => b -> b) -> KeySchemaElement -> KeySchemaElement #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KeySchemaElement -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KeySchemaElement -> r #

gmapQ :: (forall d. Data d => d -> u) -> KeySchemaElement -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> KeySchemaElement -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> KeySchemaElement -> m KeySchemaElement #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KeySchemaElement -> m KeySchemaElement #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KeySchemaElement -> m KeySchemaElement #

Read KeySchemaElement Source # 
Show KeySchemaElement Source # 
Generic KeySchemaElement Source # 
Hashable KeySchemaElement Source # 
ToJSON KeySchemaElement Source # 
FromJSON KeySchemaElement Source # 
NFData KeySchemaElement Source # 

Methods

rnf :: KeySchemaElement -> () #

type Rep KeySchemaElement Source # 
type Rep KeySchemaElement = D1 * (MetaData "KeySchemaElement" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "KeySchemaElement'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_kseAttributeName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_kseKeyType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * KeyType))))

keySchemaElement Source #

Creates a value of KeySchemaElement with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • kseAttributeName - The name of a key attribute.
  • kseKeyType - The role that this key attribute will assume: * HASH - partition key * RANGE - sort key

kseAttributeName :: Lens' KeySchemaElement Text Source #

The name of a key attribute.

kseKeyType :: Lens' KeySchemaElement KeyType Source #

The role that this key attribute will assume: * HASH - partition key * RANGE - sort key

KeysAndAttributes

data KeysAndAttributes Source #

Represents a set of primary keys and, for each key, the attributes to retrieve from the table.

For each primary key, you must provide all of the key attributes. For example, with a simple primary key, you only need to provide the partition key. For a composite primary key, you must provide both the partition key and the sort key.

See: keysAndAttributes smart constructor.

Instances

Eq KeysAndAttributes Source # 
Data KeysAndAttributes Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KeysAndAttributes -> c KeysAndAttributes #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KeysAndAttributes #

toConstr :: KeysAndAttributes -> Constr #

dataTypeOf :: KeysAndAttributes -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c KeysAndAttributes) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KeysAndAttributes) #

gmapT :: (forall b. Data b => b -> b) -> KeysAndAttributes -> KeysAndAttributes #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KeysAndAttributes -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KeysAndAttributes -> r #

gmapQ :: (forall d. Data d => d -> u) -> KeysAndAttributes -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> KeysAndAttributes -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> KeysAndAttributes -> m KeysAndAttributes #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KeysAndAttributes -> m KeysAndAttributes #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KeysAndAttributes -> m KeysAndAttributes #

Read KeysAndAttributes Source # 
Show KeysAndAttributes Source # 
Generic KeysAndAttributes Source # 
Hashable KeysAndAttributes Source # 
ToJSON KeysAndAttributes Source # 
FromJSON KeysAndAttributes Source # 
NFData KeysAndAttributes Source # 

Methods

rnf :: KeysAndAttributes -> () #

type Rep KeysAndAttributes Source # 
type Rep KeysAndAttributes = D1 * (MetaData "KeysAndAttributes" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "KeysAndAttributes'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_kaaProjectionExpression") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_kaaAttributesToGet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (List1 Text))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_kaaExpressionAttributeNames") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (Map Text Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_kaaConsistentRead") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool))) (S1 * (MetaSel (Just Symbol "_kaaKeys") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (List1 (Map Text AttributeValue))))))))

keysAndAttributes Source #

Creates a value of KeysAndAttributes with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • kaaProjectionExpression - A string that identifies one or more attributes to retrieve from the table. These attributes can include scalars, sets, or elements of a JSON document. The attributes in the ProjectionExpression must be separated by commas. If no attribute names are specified, then all attributes will be returned. If any of the requested attributes are not found, they will not appear in the result. For more information, see Accessing Item Attributes in the Amazon DynamoDB Developer Guide .
  • kaaAttributesToGet - This is a legacy parameter. Use ProjectionExpression instead. For more information, see Legacy Conditional Parameters in the Amazon DynamoDB Developer Guide .
  • kaaExpressionAttributeNames - One or more substitution tokens for attribute names in an expression. The following are some use cases for using ExpressionAttributeNames : * To access an attribute whose name conflicts with a DynamoDB reserved word. * To create a placeholder for repeating occurrences of an attribute name in an expression. * To prevent special characters in an attribute name from being misinterpreted in an expression. Use the # character in an expression to dereference an attribute name. For example, consider the following attribute name: * Percentile The name of this attribute conflicts with a reserved word, so it cannot be used directly in an expression. (For the complete list of reserved words, see Reserved Words in the Amazon DynamoDB Developer Guide ). To work around this, you could specify the following for ExpressionAttributeNames : * {"#P":Percentile} You could then use this substitution in an expression, as in this example: * #P = :val For more information on expression attribute names, see Accessing Item Attributes in the Amazon DynamoDB Developer Guide .
  • kaaConsistentRead - The consistency of a read operation. If set to true , then a strongly consistent read is used; otherwise, an eventually consistent read is used.
  • kaaKeys - The primary key attribute values that define the items and the attributes associated with the items.

kaaProjectionExpression :: Lens' KeysAndAttributes (Maybe Text) Source #

A string that identifies one or more attributes to retrieve from the table. These attributes can include scalars, sets, or elements of a JSON document. The attributes in the ProjectionExpression must be separated by commas. If no attribute names are specified, then all attributes will be returned. If any of the requested attributes are not found, they will not appear in the result. For more information, see Accessing Item Attributes in the Amazon DynamoDB Developer Guide .

kaaAttributesToGet :: Lens' KeysAndAttributes (Maybe (NonEmpty Text)) Source #

This is a legacy parameter. Use ProjectionExpression instead. For more information, see Legacy Conditional Parameters in the Amazon DynamoDB Developer Guide .

kaaExpressionAttributeNames :: Lens' KeysAndAttributes (HashMap Text Text) Source #

One or more substitution tokens for attribute names in an expression. The following are some use cases for using ExpressionAttributeNames : * To access an attribute whose name conflicts with a DynamoDB reserved word. * To create a placeholder for repeating occurrences of an attribute name in an expression. * To prevent special characters in an attribute name from being misinterpreted in an expression. Use the # character in an expression to dereference an attribute name. For example, consider the following attribute name: * Percentile The name of this attribute conflicts with a reserved word, so it cannot be used directly in an expression. (For the complete list of reserved words, see Reserved Words in the Amazon DynamoDB Developer Guide ). To work around this, you could specify the following for ExpressionAttributeNames : * {"#P":Percentile} You could then use this substitution in an expression, as in this example: * #P = :val For more information on expression attribute names, see Accessing Item Attributes in the Amazon DynamoDB Developer Guide .

kaaConsistentRead :: Lens' KeysAndAttributes (Maybe Bool) Source #

The consistency of a read operation. If set to true , then a strongly consistent read is used; otherwise, an eventually consistent read is used.

kaaKeys :: Lens' KeysAndAttributes (NonEmpty (HashMap Text AttributeValue)) Source #

The primary key attribute values that define the items and the attributes associated with the items.

LocalSecondaryIndex

data LocalSecondaryIndex Source #

Represents the properties of a local secondary index.

See: localSecondaryIndex smart constructor.

Instances

Eq LocalSecondaryIndex Source # 
Data LocalSecondaryIndex Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LocalSecondaryIndex -> c LocalSecondaryIndex #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LocalSecondaryIndex #

toConstr :: LocalSecondaryIndex -> Constr #

dataTypeOf :: LocalSecondaryIndex -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LocalSecondaryIndex) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LocalSecondaryIndex) #

gmapT :: (forall b. Data b => b -> b) -> LocalSecondaryIndex -> LocalSecondaryIndex #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LocalSecondaryIndex -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LocalSecondaryIndex -> r #

gmapQ :: (forall d. Data d => d -> u) -> LocalSecondaryIndex -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LocalSecondaryIndex -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LocalSecondaryIndex -> m LocalSecondaryIndex #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalSecondaryIndex -> m LocalSecondaryIndex #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalSecondaryIndex -> m LocalSecondaryIndex #

Read LocalSecondaryIndex Source # 
Show LocalSecondaryIndex Source # 
Generic LocalSecondaryIndex Source # 
Hashable LocalSecondaryIndex Source # 
ToJSON LocalSecondaryIndex Source # 
NFData LocalSecondaryIndex Source # 

Methods

rnf :: LocalSecondaryIndex -> () #

type Rep LocalSecondaryIndex Source # 
type Rep LocalSecondaryIndex = D1 * (MetaData "LocalSecondaryIndex" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "LocalSecondaryIndex'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_lsiIndexName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "_lsiKeySchema") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (List1 KeySchemaElement))) (S1 * (MetaSel (Just Symbol "_lsiProjection") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Projection)))))

localSecondaryIndex Source #

Creates a value of LocalSecondaryIndex with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • lsiIndexName - The name of the local secondary index. The name must be unique among all other indexes on this table.
  • lsiKeySchema - The complete key schema for the local secondary index, consisting of one or more pairs of attribute names and key types: * HASH - partition key * RANGE - sort key
  • lsiProjection - Represents attributes that are copied (projected) from the table into the local secondary index. These are in addition to the primary key attributes and index key attributes, which are automatically projected.

lsiIndexName :: Lens' LocalSecondaryIndex Text Source #

The name of the local secondary index. The name must be unique among all other indexes on this table.

lsiKeySchema :: Lens' LocalSecondaryIndex (NonEmpty KeySchemaElement) Source #

The complete key schema for the local secondary index, consisting of one or more pairs of attribute names and key types: * HASH - partition key * RANGE - sort key

lsiProjection :: Lens' LocalSecondaryIndex Projection Source #

Represents attributes that are copied (projected) from the table into the local secondary index. These are in addition to the primary key attributes and index key attributes, which are automatically projected.

LocalSecondaryIndexDescription

data LocalSecondaryIndexDescription Source #

Represents the properties of a local secondary index.

See: localSecondaryIndexDescription smart constructor.

Instances

Eq LocalSecondaryIndexDescription Source # 
Data LocalSecondaryIndexDescription Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LocalSecondaryIndexDescription -> c LocalSecondaryIndexDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LocalSecondaryIndexDescription #

toConstr :: LocalSecondaryIndexDescription -> Constr #

dataTypeOf :: LocalSecondaryIndexDescription -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LocalSecondaryIndexDescription) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LocalSecondaryIndexDescription) #

gmapT :: (forall b. Data b => b -> b) -> LocalSecondaryIndexDescription -> LocalSecondaryIndexDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LocalSecondaryIndexDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LocalSecondaryIndexDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> LocalSecondaryIndexDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LocalSecondaryIndexDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LocalSecondaryIndexDescription -> m LocalSecondaryIndexDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalSecondaryIndexDescription -> m LocalSecondaryIndexDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalSecondaryIndexDescription -> m LocalSecondaryIndexDescription #

Read LocalSecondaryIndexDescription Source # 
Show LocalSecondaryIndexDescription Source # 
Generic LocalSecondaryIndexDescription Source # 
Hashable LocalSecondaryIndexDescription Source # 
FromJSON LocalSecondaryIndexDescription Source # 
NFData LocalSecondaryIndexDescription Source # 
type Rep LocalSecondaryIndexDescription Source # 
type Rep LocalSecondaryIndexDescription = D1 * (MetaData "LocalSecondaryIndexDescription" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "LocalSecondaryIndexDescription'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_lsidIndexSizeBytes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lsidIndexARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_lsidKeySchema") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (List1 KeySchemaElement)))))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lsidProjection") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Projection))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lsidItemCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))) (S1 * (MetaSel (Just Symbol "_lsidIndexName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))))

localSecondaryIndexDescription :: LocalSecondaryIndexDescription Source #

Creates a value of LocalSecondaryIndexDescription with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • lsidIndexSizeBytes - The total size of the specified index, in bytes. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value.
  • lsidIndexARN - The Amazon Resource Name (ARN) that uniquely identifies the index.
  • lsidKeySchema - The complete key schema for the local secondary index, consisting of one or more pairs of attribute names and key types: * HASH - partition key * RANGE - sort key
  • lsidProjection - Represents attributes that are copied (projected) from the table into the global secondary index. These are in addition to the primary key attributes and index key attributes, which are automatically projected.
  • lsidItemCount - The number of items in the specified index. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value.
  • lsidIndexName - Represents the name of the local secondary index.

lsidIndexSizeBytes :: Lens' LocalSecondaryIndexDescription (Maybe Integer) Source #

The total size of the specified index, in bytes. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value.

lsidIndexARN :: Lens' LocalSecondaryIndexDescription (Maybe Text) Source #

The Amazon Resource Name (ARN) that uniquely identifies the index.

lsidKeySchema :: Lens' LocalSecondaryIndexDescription (Maybe (NonEmpty KeySchemaElement)) Source #

The complete key schema for the local secondary index, consisting of one or more pairs of attribute names and key types: * HASH - partition key * RANGE - sort key

lsidProjection :: Lens' LocalSecondaryIndexDescription (Maybe Projection) Source #

Represents attributes that are copied (projected) from the table into the global secondary index. These are in addition to the primary key attributes and index key attributes, which are automatically projected.

lsidItemCount :: Lens' LocalSecondaryIndexDescription (Maybe Integer) Source #

The number of items in the specified index. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value.

lsidIndexName :: Lens' LocalSecondaryIndexDescription (Maybe Text) Source #

Represents the name of the local secondary index.

LocalSecondaryIndexInfo

data LocalSecondaryIndexInfo Source #

Represents the properties of a local secondary index for the table when the backup was created.

See: localSecondaryIndexInfo smart constructor.

Instances

Eq LocalSecondaryIndexInfo Source # 
Data LocalSecondaryIndexInfo Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LocalSecondaryIndexInfo -> c LocalSecondaryIndexInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LocalSecondaryIndexInfo #

toConstr :: LocalSecondaryIndexInfo -> Constr #

dataTypeOf :: LocalSecondaryIndexInfo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LocalSecondaryIndexInfo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LocalSecondaryIndexInfo) #

gmapT :: (forall b. Data b => b -> b) -> LocalSecondaryIndexInfo -> LocalSecondaryIndexInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LocalSecondaryIndexInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LocalSecondaryIndexInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> LocalSecondaryIndexInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LocalSecondaryIndexInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LocalSecondaryIndexInfo -> m LocalSecondaryIndexInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalSecondaryIndexInfo -> m LocalSecondaryIndexInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalSecondaryIndexInfo -> m LocalSecondaryIndexInfo #

Read LocalSecondaryIndexInfo Source # 
Show LocalSecondaryIndexInfo Source # 
Generic LocalSecondaryIndexInfo Source # 
Hashable LocalSecondaryIndexInfo Source # 
FromJSON LocalSecondaryIndexInfo Source # 
NFData LocalSecondaryIndexInfo Source # 

Methods

rnf :: LocalSecondaryIndexInfo -> () #

type Rep LocalSecondaryIndexInfo Source # 
type Rep LocalSecondaryIndexInfo = D1 * (MetaData "LocalSecondaryIndexInfo" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "LocalSecondaryIndexInfo'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_lsiiKeySchema") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (List1 KeySchemaElement)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_lsiiProjection") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Projection))) (S1 * (MetaSel (Just Symbol "_lsiiIndexName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))))

localSecondaryIndexInfo :: LocalSecondaryIndexInfo Source #

Creates a value of LocalSecondaryIndexInfo with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • lsiiKeySchema - The complete key schema for a local secondary index, which consists of one or more pairs of attribute names and key types: * HASH - partition key * RANGE - sort key
  • lsiiProjection - Represents attributes that are copied (projected) from the table into the global secondary index. These are in addition to the primary key attributes and index key attributes, which are automatically projected.
  • lsiiIndexName - Represents the name of the local secondary index.

lsiiKeySchema :: Lens' LocalSecondaryIndexInfo (Maybe (NonEmpty KeySchemaElement)) Source #

The complete key schema for a local secondary index, which consists of one or more pairs of attribute names and key types: * HASH - partition key * RANGE - sort key

lsiiProjection :: Lens' LocalSecondaryIndexInfo (Maybe Projection) Source #

Represents attributes that are copied (projected) from the table into the global secondary index. These are in addition to the primary key attributes and index key attributes, which are automatically projected.

lsiiIndexName :: Lens' LocalSecondaryIndexInfo (Maybe Text) Source #

Represents the name of the local secondary index.

PointInTimeRecoveryDescription

data PointInTimeRecoveryDescription Source #

The description of the point in time settings applied to the table.

See: pointInTimeRecoveryDescription smart constructor.

Instances

Eq PointInTimeRecoveryDescription Source # 
Data PointInTimeRecoveryDescription Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PointInTimeRecoveryDescription -> c PointInTimeRecoveryDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PointInTimeRecoveryDescription #

toConstr :: PointInTimeRecoveryDescription -> Constr #

dataTypeOf :: PointInTimeRecoveryDescription -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PointInTimeRecoveryDescription) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PointInTimeRecoveryDescription) #

gmapT :: (forall b. Data b => b -> b) -> PointInTimeRecoveryDescription -> PointInTimeRecoveryDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PointInTimeRecoveryDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PointInTimeRecoveryDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> PointInTimeRecoveryDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PointInTimeRecoveryDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PointInTimeRecoveryDescription -> m PointInTimeRecoveryDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PointInTimeRecoveryDescription -> m PointInTimeRecoveryDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PointInTimeRecoveryDescription -> m PointInTimeRecoveryDescription #

Read PointInTimeRecoveryDescription Source # 
Show PointInTimeRecoveryDescription Source # 
Generic PointInTimeRecoveryDescription Source # 
Hashable PointInTimeRecoveryDescription Source # 
FromJSON PointInTimeRecoveryDescription Source # 
NFData PointInTimeRecoveryDescription Source # 
type Rep PointInTimeRecoveryDescription Source # 
type Rep PointInTimeRecoveryDescription = D1 * (MetaData "PointInTimeRecoveryDescription" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "PointInTimeRecoveryDescription'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_pitrdPointInTimeRecoveryStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe PointInTimeRecoveryStatus))) ((:*:) * (S1 * (MetaSel (Just Symbol "_pitrdEarliestRestorableDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))) (S1 * (MetaSel (Just Symbol "_pitrdLatestRestorableDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))))))

pointInTimeRecoveryDescription :: PointInTimeRecoveryDescription Source #

Creates a value of PointInTimeRecoveryDescription with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • pitrdPointInTimeRecoveryStatus - The current state of point in time recovery: * ENABLING - Point in time recovery is being enabled. * ENABLED - Point in time recovery is enabled. * DISABLED - Point in time recovery is disabled.
  • pitrdEarliestRestorableDateTime - Specifies the earliest point in time you can restore your table to. It You can restore your table to any point in time during the last 35 days.
  • pitrdLatestRestorableDateTime - LatestRestorableDateTime is typically 5 minutes before the current time.

pitrdPointInTimeRecoveryStatus :: Lens' PointInTimeRecoveryDescription (Maybe PointInTimeRecoveryStatus) Source #

The current state of point in time recovery: * ENABLING - Point in time recovery is being enabled. * ENABLED - Point in time recovery is enabled. * DISABLED - Point in time recovery is disabled.

pitrdEarliestRestorableDateTime :: Lens' PointInTimeRecoveryDescription (Maybe UTCTime) Source #

Specifies the earliest point in time you can restore your table to. It You can restore your table to any point in time during the last 35 days.

pitrdLatestRestorableDateTime :: Lens' PointInTimeRecoveryDescription (Maybe UTCTime) Source #

LatestRestorableDateTime is typically 5 minutes before the current time.

PointInTimeRecoverySpecification

data PointInTimeRecoverySpecification Source #

Represents the settings used to enable point in time recovery.

See: pointInTimeRecoverySpecification smart constructor.

Instances

Eq PointInTimeRecoverySpecification Source # 
Data PointInTimeRecoverySpecification Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PointInTimeRecoverySpecification -> c PointInTimeRecoverySpecification #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PointInTimeRecoverySpecification #

toConstr :: PointInTimeRecoverySpecification -> Constr #

dataTypeOf :: PointInTimeRecoverySpecification -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PointInTimeRecoverySpecification) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PointInTimeRecoverySpecification) #

gmapT :: (forall b. Data b => b -> b) -> PointInTimeRecoverySpecification -> PointInTimeRecoverySpecification #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PointInTimeRecoverySpecification -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PointInTimeRecoverySpecification -> r #

gmapQ :: (forall d. Data d => d -> u) -> PointInTimeRecoverySpecification -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PointInTimeRecoverySpecification -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PointInTimeRecoverySpecification -> m PointInTimeRecoverySpecification #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PointInTimeRecoverySpecification -> m PointInTimeRecoverySpecification #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PointInTimeRecoverySpecification -> m PointInTimeRecoverySpecification #

Read PointInTimeRecoverySpecification Source # 
Show PointInTimeRecoverySpecification Source # 
Generic PointInTimeRecoverySpecification Source # 
Hashable PointInTimeRecoverySpecification Source # 
ToJSON PointInTimeRecoverySpecification Source # 
NFData PointInTimeRecoverySpecification Source # 
type Rep PointInTimeRecoverySpecification Source # 
type Rep PointInTimeRecoverySpecification = D1 * (MetaData "PointInTimeRecoverySpecification" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" True) (C1 * (MetaCons "PointInTimeRecoverySpecification'" PrefixI True) (S1 * (MetaSel (Just Symbol "_pitrsPointInTimeRecoveryEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))

pointInTimeRecoverySpecification Source #

Creates a value of PointInTimeRecoverySpecification with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pitrsPointInTimeRecoveryEnabled :: Lens' PointInTimeRecoverySpecification Bool Source #

Indicates whether point in time recovery is enabled (true) or disabled (false) on the table.

Projection

data Projection Source #

Represents attributes that are copied (projected) from the table into an index. These are in addition to the primary key attributes and index key attributes, which are automatically projected.

See: projection smart constructor.

Instances

Eq Projection Source # 
Data Projection Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Projection -> c Projection #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Projection #

toConstr :: Projection -> Constr #

dataTypeOf :: Projection -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Projection) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Projection) #

gmapT :: (forall b. Data b => b -> b) -> Projection -> Projection #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Projection -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Projection -> r #

gmapQ :: (forall d. Data d => d -> u) -> Projection -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Projection -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Projection -> m Projection #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Projection -> m Projection #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Projection -> m Projection #

Read Projection Source # 
Show Projection Source # 
Generic Projection Source # 

Associated Types

type Rep Projection :: * -> * #

Hashable Projection Source # 
ToJSON Projection Source # 
FromJSON Projection Source # 
NFData Projection Source # 

Methods

rnf :: Projection -> () #

type Rep Projection Source # 
type Rep Projection = D1 * (MetaData "Projection" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "Projection'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_pProjectionType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ProjectionType))) (S1 * (MetaSel (Just Symbol "_pNonKeyAttributes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (List1 Text))))))

projection :: Projection Source #

Creates a value of Projection with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • pProjectionType - The set of attributes that are projected into the index: * KEYS_ONLY - Only the index and primary keys are projected into the index. * INCLUDE - Only the specified table attributes are projected into the index. The list of projected attributes are in NonKeyAttributes . * ALL - All of the table attributes are projected into the index.
  • pNonKeyAttributes - Represents the non-key attribute names which will be projected into the index. For local secondary indexes, the total count of NonKeyAttributes summed across all of the local secondary indexes, must not exceed 20. If you project the same attribute into two different indexes, this counts as two distinct attributes when determining the total.

pProjectionType :: Lens' Projection (Maybe ProjectionType) Source #

The set of attributes that are projected into the index: * KEYS_ONLY - Only the index and primary keys are projected into the index. * INCLUDE - Only the specified table attributes are projected into the index. The list of projected attributes are in NonKeyAttributes . * ALL - All of the table attributes are projected into the index.

pNonKeyAttributes :: Lens' Projection (Maybe (NonEmpty Text)) Source #

Represents the non-key attribute names which will be projected into the index. For local secondary indexes, the total count of NonKeyAttributes summed across all of the local secondary indexes, must not exceed 20. If you project the same attribute into two different indexes, this counts as two distinct attributes when determining the total.

ProvisionedThroughput

data ProvisionedThroughput Source #

Represents the provisioned throughput settings for a specified table or index. The settings can be modified using the UpdateTable operation.

For current minimum and maximum provisioned throughput values, see Limits in the Amazon DynamoDB Developer Guide .

See: provisionedThroughput smart constructor.

Instances

Eq ProvisionedThroughput Source # 
Data ProvisionedThroughput Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProvisionedThroughput -> c ProvisionedThroughput #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProvisionedThroughput #

toConstr :: ProvisionedThroughput -> Constr #

dataTypeOf :: ProvisionedThroughput -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ProvisionedThroughput) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProvisionedThroughput) #

gmapT :: (forall b. Data b => b -> b) -> ProvisionedThroughput -> ProvisionedThroughput #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProvisionedThroughput -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProvisionedThroughput -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProvisionedThroughput -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProvisionedThroughput -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProvisionedThroughput -> m ProvisionedThroughput #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProvisionedThroughput -> m ProvisionedThroughput #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProvisionedThroughput -> m ProvisionedThroughput #

Read ProvisionedThroughput Source # 
Show ProvisionedThroughput Source # 
Generic ProvisionedThroughput Source # 
Hashable ProvisionedThroughput Source # 
ToJSON ProvisionedThroughput Source # 
FromJSON ProvisionedThroughput Source # 
NFData ProvisionedThroughput Source # 

Methods

rnf :: ProvisionedThroughput -> () #

type Rep ProvisionedThroughput Source # 
type Rep ProvisionedThroughput = D1 * (MetaData "ProvisionedThroughput" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "ProvisionedThroughput'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ptReadCapacityUnits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Nat)) (S1 * (MetaSel (Just Symbol "_ptWriteCapacityUnits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Nat))))

provisionedThroughput Source #

Creates a value of ProvisionedThroughput with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ptReadCapacityUnits :: Lens' ProvisionedThroughput Natural Source #

The maximum number of strongly consistent reads consumed per second before DynamoDB returns a ThrottlingException . For more information, see Specifying Read and Write Requirements in the Amazon DynamoDB Developer Guide .

ptWriteCapacityUnits :: Lens' ProvisionedThroughput Natural Source #

The maximum number of writes consumed per second before DynamoDB returns a ThrottlingException . For more information, see Specifying Read and Write Requirements in the Amazon DynamoDB Developer Guide .

ProvisionedThroughputDescription

data ProvisionedThroughputDescription Source #

Represents the provisioned throughput settings for the table, consisting of read and write capacity units, along with data about increases and decreases.

See: provisionedThroughputDescription smart constructor.

Instances

Eq ProvisionedThroughputDescription Source # 
Data ProvisionedThroughputDescription Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProvisionedThroughputDescription -> c ProvisionedThroughputDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProvisionedThroughputDescription #

toConstr :: ProvisionedThroughputDescription -> Constr #

dataTypeOf :: ProvisionedThroughputDescription -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ProvisionedThroughputDescription) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProvisionedThroughputDescription) #

gmapT :: (forall b. Data b => b -> b) -> ProvisionedThroughputDescription -> ProvisionedThroughputDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProvisionedThroughputDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProvisionedThroughputDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProvisionedThroughputDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProvisionedThroughputDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProvisionedThroughputDescription -> m ProvisionedThroughputDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProvisionedThroughputDescription -> m ProvisionedThroughputDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProvisionedThroughputDescription -> m ProvisionedThroughputDescription #

Read ProvisionedThroughputDescription Source # 
Show ProvisionedThroughputDescription Source # 
Generic ProvisionedThroughputDescription Source # 
Hashable ProvisionedThroughputDescription Source # 
FromJSON ProvisionedThroughputDescription Source # 
NFData ProvisionedThroughputDescription Source # 
type Rep ProvisionedThroughputDescription Source # 
type Rep ProvisionedThroughputDescription = D1 * (MetaData "ProvisionedThroughputDescription" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "ProvisionedThroughputDescription'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_ptdReadCapacityUnits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_ptdLastDecreaseDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ptdWriteCapacityUnits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) ((:*:) * (S1 * (MetaSel (Just Symbol "_ptdNumberOfDecreasesToday") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_ptdLastIncreaseDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX)))))))

provisionedThroughputDescription :: ProvisionedThroughputDescription Source #

Creates a value of ProvisionedThroughputDescription with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ptdReadCapacityUnits - The maximum number of strongly consistent reads consumed per second before DynamoDB returns a ThrottlingException . Eventually consistent reads require less effort than strongly consistent reads, so a setting of 50 ReadCapacityUnits per second provides 100 eventually consistent ReadCapacityUnits per second.
  • ptdLastDecreaseDateTime - The date and time of the last provisioned throughput decrease for this table.
  • ptdWriteCapacityUnits - The maximum number of writes consumed per second before DynamoDB returns a ThrottlingException .
  • ptdNumberOfDecreasesToday - The number of provisioned throughput decreases for this table during this UTC calendar day. For current maximums on provisioned throughput decreases, see Limits in the Amazon DynamoDB Developer Guide .
  • ptdLastIncreaseDateTime - The date and time of the last provisioned throughput increase for this table.

ptdReadCapacityUnits :: Lens' ProvisionedThroughputDescription (Maybe Natural) Source #

The maximum number of strongly consistent reads consumed per second before DynamoDB returns a ThrottlingException . Eventually consistent reads require less effort than strongly consistent reads, so a setting of 50 ReadCapacityUnits per second provides 100 eventually consistent ReadCapacityUnits per second.

ptdLastDecreaseDateTime :: Lens' ProvisionedThroughputDescription (Maybe UTCTime) Source #

The date and time of the last provisioned throughput decrease for this table.

ptdWriteCapacityUnits :: Lens' ProvisionedThroughputDescription (Maybe Natural) Source #

The maximum number of writes consumed per second before DynamoDB returns a ThrottlingException .

ptdNumberOfDecreasesToday :: Lens' ProvisionedThroughputDescription (Maybe Natural) Source #

The number of provisioned throughput decreases for this table during this UTC calendar day. For current maximums on provisioned throughput decreases, see Limits in the Amazon DynamoDB Developer Guide .

ptdLastIncreaseDateTime :: Lens' ProvisionedThroughputDescription (Maybe UTCTime) Source #

The date and time of the last provisioned throughput increase for this table.

PutRequest

data PutRequest Source #

Represents a request to perform a PutItem operation on an item.

See: putRequest smart constructor.

Instances

Eq PutRequest Source # 
Data PutRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PutRequest -> c PutRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PutRequest #

toConstr :: PutRequest -> Constr #

dataTypeOf :: PutRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PutRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PutRequest) #

gmapT :: (forall b. Data b => b -> b) -> PutRequest -> PutRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PutRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PutRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> PutRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PutRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PutRequest -> m PutRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PutRequest -> m PutRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PutRequest -> m PutRequest #

Read PutRequest Source # 
Show PutRequest Source # 
Generic PutRequest Source # 

Associated Types

type Rep PutRequest :: * -> * #

Hashable PutRequest Source # 
ToJSON PutRequest Source # 
FromJSON PutRequest Source # 
NFData PutRequest Source # 

Methods

rnf :: PutRequest -> () #

type Rep PutRequest Source # 
type Rep PutRequest = D1 * (MetaData "PutRequest" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" True) (C1 * (MetaCons "PutRequest'" PrefixI True) (S1 * (MetaSel (Just Symbol "_prItem") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Map Text AttributeValue))))

putRequest :: PutRequest Source #

Creates a value of PutRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • prItem - A map of attribute name to attribute values, representing the primary key of an item to be processed by PutItem . All of the table's primary key attributes must be specified, and their data types must match those of the table's key schema. If any attributes are present in the item which are part of an index key schema for the table, their types must match the index key schema.

prItem :: Lens' PutRequest (HashMap Text AttributeValue) Source #

A map of attribute name to attribute values, representing the primary key of an item to be processed by PutItem . All of the table's primary key attributes must be specified, and their data types must match those of the table's key schema. If any attributes are present in the item which are part of an index key schema for the table, their types must match the index key schema.

Replica

data Replica Source #

Represents the properties of a replica.

See: replica smart constructor.

Instances

Eq Replica Source # 

Methods

(==) :: Replica -> Replica -> Bool #

(/=) :: Replica -> Replica -> Bool #

Data Replica Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Replica -> c Replica #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Replica #

toConstr :: Replica -> Constr #

dataTypeOf :: Replica -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Replica) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Replica) #

gmapT :: (forall b. Data b => b -> b) -> Replica -> Replica #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Replica -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Replica -> r #

gmapQ :: (forall d. Data d => d -> u) -> Replica -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Replica -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Replica -> m Replica #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Replica -> m Replica #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Replica -> m Replica #

Read Replica Source # 
Show Replica Source # 
Generic Replica Source # 

Associated Types

type Rep Replica :: * -> * #

Methods

from :: Replica -> Rep Replica x #

to :: Rep Replica x -> Replica #

Hashable Replica Source # 

Methods

hashWithSalt :: Int -> Replica -> Int #

hash :: Replica -> Int #

ToJSON Replica Source # 
FromJSON Replica Source # 
NFData Replica Source # 

Methods

rnf :: Replica -> () #

type Rep Replica Source # 
type Rep Replica = D1 * (MetaData "Replica" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" True) (C1 * (MetaCons "Replica'" PrefixI True) (S1 * (MetaSel (Just Symbol "_rRegionName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))))

replica :: Replica Source #

Creates a value of Replica with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rRegionName - The region where the replica needs to be created.

rRegionName :: Lens' Replica (Maybe Text) Source #

The region where the replica needs to be created.

ReplicaDescription

data ReplicaDescription Source #

Contains the details of the replica.

See: replicaDescription smart constructor.

Instances

Eq ReplicaDescription Source # 
Data ReplicaDescription Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReplicaDescription -> c ReplicaDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReplicaDescription #

toConstr :: ReplicaDescription -> Constr #

dataTypeOf :: ReplicaDescription -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReplicaDescription) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReplicaDescription) #

gmapT :: (forall b. Data b => b -> b) -> ReplicaDescription -> ReplicaDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReplicaDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReplicaDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReplicaDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReplicaDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReplicaDescription -> m ReplicaDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicaDescription -> m ReplicaDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicaDescription -> m ReplicaDescription #

Read ReplicaDescription Source # 
Show ReplicaDescription Source # 
Generic ReplicaDescription Source # 
Hashable ReplicaDescription Source # 
FromJSON ReplicaDescription Source # 
NFData ReplicaDescription Source # 

Methods

rnf :: ReplicaDescription -> () #

type Rep ReplicaDescription Source # 
type Rep ReplicaDescription = D1 * (MetaData "ReplicaDescription" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" True) (C1 * (MetaCons "ReplicaDescription'" PrefixI True) (S1 * (MetaSel (Just Symbol "_rdRegionName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))))

replicaDescription :: ReplicaDescription Source #

Creates a value of ReplicaDescription with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rdRegionName :: Lens' ReplicaDescription (Maybe Text) Source #

The name of the region.

ReplicaGlobalSecondaryIndexSettingsDescription

data ReplicaGlobalSecondaryIndexSettingsDescription Source #

Represents the properties of a global secondary index.

See: replicaGlobalSecondaryIndexSettingsDescription smart constructor.

Instances

Eq ReplicaGlobalSecondaryIndexSettingsDescription Source # 
Data ReplicaGlobalSecondaryIndexSettingsDescription Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReplicaGlobalSecondaryIndexSettingsDescription -> c ReplicaGlobalSecondaryIndexSettingsDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReplicaGlobalSecondaryIndexSettingsDescription #

toConstr :: ReplicaGlobalSecondaryIndexSettingsDescription -> Constr #

dataTypeOf :: ReplicaGlobalSecondaryIndexSettingsDescription -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReplicaGlobalSecondaryIndexSettingsDescription) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReplicaGlobalSecondaryIndexSettingsDescription) #

gmapT :: (forall b. Data b => b -> b) -> ReplicaGlobalSecondaryIndexSettingsDescription -> ReplicaGlobalSecondaryIndexSettingsDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReplicaGlobalSecondaryIndexSettingsDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReplicaGlobalSecondaryIndexSettingsDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReplicaGlobalSecondaryIndexSettingsDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReplicaGlobalSecondaryIndexSettingsDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReplicaGlobalSecondaryIndexSettingsDescription -> m ReplicaGlobalSecondaryIndexSettingsDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicaGlobalSecondaryIndexSettingsDescription -> m ReplicaGlobalSecondaryIndexSettingsDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicaGlobalSecondaryIndexSettingsDescription -> m ReplicaGlobalSecondaryIndexSettingsDescription #

Read ReplicaGlobalSecondaryIndexSettingsDescription Source # 
Show ReplicaGlobalSecondaryIndexSettingsDescription Source # 
Generic ReplicaGlobalSecondaryIndexSettingsDescription Source # 
Hashable ReplicaGlobalSecondaryIndexSettingsDescription Source # 
FromJSON ReplicaGlobalSecondaryIndexSettingsDescription Source # 
NFData ReplicaGlobalSecondaryIndexSettingsDescription Source # 
type Rep ReplicaGlobalSecondaryIndexSettingsDescription Source # 
type Rep ReplicaGlobalSecondaryIndexSettingsDescription = D1 * (MetaData "ReplicaGlobalSecondaryIndexSettingsDescription" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "ReplicaGlobalSecondaryIndexSettingsDescription'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_rgsisdIndexStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe IndexStatus))) (S1 * (MetaSel (Just Symbol "_rgsisdProvisionedReadCapacityUnits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rgsisdProvisionedWriteCapacityUnits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_rgsisdIndexName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

replicaGlobalSecondaryIndexSettingsDescription Source #

Creates a value of ReplicaGlobalSecondaryIndexSettingsDescription with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rgsisdIndexStatus - The current status of the global secondary index: * CREATING - The global secondary index is being created. * UPDATING - The global secondary index is being updated. * DELETING - The global secondary index is being deleted. * ACTIVE - The global secondary index is ready for use.
  • rgsisdProvisionedReadCapacityUnits - The maximum number of strongly consistent reads consumed per second before DynamoDB returns a ThrottlingException .
  • rgsisdProvisionedWriteCapacityUnits - The maximum number of writes consumed per second before DynamoDB returns a ThrottlingException .
  • rgsisdIndexName - The name of the global secondary index. The name must be unique among all other indexes on this table.

rgsisdIndexStatus :: Lens' ReplicaGlobalSecondaryIndexSettingsDescription (Maybe IndexStatus) Source #

The current status of the global secondary index: * CREATING - The global secondary index is being created. * UPDATING - The global secondary index is being updated. * DELETING - The global secondary index is being deleted. * ACTIVE - The global secondary index is ready for use.

rgsisdProvisionedReadCapacityUnits :: Lens' ReplicaGlobalSecondaryIndexSettingsDescription (Maybe Natural) Source #

The maximum number of strongly consistent reads consumed per second before DynamoDB returns a ThrottlingException .

rgsisdProvisionedWriteCapacityUnits :: Lens' ReplicaGlobalSecondaryIndexSettingsDescription (Maybe Natural) Source #

The maximum number of writes consumed per second before DynamoDB returns a ThrottlingException .

rgsisdIndexName :: Lens' ReplicaGlobalSecondaryIndexSettingsDescription Text Source #

The name of the global secondary index. The name must be unique among all other indexes on this table.

ReplicaGlobalSecondaryIndexSettingsUpdate

data ReplicaGlobalSecondaryIndexSettingsUpdate Source #

Represents the settings of a global secondary index for a global table that will be modified.

See: replicaGlobalSecondaryIndexSettingsUpdate smart constructor.

Instances

Eq ReplicaGlobalSecondaryIndexSettingsUpdate Source # 
Data ReplicaGlobalSecondaryIndexSettingsUpdate Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReplicaGlobalSecondaryIndexSettingsUpdate -> c ReplicaGlobalSecondaryIndexSettingsUpdate #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReplicaGlobalSecondaryIndexSettingsUpdate #

toConstr :: ReplicaGlobalSecondaryIndexSettingsUpdate -> Constr #

dataTypeOf :: ReplicaGlobalSecondaryIndexSettingsUpdate -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReplicaGlobalSecondaryIndexSettingsUpdate) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReplicaGlobalSecondaryIndexSettingsUpdate) #

gmapT :: (forall b. Data b => b -> b) -> ReplicaGlobalSecondaryIndexSettingsUpdate -> ReplicaGlobalSecondaryIndexSettingsUpdate #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReplicaGlobalSecondaryIndexSettingsUpdate -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReplicaGlobalSecondaryIndexSettingsUpdate -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReplicaGlobalSecondaryIndexSettingsUpdate -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReplicaGlobalSecondaryIndexSettingsUpdate -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReplicaGlobalSecondaryIndexSettingsUpdate -> m ReplicaGlobalSecondaryIndexSettingsUpdate #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicaGlobalSecondaryIndexSettingsUpdate -> m ReplicaGlobalSecondaryIndexSettingsUpdate #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicaGlobalSecondaryIndexSettingsUpdate -> m ReplicaGlobalSecondaryIndexSettingsUpdate #

Read ReplicaGlobalSecondaryIndexSettingsUpdate Source # 
Show ReplicaGlobalSecondaryIndexSettingsUpdate Source # 
Generic ReplicaGlobalSecondaryIndexSettingsUpdate Source # 
Hashable ReplicaGlobalSecondaryIndexSettingsUpdate Source # 
ToJSON ReplicaGlobalSecondaryIndexSettingsUpdate Source # 
NFData ReplicaGlobalSecondaryIndexSettingsUpdate Source # 
type Rep ReplicaGlobalSecondaryIndexSettingsUpdate Source # 
type Rep ReplicaGlobalSecondaryIndexSettingsUpdate = D1 * (MetaData "ReplicaGlobalSecondaryIndexSettingsUpdate" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "ReplicaGlobalSecondaryIndexSettingsUpdate'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_rgsisuProvisionedReadCapacityUnits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_rgsisuIndexName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

replicaGlobalSecondaryIndexSettingsUpdate Source #

Creates a value of ReplicaGlobalSecondaryIndexSettingsUpdate with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • rgsisuProvisionedReadCapacityUnits - The maximum number of strongly consistent reads consumed per second before DynamoDB returns a ThrottlingException .
  • rgsisuIndexName - The name of the global secondary index. The name must be unique among all other indexes on this table.

rgsisuProvisionedReadCapacityUnits :: Lens' ReplicaGlobalSecondaryIndexSettingsUpdate (Maybe Natural) Source #

The maximum number of strongly consistent reads consumed per second before DynamoDB returns a ThrottlingException .

rgsisuIndexName :: Lens' ReplicaGlobalSecondaryIndexSettingsUpdate Text Source #

The name of the global secondary index. The name must be unique among all other indexes on this table.

ReplicaSettingsDescription

data ReplicaSettingsDescription Source #

Represents the properties of a replica.

See: replicaSettingsDescription smart constructor.

Instances

Eq ReplicaSettingsDescription Source # 
Data ReplicaSettingsDescription Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReplicaSettingsDescription -> c ReplicaSettingsDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReplicaSettingsDescription #

toConstr :: ReplicaSettingsDescription -> Constr #

dataTypeOf :: ReplicaSettingsDescription -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReplicaSettingsDescription) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReplicaSettingsDescription) #

gmapT :: (forall b. Data b => b -> b) -> ReplicaSettingsDescription -> ReplicaSettingsDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReplicaSettingsDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReplicaSettingsDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReplicaSettingsDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReplicaSettingsDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReplicaSettingsDescription -> m ReplicaSettingsDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicaSettingsDescription -> m ReplicaSettingsDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicaSettingsDescription -> m ReplicaSettingsDescription #

Read ReplicaSettingsDescription Source # 
Show ReplicaSettingsDescription Source # 
Generic ReplicaSettingsDescription Source # 
Hashable ReplicaSettingsDescription Source # 
FromJSON ReplicaSettingsDescription Source # 
NFData ReplicaSettingsDescription Source # 
type Rep ReplicaSettingsDescription Source # 
type Rep ReplicaSettingsDescription = D1 * (MetaData "ReplicaSettingsDescription" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "ReplicaSettingsDescription'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_rsdReplicaStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ReplicaStatus))) (S1 * (MetaSel (Just Symbol "_rsdReplicaProvisionedReadCapacityUnits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rsdReplicaProvisionedWriteCapacityUnits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rsdReplicaGlobalSecondaryIndexSettings") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [ReplicaGlobalSecondaryIndexSettingsDescription]))) (S1 * (MetaSel (Just Symbol "_rsdRegionName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))))

replicaSettingsDescription Source #

Creates a value of ReplicaSettingsDescription with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rsdReplicaStatus :: Lens' ReplicaSettingsDescription (Maybe ReplicaStatus) Source #

The current state of the region: * CREATING - The region is being created. * UPDATING - The region is being updated. * DELETING - The region is being deleted. * ACTIVE - The region is ready for use.

rsdReplicaProvisionedReadCapacityUnits :: Lens' ReplicaSettingsDescription (Maybe Natural) Source #

The maximum number of strongly consistent reads consumed per second before DynamoDB returns a ThrottlingException . For more information, see Specifying Read and Write Requirements in the Amazon DynamoDB Developer Guide .

rsdReplicaProvisionedWriteCapacityUnits :: Lens' ReplicaSettingsDescription (Maybe Natural) Source #

The maximum number of writes consumed per second before DynamoDB returns a ThrottlingException . For more information, see Specifying Read and Write Requirements in the Amazon DynamoDB Developer Guide .

rsdRegionName :: Lens' ReplicaSettingsDescription Text Source #

The region name of the replica.

ReplicaSettingsUpdate

data ReplicaSettingsUpdate Source #

Represents the settings for a global table in a region that will be modified.

See: replicaSettingsUpdate smart constructor.

Instances

Eq ReplicaSettingsUpdate Source # 
Data ReplicaSettingsUpdate Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReplicaSettingsUpdate -> c ReplicaSettingsUpdate #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReplicaSettingsUpdate #

toConstr :: ReplicaSettingsUpdate -> Constr #

dataTypeOf :: ReplicaSettingsUpdate -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReplicaSettingsUpdate) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReplicaSettingsUpdate) #

gmapT :: (forall b. Data b => b -> b) -> ReplicaSettingsUpdate -> ReplicaSettingsUpdate #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReplicaSettingsUpdate -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReplicaSettingsUpdate -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReplicaSettingsUpdate -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReplicaSettingsUpdate -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReplicaSettingsUpdate -> m ReplicaSettingsUpdate #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicaSettingsUpdate -> m ReplicaSettingsUpdate #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicaSettingsUpdate -> m ReplicaSettingsUpdate #

Read ReplicaSettingsUpdate Source # 
Show ReplicaSettingsUpdate Source # 
Generic ReplicaSettingsUpdate Source # 
Hashable ReplicaSettingsUpdate Source # 
ToJSON ReplicaSettingsUpdate Source # 
NFData ReplicaSettingsUpdate Source # 

Methods

rnf :: ReplicaSettingsUpdate -> () #

type Rep ReplicaSettingsUpdate Source # 
type Rep ReplicaSettingsUpdate = D1 * (MetaData "ReplicaSettingsUpdate" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "ReplicaSettingsUpdate'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_rsuReplicaProvisionedReadCapacityUnits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rsuReplicaGlobalSecondaryIndexSettingsUpdate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (List1 ReplicaGlobalSecondaryIndexSettingsUpdate)))) (S1 * (MetaSel (Just Symbol "_rsuRegionName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

replicaSettingsUpdate Source #

Creates a value of ReplicaSettingsUpdate with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rsuReplicaProvisionedReadCapacityUnits :: Lens' ReplicaSettingsUpdate (Maybe Natural) Source #

The maximum number of strongly consistent reads consumed per second before DynamoDB returns a ThrottlingException . For more information, see Specifying Read and Write Requirements in the Amazon DynamoDB Developer Guide .

rsuReplicaGlobalSecondaryIndexSettingsUpdate :: Lens' ReplicaSettingsUpdate (Maybe (NonEmpty ReplicaGlobalSecondaryIndexSettingsUpdate)) Source #

Represents the settings of a global secondary index for a global table that will be modified.

rsuRegionName :: Lens' ReplicaSettingsUpdate Text Source #

The region of the replica to be added.

ReplicaUpdate

data ReplicaUpdate Source #

Represents one of the following:

  • A new replica to be added to an existing global table.
  • New parameters for an existing replica.
  • An existing replica to be removed from an existing global table.

See: replicaUpdate smart constructor.

Instances

Eq ReplicaUpdate Source # 
Data ReplicaUpdate Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReplicaUpdate -> c ReplicaUpdate #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReplicaUpdate #

toConstr :: ReplicaUpdate -> Constr #

dataTypeOf :: ReplicaUpdate -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ReplicaUpdate) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReplicaUpdate) #

gmapT :: (forall b. Data b => b -> b) -> ReplicaUpdate -> ReplicaUpdate #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReplicaUpdate -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReplicaUpdate -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReplicaUpdate -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReplicaUpdate -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReplicaUpdate -> m ReplicaUpdate #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicaUpdate -> m ReplicaUpdate #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReplicaUpdate -> m ReplicaUpdate #

Read ReplicaUpdate Source # 
Show ReplicaUpdate Source # 
Generic ReplicaUpdate Source # 

Associated Types

type Rep ReplicaUpdate :: * -> * #

Hashable ReplicaUpdate Source # 
ToJSON ReplicaUpdate Source # 
NFData ReplicaUpdate Source # 

Methods

rnf :: ReplicaUpdate -> () #

type Rep ReplicaUpdate Source # 
type Rep ReplicaUpdate = D1 * (MetaData "ReplicaUpdate" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "ReplicaUpdate'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ruCreate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe CreateReplicaAction))) (S1 * (MetaSel (Just Symbol "_ruDelete") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DeleteReplicaAction)))))

replicaUpdate :: ReplicaUpdate Source #

Creates a value of ReplicaUpdate with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ruCreate - The parameters required for creating a replica on an existing global table.
  • ruDelete - The name of the existing replica to be removed.

ruCreate :: Lens' ReplicaUpdate (Maybe CreateReplicaAction) Source #

The parameters required for creating a replica on an existing global table.

ruDelete :: Lens' ReplicaUpdate (Maybe DeleteReplicaAction) Source #

The name of the existing replica to be removed.

RestoreSummary

data RestoreSummary Source #

Contains details for the restore.

See: restoreSummary smart constructor.

Instances

Eq RestoreSummary Source # 
Data RestoreSummary Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RestoreSummary -> c RestoreSummary #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RestoreSummary #

toConstr :: RestoreSummary -> Constr #

dataTypeOf :: RestoreSummary -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RestoreSummary) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RestoreSummary) #

gmapT :: (forall b. Data b => b -> b) -> RestoreSummary -> RestoreSummary #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RestoreSummary -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RestoreSummary -> r #

gmapQ :: (forall d. Data d => d -> u) -> RestoreSummary -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RestoreSummary -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RestoreSummary -> m RestoreSummary #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RestoreSummary -> m RestoreSummary #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RestoreSummary -> m RestoreSummary #

Read RestoreSummary Source # 
Show RestoreSummary Source # 
Generic RestoreSummary Source # 

Associated Types

type Rep RestoreSummary :: * -> * #

Hashable RestoreSummary Source # 
FromJSON RestoreSummary Source # 
NFData RestoreSummary Source # 

Methods

rnf :: RestoreSummary -> () #

type Rep RestoreSummary Source # 
type Rep RestoreSummary = D1 * (MetaData "RestoreSummary" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "RestoreSummary'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_rsSourceTableARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_rsSourceBackupARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_rsRestoreDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * POSIX)) (S1 * (MetaSel (Just Symbol "_rsRestoreInProgress") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bool)))))

restoreSummary Source #

Creates a value of RestoreSummary with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rsSourceTableARN :: Lens' RestoreSummary (Maybe Text) Source #

ARN of the source table of the backup that is being restored.

rsSourceBackupARN :: Lens' RestoreSummary (Maybe Text) Source #

ARN of the backup from which the table was restored.

rsRestoreDateTime :: Lens' RestoreSummary UTCTime Source #

Point in time or source backup time.

rsRestoreInProgress :: Lens' RestoreSummary Bool Source #

Indicates if a restore is in progress or not.

SSEDescription

data SSEDescription Source #

The description of the server-side encryption status on the specified table.

See: sSEDescription smart constructor.

Instances

Eq SSEDescription Source # 
Data SSEDescription Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SSEDescription -> c SSEDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SSEDescription #

toConstr :: SSEDescription -> Constr #

dataTypeOf :: SSEDescription -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SSEDescription) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SSEDescription) #

gmapT :: (forall b. Data b => b -> b) -> SSEDescription -> SSEDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SSEDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SSEDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> SSEDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SSEDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SSEDescription -> m SSEDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SSEDescription -> m SSEDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SSEDescription -> m SSEDescription #

Read SSEDescription Source # 
Show SSEDescription Source # 
Generic SSEDescription Source # 

Associated Types

type Rep SSEDescription :: * -> * #

Hashable SSEDescription Source # 
FromJSON SSEDescription Source # 
NFData SSEDescription Source # 

Methods

rnf :: SSEDescription -> () #

type Rep SSEDescription Source # 
type Rep SSEDescription = D1 * (MetaData "SSEDescription" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" True) (C1 * (MetaCons "SSEDescription'" PrefixI True) (S1 * (MetaSel (Just Symbol "_ssedStatus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe SSEStatus))))

sSEDescription :: SSEDescription Source #

Creates a value of SSEDescription with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ssedStatus - The current state of server-side encryption: * ENABLING - Server-side encryption is being enabled. * ENABLED - Server-side encryption is enabled. * DISABLING - Server-side encryption is being disabled. * DISABLED - Server-side encryption is disabled.

ssedStatus :: Lens' SSEDescription (Maybe SSEStatus) Source #

The current state of server-side encryption: * ENABLING - Server-side encryption is being enabled. * ENABLED - Server-side encryption is enabled. * DISABLING - Server-side encryption is being disabled. * DISABLED - Server-side encryption is disabled.

SSESpecification

data SSESpecification Source #

Represents the settings used to enable server-side encryption.

See: sSESpecification smart constructor.

Instances

Eq SSESpecification Source # 
Data SSESpecification Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SSESpecification -> c SSESpecification #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SSESpecification #

toConstr :: SSESpecification -> Constr #

dataTypeOf :: SSESpecification -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SSESpecification) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SSESpecification) #

gmapT :: (forall b. Data b => b -> b) -> SSESpecification -> SSESpecification #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SSESpecification -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SSESpecification -> r #

gmapQ :: (forall d. Data d => d -> u) -> SSESpecification -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SSESpecification -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SSESpecification -> m SSESpecification #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SSESpecification -> m SSESpecification #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SSESpecification -> m SSESpecification #

Read SSESpecification Source # 
Show SSESpecification Source # 
Generic SSESpecification Source # 
Hashable SSESpecification Source # 
ToJSON SSESpecification Source # 
NFData SSESpecification Source # 

Methods

rnf :: SSESpecification -> () #

type Rep SSESpecification Source # 
type Rep SSESpecification = D1 * (MetaData "SSESpecification" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" True) (C1 * (MetaCons "SSESpecification'" PrefixI True) (S1 * (MetaSel (Just Symbol "_ssesEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))

sSESpecification Source #

Creates a value of SSESpecification with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ssesEnabled - Indicates whether server-side encryption is enabled (true) or disabled (false) on the table.

ssesEnabled :: Lens' SSESpecification Bool Source #

Indicates whether server-side encryption is enabled (true) or disabled (false) on the table.

SourceTableDetails

data SourceTableDetails Source #

Contains the details of the table when the backup was created.

See: sourceTableDetails smart constructor.

Instances

Eq SourceTableDetails Source # 
Data SourceTableDetails Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceTableDetails -> c SourceTableDetails #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceTableDetails #

toConstr :: SourceTableDetails -> Constr #

dataTypeOf :: SourceTableDetails -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SourceTableDetails) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceTableDetails) #

gmapT :: (forall b. Data b => b -> b) -> SourceTableDetails -> SourceTableDetails #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceTableDetails -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceTableDetails -> r #

gmapQ :: (forall d. Data d => d -> u) -> SourceTableDetails -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceTableDetails -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceTableDetails -> m SourceTableDetails #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceTableDetails -> m SourceTableDetails #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceTableDetails -> m SourceTableDetails #

Read SourceTableDetails Source # 
Show SourceTableDetails Source # 
Generic SourceTableDetails Source # 
Hashable SourceTableDetails Source # 
FromJSON SourceTableDetails Source # 
NFData SourceTableDetails Source # 

Methods

rnf :: SourceTableDetails -> () #

type Rep SourceTableDetails Source # 
type Rep SourceTableDetails = D1 * (MetaData "SourceTableDetails" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "SourceTableDetails'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_stdTableSizeBytes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))) (S1 * (MetaSel (Just Symbol "_stdTableARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_stdItemCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Nat))) (S1 * (MetaSel (Just Symbol "_stdTableName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_stdTableId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_stdKeySchema") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (List1 KeySchemaElement)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_stdTableCreationDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * POSIX)) (S1 * (MetaSel (Just Symbol "_stdProvisionedThroughput") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProvisionedThroughput))))))

sourceTableDetails Source #

Creates a value of SourceTableDetails with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

stdTableSizeBytes :: Lens' SourceTableDetails (Maybe Integer) Source #

Size of the table in bytes. Please note this is an approximate value.

stdTableARN :: Lens' SourceTableDetails (Maybe Text) Source #

ARN of the table for which backup was created.

stdItemCount :: Lens' SourceTableDetails (Maybe Natural) Source #

Number of items in the table. Please note this is an approximate value.

stdTableName :: Lens' SourceTableDetails Text Source #

The name of the table for which the backup was created.

stdTableId :: Lens' SourceTableDetails Text Source #

Unique identifier for the table for which the backup was created.

stdTableCreationDateTime :: Lens' SourceTableDetails UTCTime Source #

Time when the source table was created.

stdProvisionedThroughput :: Lens' SourceTableDetails ProvisionedThroughput Source #

Read IOPs and Write IOPS on the table when the backup was created.

SourceTableFeatureDetails

data SourceTableFeatureDetails Source #

Contains the details of the features enabled on the table when the backup was created. For example, LSIs, GSIs, streams, TTL.

See: sourceTableFeatureDetails smart constructor.

Instances

Eq SourceTableFeatureDetails Source # 
Data SourceTableFeatureDetails Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceTableFeatureDetails -> c SourceTableFeatureDetails #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceTableFeatureDetails #

toConstr :: SourceTableFeatureDetails -> Constr #

dataTypeOf :: SourceTableFeatureDetails -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SourceTableFeatureDetails) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceTableFeatureDetails) #

gmapT :: (forall b. Data b => b -> b) -> SourceTableFeatureDetails -> SourceTableFeatureDetails #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceTableFeatureDetails -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceTableFeatureDetails -> r #

gmapQ :: (forall d. Data d => d -> u) -> SourceTableFeatureDetails -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceTableFeatureDetails -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceTableFeatureDetails -> m SourceTableFeatureDetails #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceTableFeatureDetails -> m SourceTableFeatureDetails #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceTableFeatureDetails -> m SourceTableFeatureDetails #

Read SourceTableFeatureDetails Source # 
Show SourceTableFeatureDetails Source # 
Generic SourceTableFeatureDetails Source # 
Hashable SourceTableFeatureDetails Source # 
FromJSON SourceTableFeatureDetails Source # 
NFData SourceTableFeatureDetails Source # 
type Rep SourceTableFeatureDetails Source # 
type Rep SourceTableFeatureDetails = D1 * (MetaData "SourceTableFeatureDetails" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "SourceTableFeatureDetails'" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_stfdStreamDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe StreamSpecification))) (S1 * (MetaSel (Just Symbol "_stfdGlobalSecondaryIndexes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [GlobalSecondaryIndexInfo])))) ((:*:) * (S1 * (MetaSel (Just Symbol "_stfdLocalSecondaryIndexes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [LocalSecondaryIndexInfo]))) ((:*:) * (S1 * (MetaSel (Just Symbol "_stfdSSEDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe SSEDescription))) (S1 * (MetaSel (Just Symbol "_stfdTimeToLiveDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe TimeToLiveDescription)))))))

sourceTableFeatureDetails :: SourceTableFeatureDetails Source #

Creates a value of SourceTableFeatureDetails with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • stfdStreamDescription - Stream settings on the table when the backup was created.
  • stfdGlobalSecondaryIndexes - Represents the GSI properties for the table when the backup was created. It includes the IndexName, KeySchema, Projection and ProvisionedThroughput for the GSIs on the table at the time of backup.
  • stfdLocalSecondaryIndexes - Represents the LSI properties for the table when the backup was created. It includes the IndexName, KeySchema and Projection for the LSIs on the table at the time of backup.
  • stfdSSEDescription - The description of the server-side encryption status on the table when the backup was created.
  • stfdTimeToLiveDescription - Time to Live settings on the table when the backup was created.

stfdStreamDescription :: Lens' SourceTableFeatureDetails (Maybe StreamSpecification) Source #

Stream settings on the table when the backup was created.

stfdGlobalSecondaryIndexes :: Lens' SourceTableFeatureDetails [GlobalSecondaryIndexInfo] Source #

Represents the GSI properties for the table when the backup was created. It includes the IndexName, KeySchema, Projection and ProvisionedThroughput for the GSIs on the table at the time of backup.

stfdLocalSecondaryIndexes :: Lens' SourceTableFeatureDetails [LocalSecondaryIndexInfo] Source #

Represents the LSI properties for the table when the backup was created. It includes the IndexName, KeySchema and Projection for the LSIs on the table at the time of backup.

stfdSSEDescription :: Lens' SourceTableFeatureDetails (Maybe SSEDescription) Source #

The description of the server-side encryption status on the table when the backup was created.

stfdTimeToLiveDescription :: Lens' SourceTableFeatureDetails (Maybe TimeToLiveDescription) Source #

Time to Live settings on the table when the backup was created.

StreamSpecification

data StreamSpecification Source #

Represents the DynamoDB Streams configuration for a table in DynamoDB.

See: streamSpecification smart constructor.

Instances

Eq StreamSpecification Source # 
Data StreamSpecification Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StreamSpecification -> c StreamSpecification #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StreamSpecification #

toConstr :: StreamSpecification -> Constr #

dataTypeOf :: StreamSpecification -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StreamSpecification) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StreamSpecification) #

gmapT :: (forall b. Data b => b -> b) -> StreamSpecification -> StreamSpecification #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StreamSpecification -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StreamSpecification -> r #

gmapQ :: (forall d. Data d => d -> u) -> StreamSpecification -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StreamSpecification -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StreamSpecification -> m StreamSpecification #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StreamSpecification -> m StreamSpecification #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StreamSpecification -> m StreamSpecification #

Read StreamSpecification Source # 
Show StreamSpecification Source # 
Generic StreamSpecification Source # 
Hashable StreamSpecification Source # 
ToJSON StreamSpecification Source # 
FromJSON StreamSpecification Source # 
NFData StreamSpecification Source # 

Methods

rnf :: StreamSpecification -> () #

type Rep StreamSpecification Source # 
type Rep StreamSpecification = D1 * (MetaData "StreamSpecification" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "StreamSpecification'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ssStreamViewType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe StreamViewType))) (S1 * (MetaSel (Just Symbol "_ssStreamEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Bool)))))

streamSpecification :: StreamSpecification Source #

Creates a value of StreamSpecification with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ssStreamViewType - When an item in the table is modified, StreamViewType determines what information is written to the stream for this table. Valid values for StreamViewType are: * KEYS_ONLY - Only the key attributes of the modified item are written to the stream. * NEW_IMAGE - The entire item, as it appears after it was modified, is written to the stream. * OLD_IMAGE - The entire item, as it appeared before it was modified, is written to the stream. * NEW_AND_OLD_IMAGES - Both the new and the old item images of the item are written to the stream.
  • ssStreamEnabled - Indicates whether DynamoDB Streams is enabled (true) or disabled (false) on the table.

ssStreamViewType :: Lens' StreamSpecification (Maybe StreamViewType) Source #

When an item in the table is modified, StreamViewType determines what information is written to the stream for this table. Valid values for StreamViewType are: * KEYS_ONLY - Only the key attributes of the modified item are written to the stream. * NEW_IMAGE - The entire item, as it appears after it was modified, is written to the stream. * OLD_IMAGE - The entire item, as it appeared before it was modified, is written to the stream. * NEW_AND_OLD_IMAGES - Both the new and the old item images of the item are written to the stream.

ssStreamEnabled :: Lens' StreamSpecification (Maybe Bool) Source #

Indicates whether DynamoDB Streams is enabled (true) or disabled (false) on the table.

TableDescription

data TableDescription Source #

Represents the properties of a table.

See: tableDescription smart constructor.

Instances

Eq TableDescription Source # 
Data TableDescription Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableDescription -> c TableDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableDescription #

toConstr :: TableDescription -> Constr #

dataTypeOf :: TableDescription -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TableDescription) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableDescription) #

gmapT :: (forall b. Data b => b -> b) -> TableDescription -> TableDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> TableDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TableDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableDescription -> m TableDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableDescription -> m TableDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableDescription -> m TableDescription #

Read TableDescription Source # 
Show TableDescription Source # 
Generic TableDescription Source # 
Hashable TableDescription Source # 
FromJSON TableDescription Source # 
NFData TableDescription Source # 

Methods

rnf :: TableDescription -> () #

type Rep TableDescription Source # 
type Rep TableDescription = D1 * (MetaData "TableDescription" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "TableDescription'" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_tdRestoreSummary") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe RestoreSummary))) (S1 * (MetaSel (Just Symbol "_tdTableSizeBytes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tdAttributeDefinitions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [AttributeDefinition]))) (S1 * (MetaSel (Just Symbol "_tdLatestStreamARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_tdProvisionedThroughput") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe ProvisionedThroughputDescription))) (S1 * (MetaSel (Just Symbol "_tdTableStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe TableStatus)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tdTableARN") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tdKeySchema") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (List1 KeySchemaElement))))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_tdGlobalSecondaryIndexes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [GlobalSecondaryIndexDescription]))) (S1 * (MetaSel (Just Symbol "_tdLatestStreamLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tdLocalSecondaryIndexes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe [LocalSecondaryIndexDescription]))) (S1 * (MetaSel (Just Symbol "_tdCreationDateTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe POSIX))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_tdSSEDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe SSEDescription))) (S1 * (MetaSel (Just Symbol "_tdTableId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tdItemCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Integer))) ((:*:) * (S1 * (MetaSel (Just Symbol "_tdTableName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "_tdStreamSpecification") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe StreamSpecification)))))))))

tableDescription :: TableDescription Source #

Creates a value of TableDescription with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • tdRestoreSummary - Contains details for the restore.
  • tdTableSizeBytes - The total size of the specified table, in bytes. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value.
  • tdAttributeDefinitions - An array of AttributeDefinition objects. Each of these objects describes one attribute in the table and index key schema. Each AttributeDefinition object in this array is composed of: * AttributeName - The name of the attribute. * AttributeType - The data type for the attribute.
  • tdLatestStreamARN - The Amazon Resource Name (ARN) that uniquely identifies the latest stream for this table.
  • tdProvisionedThroughput - The provisioned throughput settings for the table, consisting of read and write capacity units, along with data about increases and decreases.
  • tdTableStatus - The current state of the table: * CREATING - The table is being created. * UPDATING - The table is being updated. * DELETING - The table is being deleted. * ACTIVE - The table is ready for use.
  • tdTableARN - The Amazon Resource Name (ARN) that uniquely identifies the table.
  • tdKeySchema - The primary key structure for the table. Each KeySchemaElement consists of: * AttributeName - The name of the attribute. * KeyType - The role of the attribute: * HASH - partition key * RANGE - sort key For more information about primary keys, see Primary Key in the Amazon DynamoDB Developer Guide .
  • tdGlobalSecondaryIndexes - The global secondary indexes, if any, on the table. Each index is scoped to a given partition key value. Each element is composed of: * Backfilling - If true, then the index is currently in the backfilling phase. Backfilling occurs only when a new global secondary index is added to the table; it is the process by which DynamoDB populates the new index with data from the table. (This attribute does not appear for indexes that were created during a CreateTable operation.) * IndexName - The name of the global secondary index. * IndexSizeBytes - The total size of the global secondary index, in bytes. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value. * IndexStatus - The current status of the global secondary index: * CREATING - The index is being created. * UPDATING - The index is being updated. * DELETING - The index is being deleted. * ACTIVE - The index is ready for use. * ItemCount - The number of items in the global secondary index. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value. * KeySchema - Specifies the complete index key schema. The attribute names in the key schema must be between 1 and 255 characters (inclusive). The key schema must begin with the same partition key as the table. * Projection - Specifies attributes that are copied (projected) from the table into the index. These are in addition to the primary key attributes and index key attributes, which are automatically projected. Each attribute specification is composed of: * ProjectionType - One of the following: * KEYS_ONLY - Only the index and primary keys are projected into the index. * INCLUDE - Only the specified table attributes are projected into the index. The list of projected attributes are in NonKeyAttributes . * ALL - All of the table attributes are projected into the index. * NonKeyAttributes - A list of one or more non-key attribute names that are projected into the secondary index. The total count of attributes provided in NonKeyAttributes , summed across all of the secondary indexes, must not exceed 20. If you project the same attribute into two different indexes, this counts as two distinct attributes when determining the total. * ProvisionedThroughput - The provisioned throughput settings for the global secondary index, consisting of read and write capacity units, along with data about increases and decreases. If the table is in the DELETING state, no information about indexes will be returned.
  • tdLatestStreamLabel - A timestamp, in ISO 8601 format, for this stream. Note that LatestStreamLabel is not a unique identifier for the stream, because it is possible that a stream from another table might have the same timestamp. However, the combination of the following three elements is guaranteed to be unique: * the AWS customer ID. * the table name. * the StreamLabel .
  • tdLocalSecondaryIndexes - Represents one or more local secondary indexes on the table. Each index is scoped to a given partition key value. Tables with one or more local secondary indexes are subject to an item collection size limit, where the amount of data within a given item collection cannot exceed 10 GB. Each element is composed of: * IndexName - The name of the local secondary index. * KeySchema - Specifies the complete index key schema. The attribute names in the key schema must be between 1 and 255 characters (inclusive). The key schema must begin with the same partition key as the table. * Projection - Specifies attributes that are copied (projected) from the table into the index. These are in addition to the primary key attributes and index key attributes, which are automatically projected. Each attribute specification is composed of: * ProjectionType - One of the following: * KEYS_ONLY - Only the index and primary keys are projected into the index. * INCLUDE - Only the specified table attributes are projected into the index. The list of projected attributes are in NonKeyAttributes . * ALL - All of the table attributes are projected into the index. * NonKeyAttributes - A list of one or more non-key attribute names that are projected into the secondary index. The total count of attributes provided in NonKeyAttributes , summed across all of the secondary indexes, must not exceed 20. If you project the same attribute into two different indexes, this counts as two distinct attributes when determining the total. * IndexSizeBytes - Represents the total size of the index, in bytes. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value. * ItemCount - Represents the number of items in the index. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value. If the table is in the DELETING state, no information about indexes will be returned.
  • tdCreationDateTime - The date and time when the table was created, in UNIX epoch time format.
  • tdSSEDescription - The description of the server-side encryption status on the specified table.
  • tdTableId - Unique identifier for the table for which the backup was created.
  • tdItemCount - The number of items in the specified table. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value.
  • tdTableName - The name of the table.
  • tdStreamSpecification - The current DynamoDB Streams configuration for the table.

tdRestoreSummary :: Lens' TableDescription (Maybe RestoreSummary) Source #

Contains details for the restore.

tdTableSizeBytes :: Lens' TableDescription (Maybe Integer) Source #

The total size of the specified table, in bytes. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value.

tdAttributeDefinitions :: Lens' TableDescription [AttributeDefinition] Source #

An array of AttributeDefinition objects. Each of these objects describes one attribute in the table and index key schema. Each AttributeDefinition object in this array is composed of: * AttributeName - The name of the attribute. * AttributeType - The data type for the attribute.

tdLatestStreamARN :: Lens' TableDescription (Maybe Text) Source #

The Amazon Resource Name (ARN) that uniquely identifies the latest stream for this table.

tdProvisionedThroughput :: Lens' TableDescription (Maybe ProvisionedThroughputDescription) Source #

The provisioned throughput settings for the table, consisting of read and write capacity units, along with data about increases and decreases.

tdTableStatus :: Lens' TableDescription (Maybe TableStatus) Source #

The current state of the table: * CREATING - The table is being created. * UPDATING - The table is being updated. * DELETING - The table is being deleted. * ACTIVE - The table is ready for use.

tdTableARN :: Lens' TableDescription (Maybe Text) Source #

The Amazon Resource Name (ARN) that uniquely identifies the table.

tdKeySchema :: Lens' TableDescription (Maybe (NonEmpty KeySchemaElement)) Source #

The primary key structure for the table. Each KeySchemaElement consists of: * AttributeName - The name of the attribute. * KeyType - The role of the attribute: * HASH - partition key * RANGE - sort key For more information about primary keys, see Primary Key in the Amazon DynamoDB Developer Guide .

tdGlobalSecondaryIndexes :: Lens' TableDescription [GlobalSecondaryIndexDescription] Source #

The global secondary indexes, if any, on the table. Each index is scoped to a given partition key value. Each element is composed of: * Backfilling - If true, then the index is currently in the backfilling phase. Backfilling occurs only when a new global secondary index is added to the table; it is the process by which DynamoDB populates the new index with data from the table. (This attribute does not appear for indexes that were created during a CreateTable operation.) * IndexName - The name of the global secondary index. * IndexSizeBytes - The total size of the global secondary index, in bytes. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value. * IndexStatus - The current status of the global secondary index: * CREATING - The index is being created. * UPDATING - The index is being updated. * DELETING - The index is being deleted. * ACTIVE - The index is ready for use. * ItemCount - The number of items in the global secondary index. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value. * KeySchema - Specifies the complete index key schema. The attribute names in the key schema must be between 1 and 255 characters (inclusive). The key schema must begin with the same partition key as the table. * Projection - Specifies attributes that are copied (projected) from the table into the index. These are in addition to the primary key attributes and index key attributes, which are automatically projected. Each attribute specification is composed of: * ProjectionType - One of the following: * KEYS_ONLY - Only the index and primary keys are projected into the index. * INCLUDE - Only the specified table attributes are projected into the index. The list of projected attributes are in NonKeyAttributes . * ALL - All of the table attributes are projected into the index. * NonKeyAttributes - A list of one or more non-key attribute names that are projected into the secondary index. The total count of attributes provided in NonKeyAttributes , summed across all of the secondary indexes, must not exceed 20. If you project the same attribute into two different indexes, this counts as two distinct attributes when determining the total. * ProvisionedThroughput - The provisioned throughput settings for the global secondary index, consisting of read and write capacity units, along with data about increases and decreases. If the table is in the DELETING state, no information about indexes will be returned.

tdLatestStreamLabel :: Lens' TableDescription (Maybe Text) Source #

A timestamp, in ISO 8601 format, for this stream. Note that LatestStreamLabel is not a unique identifier for the stream, because it is possible that a stream from another table might have the same timestamp. However, the combination of the following three elements is guaranteed to be unique: * the AWS customer ID. * the table name. * the StreamLabel .

tdLocalSecondaryIndexes :: Lens' TableDescription [LocalSecondaryIndexDescription] Source #

Represents one or more local secondary indexes on the table. Each index is scoped to a given partition key value. Tables with one or more local secondary indexes are subject to an item collection size limit, where the amount of data within a given item collection cannot exceed 10 GB. Each element is composed of: * IndexName - The name of the local secondary index. * KeySchema - Specifies the complete index key schema. The attribute names in the key schema must be between 1 and 255 characters (inclusive). The key schema must begin with the same partition key as the table. * Projection - Specifies attributes that are copied (projected) from the table into the index. These are in addition to the primary key attributes and index key attributes, which are automatically projected. Each attribute specification is composed of: * ProjectionType - One of the following: * KEYS_ONLY - Only the index and primary keys are projected into the index. * INCLUDE - Only the specified table attributes are projected into the index. The list of projected attributes are in NonKeyAttributes . * ALL - All of the table attributes are projected into the index. * NonKeyAttributes - A list of one or more non-key attribute names that are projected into the secondary index. The total count of attributes provided in NonKeyAttributes , summed across all of the secondary indexes, must not exceed 20. If you project the same attribute into two different indexes, this counts as two distinct attributes when determining the total. * IndexSizeBytes - Represents the total size of the index, in bytes. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value. * ItemCount - Represents the number of items in the index. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value. If the table is in the DELETING state, no information about indexes will be returned.

tdCreationDateTime :: Lens' TableDescription (Maybe UTCTime) Source #

The date and time when the table was created, in UNIX epoch time format.

tdSSEDescription :: Lens' TableDescription (Maybe SSEDescription) Source #

The description of the server-side encryption status on the specified table.

tdTableId :: Lens' TableDescription (Maybe Text) Source #

Unique identifier for the table for which the backup was created.

tdItemCount :: Lens' TableDescription (Maybe Integer) Source #

The number of items in the specified table. DynamoDB updates this value approximately every six hours. Recent changes might not be reflected in this value.

tdTableName :: Lens' TableDescription (Maybe Text) Source #

The name of the table.

tdStreamSpecification :: Lens' TableDescription (Maybe StreamSpecification) Source #

The current DynamoDB Streams configuration for the table.

Tag

data Tag Source #

Describes a tag. A tag is a key-value pair. You can add up to 50 tags to a single DynamoDB table.

AWS-assigned tag names and values are automatically assigned the aws: prefix, which the user cannot assign. AWS-assigned tag names do not count towards the tag limit of 50. User-assigned tag names have the prefix user: in the Cost Allocation Report. You cannot backdate the application of a tag.

For an overview on tagging DynamoDB resources, see Tagging for DynamoDB in the Amazon DynamoDB Developer Guide .

See: tag smart constructor.

Instances

Eq Tag Source # 

Methods

(==) :: Tag -> Tag -> Bool #

(/=) :: Tag -> Tag -> Bool #

Data Tag Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tag -> c Tag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tag #

toConstr :: Tag -> Constr #

dataTypeOf :: Tag -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Tag) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag) #

gmapT :: (forall b. Data b => b -> b) -> Tag -> Tag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

Read Tag Source # 
Show Tag Source # 

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 

Associated Types

type Rep Tag :: * -> * #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

Hashable Tag Source # 

Methods

hashWithSalt :: Int -> Tag -> Int #

hash :: Tag -> Int #

ToJSON Tag Source # 
FromJSON Tag Source # 
NFData Tag Source # 

Methods

rnf :: Tag -> () #

type Rep Tag Source # 
type Rep Tag = D1 * (MetaData "Tag" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "Tag'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_tagKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_tagValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

tag Source #

Arguments

:: Text

tagKey

-> Text

tagValue

-> Tag 

Creates a value of Tag with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • tagKey - The key of the tag.Tag keys are case sensitive. Each DynamoDB table can only have up to one tag with the same key. If you try to add an existing tag (same key), the existing tag value will be updated to the new value.
  • tagValue - The value of the tag. Tag values are case-sensitive and can be null.

tagKey :: Lens' Tag Text Source #

The key of the tag.Tag keys are case sensitive. Each DynamoDB table can only have up to one tag with the same key. If you try to add an existing tag (same key), the existing tag value will be updated to the new value.

tagValue :: Lens' Tag Text Source #

The value of the tag. Tag values are case-sensitive and can be null.

TimeToLiveDescription

data TimeToLiveDescription Source #

The description of the Time to Live (TTL) status on the specified table.

See: timeToLiveDescription smart constructor.

Instances

Eq TimeToLiveDescription Source # 
Data TimeToLiveDescription Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeToLiveDescription -> c TimeToLiveDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeToLiveDescription #

toConstr :: TimeToLiveDescription -> Constr #

dataTypeOf :: TimeToLiveDescription -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TimeToLiveDescription) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeToLiveDescription) #

gmapT :: (forall b. Data b => b -> b) -> TimeToLiveDescription -> TimeToLiveDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeToLiveDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeToLiveDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> TimeToLiveDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeToLiveDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeToLiveDescription -> m TimeToLiveDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeToLiveDescription -> m TimeToLiveDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeToLiveDescription -> m TimeToLiveDescription #

Read TimeToLiveDescription Source # 
Show TimeToLiveDescription Source # 
Generic TimeToLiveDescription Source # 
Hashable TimeToLiveDescription Source # 
FromJSON TimeToLiveDescription Source # 
NFData TimeToLiveDescription Source # 

Methods

rnf :: TimeToLiveDescription -> () #

type Rep TimeToLiveDescription Source # 
type Rep TimeToLiveDescription = D1 * (MetaData "TimeToLiveDescription" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "TimeToLiveDescription'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ttldTimeToLiveStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe TimeToLiveStatus))) (S1 * (MetaSel (Just Symbol "_ttldAttributeName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))

timeToLiveDescription :: TimeToLiveDescription Source #

Creates a value of TimeToLiveDescription with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ttldAttributeName :: Lens' TimeToLiveDescription (Maybe Text) Source #

The name of the Time to Live attribute for items in the table.

TimeToLiveSpecification

data TimeToLiveSpecification Source #

Represents the settings used to enable or disable Time to Live for the specified table.

See: timeToLiveSpecification smart constructor.

Instances

Eq TimeToLiveSpecification Source # 
Data TimeToLiveSpecification Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeToLiveSpecification -> c TimeToLiveSpecification #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeToLiveSpecification #

toConstr :: TimeToLiveSpecification -> Constr #

dataTypeOf :: TimeToLiveSpecification -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TimeToLiveSpecification) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeToLiveSpecification) #

gmapT :: (forall b. Data b => b -> b) -> TimeToLiveSpecification -> TimeToLiveSpecification #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeToLiveSpecification -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeToLiveSpecification -> r #

gmapQ :: (forall d. Data d => d -> u) -> TimeToLiveSpecification -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeToLiveSpecification -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeToLiveSpecification -> m TimeToLiveSpecification #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeToLiveSpecification -> m TimeToLiveSpecification #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeToLiveSpecification -> m TimeToLiveSpecification #

Read TimeToLiveSpecification Source # 
Show TimeToLiveSpecification Source # 
Generic TimeToLiveSpecification Source # 
Hashable TimeToLiveSpecification Source # 
ToJSON TimeToLiveSpecification Source # 
FromJSON TimeToLiveSpecification Source # 
NFData TimeToLiveSpecification Source # 

Methods

rnf :: TimeToLiveSpecification -> () #

type Rep TimeToLiveSpecification Source # 
type Rep TimeToLiveSpecification = D1 * (MetaData "TimeToLiveSpecification" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "TimeToLiveSpecification'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ttlsEnabled") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "_ttlsAttributeName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

timeToLiveSpecification Source #

Creates a value of TimeToLiveSpecification with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ttlsEnabled - Indicates whether Time To Live is to be enabled (true) or disabled (false) on the table.
  • ttlsAttributeName - The name of the Time to Live attribute used to store the expiration time for items in the table.

ttlsEnabled :: Lens' TimeToLiveSpecification Bool Source #

Indicates whether Time To Live is to be enabled (true) or disabled (false) on the table.

ttlsAttributeName :: Lens' TimeToLiveSpecification Text Source #

The name of the Time to Live attribute used to store the expiration time for items in the table.

UpdateGlobalSecondaryIndexAction

data UpdateGlobalSecondaryIndexAction Source #

Represents the new provisioned throughput settings to be applied to a global secondary index.

See: updateGlobalSecondaryIndexAction smart constructor.

Instances

Eq UpdateGlobalSecondaryIndexAction Source # 
Data UpdateGlobalSecondaryIndexAction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UpdateGlobalSecondaryIndexAction -> c UpdateGlobalSecondaryIndexAction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UpdateGlobalSecondaryIndexAction #

toConstr :: UpdateGlobalSecondaryIndexAction -> Constr #

dataTypeOf :: UpdateGlobalSecondaryIndexAction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UpdateGlobalSecondaryIndexAction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UpdateGlobalSecondaryIndexAction) #

gmapT :: (forall b. Data b => b -> b) -> UpdateGlobalSecondaryIndexAction -> UpdateGlobalSecondaryIndexAction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UpdateGlobalSecondaryIndexAction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UpdateGlobalSecondaryIndexAction -> r #

gmapQ :: (forall d. Data d => d -> u) -> UpdateGlobalSecondaryIndexAction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UpdateGlobalSecondaryIndexAction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UpdateGlobalSecondaryIndexAction -> m UpdateGlobalSecondaryIndexAction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateGlobalSecondaryIndexAction -> m UpdateGlobalSecondaryIndexAction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UpdateGlobalSecondaryIndexAction -> m UpdateGlobalSecondaryIndexAction #

Read UpdateGlobalSecondaryIndexAction Source # 
Show UpdateGlobalSecondaryIndexAction Source # 
Generic UpdateGlobalSecondaryIndexAction Source # 
Hashable UpdateGlobalSecondaryIndexAction Source # 
ToJSON UpdateGlobalSecondaryIndexAction Source # 
NFData UpdateGlobalSecondaryIndexAction Source # 
type Rep UpdateGlobalSecondaryIndexAction Source # 
type Rep UpdateGlobalSecondaryIndexAction = D1 * (MetaData "UpdateGlobalSecondaryIndexAction" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "UpdateGlobalSecondaryIndexAction'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_ugsiaIndexName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "_ugsiaProvisionedThroughput") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProvisionedThroughput))))

updateGlobalSecondaryIndexAction Source #

Creates a value of UpdateGlobalSecondaryIndexAction with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

  • ugsiaIndexName - The name of the global secondary index to be updated.
  • ugsiaProvisionedThroughput - Represents the provisioned throughput settings for the specified global secondary index. For current minimum and maximum provisioned throughput values, see Limits in the Amazon DynamoDB Developer Guide .

ugsiaIndexName :: Lens' UpdateGlobalSecondaryIndexAction Text Source #

The name of the global secondary index to be updated.

ugsiaProvisionedThroughput :: Lens' UpdateGlobalSecondaryIndexAction ProvisionedThroughput Source #

Represents the provisioned throughput settings for the specified global secondary index. For current minimum and maximum provisioned throughput values, see Limits in the Amazon DynamoDB Developer Guide .

WriteRequest

data WriteRequest Source #

Represents an operation to perform - either DeleteItem or PutItem . You can only request one of these operations, not both, in a single WriteRequest . If you do need to perform both of these operations, you will need to provide two separate WriteRequest objects.

See: writeRequest smart constructor.

Instances

Eq WriteRequest Source # 
Data WriteRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WriteRequest -> c WriteRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WriteRequest #

toConstr :: WriteRequest -> Constr #

dataTypeOf :: WriteRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c WriteRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WriteRequest) #

gmapT :: (forall b. Data b => b -> b) -> WriteRequest -> WriteRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WriteRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WriteRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> WriteRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WriteRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WriteRequest -> m WriteRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WriteRequest -> m WriteRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WriteRequest -> m WriteRequest #

Read WriteRequest Source # 
Show WriteRequest Source # 
Generic WriteRequest Source # 

Associated Types

type Rep WriteRequest :: * -> * #

Hashable WriteRequest Source # 
ToJSON WriteRequest Source # 
FromJSON WriteRequest Source # 
NFData WriteRequest Source # 

Methods

rnf :: WriteRequest -> () #

type Rep WriteRequest Source # 
type Rep WriteRequest = D1 * (MetaData "WriteRequest" "Network.AWS.DynamoDB.Types.Product" "amazonka-dynamodb-1.6.0-Be8FXVQVyEHEMZza56FG0o" False) (C1 * (MetaCons "WriteRequest'" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_wrDeleteRequest") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe DeleteRequest))) (S1 * (MetaSel (Just Symbol "_wrPutRequest") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe PutRequest)))))

writeRequest :: WriteRequest Source #

Creates a value of WriteRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

wrDeleteRequest :: Lens' WriteRequest (Maybe DeleteRequest) Source #

A request to perform a DeleteItem operation.

wrPutRequest :: Lens' WriteRequest (Maybe PutRequest) Source #

A request to perform a PutItem operation.