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

    -- * Errors
    _DirectoryInUseException,
    _DirectoryServiceAuthenticationFailedException,
    _DirectoryUnavailableException,
    _EmailAddressInUseException,
    _EntityAlreadyRegisteredException,
    _EntityNotFoundException,
    _EntityStateException,
    _InvalidConfigurationException,
    _InvalidCustomSesConfigurationException,
    _InvalidParameterException,
    _InvalidPasswordException,
    _LimitExceededException,
    _MailDomainInUseException,
    _MailDomainNotFoundException,
    _MailDomainStateException,
    _NameAvailabilityException,
    _OrganizationNotFoundException,
    _OrganizationStateException,
    _ReservedNameException,
    _ResourceNotFoundException,
    _TooManyTagsException,
    _UnsupportedOperationException,

    -- * AccessControlRuleEffect
    AccessControlRuleEffect (..),

    -- * AccessEffect
    AccessEffect (..),

    -- * AvailabilityProviderType
    AvailabilityProviderType (..),

    -- * DnsRecordVerificationStatus
    DnsRecordVerificationStatus (..),

    -- * EntityState
    EntityState (..),

    -- * FolderName
    FolderName (..),

    -- * ImpersonationRoleType
    ImpersonationRoleType (..),

    -- * MailboxExportJobState
    MailboxExportJobState (..),

    -- * MemberType
    MemberType (..),

    -- * MobileDeviceAccessRuleEffect
    MobileDeviceAccessRuleEffect (..),

    -- * PermissionType
    PermissionType (..),

    -- * ResourceType
    ResourceType (..),

    -- * RetentionAction
    RetentionAction (..),

    -- * UserRole
    UserRole (..),

    -- * AccessControlRule
    AccessControlRule (..),
    newAccessControlRule,
    accessControlRule_actions,
    accessControlRule_dateCreated,
    accessControlRule_dateModified,
    accessControlRule_description,
    accessControlRule_effect,
    accessControlRule_impersonationRoleIds,
    accessControlRule_ipRanges,
    accessControlRule_name,
    accessControlRule_notActions,
    accessControlRule_notImpersonationRoleIds,
    accessControlRule_notIpRanges,
    accessControlRule_notUserIds,
    accessControlRule_userIds,

    -- * AvailabilityConfiguration
    AvailabilityConfiguration (..),
    newAvailabilityConfiguration,
    availabilityConfiguration_dateCreated,
    availabilityConfiguration_dateModified,
    availabilityConfiguration_domainName,
    availabilityConfiguration_ewsProvider,
    availabilityConfiguration_lambdaProvider,
    availabilityConfiguration_providerType,

    -- * BookingOptions
    BookingOptions (..),
    newBookingOptions,
    bookingOptions_autoAcceptRequests,
    bookingOptions_autoDeclineConflictingRequests,
    bookingOptions_autoDeclineRecurringRequests,

    -- * Delegate
    Delegate (..),
    newDelegate,
    delegate_id,
    delegate_type,

    -- * DnsRecord
    DnsRecord (..),
    newDnsRecord,
    dnsRecord_hostname,
    dnsRecord_type,
    dnsRecord_value,

    -- * Domain
    Domain (..),
    newDomain,
    domain_domainName,
    domain_hostedZoneId,

    -- * EwsAvailabilityProvider
    EwsAvailabilityProvider (..),
    newEwsAvailabilityProvider,
    ewsAvailabilityProvider_ewsEndpoint,
    ewsAvailabilityProvider_ewsUsername,
    ewsAvailabilityProvider_ewsPassword,

    -- * FolderConfiguration
    FolderConfiguration (..),
    newFolderConfiguration,
    folderConfiguration_period,
    folderConfiguration_name,
    folderConfiguration_action,

    -- * Group
    Group (..),
    newGroup,
    group_disabledDate,
    group_email,
    group_enabledDate,
    group_id,
    group_name,
    group_state,

    -- * ImpersonationMatchedRule
    ImpersonationMatchedRule (..),
    newImpersonationMatchedRule,
    impersonationMatchedRule_impersonationRuleId,
    impersonationMatchedRule_name,

    -- * ImpersonationRole
    ImpersonationRole (..),
    newImpersonationRole,
    impersonationRole_dateCreated,
    impersonationRole_dateModified,
    impersonationRole_impersonationRoleId,
    impersonationRole_name,
    impersonationRole_type,

    -- * ImpersonationRule
    ImpersonationRule (..),
    newImpersonationRule,
    impersonationRule_description,
    impersonationRule_name,
    impersonationRule_notTargetUsers,
    impersonationRule_targetUsers,
    impersonationRule_impersonationRuleId,
    impersonationRule_effect,

    -- * LambdaAvailabilityProvider
    LambdaAvailabilityProvider (..),
    newLambdaAvailabilityProvider,
    lambdaAvailabilityProvider_lambdaArn,

    -- * MailDomainSummary
    MailDomainSummary (..),
    newMailDomainSummary,
    mailDomainSummary_defaultDomain,
    mailDomainSummary_domainName,

    -- * MailboxExportJob
    MailboxExportJob (..),
    newMailboxExportJob,
    mailboxExportJob_description,
    mailboxExportJob_endTime,
    mailboxExportJob_entityId,
    mailboxExportJob_estimatedProgress,
    mailboxExportJob_jobId,
    mailboxExportJob_s3BucketName,
    mailboxExportJob_s3Path,
    mailboxExportJob_startTime,
    mailboxExportJob_state,

    -- * Member
    Member (..),
    newMember,
    member_disabledDate,
    member_enabledDate,
    member_id,
    member_name,
    member_state,
    member_type,

    -- * MobileDeviceAccessMatchedRule
    MobileDeviceAccessMatchedRule (..),
    newMobileDeviceAccessMatchedRule,
    mobileDeviceAccessMatchedRule_mobileDeviceAccessRuleId,
    mobileDeviceAccessMatchedRule_name,

    -- * MobileDeviceAccessOverride
    MobileDeviceAccessOverride (..),
    newMobileDeviceAccessOverride,
    mobileDeviceAccessOverride_dateCreated,
    mobileDeviceAccessOverride_dateModified,
    mobileDeviceAccessOverride_description,
    mobileDeviceAccessOverride_deviceId,
    mobileDeviceAccessOverride_effect,
    mobileDeviceAccessOverride_userId,

    -- * MobileDeviceAccessRule
    MobileDeviceAccessRule (..),
    newMobileDeviceAccessRule,
    mobileDeviceAccessRule_dateCreated,
    mobileDeviceAccessRule_dateModified,
    mobileDeviceAccessRule_description,
    mobileDeviceAccessRule_deviceModels,
    mobileDeviceAccessRule_deviceOperatingSystems,
    mobileDeviceAccessRule_deviceTypes,
    mobileDeviceAccessRule_deviceUserAgents,
    mobileDeviceAccessRule_effect,
    mobileDeviceAccessRule_mobileDeviceAccessRuleId,
    mobileDeviceAccessRule_name,
    mobileDeviceAccessRule_notDeviceModels,
    mobileDeviceAccessRule_notDeviceOperatingSystems,
    mobileDeviceAccessRule_notDeviceTypes,
    mobileDeviceAccessRule_notDeviceUserAgents,

    -- * OrganizationSummary
    OrganizationSummary (..),
    newOrganizationSummary,
    organizationSummary_alias,
    organizationSummary_defaultMailDomain,
    organizationSummary_errorMessage,
    organizationSummary_organizationId,
    organizationSummary_state,

    -- * Permission
    Permission (..),
    newPermission,
    permission_granteeId,
    permission_granteeType,
    permission_permissionValues,

    -- * RedactedEwsAvailabilityProvider
    RedactedEwsAvailabilityProvider (..),
    newRedactedEwsAvailabilityProvider,
    redactedEwsAvailabilityProvider_ewsEndpoint,
    redactedEwsAvailabilityProvider_ewsUsername,

    -- * Resource
    Resource (..),
    newResource,
    resource_disabledDate,
    resource_email,
    resource_enabledDate,
    resource_id,
    resource_name,
    resource_state,
    resource_type,

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

    -- * User
    User (..),
    newUser,
    user_disabledDate,
    user_displayName,
    user_email,
    user_enabledDate,
    user_id,
    user_name,
    user_state,
    user_userRole,
  )
