{-# LANGUAGE DisambiguateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Amazonka.Route53.Types
(
defaultService,
_CidrBlockInUseException,
_CidrCollectionAlreadyExistsException,
_CidrCollectionInUseException,
_CidrCollectionVersionMismatchException,
_ConcurrentModification,
_ConflictingDomainExists,
_ConflictingTypes,
_DNSSECNotFound,
_DelegationSetAlreadyCreated,
_DelegationSetAlreadyReusable,
_DelegationSetInUse,
_DelegationSetNotAvailable,
_DelegationSetNotReusable,
_HealthCheckAlreadyExists,
_HealthCheckInUse,
_HealthCheckVersionMismatch,
_HostedZoneAlreadyExists,
_HostedZoneNotEmpty,
_HostedZoneNotFound,
_HostedZoneNotPrivate,
_HostedZonePartiallyDelegated,
_IncompatibleVersion,
_InsufficientCloudWatchLogsResourcePolicy,
_InvalidArgument,
_InvalidChangeBatch,
_InvalidDomainName,
_InvalidInput,
_InvalidKMSArn,
_InvalidKeySigningKeyName,
_InvalidKeySigningKeyStatus,
_InvalidPaginationToken,
_InvalidSigningStatus,
_InvalidTrafficPolicyDocument,
_InvalidVPCId,
_KeySigningKeyAlreadyExists,
_KeySigningKeyInParentDSRecord,
_KeySigningKeyInUse,
_KeySigningKeyWithActiveStatusNotFound,
_LastVPCAssociation,
_LimitsExceeded,
_NoSuchChange,
_NoSuchCidrCollectionException,
_NoSuchCidrLocationException,
_NoSuchCloudWatchLogsLogGroup,
_NoSuchDelegationSet,
_NoSuchGeoLocation,
_NoSuchHealthCheck,
_NoSuchHostedZone,
_NoSuchKeySigningKey,
_NoSuchQueryLoggingConfig,
_NoSuchTrafficPolicy,
_NoSuchTrafficPolicyInstance,
_NotAuthorizedException,
_PriorRequestNotComplete,
_PublicZoneVPCAssociation,
_QueryLoggingConfigAlreadyExists,
_ThrottlingException,
_TooManyHealthChecks,
_TooManyHostedZones,
_TooManyKeySigningKeys,
_TooManyTrafficPolicies,
_TooManyTrafficPolicyInstances,
_TooManyTrafficPolicyVersionsForCurrentPolicy,
_TooManyVPCAssociationAuthorizations,
_TrafficPolicyAlreadyExists,
_TrafficPolicyInUse,
_TrafficPolicyInstanceAlreadyExists,
_VPCAssociationAuthorizationNotFound,
_VPCAssociationNotFound,
module Amazonka.Route53.Internal,
AccountLimitType (..),
ChangeAction (..),
ChangeStatus (..),
CidrCollectionChangeAction (..),
CloudWatchRegion (..),
ComparisonOperator (..),
HealthCheckRegion (..),
HealthCheckType (..),
HostedZoneLimitType (..),
InsufficientDataHealthStatus (..),
RRType (..),
ResettableElementName (..),
ResourceRecordSetFailover (..),
ReusableDelegationSetLimitType (..),
Statistic (..),
TagResourceType (..),
VPCRegion (..),
AccountLimit (..),
newAccountLimit,
accountLimit_type,
accountLimit_value,
AlarmIdentifier (..),
newAlarmIdentifier,
alarmIdentifier_region,
alarmIdentifier_name,
AliasTarget (..),
newAliasTarget,
aliasTarget_hostedZoneId,
aliasTarget_dNSName,
aliasTarget_evaluateTargetHealth,
Change (..),
newChange,
change_action,
change_resourceRecordSet,
ChangeBatch (..),
newChangeBatch,
changeBatch_comment,
changeBatch_changes,
ChangeInfo (..),
newChangeInfo,
changeInfo_comment,
changeInfo_id,
changeInfo_status,
changeInfo_submittedAt,
CidrBlockSummary (..),
newCidrBlockSummary,
cidrBlockSummary_cidrBlock,
cidrBlockSummary_locationName,
CidrCollection (..),
newCidrCollection,
cidrCollection_arn,
cidrCollection_id,
cidrCollection_name,
cidrCollection_version,
CidrCollectionChange (..),
newCidrCollectionChange,
cidrCollectionChange_locationName,
cidrCollectionChange_action,
cidrCollectionChange_cidrList,
CidrRoutingConfig (..),
newCidrRoutingConfig,
cidrRoutingConfig_collectionId,
cidrRoutingConfig_locationName,
CloudWatchAlarmConfiguration (..),
newCloudWatchAlarmConfiguration,
cloudWatchAlarmConfiguration_dimensions,
cloudWatchAlarmConfiguration_evaluationPeriods,
cloudWatchAlarmConfiguration_threshold,
cloudWatchAlarmConfiguration_comparisonOperator,
cloudWatchAlarmConfiguration_period,
cloudWatchAlarmConfiguration_metricName,
cloudWatchAlarmConfiguration_namespace,
cloudWatchAlarmConfiguration_statistic,
CollectionSummary (..),
newCollectionSummary,
collectionSummary_arn,
collectionSummary_id,
collectionSummary_name,
collectionSummary_version,
DNSSECStatus (..),
newDNSSECStatus,
dNSSECStatus_serveSignature,
dNSSECStatus_statusMessage,
DelegationSet (..),
newDelegationSet,
delegationSet_callerReference,
delegationSet_id,
delegationSet_nameServers,
Dimension (..),
newDimension,
dimension_name,
dimension_value,
GeoLocation (..),
newGeoLocation,
geoLocation_continentCode,
geoLocation_countryCode,
geoLocation_subdivisionCode,
GeoLocationDetails (..),
newGeoLocationDetails,
geoLocationDetails_continentCode,
geoLocationDetails_continentName,
geoLocationDetails_countryCode,
geoLocationDetails_countryName,
geoLocationDetails_subdivisionCode,
geoLocationDetails_subdivisionName,
HealthCheck (..),
newHealthCheck,
healthCheck_cloudWatchAlarmConfiguration,
healthCheck_linkedService,
healthCheck_id,
healthCheck_callerReference,
healthCheck_healthCheckConfig,
healthCheck_healthCheckVersion,
HealthCheckConfig (..),
newHealthCheckConfig,
healthCheckConfig_alarmIdentifier,
healthCheckConfig_childHealthChecks,
healthCheckConfig_disabled,
healthCheckConfig_enableSNI,
healthCheckConfig_failureThreshold,
healthCheckConfig_fullyQualifiedDomainName,
healthCheckConfig_healthThreshold,
healthCheckConfig_iPAddress,
healthCheckConfig_insufficientDataHealthStatus,
healthCheckConfig_inverted,
healthCheckConfig_measureLatency,
healthCheckConfig_port,
healthCheckConfig_regions,
healthCheckConfig_requestInterval,
healthCheckConfig_resourcePath,
healthCheckConfig_routingControlArn,
healthCheckConfig_searchString,
healthCheckConfig_type,
HealthCheckObservation (..),
newHealthCheckObservation,
healthCheckObservation_iPAddress,
healthCheckObservation_region,
healthCheckObservation_statusReport,
HostedZone (..),
newHostedZone,
hostedZone_config,
hostedZone_linkedService,
hostedZone_resourceRecordSetCount,
hostedZone_id,
hostedZone_name,
hostedZone_callerReference,
HostedZoneConfig (..),
newHostedZoneConfig,
hostedZoneConfig_comment,
hostedZoneConfig_privateZone,
HostedZoneLimit (..),
newHostedZoneLimit,
hostedZoneLimit_type,
hostedZoneLimit_value,
HostedZoneOwner (..),
newHostedZoneOwner,
hostedZoneOwner_owningAccount,
hostedZoneOwner_owningService,
HostedZoneSummary (..),
newHostedZoneSummary,
hostedZoneSummary_hostedZoneId,
hostedZoneSummary_name,
hostedZoneSummary_owner,
KeySigningKey (..),
newKeySigningKey,
keySigningKey_createdDate,
keySigningKey_dNSKEYRecord,
keySigningKey_dSRecord,
keySigningKey_digestAlgorithmMnemonic,
keySigningKey_digestAlgorithmType,
keySigningKey_digestValue,
keySigningKey_flag,
keySigningKey_keyTag,
keySigningKey_kmsArn,
keySigningKey_lastModifiedDate,
keySigningKey_name,
keySigningKey_publicKey,
keySigningKey_signingAlgorithmMnemonic,
keySigningKey_signingAlgorithmType,
keySigningKey_status,
keySigningKey_statusMessage,
LinkedService (..),
newLinkedService,
linkedService_description,
linkedService_servicePrincipal,
LocationSummary (..),
newLocationSummary,
locationSummary_locationName,
QueryLoggingConfig (..),
newQueryLoggingConfig,
queryLoggingConfig_id,
queryLoggingConfig_hostedZoneId,
queryLoggingConfig_cloudWatchLogsLogGroupArn,
ResourceRecord (..),
newResourceRecord,
resourceRecord_value,
ResourceRecordSet (..),
newResourceRecordSet,
resourceRecordSet_aliasTarget,
resourceRecordSet_cidrRoutingConfig,
resourceRecordSet_failover,
resourceRecordSet_geoLocation,
resourceRecordSet_healthCheckId,
resourceRecordSet_multiValueAnswer,
resourceRecordSet_region,
resourceRecordSet_resourceRecords,
resourceRecordSet_setIdentifier,
resourceRecordSet_ttl,
resourceRecordSet_trafficPolicyInstanceId,
resourceRecordSet_weight,
resourceRecordSet_name,
resourceRecordSet_type,
ResourceTagSet (..),
newResourceTagSet,
resourceTagSet_resourceId,
resourceTagSet_resourceType,
resourceTagSet_tags,
ReusableDelegationSetLimit (..),
newReusableDelegationSetLimit,
reusableDelegationSetLimit_type,
reusableDelegationSetLimit_value,
StatusReport (..),
newStatusReport,
statusReport_checkedTime,
statusReport_status,
Tag (..),
newTag,
tag_key,
tag_value,
TrafficPolicy (..),
newTrafficPolicy,
trafficPolicy_comment,
trafficPolicy_id,
trafficPolicy_version,
trafficPolicy_name,
trafficPolicy_type,
trafficPolicy_document,
TrafficPolicyInstance (..),
newTrafficPolicyInstance,
trafficPolicyInstance_id,
trafficPolicyInstance_hostedZoneId,
trafficPolicyInstance_name,
trafficPolicyInstance_ttl,
trafficPolicyInstance_state,
trafficPolicyInstance_message,
trafficPolicyInstance_trafficPolicyId,
trafficPolicyInstance_trafficPolicyVersion,
trafficPolicyInstance_trafficPolicyType,
TrafficPolicySummary (..),
newTrafficPolicySummary,
trafficPolicySummary_id,
trafficPolicySummary_name,
trafficPolicySummary_type,
trafficPolicySummary_latestVersion,
trafficPolicySummary_trafficPolicyCount,
VPC (..),
newVPC,
vpc_vPCId,
vpc_vPCRegion,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Prelude as Prelude
import Amazonka.Route53.Internal
import Amazonka.Route53.Types.AccountLimit
import Amazonka.Route53.Types.AccountLimitType
import Amazonka.Route53.Types.AlarmIdentifier
import Amazonka.Route53.Types.AliasTarget
import Amazonka.Route53.Types.Change
import Amazonka.Route53.Types.ChangeAction
import Amazonka.Route53.Types.ChangeBatch
import Amazonka.Route53.Types.ChangeInfo
import Amazonka.Route53.Types.ChangeStatus
import Amazonka.Route53.Types.CidrBlockSummary
import Amazonka.Route53.Types.CidrCollection
import Amazonka.Route53.Types.CidrCollectionChange
import Amazonka.Route53.Types.CidrCollectionChangeAction
import Amazonka.Route53.Types.CidrRoutingConfig
import Amazonka.Route53.Types.CloudWatchAlarmConfiguration
import Amazonka.Route53.Types.CloudWatchRegion
import Amazonka.Route53.Types.CollectionSummary
import Amazonka.Route53.Types.ComparisonOperator
import Amazonka.Route53.Types.DNSSECStatus
import Amazonka.Route53.Types.DelegationSet
import Amazonka.Route53.Types.Dimension
import Amazonka.Route53.Types.GeoLocation
import Amazonka.Route53.Types.GeoLocationDetails
import Amazonka.Route53.Types.HealthCheck
import Amazonka.Route53.Types.HealthCheckConfig
import Amazonka.Route53.Types.HealthCheckObservation
import Amazonka.Route53.Types.HealthCheckRegion
import Amazonka.Route53.Types.HealthCheckType
import Amazonka.Route53.Types.HostedZone
import Amazonka.Route53.Types.HostedZoneConfig
import Amazonka.Route53.Types.HostedZoneLimit
import Amazonka.Route53.Types.HostedZoneLimitType
import Amazonka.Route53.Types.HostedZoneOwner
import Amazonka.Route53.Types.HostedZoneSummary
import Amazonka.Route53.Types.InsufficientDataHealthStatus
import Amazonka.Route53.Types.KeySigningKey
import Amazonka.Route53.Types.LinkedService
import Amazonka.Route53.Types.LocationSummary
import Amazonka.Route53.Types.QueryLoggingConfig
import Amazonka.Route53.Types.RRType
import Amazonka.Route53.Types.ResettableElementName
import Amazonka.Route53.Types.ResourceRecord
import Amazonka.Route53.Types.ResourceRecordSet
import Amazonka.Route53.Types.ResourceRecordSetFailover
import Amazonka.Route53.Types.ResourceTagSet
import Amazonka.Route53.Types.ReusableDelegationSetLimit
import Amazonka.Route53.Types.ReusableDelegationSetLimitType
import Amazonka.Route53.Types.Statistic
import Amazonka.Route53.Types.StatusReport
import Amazonka.Route53.Types.Tag
import Amazonka.Route53.Types.TagResourceType
import Amazonka.Route53.Types.TrafficPolicy
import Amazonka.Route53.Types.TrafficPolicyInstance
import Amazonka.Route53.Types.TrafficPolicySummary
import Amazonka.Route53.Types.VPC
import Amazonka.Route53.Types.VPCRegion
import qualified Amazonka.Sign.V4 as Sign
defaultService :: Core.Service
defaultService :: Service
defaultService =
Core.Service
{ $sel:abbrev:Service :: Abbrev
Core.abbrev = Abbrev
"Route53",
$sel:signer:Service :: Signer
Core.signer = Signer
Sign.v4,
$sel:endpointPrefix:Service :: ByteString
Core.endpointPrefix = ByteString
"route53",
$sel:signingName:Service :: ByteString
Core.signingName = ByteString
"route53",
$sel:version:Service :: ByteString
Core.version = ByteString
"2013-04-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.parseXMLError Abbrev
"Route53",
$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
"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
"request_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
"PriorRequestNotComplete"
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
"still_processing"
| 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
_CidrBlockInUseException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CidrBlockInUseException :: forall a. AsError a => Fold a ServiceError
_CidrBlockInUseException =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"CidrBlockInUseException"
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
_CidrCollectionAlreadyExistsException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CidrCollectionAlreadyExistsException :: forall a. AsError a => Fold a ServiceError
_CidrCollectionAlreadyExistsException =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"CidrCollectionAlreadyExistsException"
_CidrCollectionInUseException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CidrCollectionInUseException :: forall a. AsError a => Fold a ServiceError
_CidrCollectionInUseException =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"CidrCollectionInUseException"
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
_CidrCollectionVersionMismatchException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CidrCollectionVersionMismatchException :: forall a. AsError a => Fold a ServiceError
_CidrCollectionVersionMismatchException =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"CidrCollectionVersionMismatchException"
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
409
_ConcurrentModification :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ConcurrentModification :: forall a. AsError a => Fold a ServiceError
_ConcurrentModification =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"ConcurrentModification"
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
_ConflictingDomainExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ConflictingDomainExists :: forall a. AsError a => Fold a ServiceError
_ConflictingDomainExists =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"ConflictingDomainExists"
_ConflictingTypes :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ConflictingTypes :: forall a. AsError a => Fold a ServiceError
_ConflictingTypes =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"ConflictingTypes"
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
_DNSSECNotFound :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DNSSECNotFound :: forall a. AsError a => Fold a ServiceError
_DNSSECNotFound =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"DNSSECNotFound"
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
_DelegationSetAlreadyCreated :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DelegationSetAlreadyCreated :: forall a. AsError a => Fold a ServiceError
_DelegationSetAlreadyCreated =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"DelegationSetAlreadyCreated"
_DelegationSetAlreadyReusable :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DelegationSetAlreadyReusable :: forall a. AsError a => Fold a ServiceError
_DelegationSetAlreadyReusable =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"DelegationSetAlreadyReusable"
_DelegationSetInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DelegationSetInUse :: forall a. AsError a => Fold a ServiceError
_DelegationSetInUse =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"DelegationSetInUse"
_DelegationSetNotAvailable :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DelegationSetNotAvailable :: forall a. AsError a => Fold a ServiceError
_DelegationSetNotAvailable =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"DelegationSetNotAvailable"
_DelegationSetNotReusable :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DelegationSetNotReusable :: forall a. AsError a => Fold a ServiceError
_DelegationSetNotReusable =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"DelegationSetNotReusable"
_HealthCheckAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_HealthCheckAlreadyExists :: forall a. AsError a => Fold a ServiceError
_HealthCheckAlreadyExists =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"HealthCheckAlreadyExists"
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
409
_HealthCheckInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_HealthCheckInUse :: forall a. AsError a => Fold a ServiceError
_HealthCheckInUse =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"HealthCheckInUse"
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
_HealthCheckVersionMismatch :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_HealthCheckVersionMismatch :: forall a. AsError a => Fold a ServiceError
_HealthCheckVersionMismatch =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"HealthCheckVersionMismatch"
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
409
_HostedZoneAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_HostedZoneAlreadyExists :: forall a. AsError a => Fold a ServiceError
_HostedZoneAlreadyExists =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"HostedZoneAlreadyExists"
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
409
_HostedZoneNotEmpty :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_HostedZoneNotEmpty :: forall a. AsError a => Fold a ServiceError
_HostedZoneNotEmpty =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"HostedZoneNotEmpty"
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
_HostedZoneNotFound :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_HostedZoneNotFound :: forall a. AsError a => Fold a ServiceError
_HostedZoneNotFound =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"HostedZoneNotFound"
_HostedZoneNotPrivate :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_HostedZoneNotPrivate :: forall a. AsError a => Fold a ServiceError
_HostedZoneNotPrivate =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"HostedZoneNotPrivate"
_HostedZonePartiallyDelegated :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_HostedZonePartiallyDelegated :: forall a. AsError a => Fold a ServiceError
_HostedZonePartiallyDelegated =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"HostedZonePartiallyDelegated"
_IncompatibleVersion :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_IncompatibleVersion :: forall a. AsError a => Fold a ServiceError
_IncompatibleVersion =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"IncompatibleVersion"
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
_InsufficientCloudWatchLogsResourcePolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InsufficientCloudWatchLogsResourcePolicy :: forall a. AsError a => Fold a ServiceError
_InsufficientCloudWatchLogsResourcePolicy =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"InsufficientCloudWatchLogsResourcePolicy"
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
_InvalidArgument :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidArgument :: forall a. AsError a => Fold a ServiceError
_InvalidArgument =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"InvalidArgument"
_InvalidChangeBatch :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidChangeBatch :: forall a. AsError a => Fold a ServiceError
_InvalidChangeBatch =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"InvalidChangeBatch"
_InvalidDomainName :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidDomainName :: forall a. AsError a => Fold a ServiceError
_InvalidDomainName =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"InvalidDomainName"
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
_InvalidInput :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidInput :: forall a. AsError a => Fold a ServiceError
_InvalidInput =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"InvalidInput"
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
_InvalidKMSArn :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidKMSArn :: forall a. AsError a => Fold a ServiceError
_InvalidKMSArn =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"InvalidKMSArn"
_InvalidKeySigningKeyName :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidKeySigningKeyName :: forall a. AsError a => Fold a ServiceError
_InvalidKeySigningKeyName =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"InvalidKeySigningKeyName"
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
_InvalidKeySigningKeyStatus :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidKeySigningKeyStatus :: forall a. AsError a => Fold a ServiceError
_InvalidKeySigningKeyStatus =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"InvalidKeySigningKeyStatus"
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
_InvalidPaginationToken :: (Core.AsError a) => Lens.Fold a Core.ServiceError
=
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"InvalidPaginationToken"
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
_InvalidSigningStatus :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidSigningStatus :: forall a. AsError a => Fold a ServiceError
_InvalidSigningStatus =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"InvalidSigningStatus"
_InvalidTrafficPolicyDocument :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidTrafficPolicyDocument :: forall a. AsError a => Fold a ServiceError
_InvalidTrafficPolicyDocument =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"InvalidTrafficPolicyDocument"
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
_InvalidVPCId :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidVPCId :: forall a. AsError a => Fold a ServiceError
_InvalidVPCId =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"InvalidVPCId"
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
_KeySigningKeyAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_KeySigningKeyAlreadyExists :: forall a. AsError a => Fold a ServiceError
_KeySigningKeyAlreadyExists =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"KeySigningKeyAlreadyExists"
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
409
_KeySigningKeyInParentDSRecord :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_KeySigningKeyInParentDSRecord :: forall a. AsError a => Fold a ServiceError
_KeySigningKeyInParentDSRecord =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"KeySigningKeyInParentDSRecord"
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
_KeySigningKeyInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_KeySigningKeyInUse :: forall a. AsError a => Fold a ServiceError
_KeySigningKeyInUse =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"KeySigningKeyInUse"
_KeySigningKeyWithActiveStatusNotFound :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_KeySigningKeyWithActiveStatusNotFound :: forall a. AsError a => Fold a ServiceError
_KeySigningKeyWithActiveStatusNotFound =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"KeySigningKeyWithActiveStatusNotFound"
_LastVPCAssociation :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_LastVPCAssociation :: forall a. AsError a => Fold a ServiceError
_LastVPCAssociation =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"LastVPCAssociation"
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
_LimitsExceeded :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_LimitsExceeded :: forall a. AsError a => Fold a ServiceError
_LimitsExceeded =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"LimitsExceeded"
_NoSuchChange :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchChange :: forall a. AsError a => Fold a ServiceError
_NoSuchChange =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"NoSuchChange"
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
404
_NoSuchCidrCollectionException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchCidrCollectionException :: forall a. AsError a => Fold a ServiceError
_NoSuchCidrCollectionException =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"NoSuchCidrCollectionException"
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
404
_NoSuchCidrLocationException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchCidrLocationException :: forall a. AsError a => Fold a ServiceError
_NoSuchCidrLocationException =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"NoSuchCidrLocationException"
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
404
_NoSuchCloudWatchLogsLogGroup :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchCloudWatchLogsLogGroup :: forall a. AsError a => Fold a ServiceError
_NoSuchCloudWatchLogsLogGroup =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"NoSuchCloudWatchLogsLogGroup"
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
404
_NoSuchDelegationSet :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchDelegationSet :: forall a. AsError a => Fold a ServiceError
_NoSuchDelegationSet =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"NoSuchDelegationSet"
_NoSuchGeoLocation :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchGeoLocation :: forall a. AsError a => Fold a ServiceError
_NoSuchGeoLocation =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"NoSuchGeoLocation"
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
404
_NoSuchHealthCheck :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchHealthCheck :: forall a. AsError a => Fold a ServiceError
_NoSuchHealthCheck =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"NoSuchHealthCheck"
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
404
_NoSuchHostedZone :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchHostedZone :: forall a. AsError a => Fold a ServiceError
_NoSuchHostedZone =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"NoSuchHostedZone"
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
404
_NoSuchKeySigningKey :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchKeySigningKey :: forall a. AsError a => Fold a ServiceError
_NoSuchKeySigningKey =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"NoSuchKeySigningKey"
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
404
_NoSuchQueryLoggingConfig :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchQueryLoggingConfig :: forall a. AsError a => Fold a ServiceError
_NoSuchQueryLoggingConfig =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"NoSuchQueryLoggingConfig"
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
404
_NoSuchTrafficPolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchTrafficPolicy :: forall a. AsError a => Fold a ServiceError
_NoSuchTrafficPolicy =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"NoSuchTrafficPolicy"
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
404
_NoSuchTrafficPolicyInstance :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchTrafficPolicyInstance :: forall a. AsError a => Fold a ServiceError
_NoSuchTrafficPolicyInstance =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"NoSuchTrafficPolicyInstance"
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
404
_NotAuthorizedException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NotAuthorizedException :: forall a. AsError a => Fold a ServiceError
_NotAuthorizedException =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"NotAuthorizedException"
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
401
_PriorRequestNotComplete :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_PriorRequestNotComplete :: forall a. AsError a => Fold a ServiceError
_PriorRequestNotComplete =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"PriorRequestNotComplete"
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
_PublicZoneVPCAssociation :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_PublicZoneVPCAssociation :: forall a. AsError a => Fold a ServiceError
_PublicZoneVPCAssociation =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"PublicZoneVPCAssociation"
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
_QueryLoggingConfigAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_QueryLoggingConfigAlreadyExists :: forall a. AsError a => Fold a ServiceError
_QueryLoggingConfigAlreadyExists =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"QueryLoggingConfigAlreadyExists"
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
409
_ThrottlingException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ThrottlingException :: forall a. AsError a => Fold a ServiceError
_ThrottlingException =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
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
_TooManyHealthChecks :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyHealthChecks :: forall a. AsError a => Fold a ServiceError
_TooManyHealthChecks =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"TooManyHealthChecks"
_TooManyHostedZones :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyHostedZones :: forall a. AsError a => Fold a ServiceError
_TooManyHostedZones =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"TooManyHostedZones"
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
_TooManyKeySigningKeys :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyKeySigningKeys :: forall a. AsError a => Fold a ServiceError
_TooManyKeySigningKeys =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"TooManyKeySigningKeys"
_TooManyTrafficPolicies :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyTrafficPolicies :: forall a. AsError a => Fold a ServiceError
_TooManyTrafficPolicies =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"TooManyTrafficPolicies"
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
_TooManyTrafficPolicyInstances :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyTrafficPolicyInstances :: forall a. AsError a => Fold a ServiceError
_TooManyTrafficPolicyInstances =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"TooManyTrafficPolicyInstances"
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
_TooManyTrafficPolicyVersionsForCurrentPolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyTrafficPolicyVersionsForCurrentPolicy :: forall a. AsError a => Fold a ServiceError
_TooManyTrafficPolicyVersionsForCurrentPolicy =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"TooManyTrafficPolicyVersionsForCurrentPolicy"
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
_TooManyVPCAssociationAuthorizations :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyVPCAssociationAuthorizations :: forall a. AsError a => Fold a ServiceError
_TooManyVPCAssociationAuthorizations =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"TooManyVPCAssociationAuthorizations"
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
_TrafficPolicyAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TrafficPolicyAlreadyExists :: forall a. AsError a => Fold a ServiceError
_TrafficPolicyAlreadyExists =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"TrafficPolicyAlreadyExists"
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
409
_TrafficPolicyInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TrafficPolicyInUse :: forall a. AsError a => Fold a ServiceError
_TrafficPolicyInUse =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"TrafficPolicyInUse"
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
_TrafficPolicyInstanceAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TrafficPolicyInstanceAlreadyExists :: forall a. AsError a => Fold a ServiceError
_TrafficPolicyInstanceAlreadyExists =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"TrafficPolicyInstanceAlreadyExists"
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
409
_VPCAssociationAuthorizationNotFound :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_VPCAssociationAuthorizationNotFound :: forall a. AsError a => Fold a ServiceError
_VPCAssociationAuthorizationNotFound =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"VPCAssociationAuthorizationNotFound"
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
404
_VPCAssociationNotFound :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_VPCAssociationNotFound :: forall a. AsError a => Fold a ServiceError
_VPCAssociationNotFound =
forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
Service
defaultService
ErrorCode
"VPCAssociationNotFound"
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
404