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

    -- * Errors
    _AccessDenied,
    _BatchTooLarge,
    _CNAMEAlreadyExists,
    _CachePolicyAlreadyExists,
    _CachePolicyInUse,
    _CannotChangeImmutablePublicKeyFields,
    _CloudFrontOriginAccessIdentityAlreadyExists,
    _CloudFrontOriginAccessIdentityInUse,
    _ContinuousDeploymentPolicyAlreadyExists,
    _ContinuousDeploymentPolicyInUse,
    _DistributionAlreadyExists,
    _DistributionNotDisabled,
    _FieldLevelEncryptionConfigAlreadyExists,
    _FieldLevelEncryptionConfigInUse,
    _FieldLevelEncryptionProfileAlreadyExists,
    _FieldLevelEncryptionProfileInUse,
    _FieldLevelEncryptionProfileSizeExceeded,
    _FunctionAlreadyExists,
    _FunctionInUse,
    _FunctionSizeLimitExceeded,
    _IllegalDelete,
    _IllegalFieldLevelEncryptionConfigAssociationWithCacheBehavior,
    _IllegalOriginAccessConfiguration,
    _IllegalUpdate,
    _InconsistentQuantities,
    _InvalidArgument,
    _InvalidDefaultRootObject,
    _InvalidDomainNameForOriginAccessControl,
    _InvalidErrorCode,
    _InvalidForwardCookies,
    _InvalidFunctionAssociation,
    _InvalidGeoRestrictionParameter,
    _InvalidHeadersForS3Origin,
    _InvalidIfMatchVersion,
    _InvalidLambdaFunctionAssociation,
    _InvalidLocationCode,
    _InvalidMinimumProtocolVersion,
    _InvalidOrigin,
    _InvalidOriginAccessControl,
    _InvalidOriginAccessIdentity,
    _InvalidOriginKeepaliveTimeout,
    _InvalidOriginReadTimeout,
    _InvalidProtocolSettings,
    _InvalidQueryStringParameters,
    _InvalidRelativePath,
    _InvalidRequiredProtocol,
    _InvalidResponseCode,
    _InvalidTTLOrder,
    _InvalidTagging,
    _InvalidViewerCertificate,
    _InvalidWebACLId,
    _KeyGroupAlreadyExists,
    _MissingBody,
    _MonitoringSubscriptionAlreadyExists,
    _NoSuchCachePolicy,
    _NoSuchCloudFrontOriginAccessIdentity,
    _NoSuchContinuousDeploymentPolicy,
    _NoSuchDistribution,
    _NoSuchFieldLevelEncryptionConfig,
    _NoSuchFieldLevelEncryptionProfile,
    _NoSuchFunctionExists,
    _NoSuchInvalidation,
    _NoSuchMonitoringSubscription,
    _NoSuchOrigin,
    _NoSuchOriginAccessControl,
    _NoSuchOriginRequestPolicy,
    _NoSuchPublicKey,
    _NoSuchRealtimeLogConfig,
    _NoSuchResource,
    _NoSuchResponseHeadersPolicy,
    _NoSuchStreamingDistribution,
    _OriginAccessControlAlreadyExists,
    _OriginAccessControlInUse,
    _OriginRequestPolicyAlreadyExists,
    _OriginRequestPolicyInUse,
    _PreconditionFailed,
    _PublicKeyAlreadyExists,
    _PublicKeyInUse,
    _QueryArgProfileEmpty,
    _RealtimeLogConfigAlreadyExists,
    _RealtimeLogConfigInUse,
    _RealtimeLogConfigOwnerMismatch,
    _ResourceInUse,
    _ResponseHeadersPolicyAlreadyExists,
    _ResponseHeadersPolicyInUse,
    _StagingDistributionInUse,
    _StreamingDistributionAlreadyExists,
    _StreamingDistributionNotDisabled,
    _TestFunctionFailed,
    _TooLongCSPInResponseHeadersPolicy,
    _TooManyCacheBehaviors,
    _TooManyCachePolicies,
    _TooManyCertificates,
    _TooManyCloudFrontOriginAccessIdentities,
    _TooManyContinuousDeploymentPolicies,
    _TooManyCookieNamesInWhiteList,
    _TooManyCookiesInCachePolicy,
    _TooManyCookiesInOriginRequestPolicy,
    _TooManyCustomHeadersInResponseHeadersPolicy,
    _TooManyDistributionCNAMEs,
    _TooManyDistributions,
    _TooManyDistributionsAssociatedToCachePolicy,
    _TooManyDistributionsAssociatedToFieldLevelEncryptionConfig,
    _TooManyDistributionsAssociatedToKeyGroup,
    _TooManyDistributionsAssociatedToOriginAccessControl,
    _TooManyDistributionsAssociatedToOriginRequestPolicy,
    _TooManyDistributionsAssociatedToResponseHeadersPolicy,
    _TooManyDistributionsWithFunctionAssociations,
    _TooManyDistributionsWithLambdaAssociations,
    _TooManyDistributionsWithSingleFunctionARN,
    _TooManyFieldLevelEncryptionConfigs,
    _TooManyFieldLevelEncryptionContentTypeProfiles,
    _TooManyFieldLevelEncryptionEncryptionEntities,
    _TooManyFieldLevelEncryptionFieldPatterns,
    _TooManyFieldLevelEncryptionProfiles,
    _TooManyFieldLevelEncryptionQueryArgProfiles,
    _TooManyFunctionAssociations,
    _TooManyFunctions,
    _TooManyHeadersInCachePolicy,
    _TooManyHeadersInForwardedValues,
    _TooManyHeadersInOriginRequestPolicy,
    _TooManyInvalidationsInProgress,
    _TooManyKeyGroups,
    _TooManyKeyGroupsAssociatedToDistribution,
    _TooManyLambdaFunctionAssociations,
    _TooManyOriginAccessControls,
    _TooManyOriginCustomHeaders,
    _TooManyOriginGroupsPerDistribution,
    _TooManyOriginRequestPolicies,
    _TooManyOrigins,
    _TooManyPublicKeys,
    _TooManyPublicKeysInKeyGroup,
    _TooManyQueryStringParameters,
    _TooManyQueryStringsInCachePolicy,
    _TooManyQueryStringsInOriginRequestPolicy,
    _TooManyRealtimeLogConfigs,
    _TooManyRemoveHeadersInResponseHeadersPolicy,
    _TooManyResponseHeadersPolicies,
    _TooManyStreamingDistributionCNAMEs,
    _TooManyStreamingDistributions,
    _TooManyTrustedSigners,
    _TrustedKeyGroupDoesNotExist,
    _TrustedSignerDoesNotExist,
    _UnsupportedOperation,

    -- * CachePolicyCookieBehavior
    CachePolicyCookieBehavior (..),

    -- * CachePolicyHeaderBehavior
    CachePolicyHeaderBehavior (..),

    -- * CachePolicyQueryStringBehavior
    CachePolicyQueryStringBehavior (..),

    -- * CachePolicyType
    CachePolicyType (..),

    -- * CertificateSource
    CertificateSource (..),

    -- * ContinuousDeploymentPolicyType
    ContinuousDeploymentPolicyType (..),

    -- * EventType
    EventType (..),

    -- * Format
    Format (..),

    -- * FrameOptionsList
    FrameOptionsList (..),

    -- * FunctionRuntime
    FunctionRuntime (..),

    -- * FunctionStage
    FunctionStage (..),

    -- * GeoRestrictionType
    GeoRestrictionType (..),

    -- * HttpVersion
    HttpVersion (..),

    -- * ICPRecordalStatus
    ICPRecordalStatus (..),

    -- * ItemSelection
    ItemSelection (..),

    -- * Method
    Method (..),

    -- * MinimumProtocolVersion
    MinimumProtocolVersion (..),

    -- * OriginAccessControlOriginTypes
    OriginAccessControlOriginTypes (..),

    -- * OriginAccessControlSigningBehaviors
    OriginAccessControlSigningBehaviors (..),

    -- * OriginAccessControlSigningProtocols
    OriginAccessControlSigningProtocols (..),

    -- * OriginProtocolPolicy
    OriginProtocolPolicy (..),

    -- * OriginRequestPolicyCookieBehavior
    OriginRequestPolicyCookieBehavior (..),

    -- * OriginRequestPolicyHeaderBehavior
    OriginRequestPolicyHeaderBehavior (..),

    -- * OriginRequestPolicyQueryStringBehavior
    OriginRequestPolicyQueryStringBehavior (..),

    -- * OriginRequestPolicyType
    OriginRequestPolicyType (..),

    -- * PriceClass
    PriceClass (..),

    -- * RealtimeMetricsSubscriptionStatus
    RealtimeMetricsSubscriptionStatus (..),

    -- * ReferrerPolicyList
    ReferrerPolicyList (..),

    -- * ResponseHeadersPolicyAccessControlAllowMethodsValues
    ResponseHeadersPolicyAccessControlAllowMethodsValues (..),

    -- * ResponseHeadersPolicyType
    ResponseHeadersPolicyType (..),

    -- * SSLSupportMethod
    SSLSupportMethod (..),

    -- * SslProtocol
    SslProtocol (..),

    -- * ViewerProtocolPolicy
    ViewerProtocolPolicy (..),

    -- * ActiveTrustedKeyGroups
    ActiveTrustedKeyGroups (..),
    newActiveTrustedKeyGroups,
    activeTrustedKeyGroups_items,
    activeTrustedKeyGroups_enabled,
    activeTrustedKeyGroups_quantity,

    -- * ActiveTrustedSigners
    ActiveTrustedSigners (..),
    newActiveTrustedSigners,
    activeTrustedSigners_items,
    activeTrustedSigners_enabled,
    activeTrustedSigners_quantity,

    -- * AliasICPRecordal
    AliasICPRecordal (..),
    newAliasICPRecordal,
    aliasICPRecordal_cname,
    aliasICPRecordal_iCPRecordalStatus,

    -- * Aliases
    Aliases (..),
    newAliases,
    aliases_items,
    aliases_quantity,

    -- * AllowedMethods
    AllowedMethods (..),
    newAllowedMethods,
    allowedMethods_cachedMethods,
    allowedMethods_quantity,
    allowedMethods_items,

    -- * CacheBehavior
    CacheBehavior (..),
    newCacheBehavior,
    cacheBehavior_allowedMethods,
    cacheBehavior_cachePolicyId,
    cacheBehavior_compress,
    cacheBehavior_defaultTTL,
    cacheBehavior_fieldLevelEncryptionId,
    cacheBehavior_forwardedValues,
    cacheBehavior_functionAssociations,
    cacheBehavior_lambdaFunctionAssociations,
    cacheBehavior_maxTTL,
    cacheBehavior_minTTL,
    cacheBehavior_originRequestPolicyId,
    cacheBehavior_realtimeLogConfigArn,
    cacheBehavior_responseHeadersPolicyId,
    cacheBehavior_smoothStreaming,
    cacheBehavior_trustedKeyGroups,
    cacheBehavior_trustedSigners,
    cacheBehavior_pathPattern,
    cacheBehavior_targetOriginId,
    cacheBehavior_viewerProtocolPolicy,

    -- * CacheBehaviors
    CacheBehaviors (..),
    newCacheBehaviors,
    cacheBehaviors_items,
    cacheBehaviors_quantity,

    -- * CachePolicy
    CachePolicy (..),
    newCachePolicy,
    cachePolicy_id,
    cachePolicy_lastModifiedTime,
    cachePolicy_cachePolicyConfig,

    -- * CachePolicyConfig
    CachePolicyConfig (..),
    newCachePolicyConfig,
    cachePolicyConfig_comment,
    cachePolicyConfig_defaultTTL,
    cachePolicyConfig_maxTTL,
    cachePolicyConfig_parametersInCacheKeyAndForwardedToOrigin,
    cachePolicyConfig_name,
    cachePolicyConfig_minTTL,

    -- * CachePolicyCookiesConfig
    CachePolicyCookiesConfig (..),
    newCachePolicyCookiesConfig,
    cachePolicyCookiesConfig_cookies,
    cachePolicyCookiesConfig_cookieBehavior,

    -- * CachePolicyHeadersConfig
    CachePolicyHeadersConfig (..),
    newCachePolicyHeadersConfig,
    cachePolicyHeadersConfig_headers,
    cachePolicyHeadersConfig_headerBehavior,

    -- * CachePolicyList
    CachePolicyList (..),
    newCachePolicyList,
    cachePolicyList_items,
    cachePolicyList_nextMarker,
    cachePolicyList_maxItems,
    cachePolicyList_quantity,

    -- * CachePolicyQueryStringsConfig
    CachePolicyQueryStringsConfig (..),
    newCachePolicyQueryStringsConfig,
    cachePolicyQueryStringsConfig_queryStrings,
    cachePolicyQueryStringsConfig_queryStringBehavior,

    -- * CachePolicySummary
    CachePolicySummary (..),
    newCachePolicySummary,
    cachePolicySummary_type,
    cachePolicySummary_cachePolicy,

    -- * CachedMethods
    CachedMethods (..),
    newCachedMethods,
    cachedMethods_quantity,
    cachedMethods_items,

    -- * CloudFrontOriginAccessIdentity
    CloudFrontOriginAccessIdentity (..),
    newCloudFrontOriginAccessIdentity,
    cloudFrontOriginAccessIdentity_cloudFrontOriginAccessIdentityConfig,
    cloudFrontOriginAccessIdentity_id,
    cloudFrontOriginAccessIdentity_s3CanonicalUserId,

    -- * CloudFrontOriginAccessIdentityConfig
    CloudFrontOriginAccessIdentityConfig (..),
    newCloudFrontOriginAccessIdentityConfig,
    cloudFrontOriginAccessIdentityConfig_callerReference,
    cloudFrontOriginAccessIdentityConfig_comment,

    -- * CloudFrontOriginAccessIdentityList
    CloudFrontOriginAccessIdentityList (..),
    newCloudFrontOriginAccessIdentityList,
    cloudFrontOriginAccessIdentityList_items,
    cloudFrontOriginAccessIdentityList_nextMarker,
    cloudFrontOriginAccessIdentityList_marker,
    cloudFrontOriginAccessIdentityList_maxItems,
    cloudFrontOriginAccessIdentityList_isTruncated,
    cloudFrontOriginAccessIdentityList_quantity,

    -- * CloudFrontOriginAccessIdentitySummary
    CloudFrontOriginAccessIdentitySummary (..),
    newCloudFrontOriginAccessIdentitySummary,
    cloudFrontOriginAccessIdentitySummary_id,
    cloudFrontOriginAccessIdentitySummary_s3CanonicalUserId,
    cloudFrontOriginAccessIdentitySummary_comment,

    -- * ConflictingAlias
    ConflictingAlias (..),
    newConflictingAlias,
    conflictingAlias_accountId,
    conflictingAlias_alias,
    conflictingAlias_distributionId,

    -- * ConflictingAliasesList
    ConflictingAliasesList (..),
    newConflictingAliasesList,
    conflictingAliasesList_items,
    conflictingAliasesList_maxItems,
    conflictingAliasesList_nextMarker,
    conflictingAliasesList_quantity,

    -- * ContentTypeProfile
    ContentTypeProfile (..),
    newContentTypeProfile,
    contentTypeProfile_profileId,
    contentTypeProfile_format,
    contentTypeProfile_contentType,

    -- * ContentTypeProfileConfig
    ContentTypeProfileConfig (..),
    newContentTypeProfileConfig,
    contentTypeProfileConfig_contentTypeProfiles,
    contentTypeProfileConfig_forwardWhenContentTypeIsUnknown,

    -- * ContentTypeProfiles
    ContentTypeProfiles (..),
    newContentTypeProfiles,
    contentTypeProfiles_items,
    contentTypeProfiles_quantity,

    -- * ContinuousDeploymentPolicy
    ContinuousDeploymentPolicy (..),
    newContinuousDeploymentPolicy,
    continuousDeploymentPolicy_id,
    continuousDeploymentPolicy_lastModifiedTime,
    continuousDeploymentPolicy_continuousDeploymentPolicyConfig,

    -- * ContinuousDeploymentPolicyConfig
    ContinuousDeploymentPolicyConfig (..),
    newContinuousDeploymentPolicyConfig,
    continuousDeploymentPolicyConfig_trafficConfig,
    continuousDeploymentPolicyConfig_stagingDistributionDnsNames,
    continuousDeploymentPolicyConfig_enabled,

    -- * ContinuousDeploymentPolicyList
    ContinuousDeploymentPolicyList (..),
    newContinuousDeploymentPolicyList,
    continuousDeploymentPolicyList_items,
    continuousDeploymentPolicyList_nextMarker,
    continuousDeploymentPolicyList_maxItems,
    continuousDeploymentPolicyList_quantity,

    -- * ContinuousDeploymentPolicySummary
    ContinuousDeploymentPolicySummary (..),
    newContinuousDeploymentPolicySummary,
    continuousDeploymentPolicySummary_continuousDeploymentPolicy,

    -- * ContinuousDeploymentSingleHeaderConfig
    ContinuousDeploymentSingleHeaderConfig (..),
    newContinuousDeploymentSingleHeaderConfig,
    continuousDeploymentSingleHeaderConfig_header,
    continuousDeploymentSingleHeaderConfig_value,

    -- * ContinuousDeploymentSingleWeightConfig
    ContinuousDeploymentSingleWeightConfig (..),
    newContinuousDeploymentSingleWeightConfig,
    continuousDeploymentSingleWeightConfig_sessionStickinessConfig,
    continuousDeploymentSingleWeightConfig_weight,

    -- * CookieNames
    CookieNames (..),
    newCookieNames,
    cookieNames_items,
    cookieNames_quantity,

    -- * CookiePreference
    CookiePreference (..),
    newCookiePreference,
    cookiePreference_whitelistedNames,
    cookiePreference_forward,

    -- * CustomErrorResponse
    CustomErrorResponse (..),
    newCustomErrorResponse,
    customErrorResponse_errorCachingMinTTL,
    customErrorResponse_responseCode,
    customErrorResponse_responsePagePath,
    customErrorResponse_errorCode,

    -- * CustomErrorResponses
    CustomErrorResponses (..),
    newCustomErrorResponses,
    customErrorResponses_items,
    customErrorResponses_quantity,

    -- * CustomHeaders
    CustomHeaders (..),
    newCustomHeaders,
    customHeaders_items,
    customHeaders_quantity,

    -- * CustomOriginConfig
    CustomOriginConfig (..),
    newCustomOriginConfig,
    customOriginConfig_originKeepaliveTimeout,
    customOriginConfig_originReadTimeout,
    customOriginConfig_originSslProtocols,
    customOriginConfig_hTTPPort,
    customOriginConfig_hTTPSPort,
    customOriginConfig_originProtocolPolicy,

    -- * DefaultCacheBehavior
    DefaultCacheBehavior (..),
    newDefaultCacheBehavior,
    defaultCacheBehavior_allowedMethods,
    defaultCacheBehavior_cachePolicyId,
    defaultCacheBehavior_compress,
    defaultCacheBehavior_defaultTTL,
    defaultCacheBehavior_fieldLevelEncryptionId,
    defaultCacheBehavior_forwardedValues,
    defaultCacheBehavior_functionAssociations,
    defaultCacheBehavior_lambdaFunctionAssociations,
    defaultCacheBehavior_maxTTL,
    defaultCacheBehavior_minTTL,
    defaultCacheBehavior_originRequestPolicyId,
    defaultCacheBehavior_realtimeLogConfigArn,
    defaultCacheBehavior_responseHeadersPolicyId,
    defaultCacheBehavior_smoothStreaming,
    defaultCacheBehavior_trustedKeyGroups,
    defaultCacheBehavior_trustedSigners,
    defaultCacheBehavior_targetOriginId,
    defaultCacheBehavior_viewerProtocolPolicy,

    -- * Distribution
    Distribution (..),
    newDistribution,
    distribution_activeTrustedKeyGroups,
    distribution_activeTrustedSigners,
    distribution_aliasICPRecordals,
    distribution_id,
    distribution_arn,
    distribution_status,
    distribution_lastModifiedTime,
    distribution_inProgressInvalidationBatches,
    distribution_domainName,
    distribution_distributionConfig,

    -- * DistributionConfig
    DistributionConfig (..),
    newDistributionConfig,
    distributionConfig_aliases,
    distributionConfig_cacheBehaviors,
    distributionConfig_continuousDeploymentPolicyId,
    distributionConfig_customErrorResponses,
    distributionConfig_defaultRootObject,
    distributionConfig_httpVersion,
    distributionConfig_isIPV6Enabled,
    distributionConfig_logging,
    distributionConfig_originGroups,
    distributionConfig_priceClass,
    distributionConfig_restrictions,
    distributionConfig_staging,
    distributionConfig_viewerCertificate,
    distributionConfig_webACLId,
    distributionConfig_callerReference,
    distributionConfig_origins,
    distributionConfig_defaultCacheBehavior,
    distributionConfig_comment,
    distributionConfig_enabled,

    -- * DistributionConfigWithTags
    DistributionConfigWithTags (..),
    newDistributionConfigWithTags,
    distributionConfigWithTags_distributionConfig,
    distributionConfigWithTags_tags,

    -- * DistributionIdList
    DistributionIdList (..),
    newDistributionIdList,
    distributionIdList_items,
    distributionIdList_nextMarker,
    distributionIdList_marker,
    distributionIdList_maxItems,
    distributionIdList_isTruncated,
    distributionIdList_quantity,

    -- * DistributionList
    DistributionList (..),
    newDistributionList,
    distributionList_items,
    distributionList_nextMarker,
    distributionList_marker,
    distributionList_maxItems,
    distributionList_isTruncated,
    distributionList_quantity,

    -- * DistributionSummary
    DistributionSummary (..),
    newDistributionSummary,
    distributionSummary_aliasICPRecordals,
    distributionSummary_originGroups,
    distributionSummary_id,
    distributionSummary_arn,
    distributionSummary_status,
    distributionSummary_lastModifiedTime,
    distributionSummary_domainName,
    distributionSummary_aliases,
    distributionSummary_origins,
    distributionSummary_defaultCacheBehavior,
    distributionSummary_cacheBehaviors,
    distributionSummary_customErrorResponses,
    distributionSummary_comment,
    distributionSummary_priceClass,
    distributionSummary_enabled,
    distributionSummary_viewerCertificate,
    distributionSummary_restrictions,
    distributionSummary_webACLId,
    distributionSummary_httpVersion,
    distributionSummary_isIPV6Enabled,
    distributionSummary_staging,

    -- * EncryptionEntities
    EncryptionEntities (..),
    newEncryptionEntities,
    encryptionEntities_items,
    encryptionEntities_quantity,

    -- * EncryptionEntity
    EncryptionEntity (..),
    newEncryptionEntity,
    encryptionEntity_publicKeyId,
    encryptionEntity_providerId,
    encryptionEntity_fieldPatterns,

    -- * EndPoint
    EndPoint (..),
    newEndPoint,
    endPoint_kinesisStreamConfig,
    endPoint_streamType,

    -- * FieldLevelEncryption
    FieldLevelEncryption (..),
    newFieldLevelEncryption,
    fieldLevelEncryption_id,
    fieldLevelEncryption_lastModifiedTime,
    fieldLevelEncryption_fieldLevelEncryptionConfig,

    -- * FieldLevelEncryptionConfig
    FieldLevelEncryptionConfig (..),
    newFieldLevelEncryptionConfig,
    fieldLevelEncryptionConfig_comment,
    fieldLevelEncryptionConfig_contentTypeProfileConfig,
    fieldLevelEncryptionConfig_queryArgProfileConfig,
    fieldLevelEncryptionConfig_callerReference,

    -- * FieldLevelEncryptionList
    FieldLevelEncryptionList (..),
    newFieldLevelEncryptionList,
    fieldLevelEncryptionList_items,
    fieldLevelEncryptionList_nextMarker,
    fieldLevelEncryptionList_maxItems,
    fieldLevelEncryptionList_quantity,

    -- * FieldLevelEncryptionProfile
    FieldLevelEncryptionProfile (..),
    newFieldLevelEncryptionProfile,
    fieldLevelEncryptionProfile_id,
    fieldLevelEncryptionProfile_lastModifiedTime,
    fieldLevelEncryptionProfile_fieldLevelEncryptionProfileConfig,

    -- * FieldLevelEncryptionProfileConfig
    FieldLevelEncryptionProfileConfig (..),
    newFieldLevelEncryptionProfileConfig,
    fieldLevelEncryptionProfileConfig_comment,
    fieldLevelEncryptionProfileConfig_name,
    fieldLevelEncryptionProfileConfig_callerReference,
    fieldLevelEncryptionProfileConfig_encryptionEntities,

    -- * FieldLevelEncryptionProfileList
    FieldLevelEncryptionProfileList (..),
    newFieldLevelEncryptionProfileList,
    fieldLevelEncryptionProfileList_items,
    fieldLevelEncryptionProfileList_nextMarker,
    fieldLevelEncryptionProfileList_maxItems,
    fieldLevelEncryptionProfileList_quantity,

    -- * FieldLevelEncryptionProfileSummary
    FieldLevelEncryptionProfileSummary (..),
    newFieldLevelEncryptionProfileSummary,
    fieldLevelEncryptionProfileSummary_comment,
    fieldLevelEncryptionProfileSummary_id,
    fieldLevelEncryptionProfileSummary_lastModifiedTime,
    fieldLevelEncryptionProfileSummary_name,
    fieldLevelEncryptionProfileSummary_encryptionEntities,

    -- * FieldLevelEncryptionSummary
    FieldLevelEncryptionSummary (..),
    newFieldLevelEncryptionSummary,
    fieldLevelEncryptionSummary_comment,
    fieldLevelEncryptionSummary_contentTypeProfileConfig,
    fieldLevelEncryptionSummary_queryArgProfileConfig,
    fieldLevelEncryptionSummary_id,
    fieldLevelEncryptionSummary_lastModifiedTime,

    -- * FieldPatterns
    FieldPatterns (..),
    newFieldPatterns,
    fieldPatterns_items,
    fieldPatterns_quantity,

    -- * ForwardedValues
    ForwardedValues (..),
    newForwardedValues,
    forwardedValues_headers,
    forwardedValues_queryStringCacheKeys,
    forwardedValues_queryString,
    forwardedValues_cookies,

    -- * FunctionAssociation
    FunctionAssociation (..),
    newFunctionAssociation,
    functionAssociation_functionARN,
    functionAssociation_eventType,

    -- * FunctionAssociations
    FunctionAssociations (..),
    newFunctionAssociations,
    functionAssociations_items,
    functionAssociations_quantity,

    -- * FunctionConfig
    FunctionConfig (..),
    newFunctionConfig,
    functionConfig_comment,
    functionConfig_runtime,

    -- * FunctionList
    FunctionList (..),
    newFunctionList,
    functionList_items,
    functionList_nextMarker,
    functionList_maxItems,
    functionList_quantity,

    -- * FunctionMetadata
    FunctionMetadata (..),
    newFunctionMetadata,
    functionMetadata_createdTime,
    functionMetadata_stage,
    functionMetadata_functionARN,
    functionMetadata_lastModifiedTime,

    -- * FunctionSummary
    FunctionSummary (..),
    newFunctionSummary,
    functionSummary_status,
    functionSummary_name,
    functionSummary_functionConfig,
    functionSummary_functionMetadata,

    -- * GeoRestriction
    GeoRestriction (..),
    newGeoRestriction,
    geoRestriction_items,
    geoRestriction_restrictionType,
    geoRestriction_quantity,

    -- * Headers
    Headers (..),
    newHeaders,
    headers_items,
    headers_quantity,

    -- * Invalidation
    Invalidation (..),
    newInvalidation,
    invalidation_id,
    invalidation_status,
    invalidation_createTime,
    invalidation_invalidationBatch,

    -- * InvalidationBatch
    InvalidationBatch (..),
    newInvalidationBatch,
    invalidationBatch_paths,
    invalidationBatch_callerReference,

    -- * InvalidationList
    InvalidationList (..),
    newInvalidationList,
    invalidationList_items,
    invalidationList_nextMarker,
    invalidationList_marker,
    invalidationList_maxItems,
    invalidationList_isTruncated,
    invalidationList_quantity,

    -- * InvalidationSummary
    InvalidationSummary (..),
    newInvalidationSummary,
    invalidationSummary_id,
    invalidationSummary_createTime,
    invalidationSummary_status,

    -- * KGKeyPairIds
    KGKeyPairIds (..),
    newKGKeyPairIds,
    kGKeyPairIds_keyGroupId,
    kGKeyPairIds_keyPairIds,

    -- * KeyGroup
    KeyGroup (..),
    newKeyGroup,
    keyGroup_id,
    keyGroup_lastModifiedTime,
    keyGroup_keyGroupConfig,

    -- * KeyGroupConfig
    KeyGroupConfig (..),
    newKeyGroupConfig,
    keyGroupConfig_comment,
    keyGroupConfig_name,
    keyGroupConfig_items,

    -- * KeyGroupList
    KeyGroupList (..),
    newKeyGroupList,
    keyGroupList_items,
    keyGroupList_nextMarker,
    keyGroupList_maxItems,
    keyGroupList_quantity,

    -- * KeyGroupSummary
    KeyGroupSummary (..),
    newKeyGroupSummary,
    keyGroupSummary_keyGroup,

    -- * KeyPairIds
    KeyPairIds (..),
    newKeyPairIds,
    keyPairIds_items,
    keyPairIds_quantity,

    -- * KinesisStreamConfig
    KinesisStreamConfig (..),
    newKinesisStreamConfig,
    kinesisStreamConfig_roleARN,
    kinesisStreamConfig_streamARN,

    -- * LambdaFunctionAssociation
    LambdaFunctionAssociation (..),
    newLambdaFunctionAssociation,
    lambdaFunctionAssociation_includeBody,
    lambdaFunctionAssociation_lambdaFunctionARN,
    lambdaFunctionAssociation_eventType,

    -- * LambdaFunctionAssociations
    LambdaFunctionAssociations (..),
    newLambdaFunctionAssociations,
    lambdaFunctionAssociations_items,
    lambdaFunctionAssociations_quantity,

    -- * LoggingConfig
    LoggingConfig (..),
    newLoggingConfig,
    loggingConfig_enabled,
    loggingConfig_includeCookies,
    loggingConfig_bucket,
    loggingConfig_prefix,

    -- * MonitoringSubscription
    MonitoringSubscription (..),
    newMonitoringSubscription,
    monitoringSubscription_realtimeMetricsSubscriptionConfig,

    -- * Origin
    Origin (..),
    newOrigin,
    origin_connectionAttempts,
    origin_connectionTimeout,
    origin_customHeaders,
    origin_customOriginConfig,
    origin_originAccessControlId,
    origin_originPath,
    origin_originShield,
    origin_s3OriginConfig,
    origin_id,
    origin_domainName,

    -- * OriginAccessControl
    OriginAccessControl (..),
    newOriginAccessControl,
    originAccessControl_originAccessControlConfig,
    originAccessControl_id,

    -- * OriginAccessControlConfig
    OriginAccessControlConfig (..),
    newOriginAccessControlConfig,
    originAccessControlConfig_description,
    originAccessControlConfig_name,
    originAccessControlConfig_signingProtocol,
    originAccessControlConfig_signingBehavior,
    originAccessControlConfig_originAccessControlOriginType,

    -- * OriginAccessControlList
    OriginAccessControlList (..),
    newOriginAccessControlList,
    originAccessControlList_items,
    originAccessControlList_nextMarker,
    originAccessControlList_marker,
    originAccessControlList_maxItems,
    originAccessControlList_isTruncated,
    originAccessControlList_quantity,

    -- * OriginAccessControlSummary
    OriginAccessControlSummary (..),
    newOriginAccessControlSummary,
    originAccessControlSummary_id,
    originAccessControlSummary_description,
    originAccessControlSummary_name,
    originAccessControlSummary_signingProtocol,
    originAccessControlSummary_signingBehavior,
    originAccessControlSummary_originAccessControlOriginType,

    -- * OriginCustomHeader
    OriginCustomHeader (..),
    newOriginCustomHeader,
    originCustomHeader_headerName,
    originCustomHeader_headerValue,

    -- * OriginGroup
    OriginGroup (..),
    newOriginGroup,
    originGroup_id,
    originGroup_failoverCriteria,
    originGroup_members,

    -- * OriginGroupFailoverCriteria
    OriginGroupFailoverCriteria (..),
    newOriginGroupFailoverCriteria,
    originGroupFailoverCriteria_statusCodes,

    -- * OriginGroupMember
    OriginGroupMember (..),
    newOriginGroupMember,
    originGroupMember_originId,

    -- * OriginGroupMembers
    OriginGroupMembers (..),
    newOriginGroupMembers,
    originGroupMembers_quantity,
    originGroupMembers_items,

    -- * OriginGroups
    OriginGroups (..),
    newOriginGroups,
    originGroups_items,
    originGroups_quantity,

    -- * OriginRequestPolicy
    OriginRequestPolicy (..),
    newOriginRequestPolicy,
    originRequestPolicy_id,
    originRequestPolicy_lastModifiedTime,
    originRequestPolicy_originRequestPolicyConfig,

    -- * OriginRequestPolicyConfig
    OriginRequestPolicyConfig (..),
    newOriginRequestPolicyConfig,
    originRequestPolicyConfig_comment,
    originRequestPolicyConfig_name,
    originRequestPolicyConfig_headersConfig,
    originRequestPolicyConfig_cookiesConfig,
    originRequestPolicyConfig_queryStringsConfig,

    -- * OriginRequestPolicyCookiesConfig
    OriginRequestPolicyCookiesConfig (..),
    newOriginRequestPolicyCookiesConfig,
    originRequestPolicyCookiesConfig_cookies,
    originRequestPolicyCookiesConfig_cookieBehavior,

    -- * OriginRequestPolicyHeadersConfig
    OriginRequestPolicyHeadersConfig (..),
    newOriginRequestPolicyHeadersConfig,
    originRequestPolicyHeadersConfig_headers,
    originRequestPolicyHeadersConfig_headerBehavior,

    -- * OriginRequestPolicyList
    OriginRequestPolicyList (..),
    newOriginRequestPolicyList,
    originRequestPolicyList_items,
    originRequestPolicyList_nextMarker,
    originRequestPolicyList_maxItems,
    originRequestPolicyList_quantity,

    -- * OriginRequestPolicyQueryStringsConfig
    OriginRequestPolicyQueryStringsConfig (..),
    newOriginRequestPolicyQueryStringsConfig,
    originRequestPolicyQueryStringsConfig_queryStrings,
    originRequestPolicyQueryStringsConfig_queryStringBehavior,

    -- * OriginRequestPolicySummary
    OriginRequestPolicySummary (..),
    newOriginRequestPolicySummary,
    originRequestPolicySummary_type,
    originRequestPolicySummary_originRequestPolicy,

    -- * OriginShield
    OriginShield (..),
    newOriginShield,
    originShield_originShieldRegion,
    originShield_enabled,

    -- * OriginSslProtocols
    OriginSslProtocols (..),
    newOriginSslProtocols,
    originSslProtocols_quantity,
    originSslProtocols_items,

    -- * Origins
    Origins (..),
    newOrigins,
    origins_quantity,
    origins_items,

    -- * ParametersInCacheKeyAndForwardedToOrigin
    ParametersInCacheKeyAndForwardedToOrigin (..),
    newParametersInCacheKeyAndForwardedToOrigin,
    parametersInCacheKeyAndForwardedToOrigin_enableAcceptEncodingBrotli,
    parametersInCacheKeyAndForwardedToOrigin_enableAcceptEncodingGzip,
    parametersInCacheKeyAndForwardedToOrigin_headersConfig,
    parametersInCacheKeyAndForwardedToOrigin_cookiesConfig,
    parametersInCacheKeyAndForwardedToOrigin_queryStringsConfig,

    -- * Paths
    Paths (..),
    newPaths,
    paths_items,
    paths_quantity,

    -- * PublicKey
    PublicKey (..),
    newPublicKey,
    publicKey_id,
    publicKey_createdTime,
    publicKey_publicKeyConfig,

    -- * PublicKeyConfig
    PublicKeyConfig (..),
    newPublicKeyConfig,
    publicKeyConfig_comment,
    publicKeyConfig_callerReference,
    publicKeyConfig_name,
    publicKeyConfig_encodedKey,

    -- * PublicKeyList
    PublicKeyList (..),
    newPublicKeyList,
    publicKeyList_items,
    publicKeyList_nextMarker,
    publicKeyList_maxItems,
    publicKeyList_quantity,

    -- * PublicKeySummary
    PublicKeySummary (..),
    newPublicKeySummary,
    publicKeySummary_comment,
    publicKeySummary_id,
    publicKeySummary_name,
    publicKeySummary_createdTime,
    publicKeySummary_encodedKey,

    -- * QueryArgProfile
    QueryArgProfile (..),
    newQueryArgProfile,
    queryArgProfile_queryArg,
    queryArgProfile_profileId,

    -- * QueryArgProfileConfig
    QueryArgProfileConfig (..),
    newQueryArgProfileConfig,
    queryArgProfileConfig_queryArgProfiles,
    queryArgProfileConfig_forwardWhenQueryArgProfileIsUnknown,

    -- * QueryArgProfiles
    QueryArgProfiles (..),
    newQueryArgProfiles,
    queryArgProfiles_items,
    queryArgProfiles_quantity,

    -- * QueryStringCacheKeys
    QueryStringCacheKeys (..),
    newQueryStringCacheKeys,
    queryStringCacheKeys_items,
    queryStringCacheKeys_quantity,

    -- * QueryStringNames
    QueryStringNames (..),
    newQueryStringNames,
    queryStringNames_items,
    queryStringNames_quantity,

    -- * RealtimeLogConfig
    RealtimeLogConfig (..),
    newRealtimeLogConfig,
    realtimeLogConfig_arn,
    realtimeLogConfig_name,
    realtimeLogConfig_samplingRate,
    realtimeLogConfig_endPoints,
    realtimeLogConfig_fields,

    -- * RealtimeLogConfigs
    RealtimeLogConfigs (..),
    newRealtimeLogConfigs,
    realtimeLogConfigs_items,
    realtimeLogConfigs_nextMarker,
    realtimeLogConfigs_maxItems,
    realtimeLogConfigs_isTruncated,
    realtimeLogConfigs_marker,

    -- * RealtimeMetricsSubscriptionConfig
    RealtimeMetricsSubscriptionConfig (..),
    newRealtimeMetricsSubscriptionConfig,
    realtimeMetricsSubscriptionConfig_realtimeMetricsSubscriptionStatus,

    -- * ResponseHeadersPolicy
    ResponseHeadersPolicy (..),
    newResponseHeadersPolicy,
    responseHeadersPolicy_id,
    responseHeadersPolicy_lastModifiedTime,
    responseHeadersPolicy_responseHeadersPolicyConfig,

    -- * ResponseHeadersPolicyAccessControlAllowHeaders
    ResponseHeadersPolicyAccessControlAllowHeaders (..),
    newResponseHeadersPolicyAccessControlAllowHeaders,
    responseHeadersPolicyAccessControlAllowHeaders_quantity,
    responseHeadersPolicyAccessControlAllowHeaders_items,

    -- * ResponseHeadersPolicyAccessControlAllowMethods
    ResponseHeadersPolicyAccessControlAllowMethods (..),
    newResponseHeadersPolicyAccessControlAllowMethods,
    responseHeadersPolicyAccessControlAllowMethods_quantity,
    responseHeadersPolicyAccessControlAllowMethods_items,

    -- * ResponseHeadersPolicyAccessControlAllowOrigins
    ResponseHeadersPolicyAccessControlAllowOrigins (..),
    newResponseHeadersPolicyAccessControlAllowOrigins,
    responseHeadersPolicyAccessControlAllowOrigins_quantity,
    responseHeadersPolicyAccessControlAllowOrigins_items,

    -- * ResponseHeadersPolicyAccessControlExposeHeaders
    ResponseHeadersPolicyAccessControlExposeHeaders (..),
    newResponseHeadersPolicyAccessControlExposeHeaders,
    responseHeadersPolicyAccessControlExposeHeaders_items,
    responseHeadersPolicyAccessControlExposeHeaders_quantity,

    -- * ResponseHeadersPolicyConfig
    ResponseHeadersPolicyConfig (..),
    newResponseHeadersPolicyConfig,
    responseHeadersPolicyConfig_comment,
    responseHeadersPolicyConfig_corsConfig,
    responseHeadersPolicyConfig_customHeadersConfig,
    responseHeadersPolicyConfig_removeHeadersConfig,
    responseHeadersPolicyConfig_securityHeadersConfig,
    responseHeadersPolicyConfig_serverTimingHeadersConfig,
    responseHeadersPolicyConfig_name,

    -- * ResponseHeadersPolicyContentSecurityPolicy
    ResponseHeadersPolicyContentSecurityPolicy (..),
    newResponseHeadersPolicyContentSecurityPolicy,
    responseHeadersPolicyContentSecurityPolicy_override,
    responseHeadersPolicyContentSecurityPolicy_contentSecurityPolicy,

    -- * ResponseHeadersPolicyContentTypeOptions
    ResponseHeadersPolicyContentTypeOptions (..),
    newResponseHeadersPolicyContentTypeOptions,
    responseHeadersPolicyContentTypeOptions_override,

    -- * ResponseHeadersPolicyCorsConfig
    ResponseHeadersPolicyCorsConfig (..),
    newResponseHeadersPolicyCorsConfig,
    responseHeadersPolicyCorsConfig_accessControlExposeHeaders,
    responseHeadersPolicyCorsConfig_accessControlMaxAgeSec,
    responseHeadersPolicyCorsConfig_accessControlAllowOrigins,
    responseHeadersPolicyCorsConfig_accessControlAllowHeaders,
    responseHeadersPolicyCorsConfig_accessControlAllowMethods,
    responseHeadersPolicyCorsConfig_accessControlAllowCredentials,
    responseHeadersPolicyCorsConfig_originOverride,

    -- * ResponseHeadersPolicyCustomHeader
    ResponseHeadersPolicyCustomHeader (..),
    newResponseHeadersPolicyCustomHeader,
    responseHeadersPolicyCustomHeader_header,
    responseHeadersPolicyCustomHeader_value,
    responseHeadersPolicyCustomHeader_override,

    -- * ResponseHeadersPolicyCustomHeadersConfig
    ResponseHeadersPolicyCustomHeadersConfig (..),
    newResponseHeadersPolicyCustomHeadersConfig,
    responseHeadersPolicyCustomHeadersConfig_items,
    responseHeadersPolicyCustomHeadersConfig_quantity,

    -- * ResponseHeadersPolicyFrameOptions
    ResponseHeadersPolicyFrameOptions (..),
    newResponseHeadersPolicyFrameOptions,
    responseHeadersPolicyFrameOptions_override,
    responseHeadersPolicyFrameOptions_frameOption,

    -- * ResponseHeadersPolicyList
    ResponseHeadersPolicyList (..),
    newResponseHeadersPolicyList,
    responseHeadersPolicyList_items,
    responseHeadersPolicyList_nextMarker,
    responseHeadersPolicyList_maxItems,
    responseHeadersPolicyList_quantity,

    -- * ResponseHeadersPolicyReferrerPolicy
    ResponseHeadersPolicyReferrerPolicy (..),
    newResponseHeadersPolicyReferrerPolicy,
    responseHeadersPolicyReferrerPolicy_override,
    responseHeadersPolicyReferrerPolicy_referrerPolicy,

    -- * ResponseHeadersPolicyRemoveHeader
    ResponseHeadersPolicyRemoveHeader (..),
    newResponseHeadersPolicyRemoveHeader,
    responseHeadersPolicyRemoveHeader_header,

    -- * ResponseHeadersPolicyRemoveHeadersConfig
    ResponseHeadersPolicyRemoveHeadersConfig (..),
    newResponseHeadersPolicyRemoveHeadersConfig,
    responseHeadersPolicyRemoveHeadersConfig_items,
    responseHeadersPolicyRemoveHeadersConfig_quantity,

    -- * ResponseHeadersPolicySecurityHeadersConfig
    ResponseHeadersPolicySecurityHeadersConfig (..),
    newResponseHeadersPolicySecurityHeadersConfig,
    responseHeadersPolicySecurityHeadersConfig_contentSecurityPolicy,
    responseHeadersPolicySecurityHeadersConfig_contentTypeOptions,
    responseHeadersPolicySecurityHeadersConfig_frameOptions,
    responseHeadersPolicySecurityHeadersConfig_referrerPolicy,
    responseHeadersPolicySecurityHeadersConfig_strictTransportSecurity,
    responseHeadersPolicySecurityHeadersConfig_xSSProtection,

    -- * ResponseHeadersPolicyServerTimingHeadersConfig
    ResponseHeadersPolicyServerTimingHeadersConfig (..),
    newResponseHeadersPolicyServerTimingHeadersConfig,
    responseHeadersPolicyServerTimingHeadersConfig_samplingRate,
    responseHeadersPolicyServerTimingHeadersConfig_enabled,

    -- * ResponseHeadersPolicyStrictTransportSecurity
    ResponseHeadersPolicyStrictTransportSecurity (..),
    newResponseHeadersPolicyStrictTransportSecurity,
    responseHeadersPolicyStrictTransportSecurity_includeSubdomains,
    responseHeadersPolicyStrictTransportSecurity_preload,
    responseHeadersPolicyStrictTransportSecurity_override,
    responseHeadersPolicyStrictTransportSecurity_accessControlMaxAgeSec,

    -- * ResponseHeadersPolicySummary
    ResponseHeadersPolicySummary (..),
    newResponseHeadersPolicySummary,
    responseHeadersPolicySummary_type,
    responseHeadersPolicySummary_responseHeadersPolicy,

    -- * ResponseHeadersPolicyXSSProtection
    ResponseHeadersPolicyXSSProtection (..),
    newResponseHeadersPolicyXSSProtection,
    responseHeadersPolicyXSSProtection_modeBlock,
    responseHeadersPolicyXSSProtection_reportUri,
    responseHeadersPolicyXSSProtection_override,
    responseHeadersPolicyXSSProtection_protection,

    -- * Restrictions
    Restrictions (..),
    newRestrictions,
    restrictions_geoRestriction,

    -- * S3Origin
    S3Origin (..),
    newS3Origin,
    s3Origin_domainName,
    s3Origin_originAccessIdentity,

    -- * S3OriginConfig
    S3OriginConfig (..),
    newS3OriginConfig,
    s3OriginConfig_originAccessIdentity,

    -- * SessionStickinessConfig
    SessionStickinessConfig (..),
    newSessionStickinessConfig,
    sessionStickinessConfig_idleTTL,
    sessionStickinessConfig_maximumTTL,

    -- * Signer
    Signer (..),
    newSigner,
    signer_awsAccountNumber,
    signer_keyPairIds,

    -- * StagingDistributionDnsNames
    StagingDistributionDnsNames (..),
    newStagingDistributionDnsNames,
    stagingDistributionDnsNames_items,
    stagingDistributionDnsNames_quantity,

    -- * StatusCodes
    StatusCodes (..),
    newStatusCodes,
    statusCodes_quantity,
    statusCodes_items,

    -- * StreamingDistribution
    StreamingDistribution (..),
    newStreamingDistribution,
    streamingDistribution_lastModifiedTime,
    streamingDistribution_id,
    streamingDistribution_arn,
    streamingDistribution_status,
    streamingDistribution_domainName,
    streamingDistribution_activeTrustedSigners,
    streamingDistribution_streamingDistributionConfig,

    -- * StreamingDistributionConfig
    StreamingDistributionConfig (..),
    newStreamingDistributionConfig,
    streamingDistributionConfig_aliases,
    streamingDistributionConfig_logging,
    streamingDistributionConfig_priceClass,
    streamingDistributionConfig_callerReference,
    streamingDistributionConfig_s3Origin,
    streamingDistributionConfig_comment,
    streamingDistributionConfig_trustedSigners,
    streamingDistributionConfig_enabled,

    -- * StreamingDistributionConfigWithTags
    StreamingDistributionConfigWithTags (..),
    newStreamingDistributionConfigWithTags,
    streamingDistributionConfigWithTags_streamingDistributionConfig,
    streamingDistributionConfigWithTags_tags,

    -- * StreamingDistributionList
    StreamingDistributionList (..),
    newStreamingDistributionList,
    streamingDistributionList_items,
    streamingDistributionList_nextMarker,
    streamingDistributionList_marker,
    streamingDistributionList_maxItems,
    streamingDistributionList_isTruncated,
    streamingDistributionList_quantity,

    -- * StreamingDistributionSummary
    StreamingDistributionSummary (..),
    newStreamingDistributionSummary,
    streamingDistributionSummary_id,
    streamingDistributionSummary_arn,
    streamingDistributionSummary_status,
    streamingDistributionSummary_lastModifiedTime,
    streamingDistributionSummary_domainName,
    streamingDistributionSummary_s3Origin,
    streamingDistributionSummary_aliases,
    streamingDistributionSummary_trustedSigners,
    streamingDistributionSummary_comment,
    streamingDistributionSummary_priceClass,
    streamingDistributionSummary_enabled,

    -- * StreamingLoggingConfig
    StreamingLoggingConfig (..),
    newStreamingLoggingConfig,
    streamingLoggingConfig_enabled,
    streamingLoggingConfig_bucket,
    streamingLoggingConfig_prefix,

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

    -- * TagKeys
    TagKeys (..),
    newTagKeys,
    tagKeys_items,

    -- * Tags
    Tags (..),
    newTags,
    tags_items,

    -- * TestResult
    TestResult (..),
    newTestResult,
    testResult_computeUtilization,
    testResult_functionErrorMessage,
    testResult_functionExecutionLogs,
    testResult_functionOutput,
    testResult_functionSummary,

    -- * TrafficConfig
    TrafficConfig (..),
    newTrafficConfig,
    trafficConfig_singleHeaderConfig,
    trafficConfig_singleWeightConfig,
    trafficConfig_type,

    -- * TrustedKeyGroups
    TrustedKeyGroups (..),
    newTrustedKeyGroups,
    trustedKeyGroups_items,
    trustedKeyGroups_enabled,
    trustedKeyGroups_quantity,

    -- * TrustedSigners
    TrustedSigners (..),
    newTrustedSigners,
    trustedSigners_items,
    trustedSigners_enabled,
    trustedSigners_quantity,

    -- * ViewerCertificate
    ViewerCertificate (..),
    newViewerCertificate,
    viewerCertificate_aCMCertificateArn,
    viewerCertificate_certificate,
    viewerCertificate_certificateSource,
    viewerCertificate_cloudFrontDefaultCertificate,
    viewerCertificate_iAMCertificateId,
    viewerCertificate_minimumProtocolVersion,
    viewerCertificate_sSLSupportMethod,
  )