where

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
import Amazonka.WorkMail.Types.AccessControlRule
import Amazonka.WorkMail.Types.AccessControlRuleEffect
import Amazonka.WorkMail.Types.AccessEffect
import Amazonka.WorkMail.Types.AvailabilityConfiguration
import Amazonka.WorkMail.Types.AvailabilityProviderType
import Amazonka.WorkMail.Types.BookingOptions
import Amazonka.WorkMail.Types.Delegate
import Amazonka.WorkMail.Types.DnsRecord
import Amazonka.WorkMail.Types.DnsRecordVerificationStatus
import Amazonka.WorkMail.Types.Domain
import Amazonka.WorkMail.Types.EntityState
import Amazonka.WorkMail.Types.EwsAvailabilityProvider
import Amazonka.WorkMail.Types.FolderConfiguration
import Amazonka.WorkMail.Types.FolderName
import Amazonka.WorkMail.Types.Group
import Amazonka.WorkMail.Types.ImpersonationMatchedRule
import Amazonka.WorkMail.Types.ImpersonationRole
import Amazonka.WorkMail.Types.ImpersonationRoleType
import Amazonka.WorkMail.Types.ImpersonationRule
import Amazonka.WorkMail.Types.LambdaAvailabilityProvider
import Amazonka.WorkMail.Types.MailDomainSummary
import Amazonka.WorkMail.Types.MailboxExportJob
import Amazonka.WorkMail.Types.MailboxExportJobState
import Amazonka.WorkMail.Types.Member
import Amazonka.WorkMail.Types.MemberType
import Amazonka.WorkMail.Types.MobileDeviceAccessMatchedRule
import Amazonka.WorkMail.Types.MobileDeviceAccessOverride
import Amazonka.WorkMail.Types.MobileDeviceAccessRule
import Amazonka.WorkMail.Types.MobileDeviceAccessRuleEffect
import Amazonka.WorkMail.Types.OrganizationSummary
import Amazonka.WorkMail.Types.Permission
import Amazonka.WorkMail.Types.PermissionType
import Amazonka.WorkMail.Types.RedactedEwsAvailabilityProvider
import Amazonka.WorkMail.Types.Resource
import Amazonka.WorkMail.Types.ResourceType
import Amazonka.WorkMail.Types.RetentionAction
import Amazonka.WorkMail.Types.Tag
import Amazonka.WorkMail.Types.User
import Amazonka.WorkMail.Types.UserRole

