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

    -- * Errors
    _AlreadyExistsException,
    _ClientTokenConflictException,
    _ConcurrentModificationException,
    _ConcurrentOperationException,
    _GeneralServiceException,
    _HandlerFailureException,
    _HandlerInternalFailureException,
    _InvalidCredentialsException,
    _InvalidRequestException,
    _NetworkFailureException,
    _NotStabilizedException,
    _NotUpdatableException,
    _PrivateTypeException,
    _RequestTokenNotFoundException,
    _ResourceConflictException,
    _ResourceNotFoundException,
    _ServiceInternalErrorException,
    _ServiceLimitExceededException,
    _ThrottlingException,
    _TypeNotFoundException,
    _UnsupportedActionException,

    -- * HandlerErrorCode
    HandlerErrorCode (..),

    -- * Operation
    Operation (..),

    -- * OperationStatus
    OperationStatus (..),

    -- * ProgressEvent
    ProgressEvent (..),
    newProgressEvent,
    progressEvent_errorCode,
    progressEvent_eventTime,
    progressEvent_identifier,
    progressEvent_operation,
    progressEvent_operationStatus,
    progressEvent_requestToken,
    progressEvent_resourceModel,
    progressEvent_retryAfter,
    progressEvent_statusMessage,
    progressEvent_typeName,

    -- * ResourceDescription
    ResourceDescription (..),
    newResourceDescription,
    resourceDescription_identifier,
    resourceDescription_properties,

    -- * ResourceRequestStatusFilter
    ResourceRequestStatusFilter (..),
    newResourceRequestStatusFilter,
    resourceRequestStatusFilter_operationStatuses,
    resourceRequestStatusFilter_operations,
  )
where