where

import Amazonka.CloudFront.Types.ActiveTrustedKeyGroups
import Amazonka.CloudFront.Types.ActiveTrustedSigners
import Amazonka.CloudFront.Types.AliasICPRecordal
import Amazonka.CloudFront.Types.Aliases
import Amazonka.CloudFront.Types.AllowedMethods
import Amazonka.CloudFront.Types.CacheBehavior
import Amazonka.CloudFront.Types.CacheBehaviors
import Amazonka.CloudFront.Types.CachePolicy
import Amazonka.CloudFront.Types.CachePolicyConfig
import Amazonka.CloudFront.Types.CachePolicyCookieBehavior
import Amazonka.CloudFront.Types.CachePolicyCookiesConfig
import Amazonka.CloudFront.Types.CachePolicyHeaderBehavior
import Amazonka.CloudFront.Types.CachePolicyHeadersConfig
import Amazonka.CloudFront.Types.CachePolicyList
import Amazonka.CloudFront.Types.CachePolicyQueryStringBehavior
import Amazonka.CloudFront.Types.CachePolicyQueryStringsConfig
import Amazonka.CloudFront.Types.CachePolicySummary
import Amazonka.CloudFront.Types.CachePolicyType
import Amazonka.CloudFront.Types.CachedMethods
import Amazonka.CloudFront.Types.CertificateSource
import Amazonka.CloudFront.Types.CloudFrontOriginAccessIdentity
import Amazonka.CloudFront.Types.CloudFrontOriginAccessIdentityConfig
import Amazonka.CloudFront.Types.CloudFrontOriginAccessIdentityList
import Amazonka.CloudFront.Types.CloudFrontOriginAccessIdentitySummary
import Amazonka.CloudFront.Types.ConflictingAlias
import Amazonka.CloudFront.Types.ConflictingAliasesList
import Amazonka.CloudFront.Types.ContentTypeProfile
import Amazonka.CloudFront.Types.ContentTypeProfileConfig
import Amazonka.CloudFront.Types.ContentTypeProfiles
import Amazonka.CloudFront.Types.ContinuousDeploymentPolicy
import Amazonka.CloudFront.Types.ContinuousDeploymentPolicyConfig
import Amazonka.CloudFront.Types.ContinuousDeploymentPolicyList
import Amazonka.CloudFront.Types.ContinuousDeploymentPolicySummary
import Amazonka.CloudFront.Types.ContinuousDeploymentPolicyType
import Amazonka.CloudFront.Types.ContinuousDeploymentSingleHeaderConfig
import Amazonka.CloudFront.Types.ContinuousDeploymentSingleWeightConfig
import Amazonka.CloudFront.Types.CookieNames
import Amazonka.CloudFront.Types.CookiePreference
import Amazonka.CloudFront.Types.CustomErrorResponse
import Amazonka.CloudFront.Types.CustomErrorResponses
import Amazonka.CloudFront.Types.CustomHeaders
import Amazonka.CloudFront.Types.CustomOriginConfig
import Amazonka.CloudFront.Types.DefaultCacheBehavior
import Amazonka.CloudFront.Types.Distribution
import Amazonka.CloudFront.Types.DistributionConfig
import Amazonka.CloudFront.Types.DistributionConfigWithTags
import Amazonka.CloudFront.Types.DistributionIdList
import Amazonka.CloudFront.Types.DistributionList
import Amazonka.CloudFront.Types.DistributionSummary
import Amazonka.CloudFront.Types.EncryptionEntities
import Amazonka.CloudFront.Types.EncryptionEntity
import Amazonka.CloudFront.Types.EndPoint
import Amazonka.CloudFront.Types.EventType
import Amazonka.CloudFront.Types.FieldLevelEncryption
import Amazonka.CloudFront.Types.FieldLevelEncryptionConfig
import Amazonka.CloudFront.Types.FieldLevelEncryptionList
import Amazonka.CloudFront.Types.FieldLevelEncryptionProfile
import Amazonka.CloudFront.Types.FieldLevelEncryptionProfileConfig
import Amazonka.CloudFront.Types.FieldLevelEncryptionProfileList
import Amazonka.CloudFront.Types.FieldLevelEncryptionProfileSummary
import Amazonka.CloudFront.Types.FieldLevelEncryptionSummary
import Amazonka.CloudFront.Types.FieldPatterns
import Amazonka.CloudFront.Types.Format
import Amazonka.CloudFront.Types.ForwardedValues
import Amazonka.CloudFront.Types.FrameOptionsList
import Amazonka.CloudFront.Types.FunctionAssociation
import Amazonka.CloudFront.Types.FunctionAssociations
import Amazonka.CloudFront.Types.FunctionConfig
import Amazonka.CloudFront.Types.FunctionList
import Amazonka.CloudFront.Types.FunctionMetadata
import Amazonka.CloudFront.Types.FunctionRuntime
import Amazonka.CloudFront.Types.FunctionStage
import Amazonka.CloudFront.Types.FunctionSummary
import Amazonka.CloudFront.Types.GeoRestriction
import Amazonka.CloudFront.Types.GeoRestrictionType
import Amazonka.CloudFront.Types.Headers
import Amazonka.CloudFront.Types.HttpVersion
import Amazonka.CloudFront.Types.ICPRecordalStatus
import Amazonka.CloudFront.Types.Invalidation
import Amazonka.CloudFront.Types.InvalidationBatch
import Amazonka.CloudFront.Types.InvalidationList
import Amazonka.CloudFront.Types.InvalidationSummary
import Amazonka.CloudFront.Types.ItemSelection
import Amazonka.CloudFront.Types.KGKeyPairIds
import Amazonka.CloudFront.Types.KeyGroup
import Amazonka.CloudFront.Types.KeyGroupConfig
import Amazonka.CloudFront.Types.KeyGroupList
import Amazonka.CloudFront.Types.KeyGroupSummary
import Amazonka.CloudFront.Types.KeyPairIds
import Amazonka.CloudFront.Types.KinesisStreamConfig
import Amazonka.CloudFront.Types.LambdaFunctionAssociation
import Amazonka.CloudFront.Types.LambdaFunctionAssociations
import Amazonka.CloudFront.Types.LoggingConfig
import Amazonka.CloudFront.Types.Method
import Amazonka.CloudFront.Types.MinimumProtocolVersion
import Amazonka.CloudFront.Types.MonitoringSubscription
import Amazonka.CloudFront.Types.Origin
import Amazonka.CloudFront.Types.OriginAccessControl
import Amazonka.CloudFront.Types.OriginAccessControlConfig
import Amazonka.CloudFront.Types.OriginAccessControlList
import Amazonka.CloudFront.Types.OriginAccessControlOriginTypes
import Amazonka.CloudFront.Types.OriginAccessControlSigningBehaviors
import Amazonka.CloudFront.Types.OriginAccessControlSigningProtocols
import Amazonka.CloudFront.Types.OriginAccessControlSummary
import Amazonka.CloudFront.Types.OriginCustomHeader
import Amazonka.CloudFront.Types.OriginGroup
import Amazonka.CloudFront.Types.OriginGroupFailoverCriteria
import Amazonka.CloudFront.Types.OriginGroupMember
import Amazonka.CloudFront.Types.OriginGroupMembers
import Amazonka.CloudFront.Types.OriginGroups
import Amazonka.CloudFront.Types.OriginProtocolPolicy
import Amazonka.CloudFront.Types.OriginRequestPolicy
import Amazonka.CloudFront.Types.OriginRequestPolicyConfig
import Amazonka.CloudFront.Types.OriginRequestPolicyCookieBehavior
import Amazonka.CloudFront.Types.OriginRequestPolicyCookiesConfig
import Amazonka.CloudFront.Types.OriginRequestPolicyHeaderBehavior
import Amazonka.CloudFront.Types.OriginRequestPolicyHeadersConfig
import Amazonka.CloudFront.Types.OriginRequestPolicyList
import Amazonka.CloudFront.Types.OriginRequestPolicyQueryStringBehavior
import Amazonka.CloudFront.Types.OriginRequestPolicyQueryStringsConfig
import Amazonka.CloudFront.Types.OriginRequestPolicySummary
import Amazonka.CloudFront.Types.OriginRequestPolicyType
import Amazonka.CloudFront.Types.OriginShield
import Amazonka.CloudFront.Types.OriginSslProtocols
import Amazonka.CloudFront.Types.Origins
import Amazonka.CloudFront.Types.ParametersInCacheKeyAndForwardedToOrigin
import Amazonka.CloudFront.Types.Paths
import Amazonka.CloudFront.Types.PriceClass
import Amazonka.CloudFront.Types.PublicKey
import Amazonka.CloudFront.Types.PublicKeyConfig
import Amazonka.CloudFront.Types.PublicKeyList
import Amazonka.CloudFront.Types.PublicKeySummary
import Amazonka.CloudFront.Types.QueryArgProfile
import Amazonka.CloudFront.Types.QueryArgProfileConfig
import Amazonka.CloudFront.Types.QueryArgProfiles
import Amazonka.CloudFront.Types.QueryStringCacheKeys
import Amazonka.CloudFront.Types.QueryStringNames
import Amazonka.CloudFront.Types.RealtimeLogConfig
import Amazonka.CloudFront.Types.RealtimeLogConfigs
import Amazonka.CloudFront.Types.RealtimeMetricsSubscriptionConfig
import Amazonka.CloudFront.Types.RealtimeMetricsSubscriptionStatus
import Amazonka.CloudFront.Types.ReferrerPolicyList
import Amazonka.CloudFront.Types.ResponseHeadersPolicy
import Amazonka.CloudFront.Types.ResponseHeadersPolicyAccessControlAllowHeaders
import Amazonka.CloudFront.Types.ResponseHeadersPolicyAccessControlAllowMethods
import Amazonka.CloudFront.Types.ResponseHeadersPolicyAccessControlAllowMethodsValues
import Amazonka.CloudFront.Types.ResponseHeadersPolicyAccessControlAllowOrigins
import Amazonka.CloudFront.Types.ResponseHeadersPolicyAccessControlExposeHeaders
import Amazonka.CloudFront.Types.ResponseHeadersPolicyConfig
import Amazonka.CloudFront.Types.ResponseHeadersPolicyContentSecurityPolicy
import Amazonka.CloudFront.Types.ResponseHeadersPolicyContentTypeOptions
import Amazonka.CloudFront.Types.ResponseHeadersPolicyCorsConfig
import Amazonka.CloudFront.Types.ResponseHeadersPolicyCustomHeader
import Amazonka.CloudFront.Types.ResponseHeadersPolicyCustomHeadersConfig
import Amazonka.CloudFront.Types.ResponseHeadersPolicyFrameOptions
import Amazonka.CloudFront.Types.ResponseHeadersPolicyList
import Amazonka.CloudFront.Types.ResponseHeadersPolicyReferrerPolicy
import Amazonka.CloudFront.Types.ResponseHeadersPolicyRemoveHeader
import Amazonka.CloudFront.Types.ResponseHeadersPolicyRemoveHeadersConfig
import Amazonka.CloudFront.Types.ResponseHeadersPolicySecurityHeadersConfig
import Amazonka.CloudFront.Types.ResponseHeadersPolicyServerTimingHeadersConfig
import Amazonka.CloudFront.Types.ResponseHeadersPolicyStrictTransportSecurity
import Amazonka.CloudFront.Types.ResponseHeadersPolicySummary
import Amazonka.CloudFront.Types.ResponseHeadersPolicyType
import Amazonka.CloudFront.Types.ResponseHeadersPolicyXSSProtection
import Amazonka.CloudFront.Types.Restrictions
import Amazonka.CloudFront.Types.S3Origin
import Amazonka.CloudFront.Types.S3OriginConfig
import Amazonka.CloudFront.Types.SSLSupportMethod
import Amazonka.CloudFront.Types.SessionStickinessConfig
import Amazonka.CloudFront.Types.Signer
import Amazonka.CloudFront.Types.SslProtocol
import Amazonka.CloudFront.Types.StagingDistributionDnsNames
import Amazonka.CloudFront.Types.StatusCodes
import Amazonka.CloudFront.Types.StreamingDistribution
import Amazonka.CloudFront.Types.StreamingDistributionConfig
import Amazonka.CloudFront.Types.StreamingDistributionConfigWithTags
import Amazonka.CloudFront.Types.StreamingDistributionList
import Amazonka.CloudFront.Types.StreamingDistributionSummary
import Amazonka.CloudFront.Types.StreamingLoggingConfig
import Amazonka.CloudFront.Types.Tag
import Amazonka.CloudFront.Types.TagKeys
import Amazonka.CloudFront.Types.Tags
import Amazonka.CloudFront.Types.TestResult
import Amazonka.CloudFront.Types.TrafficConfig
import Amazonka.CloudFront.Types.TrustedKeyGroups
import Amazonka.CloudFront.Types.TrustedSigners
import Amazonka.CloudFront.Types.ViewerCertificate
import Amazonka.CloudFront.Types.ViewerProtocolPolicy
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Sign.V4 as Sign