-- | API version @2017-10-01@ of the Amazon WorkMail SDK configuration.
defaultService :: Core.Service
defaultService :: Service
defaultService =
  Core.Service
    { $sel:abbrev:Service :: Abbrev
Core.abbrev = Abbrev
"WorkMail",
      $sel:signer:Service :: Signer
Core.signer = Signer
Sign.v4,
      $sel:endpointPrefix:Service :: ByteString
Core.endpointPrefix = ByteString
"workmail",
      $sel:signingName:Service :: ByteString
Core.signingName = ByteString
"workmail",
      $sel:version:Service :: ByteString
Core.version = ByteString
"2017-10-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
"WorkMail",
      $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 directory is already in use by another WorkMail organization in the
-- same account and Region.
_DirectoryInUseException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DirectoryInUseException :: forall a. AsError a => Fold a ServiceError
_DirectoryInUseException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"DirectoryInUseException"

-- | The directory service doesn\'t recognize the credentials supplied by
-- WorkMail.
_DirectoryServiceAuthenticationFailedException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DirectoryServiceAuthenticationFailedException :: forall a. AsError a => Fold a ServiceError
_DirectoryServiceAuthenticationFailedException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"DirectoryServiceAuthenticationFailedException"

-- | The directory is unavailable. It might be located in another Region or
-- deleted.
_DirectoryUnavailableException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DirectoryUnavailableException :: forall a. AsError a => Fold a ServiceError
_DirectoryUnavailableException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"DirectoryUnavailableException"

-- | The email address that you\'re trying to assign is already created for a
-- different user, group, or resource.
_EmailAddressInUseException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_EmailAddressInUseException :: forall a. AsError a => Fold a ServiceError
_EmailAddressInUseException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"EmailAddressInUseException"

-- | The user, group, or resource that you\'re trying to register is already
-- registered.
_EntityAlreadyRegisteredException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_EntityAlreadyRegisteredException :: forall a. AsError a => Fold a ServiceError
_EntityAlreadyRegisteredException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"EntityAlreadyRegisteredException"

-- | The identifier supplied for the user, group, or resource does not exist
-- in your organization.
_EntityNotFoundException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_EntityNotFoundException :: forall a. AsError a => Fold a ServiceError
_EntityNotFoundException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"EntityNotFoundException"

-- | You are performing an operation on a user, group, or resource that
-- isn\'t in the expected state, such as trying to delete an active user.
_EntityStateException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_EntityStateException :: forall a. AsError a => Fold a ServiceError
_EntityStateException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"EntityStateException"

-- | The configuration for a resource isn\'t valid. A resource must either be
-- able to auto-respond to requests or have at least one delegate
-- associated that can do so on its behalf.
_InvalidConfigurationException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidConfigurationException :: forall a. AsError a => Fold a ServiceError
_InvalidConfigurationException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidConfigurationException"

-- | You SES configuration has customizations that WorkMail cannot save. The
-- error message lists the invalid setting. For examples of invalid
-- settings, refer to
-- <https://docs.aws.amazon.com/ses/latest/APIReference/API_CreateReceiptRule.html CreateReceiptRule>.
_InvalidCustomSesConfigurationException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidCustomSesConfigurationException :: forall a. AsError a => Fold a ServiceError
_InvalidCustomSesConfigurationException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidCustomSesConfigurationException"

-- | One or more of the input parameters don\'t match the service\'s
-- restrictions.
_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 supplied password doesn\'t match the minimum security constraints,
-- such as length or use of special characters.
_InvalidPasswordException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidPasswordException :: forall a. AsError a => Fold a ServiceError
_InvalidPasswordException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidPasswordException"

-- | The request exceeds the limit of the resource.
_LimitExceededException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_LimitExceededException :: forall a. AsError a => Fold a ServiceError
_LimitExceededException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"LimitExceededException"

-- | The domain you\'re trying to change is in use by another user or
-- organization in your account. See the error message for details.
_MailDomainInUseException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_MailDomainInUseException :: forall a. AsError a => Fold a ServiceError
_MailDomainInUseException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"MailDomainInUseException"

-- | The domain specified is not found in your organization.
_MailDomainNotFoundException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_MailDomainNotFoundException :: forall a. AsError a => Fold a ServiceError
_MailDomainNotFoundException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"MailDomainNotFoundException"

-- | After a domain has been added to the organization, it must be verified.
-- The domain is not yet verified.
_MailDomainStateException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_MailDomainStateException :: forall a. AsError a => Fold a ServiceError
_MailDomainStateException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"MailDomainStateException"

-- | The user, group, or resource name isn\'t unique in WorkMail.
_NameAvailabilityException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NameAvailabilityException :: forall a. AsError a => Fold a ServiceError
_NameAvailabilityException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NameAvailabilityException"

-- | An operation received a valid organization identifier that either
-- doesn\'t belong or exist in the system.
_OrganizationNotFoundException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_OrganizationNotFoundException :: forall a. AsError a => Fold a ServiceError
_OrganizationNotFoundException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"OrganizationNotFoundException"

-- | The organization must have a valid state to perform certain operations
-- on the organization or its members.
_OrganizationStateException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_OrganizationStateException :: forall a. AsError a => Fold a ServiceError
_OrganizationStateException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"OrganizationStateException"

-- | This user, group, or resource name is not allowed in WorkMail.
_ReservedNameException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ReservedNameException :: forall a. AsError a => Fold a ServiceError
_ReservedNameException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ReservedNameException"

-- | The resource cannot 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 can have up to 50 user-applied tags.
_TooManyTagsException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_TooManyTagsException :: forall a. AsError a => Fold a ServiceError
_TooManyTagsException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"TooManyTagsException"

-- | You can\'t perform a write operation against a read-only directory.
_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"