{-# LANGUAGE OverloadedStrings #-}
module Network.AWS.DynamoDB.Types
(
dynamoDB
, _BackupNotFoundException
, _TableInUseException
, _ContinuousBackupsUnavailableException
, _ProvisionedThroughputExceededException
, _GlobalTableNotFoundException
, _ConditionalCheckFailedException
, _GlobalTableAlreadyExistsException
, _ReplicaNotFoundException
, _TableAlreadyExistsException
, _ItemCollectionSizeLimitExceededException
, _InternalServerError
, _TableNotFoundException
, _IndexNotFoundException
, _BackupInUseException
, _PointInTimeRecoveryUnavailableException
, _InvalidRestoreTimeException
, _ResourceNotFoundException
, _ReplicaAlreadyExistsException
, _LimitExceededException
, _ResourceInUseException
, AttributeAction (..)
, BackupStatus (..)
, ComparisonOperator (..)
, ConditionalOperator (..)
, ContinuousBackupsStatus (..)
, GlobalTableStatus (..)
, IndexStatus (..)
, KeyType (..)
, PointInTimeRecoveryStatus (..)
, ProjectionType (..)
, ReplicaStatus (..)
, ReturnConsumedCapacity (..)
, ReturnItemCollectionMetrics (..)
, ReturnValue (..)
, SSEStatus (..)
, ScalarAttributeType (..)
, Select (..)
, StreamViewType (..)
, TableStatus (..)
, TimeToLiveStatus (..)
, AttributeDefinition
, attributeDefinition
, adAttributeName
, adAttributeType
, AttributeValue
, attributeValue
, avL
, avNS
, avM
, avNULL
, avN
, avBS
, avB
, avSS
, avS
, avBOOL
, AttributeValueUpdate
, attributeValueUpdate
, avuValue
, avuAction
, BackupDescription
, backupDescription
, bdBackupDetails
, bdSourceTableDetails
, bdSourceTableFeatureDetails
, BackupDetails
, backupDetails
, bdBackupSizeBytes
, bdBackupARN
, bdBackupName
, bdBackupStatus
, bdBackupCreationDateTime
, BackupSummary
, backupSummary
, bsTableARN
, bsBackupName
, bsBackupStatus
, bsBackupSizeBytes
, bsBackupARN
, bsTableId
, bsBackupCreationDateTime
, bsTableName
, Capacity
, capacity
, cCapacityUnits
, Condition
, condition
, cAttributeValueList
, cComparisonOperator
, ConsumedCapacity
, consumedCapacity
, ccGlobalSecondaryIndexes
, ccCapacityUnits
, ccLocalSecondaryIndexes
, ccTable
, ccTableName
, ContinuousBackupsDescription
, continuousBackupsDescription
, cbdPointInTimeRecoveryDescription
, cbdContinuousBackupsStatus
, CreateGlobalSecondaryIndexAction
, createGlobalSecondaryIndexAction
, cgsiaIndexName
, cgsiaKeySchema
, cgsiaProjection
, cgsiaProvisionedThroughput
, CreateReplicaAction
, createReplicaAction
, craRegionName
, DeleteGlobalSecondaryIndexAction
, deleteGlobalSecondaryIndexAction
, dgsiaIndexName
, DeleteReplicaAction
, deleteReplicaAction
, draRegionName
, DeleteRequest
, deleteRequest
, drKey
, ExpectedAttributeValue
, expectedAttributeValue
, eavAttributeValueList
, eavExists
, eavValue
, eavComparisonOperator
, GlobalSecondaryIndex
, globalSecondaryIndex
, gsiIndexName
, gsiKeySchema
, gsiProjection
, gsiProvisionedThroughput
, GlobalSecondaryIndexDescription
, globalSecondaryIndexDescription
, gsidBackfilling
, gsidIndexSizeBytes
, gsidIndexStatus
, gsidProvisionedThroughput
, gsidIndexARN
, gsidKeySchema
, gsidProjection
, gsidItemCount
, gsidIndexName
, GlobalSecondaryIndexInfo
, globalSecondaryIndexInfo
, gsiiProvisionedThroughput
, gsiiKeySchema
, gsiiProjection
, gsiiIndexName
, GlobalSecondaryIndexUpdate
, globalSecondaryIndexUpdate
, gsiuCreate
, gsiuDelete
, gsiuUpdate
, GlobalTable
, globalTable
, gtGlobalTableName
, gtReplicationGroup
, GlobalTableDescription
, globalTableDescription
, gtdGlobalTableStatus
, gtdGlobalTableName
, gtdGlobalTableARN
, gtdCreationDateTime
, gtdReplicationGroup
, GlobalTableGlobalSecondaryIndexSettingsUpdate
, globalTableGlobalSecondaryIndexSettingsUpdate
, gtgsisuProvisionedWriteCapacityUnits
, gtgsisuIndexName
, ItemCollectionMetrics
, itemCollectionMetrics
, icmItemCollectionKey
, icmSizeEstimateRangeGB
, KeySchemaElement
, keySchemaElement
, kseAttributeName
, kseKeyType
, KeysAndAttributes
, keysAndAttributes
, kaaProjectionExpression
, kaaAttributesToGet
, kaaExpressionAttributeNames
, kaaConsistentRead
, kaaKeys
, LocalSecondaryIndex
, localSecondaryIndex
, lsiIndexName
, lsiKeySchema
, lsiProjection
, LocalSecondaryIndexDescription
, localSecondaryIndexDescription
, lsidIndexSizeBytes
, lsidIndexARN
, lsidKeySchema
, lsidProjection
, lsidItemCount
, lsidIndexName
, LocalSecondaryIndexInfo
, localSecondaryIndexInfo
, lsiiKeySchema
, lsiiProjection
, lsiiIndexName
, PointInTimeRecoveryDescription
, pointInTimeRecoveryDescription
, pitrdPointInTimeRecoveryStatus
, pitrdEarliestRestorableDateTime
, pitrdLatestRestorableDateTime
, PointInTimeRecoverySpecification
, pointInTimeRecoverySpecification
, pitrsPointInTimeRecoveryEnabled
, Projection
, projection
, pProjectionType
, pNonKeyAttributes
, ProvisionedThroughput
, provisionedThroughput
, ptReadCapacityUnits
, ptWriteCapacityUnits
, ProvisionedThroughputDescription
, provisionedThroughputDescription
, ptdReadCapacityUnits
, ptdLastDecreaseDateTime
, ptdWriteCapacityUnits
, ptdNumberOfDecreasesToday
, ptdLastIncreaseDateTime
, PutRequest
, putRequest
, prItem
, Replica
, replica
, rRegionName
, ReplicaDescription
, replicaDescription
, rdRegionName
, ReplicaGlobalSecondaryIndexSettingsDescription
, replicaGlobalSecondaryIndexSettingsDescription
, rgsisdIndexStatus
, rgsisdProvisionedReadCapacityUnits
, rgsisdProvisionedWriteCapacityUnits
, rgsisdIndexName
, ReplicaGlobalSecondaryIndexSettingsUpdate
, replicaGlobalSecondaryIndexSettingsUpdate
, rgsisuProvisionedReadCapacityUnits
, rgsisuIndexName
, ReplicaSettingsDescription
, replicaSettingsDescription
, rsdReplicaStatus
, rsdReplicaProvisionedReadCapacityUnits
, rsdReplicaProvisionedWriteCapacityUnits
, rsdReplicaGlobalSecondaryIndexSettings
, rsdRegionName
, ReplicaSettingsUpdate
, replicaSettingsUpdate
, rsuReplicaProvisionedReadCapacityUnits
, rsuReplicaGlobalSecondaryIndexSettingsUpdate
, rsuRegionName
, ReplicaUpdate
, replicaUpdate
, ruCreate
, ruDelete
, RestoreSummary
, restoreSummary
, rsSourceTableARN
, rsSourceBackupARN
, rsRestoreDateTime
, rsRestoreInProgress
, SSEDescription
, sSEDescription
, ssedStatus
, SSESpecification
, sSESpecification
, ssesEnabled
, SourceTableDetails
, sourceTableDetails
, stdTableSizeBytes
, stdTableARN
, stdItemCount
, stdTableName
, stdTableId
, stdKeySchema
, stdTableCreationDateTime
, stdProvisionedThroughput
, SourceTableFeatureDetails
, sourceTableFeatureDetails
, stfdStreamDescription
, stfdGlobalSecondaryIndexes
, stfdLocalSecondaryIndexes
, stfdSSEDescription
, stfdTimeToLiveDescription
, StreamSpecification
, streamSpecification
, ssStreamViewType
, ssStreamEnabled
, TableDescription
, tableDescription
, tdRestoreSummary
, tdTableSizeBytes
, tdAttributeDefinitions
, tdLatestStreamARN
, tdProvisionedThroughput
, tdTableStatus
, tdTableARN
, tdKeySchema
, tdGlobalSecondaryIndexes
, tdLatestStreamLabel
, tdLocalSecondaryIndexes
, tdCreationDateTime
, tdSSEDescription
, tdTableId
, tdItemCount
, tdTableName
, tdStreamSpecification
, Tag
, tag
, tagKey
, tagValue
, TimeToLiveDescription
, timeToLiveDescription
, ttldTimeToLiveStatus
, ttldAttributeName
, TimeToLiveSpecification
, timeToLiveSpecification
, ttlsEnabled
, ttlsAttributeName
, UpdateGlobalSecondaryIndexAction
, updateGlobalSecondaryIndexAction
, ugsiaIndexName
, ugsiaProvisionedThroughput
, WriteRequest
, writeRequest
, wrDeleteRequest
, wrPutRequest
) where
import Network.AWS.DynamoDB.Types.Product
import Network.AWS.DynamoDB.Types.Sum
import Network.AWS.Lens
import Network.AWS.Prelude
import Network.AWS.Sign.V4
dynamoDB :: Service
dynamoDB =
Service
{ _svcAbbrev = "DynamoDB"
, _svcSigner = v4
, _svcPrefix = "dynamodb"
, _svcVersion = "2012-08-10"
, _svcEndpoint = defaultEndpoint dynamoDB
, _svcTimeout = Just 70
, _svcCheck = statusSuccess
, _svcError = parseJSONError "DynamoDB"
, _svcRetry = retry
}
where
retry =
Exponential
{ _retryBase = 5.0e-2
, _retryGrowth = 2
, _retryAttempts = 5
, _retryCheck = check
}
check e
| has (hasCode "ThrottledException" . hasStatus 400) e =
Just "throttled_exception"
| has (hasStatus 429) e = Just "too_many_requests"
| has (hasCode "ThrottlingException" . hasStatus 400) e =
Just "throttling_exception"
| has (hasCode "Throttling" . hasStatus 400) e = Just "throttling"
| has (hasCode "ProvisionedThroughputExceededException" . hasStatus 400) e =
Just "throughput_exceeded"
| has (hasStatus 504) e = Just "gateway_timeout"
| has (hasCode "RequestThrottledException" . hasStatus 400) e =
Just "request_throttled_exception"
| has (hasStatus 502) e = Just "bad_gateway"
| has (hasStatus 503) e = Just "service_unavailable"
| has (hasStatus 500) e = Just "general_server_error"
| has (hasStatus 509) e = Just "limit_exceeded"
| otherwise = Nothing
_BackupNotFoundException :: AsError a => Getting (First ServiceError) a ServiceError
_BackupNotFoundException = _MatchServiceError dynamoDB "BackupNotFoundException"
_TableInUseException :: AsError a => Getting (First ServiceError) a ServiceError
_TableInUseException = _MatchServiceError dynamoDB "TableInUseException"
_ContinuousBackupsUnavailableException :: AsError a => Getting (First ServiceError) a ServiceError
_ContinuousBackupsUnavailableException =
_MatchServiceError dynamoDB "ContinuousBackupsUnavailableException"
_ProvisionedThroughputExceededException :: AsError a => Getting (First ServiceError) a ServiceError
_ProvisionedThroughputExceededException =
_MatchServiceError dynamoDB "ProvisionedThroughputExceededException"
_GlobalTableNotFoundException :: AsError a => Getting (First ServiceError) a ServiceError
_GlobalTableNotFoundException =
_MatchServiceError dynamoDB "GlobalTableNotFoundException"
_ConditionalCheckFailedException :: AsError a => Getting (First ServiceError) a ServiceError
_ConditionalCheckFailedException =
_MatchServiceError dynamoDB "ConditionalCheckFailedException"
_GlobalTableAlreadyExistsException :: AsError a => Getting (First ServiceError) a ServiceError
_GlobalTableAlreadyExistsException =
_MatchServiceError dynamoDB "GlobalTableAlreadyExistsException"
_ReplicaNotFoundException :: AsError a => Getting (First ServiceError) a ServiceError
_ReplicaNotFoundException =
_MatchServiceError dynamoDB "ReplicaNotFoundException"
_TableAlreadyExistsException :: AsError a => Getting (First ServiceError) a ServiceError
_TableAlreadyExistsException =
_MatchServiceError dynamoDB "TableAlreadyExistsException"
_ItemCollectionSizeLimitExceededException :: AsError a => Getting (First ServiceError) a ServiceError
_ItemCollectionSizeLimitExceededException =
_MatchServiceError dynamoDB "ItemCollectionSizeLimitExceededException"
_InternalServerError :: AsError a => Getting (First ServiceError) a ServiceError
_InternalServerError = _MatchServiceError dynamoDB "InternalServerError"
_TableNotFoundException :: AsError a => Getting (First ServiceError) a ServiceError
_TableNotFoundException = _MatchServiceError dynamoDB "TableNotFoundException"
_IndexNotFoundException :: AsError a => Getting (First ServiceError) a ServiceError
_IndexNotFoundException = _MatchServiceError dynamoDB "IndexNotFoundException"
_BackupInUseException :: AsError a => Getting (First ServiceError) a ServiceError
_BackupInUseException = _MatchServiceError dynamoDB "BackupInUseException"
_PointInTimeRecoveryUnavailableException :: AsError a => Getting (First ServiceError) a ServiceError
_PointInTimeRecoveryUnavailableException =
_MatchServiceError dynamoDB "PointInTimeRecoveryUnavailableException"
_InvalidRestoreTimeException :: AsError a => Getting (First ServiceError) a ServiceError
_InvalidRestoreTimeException =
_MatchServiceError dynamoDB "InvalidRestoreTimeException"
_ResourceNotFoundException :: AsError a => Getting (First ServiceError) a ServiceError
_ResourceNotFoundException =
_MatchServiceError dynamoDB "ResourceNotFoundException"
_ReplicaAlreadyExistsException :: AsError a => Getting (First ServiceError) a ServiceError
_ReplicaAlreadyExistsException =
_MatchServiceError dynamoDB "ReplicaAlreadyExistsException"
_LimitExceededException :: AsError a => Getting (First ServiceError) a ServiceError
_LimitExceededException = _MatchServiceError dynamoDB "LimitExceededException"
_ResourceInUseException :: AsError a => Getting (First ServiceError) a ServiceError
_ResourceInUseException = _MatchServiceError dynamoDB "ResourceInUseException"