-- | API version @2020-05-31@ of the Amazon CloudFront SDK configuration.
defaultService :: Core.Service
defaultService :: Service
defaultService =
  Core.Service
    { $sel:abbrev:Service :: Abbrev
Core.abbrev = Abbrev
"CloudFront",
      $sel:signer:Service :: Signer
Core.signer = Signer
Sign.v4,
      $sel:endpointPrefix:Service :: ByteString
Core.endpointPrefix = ByteString
"cloudfront",
      $sel:signingName:Service :: ByteString
Core.signingName = ByteString
"cloudfront",
      $sel:version:Service :: ByteString
Core.version = ByteString
"2020-05-31",
      $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
"CloudFront",
      $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

-- | Access denied.
_AccessDenied :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_AccessDenied :: forall a. AsError a => Fold a ServiceError
_AccessDenied =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"AccessDenied"
    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
403

-- | Invalidation batch specified is too large.
_BatchTooLarge :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_BatchTooLarge :: forall a. AsError a => Fold a ServiceError
_BatchTooLarge =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"BatchTooLarge"
    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
413

-- | The CNAME specified is already defined for CloudFront.
_CNAMEAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CNAMEAlreadyExists :: forall a. AsError a => Fold a ServiceError
_CNAMEAlreadyExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"CNAMEAlreadyExists"
    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

-- | A cache policy with this name already exists. You must provide a unique
-- name. To modify an existing cache policy, use @UpdateCachePolicy@.
_CachePolicyAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CachePolicyAlreadyExists :: forall a. AsError a => Fold a ServiceError
_CachePolicyAlreadyExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"CachePolicyAlreadyExists"
    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

-- | Cannot delete the cache policy because it is attached to one or more
-- cache behaviors.
_CachePolicyInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CachePolicyInUse :: forall a. AsError a => Fold a ServiceError
_CachePolicyInUse =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"CachePolicyInUse"
    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

-- | You can\'t change the value of a public key.
_CannotChangeImmutablePublicKeyFields :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CannotChangeImmutablePublicKeyFields :: forall a. AsError a => Fold a ServiceError
_CannotChangeImmutablePublicKeyFields =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"CannotChangeImmutablePublicKeyFields"
    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

-- | If the @CallerReference@ is a value you already sent in a previous
-- request to create an identity but the content of the
-- @CloudFrontOriginAccessIdentityConfig@ is different from the original
-- request, CloudFront returns a
-- @CloudFrontOriginAccessIdentityAlreadyExists@ error.
_CloudFrontOriginAccessIdentityAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CloudFrontOriginAccessIdentityAlreadyExists :: forall a. AsError a => Fold a ServiceError
_CloudFrontOriginAccessIdentityAlreadyExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"CloudFrontOriginAccessIdentityAlreadyExists"
    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

-- | The Origin Access Identity specified is already in use.
_CloudFrontOriginAccessIdentityInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CloudFrontOriginAccessIdentityInUse :: forall a. AsError a => Fold a ServiceError
_CloudFrontOriginAccessIdentityInUse =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"CloudFrontOriginAccessIdentityInUse"
    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

-- | A continuous deployment policy with this configuration already exists.
_ContinuousDeploymentPolicyAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ContinuousDeploymentPolicyAlreadyExists :: forall a. AsError a => Fold a ServiceError
_ContinuousDeploymentPolicyAlreadyExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ContinuousDeploymentPolicyAlreadyExists"
    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

-- | You cannot delete a continuous deployment policy that is associated with
-- a primary distribution.
_ContinuousDeploymentPolicyInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ContinuousDeploymentPolicyInUse :: forall a. AsError a => Fold a ServiceError
_ContinuousDeploymentPolicyInUse =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ContinuousDeploymentPolicyInUse"
    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

-- | The caller reference you attempted to create the distribution with is
-- associated with another distribution.
_DistributionAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DistributionAlreadyExists :: forall a. AsError a => Fold a ServiceError
_DistributionAlreadyExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"DistributionAlreadyExists"
    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

-- | The specified CloudFront distribution is not disabled. You must disable
-- the distribution before you can delete it.
_DistributionNotDisabled :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DistributionNotDisabled :: forall a. AsError a => Fold a ServiceError
_DistributionNotDisabled =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"DistributionNotDisabled"
    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

-- | The specified configuration for field-level encryption already exists.
_FieldLevelEncryptionConfigAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_FieldLevelEncryptionConfigAlreadyExists :: forall a. AsError a => Fold a ServiceError
_FieldLevelEncryptionConfigAlreadyExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"FieldLevelEncryptionConfigAlreadyExists"
    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

-- | The specified configuration for field-level encryption is in use.
_FieldLevelEncryptionConfigInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_FieldLevelEncryptionConfigInUse :: forall a. AsError a => Fold a ServiceError
_FieldLevelEncryptionConfigInUse =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"FieldLevelEncryptionConfigInUse"
    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

-- | The specified profile for field-level encryption already exists.
_FieldLevelEncryptionProfileAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_FieldLevelEncryptionProfileAlreadyExists :: forall a. AsError a => Fold a ServiceError
_FieldLevelEncryptionProfileAlreadyExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"FieldLevelEncryptionProfileAlreadyExists"
    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

-- | The specified profile for field-level encryption is in use.
_FieldLevelEncryptionProfileInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_FieldLevelEncryptionProfileInUse :: forall a. AsError a => Fold a ServiceError
_FieldLevelEncryptionProfileInUse =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"FieldLevelEncryptionProfileInUse"
    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

-- | The maximum size of a profile for field-level encryption was exceeded.
_FieldLevelEncryptionProfileSizeExceeded :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_FieldLevelEncryptionProfileSizeExceeded :: forall a. AsError a => Fold a ServiceError
_FieldLevelEncryptionProfileSizeExceeded =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"FieldLevelEncryptionProfileSizeExceeded"
    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

-- | A function with the same name already exists in this Amazon Web Services
-- account. To create a function, you must provide a unique name. To update
-- an existing function, use @UpdateFunction@.
_FunctionAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_FunctionAlreadyExists :: forall a. AsError a => Fold a ServiceError
_FunctionAlreadyExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"FunctionAlreadyExists"
    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

-- | Cannot delete the function because it\'s attached to one or more cache
-- behaviors.
_FunctionInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_FunctionInUse :: forall a. AsError a => Fold a ServiceError
_FunctionInUse =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"FunctionInUse"
    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

-- | The function is too large. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_FunctionSizeLimitExceeded :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_FunctionSizeLimitExceeded :: forall a. AsError a => Fold a ServiceError
_FunctionSizeLimitExceeded =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"FunctionSizeLimitExceeded"
    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
413

-- | You cannot delete a managed policy.
_IllegalDelete :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_IllegalDelete :: forall a. AsError a => Fold a ServiceError
_IllegalDelete =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"IllegalDelete"
    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

-- | The specified configuration for field-level encryption can\'t be
-- associated with the specified cache behavior.
_IllegalFieldLevelEncryptionConfigAssociationWithCacheBehavior :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_IllegalFieldLevelEncryptionConfigAssociationWithCacheBehavior :: forall a. AsError a => Fold a ServiceError
_IllegalFieldLevelEncryptionConfigAssociationWithCacheBehavior =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"IllegalFieldLevelEncryptionConfigAssociationWithCacheBehavior"
    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

-- | An origin cannot contain both an origin access control (OAC) and an
-- origin access identity (OAI).
_IllegalOriginAccessConfiguration :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_IllegalOriginAccessConfiguration :: forall a. AsError a => Fold a ServiceError
_IllegalOriginAccessConfiguration =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"IllegalOriginAccessConfiguration"
    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

-- | The update contains modifications that are not allowed.
_IllegalUpdate :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_IllegalUpdate :: forall a. AsError a => Fold a ServiceError
_IllegalUpdate =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"IllegalUpdate"
    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

-- | The value of @Quantity@ and the size of @Items@ don\'t match.
_InconsistentQuantities :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InconsistentQuantities :: forall a. AsError a => Fold a ServiceError
_InconsistentQuantities =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InconsistentQuantities"
    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

-- | An argument is invalid.
_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"
    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

-- | The default root object file name is too big or contains an invalid
-- character.
_InvalidDefaultRootObject :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidDefaultRootObject :: forall a. AsError a => Fold a ServiceError
_InvalidDefaultRootObject =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidDefaultRootObject"
    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

-- | An origin access control is associated with an origin whose domain name
-- is not supported.
_InvalidDomainNameForOriginAccessControl :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidDomainNameForOriginAccessControl :: forall a. AsError a => Fold a ServiceError
_InvalidDomainNameForOriginAccessControl =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidDomainNameForOriginAccessControl"
    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

-- | An invalid error code was specified.
_InvalidErrorCode :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidErrorCode :: forall a. AsError a => Fold a ServiceError
_InvalidErrorCode =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidErrorCode"
    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

-- | Your request contains forward cookies option which doesn\'t match with
-- the expectation for the @whitelisted@ list of cookie names. Either list
-- of cookie names has been specified when not allowed or list of cookie
-- names is missing when expected.
_InvalidForwardCookies :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidForwardCookies :: forall a. AsError a => Fold a ServiceError
_InvalidForwardCookies =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidForwardCookies"
    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

-- | A CloudFront function association is invalid.
_InvalidFunctionAssociation :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidFunctionAssociation :: forall a. AsError a => Fold a ServiceError
_InvalidFunctionAssociation =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidFunctionAssociation"
    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

-- | The specified geo restriction parameter is not valid.
_InvalidGeoRestrictionParameter :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidGeoRestrictionParameter :: forall a. AsError a => Fold a ServiceError
_InvalidGeoRestrictionParameter =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidGeoRestrictionParameter"
    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

-- | The headers specified are not valid for an Amazon S3 origin.
_InvalidHeadersForS3Origin :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidHeadersForS3Origin :: forall a. AsError a => Fold a ServiceError
_InvalidHeadersForS3Origin =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidHeadersForS3Origin"
    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

-- | The @If-Match@ version is missing or not valid.
_InvalidIfMatchVersion :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidIfMatchVersion :: forall a. AsError a => Fold a ServiceError
_InvalidIfMatchVersion =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidIfMatchVersion"
    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

-- | The specified Lambda\@Edge function association is invalid.
_InvalidLambdaFunctionAssociation :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidLambdaFunctionAssociation :: forall a. AsError a => Fold a ServiceError
_InvalidLambdaFunctionAssociation =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidLambdaFunctionAssociation"
    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

-- | The location code specified is not valid.
_InvalidLocationCode :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidLocationCode :: forall a. AsError a => Fold a ServiceError
_InvalidLocationCode =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidLocationCode"
    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

-- | The minimum protocol version specified is not valid.
_InvalidMinimumProtocolVersion :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidMinimumProtocolVersion :: forall a. AsError a => Fold a ServiceError
_InvalidMinimumProtocolVersion =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidMinimumProtocolVersion"
    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

-- | The Amazon S3 origin server specified does not refer to a valid Amazon
-- S3 bucket.
_InvalidOrigin :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidOrigin :: forall a. AsError a => Fold a ServiceError
_InvalidOrigin =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidOrigin"
    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

-- | The origin access control is not valid.
_InvalidOriginAccessControl :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidOriginAccessControl :: forall a. AsError a => Fold a ServiceError
_InvalidOriginAccessControl =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidOriginAccessControl"
    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

-- | The origin access identity is not valid or doesn\'t exist.
_InvalidOriginAccessIdentity :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidOriginAccessIdentity :: forall a. AsError a => Fold a ServiceError
_InvalidOriginAccessIdentity =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidOriginAccessIdentity"
    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

-- | The keep alive timeout specified for the origin is not valid.
_InvalidOriginKeepaliveTimeout :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidOriginKeepaliveTimeout :: forall a. AsError a => Fold a ServiceError
_InvalidOriginKeepaliveTimeout =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidOriginKeepaliveTimeout"
    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

-- | The read timeout specified for the origin is not valid.
_InvalidOriginReadTimeout :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidOriginReadTimeout :: forall a. AsError a => Fold a ServiceError
_InvalidOriginReadTimeout =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidOriginReadTimeout"
    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

-- | You cannot specify SSLv3 as the minimum protocol version if you only
-- want to support only clients that support Server Name Indication (SNI).
_InvalidProtocolSettings :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidProtocolSettings :: forall a. AsError a => Fold a ServiceError
_InvalidProtocolSettings =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidProtocolSettings"
    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

-- | The query string parameters specified are not valid.
_InvalidQueryStringParameters :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidQueryStringParameters :: forall a. AsError a => Fold a ServiceError
_InvalidQueryStringParameters =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidQueryStringParameters"
    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

-- | The relative path is too big, is not URL-encoded, or does not begin with
-- a slash (\/).
_InvalidRelativePath :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidRelativePath :: forall a. AsError a => Fold a ServiceError
_InvalidRelativePath =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidRelativePath"
    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

-- | This operation requires the HTTPS protocol. Ensure that you specify the
-- HTTPS protocol in your request, or omit the @RequiredProtocols@ element
-- from your distribution configuration.
_InvalidRequiredProtocol :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidRequiredProtocol :: forall a. AsError a => Fold a ServiceError
_InvalidRequiredProtocol =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidRequiredProtocol"
    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

-- | A response code is not valid.
_InvalidResponseCode :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidResponseCode :: forall a. AsError a => Fold a ServiceError
_InvalidResponseCode =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidResponseCode"
    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

-- | The TTL order specified is not valid.
_InvalidTTLOrder :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidTTLOrder :: forall a. AsError a => Fold a ServiceError
_InvalidTTLOrder =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidTTLOrder"
    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

-- | The tagging specified is not valid.
_InvalidTagging :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidTagging :: forall a. AsError a => Fold a ServiceError
_InvalidTagging =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidTagging"
    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

-- | A viewer certificate specified is not valid.
_InvalidViewerCertificate :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidViewerCertificate :: forall a. AsError a => Fold a ServiceError
_InvalidViewerCertificate =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidViewerCertificate"
    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

-- | A web ACL ID specified is not valid. To specify a web ACL created using
-- the latest version of WAF, use the ACL ARN, for example
-- @arn:aws:wafv2:us-east-1:123456789012:global\/webacl\/ExampleWebACL\/473e64fd-f30b-4765-81a0-62ad96dd167a@.
-- To specify a web ACL created using WAF Classic, use the ACL ID, for
-- example @473e64fd-f30b-4765-81a0-62ad96dd167a@.
_InvalidWebACLId :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidWebACLId :: forall a. AsError a => Fold a ServiceError
_InvalidWebACLId =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidWebACLId"
    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

-- | A key group with this name already exists. You must provide a unique
-- name. To modify an existing key group, use @UpdateKeyGroup@.
_KeyGroupAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_KeyGroupAlreadyExists :: forall a. AsError a => Fold a ServiceError
_KeyGroupAlreadyExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"KeyGroupAlreadyExists"
    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

-- | This operation requires a body. Ensure that the body is present and the
-- @Content-Type@ header is set.
_MissingBody :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_MissingBody :: forall a. AsError a => Fold a ServiceError
_MissingBody =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"MissingBody"
    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

-- | A monitoring subscription already exists for the specified distribution.
_MonitoringSubscriptionAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_MonitoringSubscriptionAlreadyExists :: forall a. AsError a => Fold a ServiceError
_MonitoringSubscriptionAlreadyExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"MonitoringSubscriptionAlreadyExists"
    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

-- | The cache policy does not exist.
_NoSuchCachePolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchCachePolicy :: forall a. AsError a => Fold a ServiceError
_NoSuchCachePolicy =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchCachePolicy"
    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

-- | The specified origin access identity does not exist.
_NoSuchCloudFrontOriginAccessIdentity :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchCloudFrontOriginAccessIdentity :: forall a. AsError a => Fold a ServiceError
_NoSuchCloudFrontOriginAccessIdentity =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchCloudFrontOriginAccessIdentity"
    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

-- | The continuous deployment policy doesn\'t exist.
_NoSuchContinuousDeploymentPolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchContinuousDeploymentPolicy :: forall a. AsError a => Fold a ServiceError
_NoSuchContinuousDeploymentPolicy =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchContinuousDeploymentPolicy"
    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

-- | The specified distribution does not exist.
_NoSuchDistribution :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchDistribution :: forall a. AsError a => Fold a ServiceError
_NoSuchDistribution =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchDistribution"
    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

-- | The specified configuration for field-level encryption doesn\'t exist.
_NoSuchFieldLevelEncryptionConfig :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchFieldLevelEncryptionConfig :: forall a. AsError a => Fold a ServiceError
_NoSuchFieldLevelEncryptionConfig =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchFieldLevelEncryptionConfig"
    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

-- | The specified profile for field-level encryption doesn\'t exist.
_NoSuchFieldLevelEncryptionProfile :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchFieldLevelEncryptionProfile :: forall a. AsError a => Fold a ServiceError
_NoSuchFieldLevelEncryptionProfile =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchFieldLevelEncryptionProfile"
    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

-- | The function does not exist.
_NoSuchFunctionExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchFunctionExists :: forall a. AsError a => Fold a ServiceError
_NoSuchFunctionExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchFunctionExists"
    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

-- | The specified invalidation does not exist.
_NoSuchInvalidation :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchInvalidation :: forall a. AsError a => Fold a ServiceError
_NoSuchInvalidation =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchInvalidation"
    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

-- | A monitoring subscription does not exist for the specified distribution.
_NoSuchMonitoringSubscription :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchMonitoringSubscription :: forall a. AsError a => Fold a ServiceError
_NoSuchMonitoringSubscription =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchMonitoringSubscription"
    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

-- | No origin exists with the specified @Origin Id@.
_NoSuchOrigin :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchOrigin :: forall a. AsError a => Fold a ServiceError
_NoSuchOrigin =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchOrigin"
    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

-- | The origin access control does not exist.
_NoSuchOriginAccessControl :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchOriginAccessControl :: forall a. AsError a => Fold a ServiceError
_NoSuchOriginAccessControl =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchOriginAccessControl"
    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

-- | The origin request policy does not exist.
_NoSuchOriginRequestPolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchOriginRequestPolicy :: forall a. AsError a => Fold a ServiceError
_NoSuchOriginRequestPolicy =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchOriginRequestPolicy"
    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

-- | The specified public key doesn\'t exist.
_NoSuchPublicKey :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchPublicKey :: forall a. AsError a => Fold a ServiceError
_NoSuchPublicKey =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchPublicKey"
    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

-- | The real-time log configuration does not exist.
_NoSuchRealtimeLogConfig :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchRealtimeLogConfig :: forall a. AsError a => Fold a ServiceError
_NoSuchRealtimeLogConfig =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchRealtimeLogConfig"
    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

-- | A resource that was specified is not valid.
_NoSuchResource :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchResource :: forall a. AsError a => Fold a ServiceError
_NoSuchResource =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchResource"
    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

-- | The response headers policy does not exist.
_NoSuchResponseHeadersPolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchResponseHeadersPolicy :: forall a. AsError a => Fold a ServiceError
_NoSuchResponseHeadersPolicy =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchResponseHeadersPolicy"
    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

-- | The specified streaming distribution does not exist.
_NoSuchStreamingDistribution :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchStreamingDistribution :: forall a. AsError a => Fold a ServiceError
_NoSuchStreamingDistribution =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchStreamingDistribution"
    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

-- | An origin access control with the specified parameters already exists.
_OriginAccessControlAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_OriginAccessControlAlreadyExists :: forall a. AsError a => Fold a ServiceError
_OriginAccessControlAlreadyExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"OriginAccessControlAlreadyExists"
    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

-- | Cannot delete the origin access control because it\'s in use by one or
-- more distributions.
_OriginAccessControlInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_OriginAccessControlInUse :: forall a. AsError a => Fold a ServiceError
_OriginAccessControlInUse =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"OriginAccessControlInUse"
    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

-- | An origin request policy with this name already exists. You must provide
-- a unique name. To modify an existing origin request policy, use
-- @UpdateOriginRequestPolicy@.
_OriginRequestPolicyAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_OriginRequestPolicyAlreadyExists :: forall a. AsError a => Fold a ServiceError
_OriginRequestPolicyAlreadyExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"OriginRequestPolicyAlreadyExists"
    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

-- | Cannot delete the origin request policy because it is attached to one or
-- more cache behaviors.
_OriginRequestPolicyInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_OriginRequestPolicyInUse :: forall a. AsError a => Fold a ServiceError
_OriginRequestPolicyInUse =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"OriginRequestPolicyInUse"
    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

-- | The precondition in one or more of the request fields evaluated to
-- @false@.
_PreconditionFailed :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_PreconditionFailed :: forall a. AsError a => Fold a ServiceError
_PreconditionFailed =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"PreconditionFailed"
    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
412

-- | The specified public key already exists.
_PublicKeyAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_PublicKeyAlreadyExists :: forall a. AsError a => Fold a ServiceError
_PublicKeyAlreadyExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"PublicKeyAlreadyExists"
    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

-- | The specified public key is in use.
_PublicKeyInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_PublicKeyInUse :: forall a. AsError a => Fold a ServiceError
_PublicKeyInUse =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"PublicKeyInUse"
    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

-- | No profile specified for the field-level encryption query argument.
_QueryArgProfileEmpty :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_QueryArgProfileEmpty :: forall a. AsError a => Fold a ServiceError
_QueryArgProfileEmpty =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"QueryArgProfileEmpty"
    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

-- | A real-time log configuration with this name already exists. You must
-- provide a unique name. To modify an existing real-time log
-- configuration, use @UpdateRealtimeLogConfig@.
_RealtimeLogConfigAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_RealtimeLogConfigAlreadyExists :: forall a. AsError a => Fold a ServiceError
_RealtimeLogConfigAlreadyExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"RealtimeLogConfigAlreadyExists"
    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

-- | Cannot delete the real-time log configuration because it is attached to
-- one or more cache behaviors.
_RealtimeLogConfigInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_RealtimeLogConfigInUse :: forall a. AsError a => Fold a ServiceError
_RealtimeLogConfigInUse =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"RealtimeLogConfigInUse"
    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

-- | The specified real-time log configuration belongs to a different Amazon
-- Web Services account.
_RealtimeLogConfigOwnerMismatch :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_RealtimeLogConfigOwnerMismatch :: forall a. AsError a => Fold a ServiceError
_RealtimeLogConfigOwnerMismatch =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"RealtimeLogConfigOwnerMismatch"
    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

-- | Cannot delete this resource because it is in use.
_ResourceInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ResourceInUse :: forall a. AsError a => Fold a ServiceError
_ResourceInUse =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ResourceInUse"
    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

-- | A response headers policy with this name already exists. You must
-- provide a unique name. To modify an existing response headers policy,
-- use @UpdateResponseHeadersPolicy@.
_ResponseHeadersPolicyAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ResponseHeadersPolicyAlreadyExists :: forall a. AsError a => Fold a ServiceError
_ResponseHeadersPolicyAlreadyExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ResponseHeadersPolicyAlreadyExists"
    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

-- | Cannot delete the response headers policy because it is attached to one
-- or more cache behaviors in a CloudFront distribution.
_ResponseHeadersPolicyInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ResponseHeadersPolicyInUse :: forall a. AsError a => Fold a ServiceError
_ResponseHeadersPolicyInUse =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ResponseHeadersPolicyInUse"
    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

-- | A continuous deployment policy for this staging distribution already
-- exists.
_StagingDistributionInUse :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_StagingDistributionInUse :: forall a. AsError a => Fold a ServiceError
_StagingDistributionInUse =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"StagingDistributionInUse"
    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

-- | The caller reference you attempted to create the streaming distribution
-- with is associated with another distribution
_StreamingDistributionAlreadyExists :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_StreamingDistributionAlreadyExists :: forall a. AsError a => Fold a ServiceError
_StreamingDistributionAlreadyExists =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"StreamingDistributionAlreadyExists"
    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

-- | The specified CloudFront distribution is not disabled. You must disable
-- the distribution before you can delete it.
_StreamingDistributionNotDisabled :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_StreamingDistributionNotDisabled :: forall a. AsError a => Fold a ServiceError
_StreamingDistributionNotDisabled =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"StreamingDistributionNotDisabled"
    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

-- | The CloudFront function failed.
_TestFunctionFailed :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TestFunctionFailed :: forall a. AsError a => Fold a ServiceError
_TestFunctionFailed =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TestFunctionFailed"
    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
500

-- | The length of the @Content-Security-Policy@ header value in the response
-- headers policy exceeds the maximum.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooLongCSPInResponseHeadersPolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooLongCSPInResponseHeadersPolicy :: forall a. AsError a => Fold a ServiceError
_TooLongCSPInResponseHeadersPolicy =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooLongCSPInResponseHeadersPolicy"
    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

-- | You cannot create more cache behaviors for the distribution.
_TooManyCacheBehaviors :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyCacheBehaviors :: forall a. AsError a => Fold a ServiceError
_TooManyCacheBehaviors =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyCacheBehaviors"
    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

-- | You have reached the maximum number of cache policies for this Amazon
-- Web Services account. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyCachePolicies :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyCachePolicies :: forall a. AsError a => Fold a ServiceError
_TooManyCachePolicies =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyCachePolicies"
    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

-- | You cannot create anymore custom SSL\/TLS certificates.
_TooManyCertificates :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyCertificates :: forall a. AsError a => Fold a ServiceError
_TooManyCertificates =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyCertificates"
    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

-- | Processing your request would cause you to exceed the maximum number of
-- origin access identities allowed.
_TooManyCloudFrontOriginAccessIdentities :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyCloudFrontOriginAccessIdentities :: forall a. AsError a => Fold a ServiceError
_TooManyCloudFrontOriginAccessIdentities =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyCloudFrontOriginAccessIdentities"
    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

-- | You have reached the maximum number of continuous deployment policies
-- for this Amazon Web Services account.
_TooManyContinuousDeploymentPolicies :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyContinuousDeploymentPolicies :: forall a. AsError a => Fold a ServiceError
_TooManyContinuousDeploymentPolicies =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyContinuousDeploymentPolicies"
    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

-- | Your request contains more cookie names in the whitelist than are
-- allowed per cache behavior.
_TooManyCookieNamesInWhiteList :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyCookieNamesInWhiteList :: forall a. AsError a => Fold a ServiceError
_TooManyCookieNamesInWhiteList =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyCookieNamesInWhiteList"
    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

-- | The number of cookies in the cache policy exceeds the maximum. For more
-- information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyCookiesInCachePolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyCookiesInCachePolicy :: forall a. AsError a => Fold a ServiceError
_TooManyCookiesInCachePolicy =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyCookiesInCachePolicy"
    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

-- | The number of cookies in the origin request policy exceeds the maximum.
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyCookiesInOriginRequestPolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyCookiesInOriginRequestPolicy :: forall a. AsError a => Fold a ServiceError
_TooManyCookiesInOriginRequestPolicy =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyCookiesInOriginRequestPolicy"
    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

-- | The number of custom headers in the response headers policy exceeds the
-- maximum.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyCustomHeadersInResponseHeadersPolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyCustomHeadersInResponseHeadersPolicy :: forall a. AsError a => Fold a ServiceError
_TooManyCustomHeadersInResponseHeadersPolicy =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyCustomHeadersInResponseHeadersPolicy"
    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

-- | Your request contains more CNAMEs than are allowed per distribution.
_TooManyDistributionCNAMEs :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyDistributionCNAMEs :: forall a. AsError a => Fold a ServiceError
_TooManyDistributionCNAMEs =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyDistributionCNAMEs"
    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

-- | Processing your request would cause you to exceed the maximum number of
-- distributions allowed.
_TooManyDistributions :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyDistributions :: forall a. AsError a => Fold a ServiceError
_TooManyDistributions =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyDistributions"
    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

-- | The maximum number of distributions have been associated with the
-- specified cache policy. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyDistributionsAssociatedToCachePolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyDistributionsAssociatedToCachePolicy :: forall a. AsError a => Fold a ServiceError
_TooManyDistributionsAssociatedToCachePolicy =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyDistributionsAssociatedToCachePolicy"
    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

-- | The maximum number of distributions have been associated with the
-- specified configuration for field-level encryption.
_TooManyDistributionsAssociatedToFieldLevelEncryptionConfig :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyDistributionsAssociatedToFieldLevelEncryptionConfig :: forall a. AsError a => Fold a ServiceError
_TooManyDistributionsAssociatedToFieldLevelEncryptionConfig =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyDistributionsAssociatedToFieldLevelEncryptionConfig"
    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

-- | The number of distributions that reference this key group is more than
-- the maximum allowed. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyDistributionsAssociatedToKeyGroup :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyDistributionsAssociatedToKeyGroup :: forall a. AsError a => Fold a ServiceError
_TooManyDistributionsAssociatedToKeyGroup =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyDistributionsAssociatedToKeyGroup"
    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

-- | The maximum number of distributions have been associated with the
-- specified origin access control.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyDistributionsAssociatedToOriginAccessControl :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyDistributionsAssociatedToOriginAccessControl :: forall a. AsError a => Fold a ServiceError
_TooManyDistributionsAssociatedToOriginAccessControl =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyDistributionsAssociatedToOriginAccessControl"
    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

-- | The maximum number of distributions have been associated with the
-- specified origin request policy. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyDistributionsAssociatedToOriginRequestPolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyDistributionsAssociatedToOriginRequestPolicy :: forall a. AsError a => Fold a ServiceError
_TooManyDistributionsAssociatedToOriginRequestPolicy =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyDistributionsAssociatedToOriginRequestPolicy"
    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

-- | The maximum number of distributions have been associated with the
-- specified response headers policy.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyDistributionsAssociatedToResponseHeadersPolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyDistributionsAssociatedToResponseHeadersPolicy :: forall a. AsError a => Fold a ServiceError
_TooManyDistributionsAssociatedToResponseHeadersPolicy =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyDistributionsAssociatedToResponseHeadersPolicy"
    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

-- | You have reached the maximum number of distributions that are associated
-- with a CloudFront function. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyDistributionsWithFunctionAssociations :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyDistributionsWithFunctionAssociations :: forall a. AsError a => Fold a ServiceError
_TooManyDistributionsWithFunctionAssociations =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyDistributionsWithFunctionAssociations"
    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

-- | Processing your request would cause the maximum number of distributions
-- with Lambda\@Edge function associations per owner to be exceeded.
_TooManyDistributionsWithLambdaAssociations :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyDistributionsWithLambdaAssociations :: forall a. AsError a => Fold a ServiceError
_TooManyDistributionsWithLambdaAssociations =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyDistributionsWithLambdaAssociations"
    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

-- | The maximum number of distributions have been associated with the
-- specified Lambda\@Edge function.
_TooManyDistributionsWithSingleFunctionARN :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyDistributionsWithSingleFunctionARN :: forall a. AsError a => Fold a ServiceError
_TooManyDistributionsWithSingleFunctionARN =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyDistributionsWithSingleFunctionARN"
    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

-- | The maximum number of configurations for field-level encryption have
-- been created.
_TooManyFieldLevelEncryptionConfigs :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyFieldLevelEncryptionConfigs :: forall a. AsError a => Fold a ServiceError
_TooManyFieldLevelEncryptionConfigs =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyFieldLevelEncryptionConfigs"
    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

-- | The maximum number of content type profiles for field-level encryption
-- have been created.
_TooManyFieldLevelEncryptionContentTypeProfiles :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyFieldLevelEncryptionContentTypeProfiles :: forall a. AsError a => Fold a ServiceError
_TooManyFieldLevelEncryptionContentTypeProfiles =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyFieldLevelEncryptionContentTypeProfiles"
    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

-- | The maximum number of encryption entities for field-level encryption
-- have been created.
_TooManyFieldLevelEncryptionEncryptionEntities :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyFieldLevelEncryptionEncryptionEntities :: forall a. AsError a => Fold a ServiceError
_TooManyFieldLevelEncryptionEncryptionEntities =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyFieldLevelEncryptionEncryptionEntities"
    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

-- | The maximum number of field patterns for field-level encryption have
-- been created.
_TooManyFieldLevelEncryptionFieldPatterns :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyFieldLevelEncryptionFieldPatterns :: forall a. AsError a => Fold a ServiceError
_TooManyFieldLevelEncryptionFieldPatterns =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyFieldLevelEncryptionFieldPatterns"
    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

-- | The maximum number of profiles for field-level encryption have been
-- created.
_TooManyFieldLevelEncryptionProfiles :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyFieldLevelEncryptionProfiles :: forall a. AsError a => Fold a ServiceError
_TooManyFieldLevelEncryptionProfiles =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyFieldLevelEncryptionProfiles"
    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

-- | The maximum number of query arg profiles for field-level encryption have
-- been created.
_TooManyFieldLevelEncryptionQueryArgProfiles :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyFieldLevelEncryptionQueryArgProfiles :: forall a. AsError a => Fold a ServiceError
_TooManyFieldLevelEncryptionQueryArgProfiles =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyFieldLevelEncryptionQueryArgProfiles"
    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

-- | You have reached the maximum number of CloudFront function associations
-- for this distribution. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyFunctionAssociations :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyFunctionAssociations :: forall a. AsError a => Fold a ServiceError
_TooManyFunctionAssociations =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyFunctionAssociations"
    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

-- | You have reached the maximum number of CloudFront functions for this
-- Amazon Web Services account. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyFunctions :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyFunctions :: forall a. AsError a => Fold a ServiceError
_TooManyFunctions =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyFunctions"
    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

-- | The number of headers in the cache policy exceeds the maximum. For more
-- information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyHeadersInCachePolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyHeadersInCachePolicy :: forall a. AsError a => Fold a ServiceError
_TooManyHeadersInCachePolicy =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyHeadersInCachePolicy"
    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

-- | Your request contains too many headers in forwarded values.
_TooManyHeadersInForwardedValues :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyHeadersInForwardedValues :: forall a. AsError a => Fold a ServiceError
_TooManyHeadersInForwardedValues =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyHeadersInForwardedValues"
    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

-- | The number of headers in the origin request policy exceeds the maximum.
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyHeadersInOriginRequestPolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyHeadersInOriginRequestPolicy :: forall a. AsError a => Fold a ServiceError
_TooManyHeadersInOriginRequestPolicy =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyHeadersInOriginRequestPolicy"
    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

-- | You have exceeded the maximum number of allowable InProgress
-- invalidation batch requests, or invalidation objects.
_TooManyInvalidationsInProgress :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyInvalidationsInProgress :: forall a. AsError a => Fold a ServiceError
_TooManyInvalidationsInProgress =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyInvalidationsInProgress"
    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

-- | You have reached the maximum number of key groups for this Amazon Web
-- Services account. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyKeyGroups :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyKeyGroups :: forall a. AsError a => Fold a ServiceError
_TooManyKeyGroups =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyKeyGroups"
    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

-- | The number of key groups referenced by this distribution is more than
-- the maximum allowed. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyKeyGroupsAssociatedToDistribution :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyKeyGroupsAssociatedToDistribution :: forall a. AsError a => Fold a ServiceError
_TooManyKeyGroupsAssociatedToDistribution =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyKeyGroupsAssociatedToDistribution"
    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

-- | Your request contains more Lambda\@Edge function associations than are
-- allowed per distribution.
_TooManyLambdaFunctionAssociations :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyLambdaFunctionAssociations :: forall a. AsError a => Fold a ServiceError
_TooManyLambdaFunctionAssociations =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyLambdaFunctionAssociations"
    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

-- | The number of origin access controls in your Amazon Web Services account
-- exceeds the maximum allowed.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyOriginAccessControls :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyOriginAccessControls :: forall a. AsError a => Fold a ServiceError
_TooManyOriginAccessControls =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyOriginAccessControls"
    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

-- | Your request contains too many origin custom headers.
_TooManyOriginCustomHeaders :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyOriginCustomHeaders :: forall a. AsError a => Fold a ServiceError
_TooManyOriginCustomHeaders =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyOriginCustomHeaders"
    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

-- | Processing your request would cause you to exceed the maximum number of
-- origin groups allowed.
_TooManyOriginGroupsPerDistribution :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyOriginGroupsPerDistribution :: forall a. AsError a => Fold a ServiceError
_TooManyOriginGroupsPerDistribution =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyOriginGroupsPerDistribution"
    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

-- | You have reached the maximum number of origin request policies for this
-- Amazon Web Services account. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyOriginRequestPolicies :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyOriginRequestPolicies :: forall a. AsError a => Fold a ServiceError
_TooManyOriginRequestPolicies =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyOriginRequestPolicies"
    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

-- | You cannot create more origins for the distribution.
_TooManyOrigins :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyOrigins :: forall a. AsError a => Fold a ServiceError
_TooManyOrigins =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyOrigins"
    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

-- | The maximum number of public keys for field-level encryption have been
-- created. To create a new public key, delete one of the existing keys.
_TooManyPublicKeys :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyPublicKeys :: forall a. AsError a => Fold a ServiceError
_TooManyPublicKeys =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyPublicKeys"
    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

-- | The number of public keys in this key group is more than the maximum
-- allowed. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyPublicKeysInKeyGroup :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyPublicKeysInKeyGroup :: forall a. AsError a => Fold a ServiceError
_TooManyPublicKeysInKeyGroup =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyPublicKeysInKeyGroup"
    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

-- | Your request contains too many query string parameters.
_TooManyQueryStringParameters :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyQueryStringParameters :: forall a. AsError a => Fold a ServiceError
_TooManyQueryStringParameters =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyQueryStringParameters"
    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

-- | The number of query strings in the cache policy exceeds the maximum. For
-- more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyQueryStringsInCachePolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyQueryStringsInCachePolicy :: forall a. AsError a => Fold a ServiceError
_TooManyQueryStringsInCachePolicy =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyQueryStringsInCachePolicy"
    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

-- | The number of query strings in the origin request policy exceeds the
-- maximum. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyQueryStringsInOriginRequestPolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyQueryStringsInOriginRequestPolicy :: forall a. AsError a => Fold a ServiceError
_TooManyQueryStringsInOriginRequestPolicy =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyQueryStringsInOriginRequestPolicy"
    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

-- | You have reached the maximum number of real-time log configurations for
-- this Amazon Web Services account. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyRealtimeLogConfigs :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyRealtimeLogConfigs :: forall a. AsError a => Fold a ServiceError
_TooManyRealtimeLogConfigs =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyRealtimeLogConfigs"
    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

-- | The number of headers in @RemoveHeadersConfig@ in the response headers
-- policy exceeds the maximum.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyRemoveHeadersInResponseHeadersPolicy :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyRemoveHeadersInResponseHeadersPolicy :: forall a. AsError a => Fold a ServiceError
_TooManyRemoveHeadersInResponseHeadersPolicy =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyRemoveHeadersInResponseHeadersPolicy"
    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

-- | You have reached the maximum number of response headers policies for
-- this Amazon Web Services account.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/cloudfront-limits.html Quotas>
-- (formerly known as limits) in the /Amazon CloudFront Developer Guide/.
_TooManyResponseHeadersPolicies :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyResponseHeadersPolicies :: forall a. AsError a => Fold a ServiceError
_TooManyResponseHeadersPolicies =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyResponseHeadersPolicies"
    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

-- | Your request contains more CNAMEs than are allowed per distribution.
_TooManyStreamingDistributionCNAMEs :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyStreamingDistributionCNAMEs :: forall a. AsError a => Fold a ServiceError
_TooManyStreamingDistributionCNAMEs =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyStreamingDistributionCNAMEs"
    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

-- | Processing your request would cause you to exceed the maximum number of
-- streaming distributions allowed.
_TooManyStreamingDistributions :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyStreamingDistributions :: forall a. AsError a => Fold a ServiceError
_TooManyStreamingDistributions =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyStreamingDistributions"
    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

-- | Your request contains more trusted signers than are allowed per
-- distribution.
_TooManyTrustedSigners :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyTrustedSigners :: forall a. AsError a => Fold a ServiceError
_TooManyTrustedSigners =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyTrustedSigners"
    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

-- | The specified key group does not exist.
_TrustedKeyGroupDoesNotExist :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TrustedKeyGroupDoesNotExist :: forall a. AsError a => Fold a ServiceError
_TrustedKeyGroupDoesNotExist =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TrustedKeyGroupDoesNotExist"
    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

-- | One or more of your trusted signers don\'t exist.
_TrustedSignerDoesNotExist :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TrustedSignerDoesNotExist :: forall a. AsError a => Fold a ServiceError
_TrustedSignerDoesNotExist =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TrustedSignerDoesNotExist"
    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

-- | This operation is not supported in this region.
_UnsupportedOperation :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_UnsupportedOperation :: forall a. AsError a => Fold a ServiceError
_UnsupportedOperation =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"UnsupportedOperation"
    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