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

    -- * Errors
    _AccountHasOngoingImportException,
    _AccountNotFoundException,
    _AccountNotRegisteredException,
    _AccountRegisteredException,
    _CannotDelegateManagementAccountException,
    _ChannelARNInvalidException,
    _ChannelNotFoundException,
    _CloudTrailARNInvalidException,
    _CloudTrailAccessNotEnabledException,
    _CloudTrailInvalidClientTokenIdException,
    _CloudWatchLogsDeliveryUnavailableException,
    _ConflictException,
    _DelegatedAdminAccountLimitExceededException,
    _EventDataStoreARNInvalidException,
    _EventDataStoreAlreadyExistsException,
    _EventDataStoreHasOngoingImportException,
    _EventDataStoreMaxLimitExceededException,
    _EventDataStoreNotFoundException,
    _EventDataStoreTerminationProtectedException,
    _ImportNotFoundException,
    _InactiveEventDataStoreException,
    _InactiveQueryException,
    _InsightNotEnabledException,
    _InsufficientDependencyServiceAccessPermissionException,
    _InsufficientEncryptionPolicyException,
    _InsufficientS3BucketPolicyException,
    _InsufficientSnsTopicPolicyException,
    _InvalidCloudWatchLogsLogGroupArnException,
    _InvalidCloudWatchLogsRoleArnException,
    _InvalidDateRangeException,
    _InvalidEventCategoryException,
    _InvalidEventDataStoreCategoryException,
    _InvalidEventDataStoreStatusException,
    _InvalidEventSelectorsException,
    _InvalidHomeRegionException,
    _InvalidImportSourceException,
    _InvalidInsightSelectorsException,
    _InvalidKmsKeyIdException,
    _InvalidLookupAttributesException,
    _InvalidMaxResultsException,
    _InvalidNextTokenException,
    _InvalidParameterCombinationException,
    _InvalidParameterException,
    _InvalidQueryStatementException,
    _InvalidQueryStatusException,
    _InvalidS3BucketNameException,
    _InvalidS3PrefixException,
    _InvalidSnsTopicNameException,
    _InvalidTagParameterException,
    _InvalidTimeRangeException,
    _InvalidTokenException,
    _InvalidTrailNameException,
    _KmsException,
    _KmsKeyDisabledException,
    _KmsKeyNotFoundException,
    _MaxConcurrentQueriesException,
    _MaximumNumberOfTrailsExceededException,
    _NoManagementAccountSLRExistsException,
    _NotOrganizationManagementAccountException,
    _NotOrganizationMasterAccountException,
    _OperationNotPermittedException,
    _OrganizationNotInAllFeaturesModeException,
    _OrganizationsNotInUseException,
    _QueryIdNotFoundException,
    _ResourceNotFoundException,
    _ResourceTypeNotSupportedException,
    _S3BucketDoesNotExistException,
    _TagsLimitExceededException,
    _TrailAlreadyExistsException,
    _TrailNotFoundException,
    _TrailNotProvidedException,
    _UnsupportedOperationException,

    -- * DeliveryStatus
    DeliveryStatus (..),

    -- * DestinationType
    DestinationType (..),

    -- * EventCategory
    EventCategory (..),

    -- * EventDataStoreStatus
    EventDataStoreStatus (..),

    -- * ImportFailureStatus
    ImportFailureStatus (..),

    -- * ImportStatus
    ImportStatus (..),

    -- * InsightType
    InsightType (..),

    -- * LookupAttributeKey
    LookupAttributeKey (..),

    -- * QueryStatus
    QueryStatus (..),

    -- * ReadWriteType
    ReadWriteType (..),

    -- * AdvancedEventSelector
    AdvancedEventSelector (..),
    newAdvancedEventSelector,
    advancedEventSelector_name,
    advancedEventSelector_fieldSelectors,

    -- * AdvancedFieldSelector
    AdvancedFieldSelector (..),
    newAdvancedFieldSelector,
    advancedFieldSelector_endsWith,
    advancedFieldSelector_equals,
    advancedFieldSelector_notEndsWith,
    advancedFieldSelector_notEquals,
    advancedFieldSelector_notStartsWith,
    advancedFieldSelector_startsWith,
    advancedFieldSelector_field,

    -- * Channel
    Channel (..),
    newChannel,
    channel_channelArn,
    channel_name,

    -- * DataResource
    DataResource (..),
    newDataResource,
    dataResource_type,
    dataResource_values,

    -- * Destination
    Destination (..),
    newDestination,
    destination_type,
    destination_location,

    -- * Event
    Event (..),
    newEvent,
    event_accessKeyId,
    event_cloudTrailEvent,
    event_eventId,
    event_eventName,
    event_eventSource,
    event_eventTime,
    event_readOnly,
    event_resources,
    event_username,

    -- * EventDataStore
    EventDataStore (..),
    newEventDataStore,
    eventDataStore_advancedEventSelectors,
    eventDataStore_createdTimestamp,
    eventDataStore_eventDataStoreArn,
    eventDataStore_multiRegionEnabled,
    eventDataStore_name,
    eventDataStore_organizationEnabled,
    eventDataStore_retentionPeriod,
    eventDataStore_status,
    eventDataStore_terminationProtectionEnabled,
    eventDataStore_updatedTimestamp,

    -- * EventSelector
    EventSelector (..),
    newEventSelector,
    eventSelector_dataResources,
    eventSelector_excludeManagementEventSources,
    eventSelector_includeManagementEvents,
    eventSelector_readWriteType,

    -- * ImportFailureListItem
    ImportFailureListItem (..),
    newImportFailureListItem,
    importFailureListItem_errorMessage,
    importFailureListItem_errorType,
    importFailureListItem_lastUpdatedTime,
    importFailureListItem_location,
    importFailureListItem_status,

    -- * ImportSource
    ImportSource (..),
    newImportSource,
    importSource_s3,

    -- * ImportStatistics
    ImportStatistics (..),
    newImportStatistics,
    importStatistics_eventsCompleted,
    importStatistics_failedEntries,
    importStatistics_filesCompleted,
    importStatistics_prefixesCompleted,
    importStatistics_prefixesFound,

    -- * ImportsListItem
    ImportsListItem (..),
    newImportsListItem,
    importsListItem_createdTimestamp,
    importsListItem_destinations,
    importsListItem_importId,
    importsListItem_importStatus,
    importsListItem_updatedTimestamp,

    -- * InsightSelector
    InsightSelector (..),
    newInsightSelector,
    insightSelector_insightType,

    -- * LookupAttribute
    LookupAttribute (..),
    newLookupAttribute,
    lookupAttribute_attributeKey,
    lookupAttribute_attributeValue,

    -- * PublicKey
    PublicKey (..),
    newPublicKey,
    publicKey_fingerprint,
    publicKey_validityEndTime,
    publicKey_validityStartTime,
    publicKey_value,

    -- * Query
    Query (..),
    newQuery,
    query_creationTime,
    query_queryId,
    query_queryStatus,

    -- * QueryStatistics
    QueryStatistics (..),
    newQueryStatistics,
    queryStatistics_bytesScanned,
    queryStatistics_resultsCount,
    queryStatistics_totalResultsCount,

    -- * QueryStatisticsForDescribeQuery
    QueryStatisticsForDescribeQuery (..),
    newQueryStatisticsForDescribeQuery,
    queryStatisticsForDescribeQuery_bytesScanned,
    queryStatisticsForDescribeQuery_creationTime,
    queryStatisticsForDescribeQuery_eventsMatched,
    queryStatisticsForDescribeQuery_eventsScanned,
    queryStatisticsForDescribeQuery_executionTimeInMillis,

    -- * Resource
    Resource (..),
    newResource,
    resource_resourceName,
    resource_resourceType,

    -- * ResourceTag
    ResourceTag (..),
    newResourceTag,
    resourceTag_resourceId,
    resourceTag_tagsList,

    -- * S3ImportSource
    S3ImportSource (..),
    newS3ImportSource,
    s3ImportSource_s3LocationUri,
    s3ImportSource_s3BucketRegion,
    s3ImportSource_s3BucketAccessRoleArn,

    -- * SourceConfig
    SourceConfig (..),
    newSourceConfig,
    sourceConfig_advancedEventSelectors,
    sourceConfig_applyToAllRegions,

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

    -- * Trail
    Trail (..),
    newTrail,
    trail_cloudWatchLogsLogGroupArn,
    trail_cloudWatchLogsRoleArn,
    trail_hasCustomEventSelectors,
    trail_hasInsightSelectors,
    trail_homeRegion,
    trail_includeGlobalServiceEvents,
    trail_isMultiRegionTrail,
    trail_isOrganizationTrail,
    trail_kmsKeyId,
    trail_logFileValidationEnabled,
    trail_name,
    trail_s3BucketName,
    trail_s3KeyPrefix,
    trail_snsTopicARN,
    trail_snsTopicName,
    trail_trailARN,

    -- * TrailInfo
    TrailInfo (..),
    newTrailInfo,
    trailInfo_homeRegion,
    trailInfo_name,
    trailInfo_trailARN,
  )