import Amazonka.CloudControl.Types.HandlerErrorCode
import Amazonka.CloudControl.Types.Operation
import Amazonka.CloudControl.Types.OperationStatus
import Amazonka.CloudControl.Types.ProgressEvent
import Amazonka.CloudControl.Types.ResourceDescription
import Amazonka.CloudControl.Types.ResourceRequestStatusFilter
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 @2021-09-30@ of the Amazon Cloud Control API SDK configuration.
defaultService :: Core.Service
defaultService :: Service
defaultService =
  Core.Service
    { $sel:abbrev:Service :: Abbrev
Core.abbrev = Abbrev
"CloudControl",
      $sel:signer:Service :: Signer
Core.signer = Signer
Sign.v4,
      $sel:endpointPrefix:Service :: ByteString
Core.endpointPrefix = ByteString
"cloudcontrolapi",
      $sel:signingName:Service :: ByteString
Core.signingName = ByteString
"cloudcontrolapi",
      $sel:version:Service :: ByteString
Core.version = ByteString
"2021-09-30",
      $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
"CloudControl",
      $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

-- | The resource with the name requested already exists.
_AlreadyExistsException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_AlreadyExistsException :: forall a. AsError a => Fold a ServiceError
_AlreadyExistsException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"AlreadyExistsException"

-- | The specified client token has already been used in another resource
-- request.
--
-- It\'s best practice for client tokens to be unique for each resource
-- operation request. However, client token expire after 36 hours.
_ClientTokenConflictException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ClientTokenConflictException :: forall a. AsError a => Fold a ServiceError
_ClientTokenConflictException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ClientTokenConflictException"

-- | The resource is currently being modified by another operation.
_ConcurrentModificationException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ConcurrentModificationException :: forall a. AsError a => Fold a ServiceError
_ConcurrentModificationException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ConcurrentModificationException"

-- | Another resource operation is currently being performed on this
-- resource.
_ConcurrentOperationException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ConcurrentOperationException :: forall a. AsError a => Fold a ServiceError
_ConcurrentOperationException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ConcurrentOperationException"

-- | The resource handler has returned that the downstream service generated
-- an error that doesn\'t map to any other handler error code.
_GeneralServiceException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_GeneralServiceException :: forall a. AsError a => Fold a ServiceError
_GeneralServiceException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"GeneralServiceException"

-- | The resource handler has failed without a returning a more specific
-- error code. This can include timeouts.
_HandlerFailureException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_HandlerFailureException :: forall a. AsError a => Fold a ServiceError
_HandlerFailureException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"HandlerFailureException"

-- | The resource handler has returned that an unexpected error occurred
-- within the resource handler.
_HandlerInternalFailureException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_HandlerInternalFailureException :: forall a. AsError a => Fold a ServiceError
_HandlerInternalFailureException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"HandlerInternalFailureException"

-- | The resource handler has returned that the credentials provided by the
-- user are invalid.
_InvalidCredentialsException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidCredentialsException :: forall a. AsError a => Fold a ServiceError
_InvalidCredentialsException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidCredentialsException"

-- | The resource handler has returned that invalid input from the user has
-- generated a generic exception.
_InvalidRequestException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidRequestException :: forall a. AsError a => Fold a ServiceError
_InvalidRequestException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidRequestException"

-- | The resource handler has returned that the request couldn\'t be
-- completed due to networking issues, such as a failure to receive a
-- response from the server.
_NetworkFailureException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NetworkFailureException :: forall a. AsError a => Fold a ServiceError
_NetworkFailureException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NetworkFailureException"

-- | The resource handler has returned that the downstream resource failed to
-- complete all of its ready-state checks.
_NotStabilizedException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NotStabilizedException :: forall a. AsError a => Fold a ServiceError
_NotStabilizedException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NotStabilizedException"

-- | One or more properties included in this resource operation are defined
-- as create-only, and therefore can\'t be updated.
_NotUpdatableException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NotUpdatableException :: forall a. AsError a => Fold a ServiceError
_NotUpdatableException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NotUpdatableException"

-- | Cloud Control API hasn\'t received a valid response from the resource
-- handler, due to a configuration error. This includes issues such as the
-- resource handler returning an invalid response, or timing out.
_PrivateTypeException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_PrivateTypeException :: forall a. AsError a => Fold a ServiceError
_PrivateTypeException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"PrivateTypeException"

-- | A resource operation with the specified request token can\'t be found.
_RequestTokenNotFoundException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_RequestTokenNotFoundException :: forall a. AsError a => Fold a ServiceError
_RequestTokenNotFoundException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"RequestTokenNotFoundException"

-- | The resource is temporarily unavailable to be acted upon. For example,
-- if the resource is currently undergoing an operation and can\'t be acted
-- upon until that operation is finished.
_ResourceConflictException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ResourceConflictException :: forall a. AsError a => Fold a ServiceError
_ResourceConflictException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ResourceConflictException"

-- | A resource with the specified identifier can\'t be found.
_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"

-- | The resource handler has returned that the downstream service returned
-- an internal error, typically with a @5XX HTTP@ status code.
_ServiceInternalErrorException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ServiceInternalErrorException :: forall a. AsError a => Fold a ServiceError
_ServiceInternalErrorException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ServiceInternalErrorException"

-- | The resource handler has returned that a non-transient resource limit
-- was reached on the service side.
_ServiceLimitExceededException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ServiceLimitExceededException :: forall a. AsError a => Fold a ServiceError
_ServiceLimitExceededException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ServiceLimitExceededException"

-- | The request was denied due to request throttling.
_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"

-- | The specified extension doesn\'t exist in the CloudFormation registry.
_TypeNotFoundException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TypeNotFoundException :: forall a. AsError a => Fold a ServiceError
_TypeNotFoundException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TypeNotFoundException"

-- | The specified resource doesn\'t support this resource operation.
_UnsupportedActionException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_UnsupportedActionException :: forall a. AsError a => Fold a ServiceError
_UnsupportedActionException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"UnsupportedActionException"