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

    -- * Errors
    _AccessDeniedException,
    _ConflictException,
    _InternalServerException,
    _ResourceNotFoundException,
    _ServiceQuotaExceededException,
    _ServiceUnavailableException,
    _ThrottlingException,
    _ValidationException,

    -- * ChangeDirectionEnum
    ChangeDirectionEnum (..),

    -- * EventType
    EventType (..),

    -- * ExperimentBaseStat
    ExperimentBaseStat (..),

    -- * ExperimentReportName
    ExperimentReportName (..),

    -- * ExperimentResultRequestType
    ExperimentResultRequestType (..),

    -- * ExperimentResultResponseType
    ExperimentResultResponseType (..),

    -- * ExperimentStatus
    ExperimentStatus (..),

    -- * ExperimentStopDesiredState
    ExperimentStopDesiredState (..),

    -- * ExperimentType
    ExperimentType (..),

    -- * FeatureEvaluationStrategy
    FeatureEvaluationStrategy (..),

    -- * FeatureStatus
    FeatureStatus (..),

    -- * LaunchStatus
    LaunchStatus (..),

    -- * LaunchStopDesiredState
    LaunchStopDesiredState (..),

    -- * LaunchType
    LaunchType (..),

    -- * ProjectStatus
    ProjectStatus (..),

    -- * SegmentReferenceResourceType
    SegmentReferenceResourceType (..),

    -- * VariationValueType
    VariationValueType (..),

    -- * CloudWatchLogsDestination
    CloudWatchLogsDestination (..),
    newCloudWatchLogsDestination,
    cloudWatchLogsDestination_logGroup,

    -- * CloudWatchLogsDestinationConfig
    CloudWatchLogsDestinationConfig (..),
    newCloudWatchLogsDestinationConfig,
    cloudWatchLogsDestinationConfig_logGroup,

    -- * EvaluationRequest
    EvaluationRequest (..),
    newEvaluationRequest,
    evaluationRequest_evaluationContext,
    evaluationRequest_entityId,
    evaluationRequest_feature,

    -- * EvaluationResult
    EvaluationResult (..),
    newEvaluationResult,
    evaluationResult_details,
    evaluationResult_project,
    evaluationResult_reason,
    evaluationResult_value,
    evaluationResult_variation,
    evaluationResult_entityId,
    evaluationResult_feature,

    -- * EvaluationRule
    EvaluationRule (..),
    newEvaluationRule,
    evaluationRule_name,
    evaluationRule_type,

    -- * Event
    Event (..),
    newEvent,
    event_data,
    event_timestamp,
    event_type,

    -- * Experiment
    Experiment (..),
    newExperiment,
    experiment_description,
    experiment_execution,
    experiment_metricGoals,
    experiment_onlineAbDefinition,
    experiment_project,
    experiment_randomizationSalt,
    experiment_samplingRate,
    experiment_schedule,
    experiment_segment,
    experiment_statusReason,
    experiment_tags,
    experiment_treatments,
    experiment_arn,
    experiment_createdTime,
    experiment_lastUpdatedTime,
    experiment_name,
    experiment_status,
    experiment_type,

    -- * ExperimentExecution
    ExperimentExecution (..),
    newExperimentExecution,
    experimentExecution_endedTime,
    experimentExecution_startedTime,

    -- * ExperimentReport
    ExperimentReport (..),
    newExperimentReport,
    experimentReport_content,
    experimentReport_metricName,
    experimentReport_reportName,
    experimentReport_treatmentName,

    -- * ExperimentResultsData
    ExperimentResultsData (..),
    newExperimentResultsData,
    experimentResultsData_metricName,
    experimentResultsData_resultStat,
    experimentResultsData_treatmentName,
    experimentResultsData_values,

    -- * ExperimentSchedule
    ExperimentSchedule (..),
    newExperimentSchedule,
    experimentSchedule_analysisCompleteTime,

    -- * Feature
    Feature (..),
    newFeature,
    feature_defaultVariation,
    feature_description,
    feature_entityOverrides,
    feature_evaluationRules,
    feature_project,
    feature_tags,
    feature_arn,
    feature_createdTime,
    feature_evaluationStrategy,
    feature_lastUpdatedTime,
    feature_name,
    feature_status,
    feature_valueType,
    feature_variations,

    -- * FeatureSummary
    FeatureSummary (..),
    newFeatureSummary,
    featureSummary_defaultVariation,
    featureSummary_evaluationRules,
    featureSummary_project,
    featureSummary_tags,
    featureSummary_arn,
    featureSummary_createdTime,
    featureSummary_evaluationStrategy,
    featureSummary_lastUpdatedTime,
    featureSummary_name,
    featureSummary_status,

    -- * Launch
    Launch (..),
    newLaunch,
    launch_description,
    launch_execution,
    launch_groups,
    launch_metricMonitors,
    launch_project,
    launch_randomizationSalt,
    launch_scheduledSplitsDefinition,
    launch_statusReason,
    launch_tags,
    launch_arn,
    launch_createdTime,
    launch_lastUpdatedTime,
    launch_name,
    launch_status,
    launch_type,

    -- * LaunchExecution
    LaunchExecution (..),
    newLaunchExecution,
    launchExecution_endedTime,
    launchExecution_startedTime,

    -- * LaunchGroup
    LaunchGroup (..),
    newLaunchGroup,
    launchGroup_description,
    launchGroup_featureVariations,
    launchGroup_name,

    -- * LaunchGroupConfig
    LaunchGroupConfig (..),
    newLaunchGroupConfig,
    launchGroupConfig_description,
    launchGroupConfig_feature,
    launchGroupConfig_name,
    launchGroupConfig_variation,

    -- * MetricDefinition
    MetricDefinition (..),
    newMetricDefinition,
    metricDefinition_entityIdKey,
    metricDefinition_eventPattern,
    metricDefinition_name,
    metricDefinition_unitLabel,
    metricDefinition_valueKey,

    -- * MetricDefinitionConfig
    MetricDefinitionConfig (..),
    newMetricDefinitionConfig,
    metricDefinitionConfig_eventPattern,
    metricDefinitionConfig_unitLabel,
    metricDefinitionConfig_entityIdKey,
    metricDefinitionConfig_name,
    metricDefinitionConfig_valueKey,

    -- * MetricGoal
    MetricGoal (..),
    newMetricGoal,
    metricGoal_desiredChange,
    metricGoal_metricDefinition,

    -- * MetricGoalConfig
    MetricGoalConfig (..),
    newMetricGoalConfig,
    metricGoalConfig_desiredChange,
    metricGoalConfig_metricDefinition,

    -- * MetricMonitor
    MetricMonitor (..),
    newMetricMonitor,
    metricMonitor_metricDefinition,

    -- * MetricMonitorConfig
    MetricMonitorConfig (..),
    newMetricMonitorConfig,
    metricMonitorConfig_metricDefinition,

    -- * OnlineAbConfig
    OnlineAbConfig (..),
    newOnlineAbConfig,
    onlineAbConfig_controlTreatmentName,
    onlineAbConfig_treatmentWeights,

    -- * OnlineAbDefinition
    OnlineAbDefinition (..),
    newOnlineAbDefinition,
    onlineAbDefinition_controlTreatmentName,
    onlineAbDefinition_treatmentWeights,

    -- * Project
    Project (..),
    newProject,
    project_activeExperimentCount,
    project_activeLaunchCount,
    project_appConfigResource,
    project_dataDelivery,
    project_description,
    project_experimentCount,
    project_featureCount,
    project_launchCount,
    project_tags,
    project_arn,
    project_createdTime,
    project_lastUpdatedTime,
    project_name,
    project_status,

    -- * ProjectAppConfigResource
    ProjectAppConfigResource (..),
    newProjectAppConfigResource,
    projectAppConfigResource_applicationId,
    projectAppConfigResource_configurationProfileId,
    projectAppConfigResource_environmentId,

    -- * ProjectAppConfigResourceConfig
    ProjectAppConfigResourceConfig (..),
    newProjectAppConfigResourceConfig,
    projectAppConfigResourceConfig_applicationId,
    projectAppConfigResourceConfig_environmentId,

    -- * ProjectDataDelivery
    ProjectDataDelivery (..),
    newProjectDataDelivery,
    projectDataDelivery_cloudWatchLogs,
    projectDataDelivery_s3Destination,

    -- * ProjectDataDeliveryConfig
    ProjectDataDeliveryConfig (..),
    newProjectDataDeliveryConfig,
    projectDataDeliveryConfig_cloudWatchLogs,
    projectDataDeliveryConfig_s3Destination,

    -- * ProjectSummary
    ProjectSummary (..),
    newProjectSummary,
    projectSummary_activeExperimentCount,
    projectSummary_activeLaunchCount,
    projectSummary_description,
    projectSummary_experimentCount,
    projectSummary_featureCount,
    projectSummary_launchCount,
    projectSummary_tags,
    projectSummary_arn,
    projectSummary_createdTime,
    projectSummary_lastUpdatedTime,
    projectSummary_name,
    projectSummary_status,

    -- * PutProjectEventsResultEntry
    PutProjectEventsResultEntry (..),
    newPutProjectEventsResultEntry,
    putProjectEventsResultEntry_errorCode,
    putProjectEventsResultEntry_errorMessage,
    putProjectEventsResultEntry_eventId,

    -- * RefResource
    RefResource (..),
    newRefResource,
    refResource_arn,
    refResource_endTime,
    refResource_lastUpdatedOn,
    refResource_startTime,
    refResource_status,
    refResource_name,
    refResource_type,

    -- * S3Destination
    S3Destination (..),
    newS3Destination,
    s3Destination_bucket,
    s3Destination_prefix,

    -- * S3DestinationConfig
    S3DestinationConfig (..),
    newS3DestinationConfig,
    s3DestinationConfig_bucket,
    s3DestinationConfig_prefix,

    -- * ScheduledSplit
    ScheduledSplit (..),
    newScheduledSplit,
    scheduledSplit_groupWeights,
    scheduledSplit_segmentOverrides,
    scheduledSplit_startTime,

    -- * ScheduledSplitConfig
    ScheduledSplitConfig (..),
    newScheduledSplitConfig,
    scheduledSplitConfig_segmentOverrides,
    scheduledSplitConfig_groupWeights,
    scheduledSplitConfig_startTime,

    -- * ScheduledSplitsLaunchConfig
    ScheduledSplitsLaunchConfig (..),
    newScheduledSplitsLaunchConfig,
    scheduledSplitsLaunchConfig_steps,

    -- * ScheduledSplitsLaunchDefinition
    ScheduledSplitsLaunchDefinition (..),
    newScheduledSplitsLaunchDefinition,
    scheduledSplitsLaunchDefinition_steps,

    -- * Segment
    Segment (..),
    newSegment,
    segment_description,
    segment_experimentCount,
    segment_launchCount,
    segment_tags,
    segment_arn,
    segment_createdTime,
    segment_lastUpdatedTime,
    segment_name,
    segment_pattern,

    -- * SegmentOverride
    SegmentOverride (..),
    newSegmentOverride,
    segmentOverride_evaluationOrder,
    segmentOverride_segment,
    segmentOverride_weights,

    -- * Treatment
    Treatment (..),
    newTreatment,
    treatment_description,
    treatment_featureVariations,
    treatment_name,

    -- * TreatmentConfig
    TreatmentConfig (..),
    newTreatmentConfig,
    treatmentConfig_description,
    treatmentConfig_feature,
    treatmentConfig_name,
    treatmentConfig_variation,

    -- * VariableValue
    VariableValue (..),
    newVariableValue,
    variableValue_boolValue,
    variableValue_doubleValue,
    variableValue_longValue,
    variableValue_stringValue,

    -- * Variation
    Variation (..),
    newVariation,
    variation_name,
    variation_value,

    -- * VariationConfig
    VariationConfig (..),
    newVariationConfig,
    variationConfig_name,
    variationConfig_value,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.Evidently.Types.ChangeDirectionEnum