where

import Amazonka.CloudTrail.Types.AdvancedEventSelector
import Amazonka.CloudTrail.Types.AdvancedFieldSelector
import Amazonka.CloudTrail.Types.Channel
import Amazonka.CloudTrail.Types.DataResource
import Amazonka.CloudTrail.Types.DeliveryStatus
import Amazonka.CloudTrail.Types.Destination
import Amazonka.CloudTrail.Types.DestinationType
import Amazonka.CloudTrail.Types.Event
import Amazonka.CloudTrail.Types.EventCategory
import Amazonka.CloudTrail.Types.EventDataStore
import Amazonka.CloudTrail.Types.EventDataStoreStatus
import Amazonka.CloudTrail.Types.EventSelector
import Amazonka.CloudTrail.Types.ImportFailureListItem
import Amazonka.CloudTrail.Types.ImportFailureStatus
import Amazonka.CloudTrail.Types.ImportSource
import Amazonka.CloudTrail.Types.ImportStatistics
import Amazonka.CloudTrail.Types.ImportStatus
import Amazonka.CloudTrail.Types.ImportsListItem
import Amazonka.CloudTrail.Types.InsightSelector
import Amazonka.CloudTrail.Types.InsightType
import Amazonka.CloudTrail.Types.LookupAttribute
import Amazonka.CloudTrail.Types.LookupAttributeKey
import Amazonka.CloudTrail.Types.PublicKey
import Amazonka.CloudTrail.Types.Query
import Amazonka.CloudTrail.Types.QueryStatistics
import Amazonka.CloudTrail.Types.QueryStatisticsForDescribeQuery
import Amazonka.CloudTrail.Types.QueryStatus
import Amazonka.CloudTrail.Types.ReadWriteType
import Amazonka.CloudTrail.Types.Resource
import Amazonka.CloudTrail.Types.ResourceTag
import Amazonka.CloudTrail.Types.S3ImportSource
import Amazonka.CloudTrail.Types.SourceConfig
import Amazonka.CloudTrail.Types.Tag
import Amazonka.CloudTrail.Types.Trail
import Amazonka.CloudTrail.Types.TrailInfo
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 @2013-11-01@ of the Amazon CloudTrail SDK configuration.
defaultService :: Core.Service
defaultService :: Service
defaultService =
  Core.Service
    { $sel:abbrev:Service :: Abbrev
Core.abbrev = Abbrev
"CloudTrail",
      $sel:signer:Service :: Signer
Core.signer = Signer
Sign.v4,
      $sel:endpointPrefix:Service :: ByteString
Core.endpointPrefix = ByteString
"cloudtrail",
      $sel:signingName:Service :: ByteString
Core.signingName = ByteString
"cloudtrail",
      $sel:version:Service :: ByteString
Core.version = ByteString
"2013-11-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
"CloudTrail",
      $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

-- | This exception is thrown when you start a new import and a previous
-- import is still in progress.
_AccountHasOngoingImportException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_AccountHasOngoingImportException :: forall a. AsError a => Fold a ServiceError
_AccountHasOngoingImportException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"AccountHasOngoingImportException"

-- | This exception is thrown when when the specified account is not found or
-- not part of an organization.
_AccountNotFoundException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_AccountNotFoundException :: forall a. AsError a => Fold a ServiceError
_AccountNotFoundException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"AccountNotFoundException"

-- | This exception is thrown when the specified account is not registered as
-- the CloudTrail delegated administrator.
_AccountNotRegisteredException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_AccountNotRegisteredException :: forall a. AsError a => Fold a ServiceError
_AccountNotRegisteredException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"AccountNotRegisteredException"

-- | This exception is thrown when the account is already registered as the
-- CloudTrail delegated administrator.
_AccountRegisteredException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_AccountRegisteredException :: forall a. AsError a => Fold a ServiceError
_AccountRegisteredException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"AccountRegisteredException"

-- | This exception is thrown when the management account of an organization
-- is registered as the CloudTrail delegated administrator.
_CannotDelegateManagementAccountException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CannotDelegateManagementAccountException :: forall a. AsError a => Fold a ServiceError
_CannotDelegateManagementAccountException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"CannotDelegateManagementAccountException"

-- | This exception is thrown when the specified value of @ChannelARN@ is not
-- valid.
_ChannelARNInvalidException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ChannelARNInvalidException :: forall a. AsError a => Fold a ServiceError
_ChannelARNInvalidException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ChannelARNInvalidException"

-- | The specified channel was not found.
_ChannelNotFoundException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ChannelNotFoundException :: forall a. AsError a => Fold a ServiceError
_ChannelNotFoundException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ChannelNotFoundException"

-- | This exception is thrown when an operation is called with a trail ARN
-- that is not valid. The following is the format of a trail ARN.
--
-- @arn:aws:cloudtrail:us-east-2:123456789012:trail\/MyTrail@
_CloudTrailARNInvalidException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CloudTrailARNInvalidException :: forall a. AsError a => Fold a ServiceError
_CloudTrailARNInvalidException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"CloudTrailARNInvalidException"

-- | This exception is thrown when trusted access has not been enabled
-- between CloudTrail and Organizations. For more information, see
-- <https://docs.aws.amazon.com/organizations/latest/userguide/orgs_integrate_services.html Enabling Trusted Access with Other Amazon Web Services Services>
-- and
-- <https://docs.aws.amazon.com/awscloudtrail/latest/userguide/creating-an-organizational-trail-prepare.html Prepare For Creating a Trail For Your Organization>.
_CloudTrailAccessNotEnabledException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CloudTrailAccessNotEnabledException :: forall a. AsError a => Fold a ServiceError
_CloudTrailAccessNotEnabledException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"CloudTrailAccessNotEnabledException"

-- | This exception is thrown when a call results in the
-- @InvalidClientTokenId@ error code. This can occur when you are creating
-- or updating a trail to send notifications to an Amazon SNS topic that is
-- in a suspended Amazon Web Services account.
_CloudTrailInvalidClientTokenIdException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CloudTrailInvalidClientTokenIdException :: forall a. AsError a => Fold a ServiceError
_CloudTrailInvalidClientTokenIdException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"CloudTrailInvalidClientTokenIdException"

-- | Cannot set a CloudWatch Logs delivery for this region.
_CloudWatchLogsDeliveryUnavailableException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CloudWatchLogsDeliveryUnavailableException :: forall a. AsError a => Fold a ServiceError
_CloudWatchLogsDeliveryUnavailableException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"CloudWatchLogsDeliveryUnavailableException"

-- | This exception is thrown when the specified resource is not ready for an
-- operation. This can occur when you try to run an operation on a resource
-- before CloudTrail has time to fully load the resource. If this exception
-- occurs, wait a few minutes, and then try the operation again.
_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"

-- | This exception is thrown when the maximum number of CloudTrail delegated
-- administrators is reached.
_DelegatedAdminAccountLimitExceededException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DelegatedAdminAccountLimitExceededException :: forall a. AsError a => Fold a ServiceError
_DelegatedAdminAccountLimitExceededException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"DelegatedAdminAccountLimitExceededException"

-- | The specified event data store ARN is not valid or does not map to an
-- event data store in your account.
_EventDataStoreARNInvalidException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_EventDataStoreARNInvalidException :: forall a. AsError a => Fold a ServiceError
_EventDataStoreARNInvalidException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"EventDataStoreARNInvalidException"

-- | An event data store with that name already exists.
_EventDataStoreAlreadyExistsException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_EventDataStoreAlreadyExistsException :: forall a. AsError a => Fold a ServiceError
_EventDataStoreAlreadyExistsException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"EventDataStoreAlreadyExistsException"

-- | This exception is thrown when you try to update or delete an event data
-- store that currently has an import in progress.
_EventDataStoreHasOngoingImportException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_EventDataStoreHasOngoingImportException :: forall a. AsError a => Fold a ServiceError
_EventDataStoreHasOngoingImportException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"EventDataStoreHasOngoingImportException"

-- | Your account has used the maximum number of event data stores.
_EventDataStoreMaxLimitExceededException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_EventDataStoreMaxLimitExceededException :: forall a. AsError a => Fold a ServiceError
_EventDataStoreMaxLimitExceededException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"EventDataStoreMaxLimitExceededException"

-- | The specified event data store was not found.
_EventDataStoreNotFoundException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_EventDataStoreNotFoundException :: forall a. AsError a => Fold a ServiceError
_EventDataStoreNotFoundException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"EventDataStoreNotFoundException"

-- | The event data store cannot be deleted because termination protection is
-- enabled for it.
_EventDataStoreTerminationProtectedException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_EventDataStoreTerminationProtectedException :: forall a. AsError a => Fold a ServiceError
_EventDataStoreTerminationProtectedException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"EventDataStoreTerminationProtectedException"

-- | The specified import was not found.
_ImportNotFoundException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ImportNotFoundException :: forall a. AsError a => Fold a ServiceError
_ImportNotFoundException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ImportNotFoundException"

-- | The event data store is inactive.
_InactiveEventDataStoreException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InactiveEventDataStoreException :: forall a. AsError a => Fold a ServiceError
_InactiveEventDataStoreException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InactiveEventDataStoreException"

-- | The specified query cannot be canceled because it is in the @FINISHED@,
-- @FAILED@, @TIMED_OUT@, or @CANCELLED@ state.
_InactiveQueryException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InactiveQueryException :: forall a. AsError a => Fold a ServiceError
_InactiveQueryException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InactiveQueryException"

-- | If you run @GetInsightSelectors@ on a trail that does not have Insights
-- events enabled, the operation throws the exception
-- @InsightNotEnabledException@.
_InsightNotEnabledException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InsightNotEnabledException :: forall a. AsError a => Fold a ServiceError
_InsightNotEnabledException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InsightNotEnabledException"

-- | This exception is thrown when the IAM user or role that is used to
-- create the organization resource lacks one or more required permissions
-- for creating an organization resource in a required service.
_InsufficientDependencyServiceAccessPermissionException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InsufficientDependencyServiceAccessPermissionException :: forall a. AsError a => Fold a ServiceError
_InsufficientDependencyServiceAccessPermissionException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InsufficientDependencyServiceAccessPermissionException"

-- | This exception is thrown when the policy on the S3 bucket or KMS key
-- does not have sufficient permissions for the operation.
_InsufficientEncryptionPolicyException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InsufficientEncryptionPolicyException :: forall a. AsError a => Fold a ServiceError
_InsufficientEncryptionPolicyException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InsufficientEncryptionPolicyException"

-- | This exception is thrown when the policy on the S3 bucket is not
-- sufficient.
_InsufficientS3BucketPolicyException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InsufficientS3BucketPolicyException :: forall a. AsError a => Fold a ServiceError
_InsufficientS3BucketPolicyException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InsufficientS3BucketPolicyException"

-- | This exception is thrown when the policy on the Amazon SNS topic is not
-- sufficient.
_InsufficientSnsTopicPolicyException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InsufficientSnsTopicPolicyException :: forall a. AsError a => Fold a ServiceError
_InsufficientSnsTopicPolicyException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InsufficientSnsTopicPolicyException"

-- | This exception is thrown when the provided CloudWatch Logs log group is
-- not valid.
_InvalidCloudWatchLogsLogGroupArnException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidCloudWatchLogsLogGroupArnException :: forall a. AsError a => Fold a ServiceError
_InvalidCloudWatchLogsLogGroupArnException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidCloudWatchLogsLogGroupArnException"

-- | This exception is thrown when the provided role is not valid.
_InvalidCloudWatchLogsRoleArnException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidCloudWatchLogsRoleArnException :: forall a. AsError a => Fold a ServiceError
_InvalidCloudWatchLogsRoleArnException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidCloudWatchLogsRoleArnException"

-- | A date range for the query was specified that is not valid. Be sure that
-- the start time is chronologically before the end time. For more
-- information about writing a query, see
-- <https://docs.aws.amazon.com/awscloudtrail/latest/userguide/query-create-edit-query.html Create or edit a query>
-- in the /CloudTrail User Guide/.
_InvalidDateRangeException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidDateRangeException :: forall a. AsError a => Fold a ServiceError
_InvalidDateRangeException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidDateRangeException"

-- | Occurs if an event category that is not valid is specified as a value of
-- @EventCategory@.
_InvalidEventCategoryException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidEventCategoryException :: forall a. AsError a => Fold a ServiceError
_InvalidEventCategoryException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidEventCategoryException"

-- | This exception is thrown when event categories of specified event data
-- stores are not valid.
_InvalidEventDataStoreCategoryException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidEventDataStoreCategoryException :: forall a. AsError a => Fold a ServiceError
_InvalidEventDataStoreCategoryException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidEventDataStoreCategoryException"

-- | The event data store is not in a status that supports the operation.
_InvalidEventDataStoreStatusException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidEventDataStoreStatusException :: forall a. AsError a => Fold a ServiceError
_InvalidEventDataStoreStatusException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidEventDataStoreStatusException"

-- | This exception is thrown when the @PutEventSelectors@ operation is
-- called with a number of event selectors, advanced event selectors, or
-- data resources that is not valid. The combination of event selectors or
-- advanced event selectors and data resources is not valid. A trail can
-- have up to 5 event selectors. If a trail uses advanced event selectors,
-- a maximum of 500 total values for all conditions in all advanced event
-- selectors is allowed. A trail is limited to 250 data resources. These
-- data resources can be distributed across event selectors, but the
-- overall total cannot exceed 250.
--
-- You can:
--
-- -   Specify a valid number of event selectors (1 to 5) for a trail.
--
-- -   Specify a valid number of data resources (1 to 250) for an event
--     selector. The limit of number of resources on an individual event
--     selector is configurable up to 250. However, this upper limit is
--     allowed only if the total number of data resources does not exceed
--     250 across all event selectors for a trail.
--
-- -   Specify up to 500 values for all conditions in all advanced event
--     selectors for a trail.
--
-- -   Specify a valid value for a parameter. For example, specifying the
--     @ReadWriteType@ parameter with a value of @read-only@ is not valid.
_InvalidEventSelectorsException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidEventSelectorsException :: forall a. AsError a => Fold a ServiceError
_InvalidEventSelectorsException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidEventSelectorsException"

-- | This exception is thrown when an operation is called on a trail from a
-- region other than the region in which the trail was created.
_InvalidHomeRegionException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidHomeRegionException :: forall a. AsError a => Fold a ServiceError
_InvalidHomeRegionException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidHomeRegionException"

-- | This exception is thrown when the provided source S3 bucket is not valid
-- for import.
_InvalidImportSourceException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidImportSourceException :: forall a. AsError a => Fold a ServiceError
_InvalidImportSourceException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidImportSourceException"

-- | The formatting or syntax of the @InsightSelectors@ JSON statement in
-- your @PutInsightSelectors@ or @GetInsightSelectors@ request is not
-- valid, or the specified insight type in the @InsightSelectors@ statement
-- is not a valid insight type.
_InvalidInsightSelectorsException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidInsightSelectorsException :: forall a. AsError a => Fold a ServiceError
_InvalidInsightSelectorsException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidInsightSelectorsException"

-- | This exception is thrown when the KMS key ARN is not valid.
_InvalidKmsKeyIdException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidKmsKeyIdException :: forall a. AsError a => Fold a ServiceError
_InvalidKmsKeyIdException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidKmsKeyIdException"

-- | Occurs when a lookup attribute is specified that is not valid.
_InvalidLookupAttributesException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidLookupAttributesException :: forall a. AsError a => Fold a ServiceError
_InvalidLookupAttributesException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidLookupAttributesException"

-- | This exception is thrown if the limit specified is not valid.
_InvalidMaxResultsException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidMaxResultsException :: forall a. AsError a => Fold a ServiceError
_InvalidMaxResultsException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidMaxResultsException"

-- | A token that is not valid, or a token that was previously used in a
-- request with different parameters. This exception is thrown if the token
-- is not valid.
_InvalidNextTokenException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidNextTokenException :: forall a. AsError a => Fold a ServiceError
_InvalidNextTokenException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidNextTokenException"

-- | This exception is thrown when the combination of parameters provided is
-- not valid.
_InvalidParameterCombinationException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidParameterCombinationException :: forall a. AsError a => Fold a ServiceError
_InvalidParameterCombinationException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidParameterCombinationException"

-- | The request includes a parameter that is not valid.
_InvalidParameterException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidParameterException :: forall a. AsError a => Fold a ServiceError
_InvalidParameterException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidParameterException"

-- | The query that was submitted has validation errors, or uses incorrect
-- syntax or unsupported keywords. For more information about writing a
-- query, see
-- <https://docs.aws.amazon.com/awscloudtrail/latest/userguide/query-create-edit-query.html Create or edit a query>
-- in the /CloudTrail User Guide/.
_InvalidQueryStatementException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidQueryStatementException :: forall a. AsError a => Fold a ServiceError
_InvalidQueryStatementException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidQueryStatementException"

-- | The query status is not valid for the operation.
_InvalidQueryStatusException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidQueryStatusException :: forall a. AsError a => Fold a ServiceError
_InvalidQueryStatusException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidQueryStatusException"

-- | This exception is thrown when the provided S3 bucket name is not valid.
_InvalidS3BucketNameException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidS3BucketNameException :: forall a. AsError a => Fold a ServiceError
_InvalidS3BucketNameException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidS3BucketNameException"

-- | This exception is thrown when the provided S3 prefix is not valid.
_InvalidS3PrefixException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidS3PrefixException :: forall a. AsError a => Fold a ServiceError
_InvalidS3PrefixException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidS3PrefixException"

-- | This exception is thrown when the provided SNS topic name is not valid.
_InvalidSnsTopicNameException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidSnsTopicNameException :: forall a. AsError a => Fold a ServiceError
_InvalidSnsTopicNameException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidSnsTopicNameException"

-- | This exception is thrown when the specified tag key or values are not
-- valid. It can also occur if there are duplicate tags or too many tags on
-- the resource.
_InvalidTagParameterException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidTagParameterException :: forall a. AsError a => Fold a ServiceError
_InvalidTagParameterException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidTagParameterException"

-- | Occurs if the timestamp values are not valid. Either the start time
-- occurs after the end time, or the time range is outside the range of
-- possible values.
_InvalidTimeRangeException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidTimeRangeException :: forall a. AsError a => Fold a ServiceError
_InvalidTimeRangeException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidTimeRangeException"

-- | Reserved for future use.
_InvalidTokenException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidTokenException :: forall a. AsError a => Fold a ServiceError
_InvalidTokenException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidTokenException"

-- | This exception is thrown when the provided trail name is not valid.
-- Trail names must meet the following requirements:
--
-- -   Contain only ASCII letters (a-z, A-Z), numbers (0-9), periods (.),
--     underscores (_), or dashes (-)
--
-- -   Start with a letter or number, and end with a letter or number
--
-- -   Be between 3 and 128 characters
--
-- -   Have no adjacent periods, underscores or dashes. Names like
--     @my-_namespace@ and @my--namespace@ are not valid.
--
-- -   Not be in IP address format (for example, 192.168.5.4)
_InvalidTrailNameException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidTrailNameException :: forall a. AsError a => Fold a ServiceError
_InvalidTrailNameException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidTrailNameException"

-- | This exception is thrown when there is an issue with the specified KMS
-- key and the trail or event data store can\'t be updated.
_KmsException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_KmsException :: forall a. AsError a => Fold a ServiceError
_KmsException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"KmsException"

-- | This exception is no longer in use.
_KmsKeyDisabledException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_KmsKeyDisabledException :: forall a. AsError a => Fold a ServiceError
_KmsKeyDisabledException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"KmsKeyDisabledException"

-- | This exception is thrown when the KMS key does not exist, when the S3
-- bucket and the KMS key are not in the same region, or when the KMS key
-- associated with the Amazon SNS topic either does not exist or is not in
-- the same region.
_KmsKeyNotFoundException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_KmsKeyNotFoundException :: forall a. AsError a => Fold a ServiceError
_KmsKeyNotFoundException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"KmsKeyNotFoundException"

-- | You are already running the maximum number of concurrent queries. Wait a
-- minute for some queries to finish, and then run the query again.
_MaxConcurrentQueriesException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_MaxConcurrentQueriesException :: forall a. AsError a => Fold a ServiceError
_MaxConcurrentQueriesException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"MaxConcurrentQueriesException"

-- | This exception is thrown when the maximum number of trails is reached.
_MaximumNumberOfTrailsExceededException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_MaximumNumberOfTrailsExceededException :: forall a. AsError a => Fold a ServiceError
_MaximumNumberOfTrailsExceededException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"MaximumNumberOfTrailsExceededException"

-- | This exception is thrown when the management account does not have a
-- service-linked role.
_NoManagementAccountSLRExistsException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoManagementAccountSLRExistsException :: forall a. AsError a => Fold a ServiceError
_NoManagementAccountSLRExistsException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoManagementAccountSLRExistsException"

-- | This exception is thrown when the account making the request is not the
-- organization\'s management account.
_NotOrganizationManagementAccountException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NotOrganizationManagementAccountException :: forall a. AsError a => Fold a ServiceError
_NotOrganizationManagementAccountException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NotOrganizationManagementAccountException"

-- | This exception is thrown when the Amazon Web Services account making the
-- request to create or update an organization trail or event data store is
-- not the management account for an organization in Organizations. For
-- more information, see
-- <https://docs.aws.amazon.com/awscloudtrail/latest/userguide/creating-an-organizational-trail-prepare.html Prepare For Creating a Trail For Your Organization>
-- or
-- <https://docs.aws.amazon.com/awscloudtrail/latest/userguide/query-event-data-store.html Create an event data store>.
_NotOrganizationMasterAccountException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NotOrganizationMasterAccountException :: forall a. AsError a => Fold a ServiceError
_NotOrganizationMasterAccountException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NotOrganizationMasterAccountException"

-- | This exception is thrown when the requested operation is not permitted.
_OperationNotPermittedException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_OperationNotPermittedException :: forall a. AsError a => Fold a ServiceError
_OperationNotPermittedException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"OperationNotPermittedException"

-- | This exception is thrown when Organizations is not configured to support
-- all features. All features must be enabled in Organizations to support
-- creating an organization trail or event data store.
_OrganizationNotInAllFeaturesModeException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_OrganizationNotInAllFeaturesModeException :: forall a. AsError a => Fold a ServiceError
_OrganizationNotInAllFeaturesModeException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"OrganizationNotInAllFeaturesModeException"

-- | This exception is thrown when the request is made from an Amazon Web
-- Services account that is not a member of an organization. To make this
-- request, sign in using the credentials of an account that belongs to an
-- organization.
_OrganizationsNotInUseException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_OrganizationsNotInUseException :: forall a. AsError a => Fold a ServiceError
_OrganizationsNotInUseException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"OrganizationsNotInUseException"

-- | The query ID does not exist or does not map to a query.
_QueryIdNotFoundException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_QueryIdNotFoundException :: forall a. AsError a => Fold a ServiceError
_QueryIdNotFoundException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"QueryIdNotFoundException"

-- | This exception is thrown when the specified resource is not 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"

-- | This exception is thrown when the specified resource type is not
-- supported by CloudTrail.
_ResourceTypeNotSupportedException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ResourceTypeNotSupportedException :: forall a. AsError a => Fold a ServiceError
_ResourceTypeNotSupportedException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ResourceTypeNotSupportedException"

-- | This exception is thrown when the specified S3 bucket does not exist.
_S3BucketDoesNotExistException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_S3BucketDoesNotExistException :: forall a. AsError a => Fold a ServiceError
_S3BucketDoesNotExistException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"S3BucketDoesNotExistException"

-- | The number of tags per trail has exceeded the permitted amount.
-- Currently, the limit is 50.
_TagsLimitExceededException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TagsLimitExceededException :: forall a. AsError a => Fold a ServiceError
_TagsLimitExceededException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TagsLimitExceededException"

-- | This exception is thrown when the specified trail already exists.
_TrailAlreadyExistsException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TrailAlreadyExistsException :: forall a. AsError a => Fold a ServiceError
_TrailAlreadyExistsException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TrailAlreadyExistsException"

-- | This exception is thrown when the trail with the given name is not
-- found.
_TrailNotFoundException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TrailNotFoundException :: forall a. AsError a => Fold a ServiceError
_TrailNotFoundException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TrailNotFoundException"

-- | This exception is no longer in use.
_TrailNotProvidedException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TrailNotProvidedException :: forall a. AsError a => Fold a ServiceError
_TrailNotProvidedException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TrailNotProvidedException"

-- | This exception is thrown when the requested operation is not supported.
_UnsupportedOperationException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_UnsupportedOperationException :: forall a. AsError a => Fold a ServiceError
_UnsupportedOperationException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"UnsupportedOperationException"