{-# 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.DAX.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.DAX.Types
  ( -- * Service Configuration
    defaultService,

    -- * Errors
    _ClusterAlreadyExistsFault,
    _ClusterNotFoundFault,
    _ClusterQuotaForCustomerExceededFault,
    _InsufficientClusterCapacityFault,
    _InvalidARNFault,
    _InvalidClusterStateFault,
    _InvalidParameterCombinationException,
    _InvalidParameterGroupStateFault,
    _InvalidParameterValueException,
    _InvalidSubnet,
    _InvalidVPCNetworkStateFault,
    _NodeNotFoundFault,
    _NodeQuotaForClusterExceededFault,
    _NodeQuotaForCustomerExceededFault,
    _ParameterGroupAlreadyExistsFault,
    _ParameterGroupNotFoundFault,
    _ParameterGroupQuotaExceededFault,
    _ServiceLinkedRoleNotFoundFault,
    _ServiceQuotaExceededException,
    _SubnetGroupAlreadyExistsFault,
    _SubnetGroupInUseFault,
    _SubnetGroupNotFoundFault,
    _SubnetGroupQuotaExceededFault,
    _SubnetInUse,
    _SubnetQuotaExceededFault,
    _TagNotFoundFault,
    _TagQuotaPerResourceExceeded,

    -- * ChangeType
    ChangeType (..),

    -- * ClusterEndpointEncryptionType
    ClusterEndpointEncryptionType (..),

    -- * IsModifiable
    IsModifiable (..),

    -- * ParameterType
    ParameterType (..),

    -- * SSEStatus
    SSEStatus (..),

    -- * SourceType
    SourceType (..),

    -- * Cluster
    Cluster (..),
    newCluster,
    cluster_activeNodes,
    cluster_clusterArn,
    cluster_clusterDiscoveryEndpoint,
    cluster_clusterEndpointEncryptionType,
    cluster_clusterName,
    cluster_description,
    cluster_iamRoleArn,
    cluster_nodeIdsToRemove,
    cluster_nodeType,
    cluster_nodes,
    cluster_notificationConfiguration,
    cluster_parameterGroup,
    cluster_preferredMaintenanceWindow,
    cluster_sSEDescription,
    cluster_securityGroups,
    cluster_status,
    cluster_subnetGroup,
    cluster_totalNodes,

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

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

    -- * Node
    Node (..),
    newNode,
    node_availabilityZone,
    node_endpoint,
    node_nodeCreateTime,
    node_nodeId,
    node_nodeStatus,
    node_parameterGroupStatus,

    -- * NodeTypeSpecificValue
    NodeTypeSpecificValue (..),
    newNodeTypeSpecificValue,
    nodeTypeSpecificValue_nodeType,
    nodeTypeSpecificValue_value,

    -- * NotificationConfiguration
    NotificationConfiguration (..),
    newNotificationConfiguration,
    notificationConfiguration_topicArn,
    notificationConfiguration_topicStatus,

    -- * Parameter
    Parameter (..),
    newParameter,
    parameter_allowedValues,
    parameter_changeType,
    parameter_dataType,
    parameter_description,
    parameter_isModifiable,
    parameter_nodeTypeSpecificValues,
    parameter_parameterName,
    parameter_parameterType,
    parameter_parameterValue,
    parameter_source,

    -- * ParameterGroup
    ParameterGroup (..),
    newParameterGroup,
    parameterGroup_description,
    parameterGroup_parameterGroupName,

    -- * ParameterGroupStatus
    ParameterGroupStatus (..),
    newParameterGroupStatus,
    parameterGroupStatus_nodeIdsToReboot,
    parameterGroupStatus_parameterApplyStatus,
    parameterGroupStatus_parameterGroupName,

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

    -- * SSEDescription
    SSEDescription (..),
    newSSEDescription,
    sSEDescription_status,

    -- * SSESpecification
    SSESpecification (..),
    newSSESpecification,
    sSESpecification_enabled,

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

    -- * Subnet
    Subnet (..),
    newSubnet,
    subnet_subnetAvailabilityZone,
    subnet_subnetIdentifier,

    -- * SubnetGroup
    SubnetGroup (..),
    newSubnetGroup,
    subnetGroup_description,
    subnetGroup_subnetGroupName,
    subnetGroup_subnets,
    subnetGroup_vpcId,

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

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.DAX.Types.ChangeType
import Amazonka.DAX.Types.Cluster
import Amazonka.DAX.Types.ClusterEndpointEncryptionType
import Amazonka.DAX.Types.Endpoint
import Amazonka.DAX.Types.Event
import Amazonka.DAX.Types.IsModifiable
import Amazonka.DAX.Types.Node
import Amazonka.DAX.Types.NodeTypeSpecificValue
import Amazonka.DAX.Types.NotificationConfiguration
import Amazonka.DAX.Types.Parameter
import Amazonka.DAX.Types.ParameterGroup
import Amazonka.DAX.Types.ParameterGroupStatus
import Amazonka.DAX.Types.ParameterNameValue
import Amazonka.DAX.Types.ParameterType
import Amazonka.DAX.Types.SSEDescription
import Amazonka.DAX.Types.SSESpecification
import Amazonka.DAX.Types.SSEStatus
import Amazonka.DAX.Types.SecurityGroupMembership
import Amazonka.DAX.Types.SourceType
import Amazonka.DAX.Types.Subnet
import Amazonka.DAX.Types.SubnetGroup
import Amazonka.DAX.Types.Tag
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Sign.V4 as Sign

-- | API version @2017-04-19@ of the Amazon DynamoDB Accelerator (DAX) SDK configuration.
defaultService :: Core.Service
defaultService :: Service
defaultService =
  Core.Service
    { $sel:abbrev:Service :: Abbrev
Core.abbrev = Abbrev
"DAX",
      $sel:signer:Service :: Signer
Core.signer = Signer
Sign.v4,
      $sel:endpointPrefix:Service :: ByteString
Core.endpointPrefix = ByteString
"dax",
      $sel:signingName:Service :: ByteString
Core.signingName = ByteString
"dax",
      $sel:version:Service :: ByteString
Core.version = ByteString
"2017-04-19",
      $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
"DAX",
      $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

-- | You already have a DAX cluster with the given identifier.
_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"

-- | The requested cluster ID does not refer to an existing DAX cluster.
_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"

-- | You have attempted to exceed the maximum number of DAX clusters for your
-- AWS account.
_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"

-- | There are not enough system resources to create the cluster you
-- requested (or to resize an already-existing cluster).
_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"

-- | The Amazon Resource Name (ARN) supplied in the request is not valid.
_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"

-- | The requested DAX cluster is not in the /available/ state.
_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"

-- | Two or more incompatible parameters were specified.
_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"

-- | One or more parameters in a parameter group are in an invalid state.
_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"

-- | The value for a parameter is invalid.
_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"

-- | An invalid subnet identifier was specified.
_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"

-- | The VPC network is in an invalid state.
_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"

-- | None of the nodes in the cluster have the given node ID.
_NodeNotFoundFault :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NodeNotFoundFault :: forall a. AsError a => Fold a ServiceError
_NodeNotFoundFault =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NodeNotFoundFault"

-- | You have attempted to exceed the maximum number of nodes for a DAX
-- cluster.
_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"

-- | You have attempted to exceed the maximum number of nodes for your AWS
-- account.
_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"

-- | The specified parameter group already exists.
_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"

-- | The specified parameter group does not exist.
_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"

-- | You have attempted to exceed the maximum number of parameter groups.
_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"

-- | The specified service linked role (SLR) was not found.
_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"

-- | You have reached the maximum number of x509 certificates that can be
-- created for encrypted clusters in a 30 day period. Contact AWS customer
-- support to discuss options for continuing to create encrypted clusters.
_ServiceQuotaExceededException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ServiceQuotaExceededException :: forall a. AsError a => Fold a ServiceError
_ServiceQuotaExceededException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ServiceQuotaExceededException"

-- | The specified subnet group already exists.
_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"

-- | The specified subnet group is currently in use.
_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"

-- | The requested subnet group name does not refer to an existing subnet
-- group.
_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"

-- | The request cannot be processed because it would exceed the allowed
-- number of subnets in a subnet group.
_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"

-- | The requested subnet is being used by another subnet group.
_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"

-- | The request cannot be processed because it would exceed the allowed
-- number of subnets in a subnet group.
_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"

-- | The tag does not exist.
_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"

-- | You have exceeded the maximum number of tags for this DAX cluster.
_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"