import Amazonka.Evidently.Types.CloudWatchLogsDestination
import Amazonka.Evidently.Types.CloudWatchLogsDestinationConfig
import Amazonka.Evidently.Types.EvaluationRequest
import Amazonka.Evidently.Types.EvaluationResult
import Amazonka.Evidently.Types.EvaluationRule
import Amazonka.Evidently.Types.Event
import Amazonka.Evidently.Types.EventType
import Amazonka.Evidently.Types.Experiment
import Amazonka.Evidently.Types.ExperimentBaseStat
import Amazonka.Evidently.Types.ExperimentExecution
import Amazonka.Evidently.Types.ExperimentReport
import Amazonka.Evidently.Types.ExperimentReportName
import Amazonka.Evidently.Types.ExperimentResultRequestType
import Amazonka.Evidently.Types.ExperimentResultResponseType
import Amazonka.Evidently.Types.ExperimentResultsData
import Amazonka.Evidently.Types.ExperimentSchedule
import Amazonka.Evidently.Types.ExperimentStatus
import Amazonka.Evidently.Types.ExperimentStopDesiredState
import Amazonka.Evidently.Types.ExperimentType
import Amazonka.Evidently.Types.Feature
import Amazonka.Evidently.Types.FeatureEvaluationStrategy
import Amazonka.Evidently.Types.FeatureStatus
import Amazonka.Evidently.Types.FeatureSummary
import Amazonka.Evidently.Types.Launch
import Amazonka.Evidently.Types.LaunchExecution
import Amazonka.Evidently.Types.LaunchGroup
import Amazonka.Evidently.Types.LaunchGroupConfig
import Amazonka.Evidently.Types.LaunchStatus
import Amazonka.Evidently.Types.LaunchStopDesiredState
import Amazonka.Evidently.Types.LaunchType
import Amazonka.Evidently.Types.MetricDefinition
import Amazonka.Evidently.Types.MetricDefinitionConfig
import Amazonka.Evidently.Types.MetricGoal
import Amazonka.Evidently.Types.MetricGoalConfig
import Amazonka.Evidently.Types.MetricMonitor
import Amazonka.Evidently.Types.MetricMonitorConfig
import Amazonka.Evidently.Types.OnlineAbConfig
import Amazonka.Evidently.Types.OnlineAbDefinition
import Amazonka.Evidently.Types.Project
import Amazonka.Evidently.Types.ProjectAppConfigResource
import Amazonka.Evidently.Types.ProjectAppConfigResourceConfig
import Amazonka.Evidently.Types.ProjectDataDelivery
import Amazonka.Evidently.Types.ProjectDataDeliveryConfig
import Amazonka.Evidently.Types.ProjectStatus
import Amazonka.Evidently.Types.ProjectSummary
import Amazonka.Evidently.Types.PutProjectEventsResultEntry
import Amazonka.Evidently.Types.RefResource
import Amazonka.Evidently.Types.S3Destination
import Amazonka.Evidently.Types.S3DestinationConfig
import Amazonka.Evidently.Types.ScheduledSplit
import Amazonka.Evidently.Types.ScheduledSplitConfig
import Amazonka.Evidently.Types.ScheduledSplitsLaunchConfig
import Amazonka.Evidently.Types.ScheduledSplitsLaunchDefinition
import Amazonka.Evidently.Types.Segment
import Amazonka.Evidently.Types.SegmentOverride
import Amazonka.Evidently.Types.SegmentReferenceResourceType
import Amazonka.Evidently.Types.Treatment
import Amazonka.Evidently.Types.TreatmentConfig
import Amazonka.Evidently.Types.VariableValue
import Amazonka.Evidently.Types.Variation
import Amazonka.Evidently.Types.VariationConfig
import Amazonka.Evidently.Types.VariationValueType
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Sign.V4 as Sign

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

