{-# LANGUAGE DisambiguateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

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

-- |
-- Module      : Amazonka.MemoryDb.Types
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.MemoryDb.Types
  ( -- * Service Configuration
    defaultService,

    -- * Errors
    _ACLAlreadyExistsFault,
    _ACLNotFoundFault,
    _ACLQuotaExceededFault,
    _APICallRateForCustomerExceededFault,
    _ClusterAlreadyExistsFault,
    _ClusterNotFoundFault,
    _ClusterQuotaForCustomerExceededFault,
    _DefaultUserRequired,
    _DuplicateUserNameFault,
    _InsufficientClusterCapacityFault,
    _InvalidACLStateFault,
    _InvalidARNFault,
    _InvalidClusterStateFault,
    _InvalidCredentialsException,
    _InvalidKMSKeyFault,
    _InvalidNodeStateFault,
    _InvalidParameterCombinationException,
    _InvalidParameterGroupStateFault,
    _InvalidParameterValueException,
    _InvalidSnapshotStateFault,
    _InvalidSubnet,
    _InvalidUserStateFault,
    _InvalidVPCNetworkStateFault,
    _NoOperationFault,
    _NodeQuotaForClusterExceededFault,
    _NodeQuotaForCustomerExceededFault,
    _ParameterGroupAlreadyExistsFault,
    _ParameterGroupNotFoundFault,
    _ParameterGroupQuotaExceededFault,
    _ReservedNodeAlreadyExistsFault,
    _ReservedNodeNotFoundFault,
    _ReservedNodeQuotaExceededFault,
    _ReservedNodesOfferingNotFoundFault,
    _ServiceLinkedRoleNotFoundFault,
    _ServiceUpdateNotFoundFault,
    _ShardNotFoundFault,
    _ShardsPerClusterQuotaExceededFault,
    _SnapshotAlreadyExistsFault,
    _SnapshotNotFoundFault,
    _SnapshotQuotaExceededFault,
    _SubnetGroupAlreadyExistsFault,
    _SubnetGroupInUseFault,
    _SubnetGroupNotFoundFault,
    _SubnetGroupQuotaExceededFault,
    _SubnetInUse,
    _SubnetNotAllowedFault,
    _SubnetQuotaExceededFault,
    _TagNotFoundFault,
    _TagQuotaPerResourceExceeded,
    _TestFailoverNotAvailableFault,
    _UserAlreadyExistsFault,
    _UserNotFoundFault,
    _UserQuotaExceededFault,

    -- * AZStatus
    AZStatus (..),

    -- * AuthenticationType
    AuthenticationType (..),

    -- * DataTieringStatus
    DataTieringStatus (..),

    -- * InputAuthenticationType
    InputAuthenticationType (..),

    -- * ServiceUpdateStatus
    ServiceUpdateStatus (..),

    -- * ServiceUpdateType
    ServiceUpdateType (..),

    -- * SourceType
    SourceType (..),

    -- * ACL
    ACL (..),
    newACL,
    acl_arn,
    acl_clusters,
    acl_minimumEngineVersion,
    acl_name,
    acl_pendingChanges,
    acl_status,
    acl_userNames,

    -- * ACLPendingChanges
    ACLPendingChanges (..),
    newACLPendingChanges,
    aCLPendingChanges_userNamesToAdd,
    aCLPendingChanges_userNamesToRemove,

    -- * ACLsUpdateStatus
    ACLsUpdateStatus (..),
    newACLsUpdateStatus,
    aCLsUpdateStatus_aCLToApply,

    -- * Authentication
    Authentication (..),
    newAuthentication,
    authentication_passwordCount,
    authentication_type,

    -- * AuthenticationMode
    AuthenticationMode (..),
    newAuthenticationMode,
    authenticationMode_passwords,
    authenticationMode_type,

    -- * AvailabilityZone
    AvailabilityZone (..),
    newAvailabilityZone,
    availabilityZone_name,

    -- * Cluster
    Cluster (..),
    newCluster,
    cluster_aCLName,
    cluster_arn,
    cluster_autoMinorVersionUpgrade,
    cluster_availabilityMode,
    cluster_clusterEndpoint,
    cluster_dataTiering,
    cluster_description,
    cluster_enginePatchVersion,
    cluster_engineVersion,
    cluster_kmsKeyId,
    cluster_maintenanceWindow,
    cluster_name,
    cluster_nodeType,
    cluster_numberOfShards,
    cluster_parameterGroupName,
    cluster_parameterGroupStatus,
    cluster_pendingUpdates,
    cluster_securityGroups,
    cluster_shards,
    cluster_snapshotRetentionLimit,
    cluster_snapshotWindow,
    cluster_snsTopicArn,
    cluster_snsTopicStatus,
    cluster_status,
    cluster_subnetGroupName,
    cluster_tLSEnabled,

    -- * ClusterConfiguration
    ClusterConfiguration (..),
    newClusterConfiguration,
    clusterConfiguration_description,
    clusterConfiguration_engineVersion,
    clusterConfiguration_maintenanceWindow,
    clusterConfiguration_name,
    clusterConfiguration_nodeType,
    clusterConfiguration_numShards,
    clusterConfiguration_parameterGroupName,
    clusterConfiguration_port,
    clusterConfiguration_shards,
    clusterConfiguration_snapshotRetentionLimit,
    clusterConfiguration_snapshotWindow,
    clusterConfiguration_subnetGroupName,
    clusterConfiguration_topicArn,
    clusterConfiguration_vpcId,

    -- * ClusterPendingUpdates
    ClusterPendingUpdates (..),
    newClusterPendingUpdates,
    clusterPendingUpdates_aCLs,
    clusterPendingUpdates_resharding,
    clusterPendingUpdates_serviceUpdates,

    -- * Endpoint
    Endpoint (..),
    newEndpoint,
    endpoint_address,
    endpoint_port,

    -- * EngineVersionInfo
    EngineVersionInfo (..),
    newEngineVersionInfo,
    engineVersionInfo_enginePatchVersion,
    engineVersionInfo_engineVersion,
    engineVersionInfo_parameterGroupFamily,

    -- * Event
    Event (..),
    newEvent,
    event_date,
    event_message,
    event_sourceName,
    event_sourceType,

    -- * Filter
    Filter (..),
    newFilter,
    filter_name,
    filter_values,

    -- * Node
    Node (..),
    newNode,
    node_availabilityZone,
    node_createTime,
    node_endpoint,
    node_name,
    node_status,

    -- * Parameter
    Parameter (..),
    newParameter,
    parameter_allowedValues,
    parameter_dataType,
    parameter_description,
    parameter_minimumEngineVersion,
    parameter_name,
    parameter_value,

    -- * ParameterGroup
    ParameterGroup (..),
    newParameterGroup,
    parameterGroup_arn,
    parameterGroup_description,
    parameterGroup_family,
    parameterGroup_name,

    -- * ParameterNameValue
    ParameterNameValue (..),
    newParameterNameValue,
    parameterNameValue_parameterName,
    parameterNameValue_parameterValue,

    -- * PendingModifiedServiceUpdate
    PendingModifiedServiceUpdate (..),
    newPendingModifiedServiceUpdate,
    pendingModifiedServiceUpdate_serviceUpdateName,
    pendingModifiedServiceUpdate_status,

    -- * RecurringCharge
    RecurringCharge (..),
    newRecurringCharge,
    recurringCharge_recurringChargeAmount,
    recurringCharge_recurringChargeFrequency,

    -- * ReplicaConfigurationRequest
    ReplicaConfigurationRequest (..),
    newReplicaConfigurationRequest,
    replicaConfigurationRequest_replicaCount,

    -- * ReservedNode
    ReservedNode (..),
    newReservedNode,
    reservedNode_arn,
    reservedNode_duration,
    reservedNode_fixedPrice,
    reservedNode_nodeCount,
    reservedNode_nodeType,
    reservedNode_offeringType,
    reservedNode_recurringCharges,
    reservedNode_reservationId,
    reservedNode_reservedNodesOfferingId,
    reservedNode_startTime,
    reservedNode_state,

    -- * ReservedNodesOffering
    ReservedNodesOffering (..),
    newReservedNodesOffering,
    reservedNodesOffering_duration,
    reservedNodesOffering_fixedPrice,
    reservedNodesOffering_nodeType,
    reservedNodesOffering_offeringType,
    reservedNodesOffering_recurringCharges,
    reservedNodesOffering_reservedNodesOfferingId,

    -- * ReshardingStatus
    ReshardingStatus (..),
    newReshardingStatus,
    reshardingStatus_slotMigration,

    -- * SecurityGroupMembership
    SecurityGroupMembership (..),
    newSecurityGroupMembership,
    securityGroupMembership_securityGroupId,
    securityGroupMembership_status,

    -- * ServiceUpdate
    ServiceUpdate (..),
    newServiceUpdate,
    serviceUpdate_autoUpdateStartDate,
    serviceUpdate_clusterName,
    serviceUpdate_description,
    serviceUpdate_nodesUpdated,
    serviceUpdate_releaseDate,
    serviceUpdate_serviceUpdateName,
    serviceUpdate_status,
    serviceUpdate_type,

    -- * ServiceUpdateRequest
    ServiceUpdateRequest (..),
    newServiceUpdateRequest,
    serviceUpdateRequest_serviceUpdateNameToApply,

    -- * Shard
    Shard (..),
    newShard,
    shard_name,
    shard_nodes,
    shard_numberOfNodes,
    shard_slots,
    shard_status,

    -- * ShardConfiguration
    ShardConfiguration (..),
    newShardConfiguration,
    shardConfiguration_replicaCount,
    shardConfiguration_slots,

    -- * ShardConfigurationRequest
    ShardConfigurationRequest (..),
    newShardConfigurationRequest,
    shardConfigurationRequest_shardCount,

    -- * ShardDetail
    ShardDetail (..),
    newShardDetail,
    shardDetail_configuration,
    shardDetail_name,
    shardDetail_size,
    shardDetail_snapshotCreationTime,

    -- * SlotMigration
    SlotMigration (..),
    newSlotMigration,
    slotMigration_progressPercentage,

    -- * Snapshot
    Snapshot (..),
    newSnapshot,
    snapshot_arn,
    snapshot_clusterConfiguration,
    snapshot_dataTiering,
    snapshot_kmsKeyId,
    snapshot_name,
    snapshot_source,
    snapshot_status,

    -- * Subnet
    Subnet (..),
    newSubnet,
    subnet_availabilityZone,
    subnet_identifier,

    -- * SubnetGroup
    SubnetGroup (..),
    newSubnetGroup,
    subnetGroup_arn,
    subnetGroup_description,
    subnetGroup_name,
    subnetGroup_subnets,
    subnetGroup_vpcId,

    -- * Tag
    Tag (..),
    newTag,
    tag_key,
    tag_value,

    -- * UnprocessedCluster
    UnprocessedCluster (..),
    newUnprocessedCluster,
    unprocessedCluster_clusterName,
    unprocessedCluster_errorMessage,
    unprocessedCluster_errorType,

    -- * User
    User (..),
    newUser,
    user_aCLNames,
    user_arn,
    user_accessString,
    user_authentication,
    user_minimumEngineVersion,
    user_name,
    user_status,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.MemoryDb.Types.ACL
import Amazonka.MemoryDb.Types.ACLPendingChanges
import Amazonka.MemoryDb.Types.ACLsUpdateStatus
import Amazonka.MemoryDb.Types.AZStatus
import Amazonka.MemoryDb.Types.Authentication
import Amazonka.MemoryDb.Types.AuthenticationMode
import Amazonka.MemoryDb.Types.AuthenticationType
import Amazonka.MemoryDb.Types.AvailabilityZone
import Amazonka.MemoryDb.Types.Cluster
import Amazonka.MemoryDb.Types.ClusterConfiguration
import Amazonka.MemoryDb.Types.ClusterPendingUpdates
import Amazonka.MemoryDb.Types.DataTieringStatus
import Amazonka.MemoryDb.Types.Endpoint
import Amazonka.MemoryDb.Types.EngineVersionInfo
import Amazonka.MemoryDb.Types.Event
import Amazonka.MemoryDb.Types.Filter
import Amazonka.MemoryDb.Types.InputAuthenticationType
import Amazonka.MemoryDb.Types.Node
import Amazonka.MemoryDb.Types.Parameter
import Amazonka.MemoryDb.Types.ParameterGroup
import Amazonka.MemoryDb.Types.ParameterNameValue
import Amazonka.MemoryDb.Types.PendingModifiedServiceUpdate
import Amazonka.MemoryDb.Types.RecurringCharge
import Amazonka.MemoryDb.Types.ReplicaConfigurationRequest
import Amazonka.MemoryDb.Types.ReservedNode
import Amazonka.MemoryDb.Types.ReservedNodesOffering
import Amazonka.MemoryDb.Types.ReshardingStatus
import Amazonka.MemoryDb.Types.SecurityGroupMembership
import Amazonka.MemoryDb.Types.ServiceUpdate
import Amazonka.MemoryDb.Types.ServiceUpdateRequest
import Amazonka.MemoryDb.Types.ServiceUpdateStatus
import Amazonka.MemoryDb.Types.ServiceUpdateType
import Amazonka.MemoryDb.Types.Shard
import Amazonka.MemoryDb.Types.ShardConfiguration
import Amazonka.MemoryDb.Types.ShardConfigurationRequest
import Amazonka.MemoryDb.Types.ShardDetail
import Amazonka.MemoryDb.Types.SlotMigration
import Amazonka.MemoryDb.Types.Snapshot
import Amazonka.MemoryDb.Types.SourceType
import Amazonka.MemoryDb.Types.Subnet
import Amazonka.MemoryDb.Types.SubnetGroup
import Amazonka.MemoryDb.Types.Tag
import Amazonka.MemoryDb.Types.UnprocessedCluster
import Amazonka.MemoryDb.Types.User
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Sign.V4 as Sign

-- | API version @2021-01-01@ of the Amazon MemoryDB SDK configuration.
defaultService :: Core.Service
defaultService :: Service
defaultService =
  Core.Service
    { $sel:abbrev:Service :: Abbrev
Core.abbrev = Abbrev
"MemoryDb",
      $sel:signer:Service :: Signer
Core.signer = Signer
Sign.v4,
      $sel:endpointPrefix:Service :: ByteString
Core.endpointPrefix = ByteString
"memory-db",
      $sel:signingName:Service :: ByteString
Core.signingName = ByteString
"memorydb",
      $sel:version:Service :: ByteString
Core.version = ByteString
"2021-01-01",
      $sel:s3AddressingStyle:Service :: S3AddressingStyle
Core.s3AddressingStyle = S3AddressingStyle
Core.S3AddressingStyleAuto,
      $sel:endpoint:Service :: Region -> Endpoint
Core.endpoint = Service -> Region -> Endpoint
Core.defaultEndpoint Service
defaultService,
      $sel:timeout:Service :: Maybe Seconds
Core.timeout = forall a. a -> Maybe a
Prelude.Just Seconds
70,
      $sel:check:Service :: Status -> Bool
Core.check = Status -> Bool
Core.statusSuccess,
      $sel:error:Service :: Status -> [Header] -> ByteStringLazy -> Error
Core.error = Abbrev -> Status -> [Header] -> ByteStringLazy -> Error
Core.parseJSONError Abbrev
"MemoryDb",
      $sel:retry:Service :: Retry
Core.retry = Retry
retry
    }
  where
    retry :: Retry
retry =
      Core.Exponential
        { $sel:base:Exponential :: Double
Core.base = Double
5.0e-2,
          $sel:growth:Exponential :: Int
Core.growth = Int
2,
          $sel:attempts:Exponential :: Int
Core.attempts = Int
5,
          $sel:check:Exponential :: ServiceError -> Maybe Text
Core.check = forall {a}. IsString a => ServiceError -> Maybe a
check
        }
    check :: ServiceError -> Maybe a
check ServiceError
e
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
502) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"bad_gateway"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
504) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"gateway_timeout"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
500) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"general_server_error"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
509) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"limit_exceeded"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has
          ( forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
ErrorCode -> Optic' p f ServiceError ServiceError
Core.hasCode ErrorCode
"RequestThrottledException"
              forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400
          )
          ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"request_throttled_exception"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
503) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"service_unavailable"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has
          ( forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
ErrorCode -> Optic' p f ServiceError ServiceError
Core.hasCode ErrorCode
"ThrottledException"
              forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400
          )
          ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"throttled_exception"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has
          ( forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
ErrorCode -> Optic' p f ServiceError ServiceError
Core.hasCode ErrorCode
"Throttling"
              forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400
          )
          ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"throttling"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has
          ( forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
ErrorCode -> Optic' p f ServiceError ServiceError
Core.hasCode ErrorCode
"ThrottlingException"
              forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400
          )
          ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"throttling_exception"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has
          ( forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
ErrorCode -> Optic' p f ServiceError ServiceError
Core.hasCode
              ErrorCode
"ProvisionedThroughputExceededException"
              forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400
          )
          ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"throughput_exceeded"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
429) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"too_many_requests"
      | Bool
Prelude.otherwise = forall a. Maybe a
Prelude.Nothing

_ACLAlreadyExistsFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ACLAlreadyExistsFault :: forall a. AsError a => Fold a ServiceError
_ACLAlreadyExistsFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ACLAlreadyExistsFault"

_ACLNotFoundFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ACLNotFoundFault :: forall a. AsError a => Fold a ServiceError
_ACLNotFoundFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ACLNotFoundFault"

_ACLQuotaExceededFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ACLQuotaExceededFault :: forall a. AsError a => Fold a ServiceError
_ACLQuotaExceededFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ACLQuotaExceededFault"

_APICallRateForCustomerExceededFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_APICallRateForCustomerExceededFault :: forall a. AsError a => Fold a ServiceError
_APICallRateForCustomerExceededFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"APICallRateForCustomerExceededFault"

_ClusterAlreadyExistsFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ClusterAlreadyExistsFault :: forall a. AsError a => Fold a ServiceError
_ClusterAlreadyExistsFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ClusterAlreadyExistsFault"

_ClusterNotFoundFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ClusterNotFoundFault :: forall a. AsError a => Fold a ServiceError
_ClusterNotFoundFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ClusterNotFoundFault"

_ClusterQuotaForCustomerExceededFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ClusterQuotaForCustomerExceededFault :: forall a. AsError a => Fold a ServiceError
_ClusterQuotaForCustomerExceededFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ClusterQuotaForCustomerExceededFault"

_DefaultUserRequired :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DefaultUserRequired :: forall a. AsError a => Fold a ServiceError
_DefaultUserRequired =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"DefaultUserRequired"

_DuplicateUserNameFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DuplicateUserNameFault :: forall a. AsError a => Fold a ServiceError
_DuplicateUserNameFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"DuplicateUserNameFault"

_InsufficientClusterCapacityFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InsufficientClusterCapacityFault :: forall a. AsError a => Fold a ServiceError
_InsufficientClusterCapacityFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InsufficientClusterCapacityFault"

_InvalidACLStateFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidACLStateFault :: forall a. AsError a => Fold a ServiceError
_InvalidACLStateFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidACLStateFault"

_InvalidARNFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidARNFault :: forall a. AsError a => Fold a ServiceError
_InvalidARNFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidARNFault"

_InvalidClusterStateFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidClusterStateFault :: forall a. AsError a => Fold a ServiceError
_InvalidClusterStateFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidClusterStateFault"

_InvalidCredentialsException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidCredentialsException :: forall a. AsError a => Fold a ServiceError
_InvalidCredentialsException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidCredentialsException"

_InvalidKMSKeyFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidKMSKeyFault :: forall a. AsError a => Fold a ServiceError
_InvalidKMSKeyFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidKMSKeyFault"

_InvalidNodeStateFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidNodeStateFault :: forall a. AsError a => Fold a ServiceError
_InvalidNodeStateFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidNodeStateFault"

_InvalidParameterCombinationException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidParameterCombinationException :: forall a. AsError a => Fold a ServiceError
_InvalidParameterCombinationException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidParameterCombinationException"

_InvalidParameterGroupStateFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidParameterGroupStateFault :: forall a. AsError a => Fold a ServiceError
_InvalidParameterGroupStateFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidParameterGroupStateFault"

_InvalidParameterValueException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidParameterValueException :: forall a. AsError a => Fold a ServiceError
_InvalidParameterValueException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidParameterValueException"

_InvalidSnapshotStateFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidSnapshotStateFault :: forall a. AsError a => Fold a ServiceError
_InvalidSnapshotStateFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidSnapshotStateFault"

_InvalidSubnet :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidSubnet :: forall a. AsError a => Fold a ServiceError
_InvalidSubnet =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidSubnet"

_InvalidUserStateFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidUserStateFault :: forall a. AsError a => Fold a ServiceError
_InvalidUserStateFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidUserStateFault"

_InvalidVPCNetworkStateFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidVPCNetworkStateFault :: forall a. AsError a => Fold a ServiceError
_InvalidVPCNetworkStateFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidVPCNetworkStateFault"

_NoOperationFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoOperationFault :: forall a. AsError a => Fold a ServiceError
_NoOperationFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoOperationFault"

_NodeQuotaForClusterExceededFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NodeQuotaForClusterExceededFault :: forall a. AsError a => Fold a ServiceError
_NodeQuotaForClusterExceededFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NodeQuotaForClusterExceededFault"

_NodeQuotaForCustomerExceededFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NodeQuotaForCustomerExceededFault :: forall a. AsError a => Fold a ServiceError
_NodeQuotaForCustomerExceededFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NodeQuotaForCustomerExceededFault"

_ParameterGroupAlreadyExistsFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ParameterGroupAlreadyExistsFault :: forall a. AsError a => Fold a ServiceError
_ParameterGroupAlreadyExistsFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ParameterGroupAlreadyExistsFault"

_ParameterGroupNotFoundFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ParameterGroupNotFoundFault :: forall a. AsError a => Fold a ServiceError
_ParameterGroupNotFoundFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ParameterGroupNotFoundFault"

_ParameterGroupQuotaExceededFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ParameterGroupQuotaExceededFault :: forall a. AsError a => Fold a ServiceError
_ParameterGroupQuotaExceededFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ParameterGroupQuotaExceededFault"

-- | You already have a reservation with the given identifier.
_ReservedNodeAlreadyExistsFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ReservedNodeAlreadyExistsFault :: forall a. AsError a => Fold a ServiceError
_ReservedNodeAlreadyExistsFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ReservedNodeAlreadyExistsFault"

-- | The requested node does not exist.
_ReservedNodeNotFoundFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ReservedNodeNotFoundFault :: forall a. AsError a => Fold a ServiceError
_ReservedNodeNotFoundFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ReservedNodeNotFoundFault"

-- | The request cannot be processed because it would exceed the user\'s node
-- quota.
_ReservedNodeQuotaExceededFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ReservedNodeQuotaExceededFault :: forall a. AsError a => Fold a ServiceError
_ReservedNodeQuotaExceededFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ReservedNodeQuotaExceededFault"

-- | The requested node offering does not exist.
_ReservedNodesOfferingNotFoundFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ReservedNodesOfferingNotFoundFault :: forall a. AsError a => Fold a ServiceError
_ReservedNodesOfferingNotFoundFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ReservedNodesOfferingNotFoundFault"

_ServiceLinkedRoleNotFoundFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ServiceLinkedRoleNotFoundFault :: forall a. AsError a => Fold a ServiceError
_ServiceLinkedRoleNotFoundFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ServiceLinkedRoleNotFoundFault"

_ServiceUpdateNotFoundFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ServiceUpdateNotFoundFault :: forall a. AsError a => Fold a ServiceError
_ServiceUpdateNotFoundFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ServiceUpdateNotFoundFault"

_ShardNotFoundFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ShardNotFoundFault :: forall a. AsError a => Fold a ServiceError
_ShardNotFoundFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ShardNotFoundFault"

_ShardsPerClusterQuotaExceededFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ShardsPerClusterQuotaExceededFault :: forall a. AsError a => Fold a ServiceError
_ShardsPerClusterQuotaExceededFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ShardsPerClusterQuotaExceededFault"

_SnapshotAlreadyExistsFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_SnapshotAlreadyExistsFault :: forall a. AsError a => Fold a ServiceError
_SnapshotAlreadyExistsFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"SnapshotAlreadyExistsFault"

_SnapshotNotFoundFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_SnapshotNotFoundFault :: forall a. AsError a => Fold a ServiceError
_SnapshotNotFoundFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"SnapshotNotFoundFault"

_SnapshotQuotaExceededFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_SnapshotQuotaExceededFault :: forall a. AsError a => Fold a ServiceError
_SnapshotQuotaExceededFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"SnapshotQuotaExceededFault"

_SubnetGroupAlreadyExistsFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_SubnetGroupAlreadyExistsFault :: forall a. AsError a => Fold a ServiceError
_SubnetGroupAlreadyExistsFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"SubnetGroupAlreadyExistsFault"

_SubnetGroupInUseFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_SubnetGroupInUseFault :: forall a. AsError a => Fold a ServiceError
_SubnetGroupInUseFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"SubnetGroupInUseFault"

_SubnetGroupNotFoundFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_SubnetGroupNotFoundFault :: forall a. AsError a => Fold a ServiceError
_SubnetGroupNotFoundFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"SubnetGroupNotFoundFault"

_SubnetGroupQuotaExceededFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_SubnetGroupQuotaExceededFault :: forall a. AsError a => Fold a ServiceError
_SubnetGroupQuotaExceededFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"SubnetGroupQuotaExceededFault"

_SubnetInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_SubnetInUse :: forall a. AsError a => Fold a ServiceError
_SubnetInUse =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"SubnetInUse"

_SubnetNotAllowedFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_SubnetNotAllowedFault :: forall a. AsError a => Fold a ServiceError
_SubnetNotAllowedFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"SubnetNotAllowedFault"

_SubnetQuotaExceededFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_SubnetQuotaExceededFault :: forall a. AsError a => Fold a ServiceError
_SubnetQuotaExceededFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"SubnetQuotaExceededFault"

_TagNotFoundFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TagNotFoundFault :: forall a. AsError a => Fold a ServiceError
_TagNotFoundFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TagNotFoundFault"

_TagQuotaPerResourceExceeded :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TagQuotaPerResourceExceeded :: forall a. AsError a => Fold a ServiceError
_TagQuotaPerResourceExceeded =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TagQuotaPerResourceExceeded"

_TestFailoverNotAvailableFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TestFailoverNotAvailableFault :: forall a. AsError a => Fold a ServiceError
_TestFailoverNotAvailableFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TestFailoverNotAvailableFault"

_UserAlreadyExistsFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_UserAlreadyExistsFault :: forall a. AsError a => Fold a ServiceError
_UserAlreadyExistsFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"UserAlreadyExistsFault"

_UserNotFoundFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_UserNotFoundFault :: forall a. AsError a => Fold a ServiceError
_UserNotFoundFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"UserNotFoundFault"

_UserQuotaExceededFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_UserQuotaExceededFault :: forall a. AsError a => Fold a ServiceError
_UserQuotaExceededFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"UserQuotaExceededFault"