-- | You do not have sufficient permissions to perform this action.
_AccessDeniedException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_AccessDeniedException :: forall a. AsError a => Fold a ServiceError
_AccessDeniedException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"AccessDeniedException"
    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

-- | A resource was in an inconsistent state during an update or a deletion.
_ConflictException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ConflictException :: forall a. AsError a => Fold a ServiceError
_ConflictException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ConflictException"
    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

-- | Unexpected error while processing the request. Retry the request.
_InternalServerException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InternalServerException :: forall a. AsError a => Fold a ServiceError
_InternalServerException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InternalServerException"
    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 request references a resource that does not exist.
_ResourceNotFoundException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ResourceNotFoundException :: forall a. AsError a => Fold a ServiceError
_ResourceNotFoundException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ResourceNotFoundException"
    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 request would cause a service quota to be exceeded.
_ServiceQuotaExceededException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ServiceQuotaExceededException :: forall a. AsError a => Fold a ServiceError
_ServiceQuotaExceededException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ServiceQuotaExceededException"
    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
402

-- | The service was unavailable. Retry the request.
_ServiceUnavailableException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ServiceUnavailableException :: forall a. AsError a => Fold a ServiceError
_ServiceUnavailableException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ServiceUnavailableException"
    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
503

-- | The request was denied because of request throttling. Retry the request.
_ThrottlingException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ThrottlingException :: forall a. AsError a => Fold a ServiceError
_ThrottlingException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ThrottlingException"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
429

-- | The value of a parameter in the request caused an error.
_ValidationException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ValidationException :: forall a. AsError a => Fold a ServiceError
_ValidationException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ValidationException"
    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