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

    -- * Errors
    _ConcurrentModificationException,
    _CredentialReportExpiredException,
    _CredentialReportNotPresentException,
    _CredentialReportNotReadyException,
    _DeleteConflictException,
    _DuplicateCertificateException,
    _DuplicateSSHPublicKeyException,
    _EntityAlreadyExistsException,
    _EntityTemporarilyUnmodifiableException,
    _InvalidAuthenticationCodeException,
    _InvalidCertificateException,
    _InvalidInputException,
    _InvalidPublicKeyException,
    _InvalidUserTypeException,
    _KeyPairMismatchException,
    _LimitExceededException,
    _MalformedCertificateException,
    _MalformedPolicyDocumentException,
    _NoSuchEntityException,
    _PasswordPolicyViolationException,
    _PolicyEvaluationException,
    _PolicyNotAttachableException,
    _ReportGenerationLimitExceededException,
    _ServiceFailureException,
    _ServiceNotSupportedException,
    _UnmodifiableEntityException,
    _UnrecognizedPublicKeyEncodingException,

    -- * AccessAdvisorUsageGranularityType
    AccessAdvisorUsageGranularityType (..),

    -- * AssignmentStatusType
    AssignmentStatusType (..),

    -- * ContextKeyTypeEnum
    ContextKeyTypeEnum (..),

    -- * DeletionTaskStatusType
    DeletionTaskStatusType (..),

    -- * EncodingType
    EncodingType (..),

    -- * EntityType
    EntityType (..),

    -- * GlobalEndpointTokenVersion
    GlobalEndpointTokenVersion (..),

    -- * JobStatusType
    JobStatusType (..),

    -- * PermissionsBoundaryAttachmentType
    PermissionsBoundaryAttachmentType (..),

    -- * PolicyEvaluationDecisionType
    PolicyEvaluationDecisionType (..),

    -- * PolicyOwnerEntityType
    PolicyOwnerEntityType (..),

    -- * PolicyScopeType
    PolicyScopeType (..),

    -- * PolicySourceType
    PolicySourceType (..),

    -- * PolicyType
    PolicyType (..),

    -- * PolicyUsageType
    PolicyUsageType (..),

    -- * ReportFormatType
    ReportFormatType (..),

    -- * ReportStateType
    ReportStateType (..),

    -- * SortKeyType
    SortKeyType (..),

    -- * StatusType
    StatusType (..),

    -- * SummaryKeyType
    SummaryKeyType (..),

    -- * AccessDetail
    AccessDetail (..),
    newAccessDetail,
    accessDetail_entityPath,
    accessDetail_lastAuthenticatedTime,
    accessDetail_region,
    accessDetail_totalAuthenticatedEntities,
    accessDetail_serviceName,
    accessDetail_serviceNamespace,

    -- * AccessKeyInfo
    AccessKeyInfo (..),
    newAccessKeyInfo,
    accessKeyInfo_createDate,
    accessKeyInfo_userName,
    accessKeyInfo_accessKeyId,
    accessKeyInfo_status,
    accessKeyInfo_secretAccessKey,

    -- * AccessKeyLastUsed
    AccessKeyLastUsed (..),
    newAccessKeyLastUsed,
    accessKeyLastUsed_lastUsedDate,
    accessKeyLastUsed_serviceName,
    accessKeyLastUsed_region,

    -- * AccessKeyMetadata
    AccessKeyMetadata (..),
    newAccessKeyMetadata,
    accessKeyMetadata_accessKeyId,
    accessKeyMetadata_createDate,
    accessKeyMetadata_status,
    accessKeyMetadata_userName,

    -- * AttachedPermissionsBoundary
    AttachedPermissionsBoundary (..),
    newAttachedPermissionsBoundary,
    attachedPermissionsBoundary_permissionsBoundaryArn,
    attachedPermissionsBoundary_permissionsBoundaryType,

    -- * AttachedPolicy
    AttachedPolicy (..),
    newAttachedPolicy,
    attachedPolicy_policyArn,
    attachedPolicy_policyName,

    -- * ContextEntry
    ContextEntry (..),
    newContextEntry,
    contextEntry_contextKeyName,
    contextEntry_contextKeyType,
    contextEntry_contextKeyValues,

    -- * DeletionTaskFailureReasonType
    DeletionTaskFailureReasonType (..),
    newDeletionTaskFailureReasonType,
    deletionTaskFailureReasonType_reason,
    deletionTaskFailureReasonType_roleUsageList,

    -- * EntityDetails
    EntityDetails (..),
    newEntityDetails,
    entityDetails_lastAuthenticated,
    entityDetails_entityInfo,

    -- * EntityInfo
    EntityInfo (..),
    newEntityInfo,
    entityInfo_path,
    entityInfo_arn,
    entityInfo_name,
    entityInfo_type,
    entityInfo_id,

    -- * ErrorDetails
    ErrorDetails (..),
    newErrorDetails,
    errorDetails_message,
    errorDetails_code,

    -- * EvaluationResult
    EvaluationResult (..),
    newEvaluationResult,
    evaluationResult_evalDecisionDetails,
    evaluationResult_evalResourceName,
    evaluationResult_matchedStatements,
    evaluationResult_missingContextValues,
    evaluationResult_organizationsDecisionDetail,
    evaluationResult_permissionsBoundaryDecisionDetail,
    evaluationResult_resourceSpecificResults,
    evaluationResult_evalActionName,
    evaluationResult_evalDecision,

    -- * GetContextKeysForPolicyResponse
    GetContextKeysForPolicyResponse (..),
    newGetContextKeysForPolicyResponse,
    getContextKeysForPolicyResponse_contextKeyNames,

    -- * Group
    Group (..),
    newGroup,
    group_path,
    group_groupName,
    group_groupId,
    group_arn,
    group_createDate,

    -- * GroupDetail
    GroupDetail (..),
    newGroupDetail,
    groupDetail_arn,
    groupDetail_attachedManagedPolicies,
    groupDetail_createDate,
    groupDetail_groupId,
    groupDetail_groupName,
    groupDetail_groupPolicyList,
    groupDetail_path,

    -- * InstanceProfile
    InstanceProfile (..),
    newInstanceProfile,
    instanceProfile_tags,
    instanceProfile_path,
    instanceProfile_instanceProfileName,
    instanceProfile_instanceProfileId,
    instanceProfile_arn,
    instanceProfile_createDate,
    instanceProfile_roles,

    -- * ListPoliciesGrantingServiceAccessEntry
    ListPoliciesGrantingServiceAccessEntry (..),
    newListPoliciesGrantingServiceAccessEntry,
    listPoliciesGrantingServiceAccessEntry_policies,
    listPoliciesGrantingServiceAccessEntry_serviceNamespace,

    -- * LoginProfile
    LoginProfile (..),
    newLoginProfile,
    loginProfile_passwordResetRequired,
    loginProfile_userName,
    loginProfile_createDate,

    -- * MFADevice
    MFADevice (..),
    newMFADevice,
    mfaDevice_userName,
    mfaDevice_serialNumber,
    mfaDevice_enableDate,

    -- * ManagedPolicyDetail
    ManagedPolicyDetail (..),
    newManagedPolicyDetail,
    managedPolicyDetail_arn,
    managedPolicyDetail_attachmentCount,
    managedPolicyDetail_createDate,
    managedPolicyDetail_defaultVersionId,
    managedPolicyDetail_description,
    managedPolicyDetail_isAttachable,
    managedPolicyDetail_path,
    managedPolicyDetail_permissionsBoundaryUsageCount,
    managedPolicyDetail_policyId,
    managedPolicyDetail_policyName,
    managedPolicyDetail_policyVersionList,
    managedPolicyDetail_updateDate,

    -- * OpenIDConnectProviderListEntry
    OpenIDConnectProviderListEntry (..),
    newOpenIDConnectProviderListEntry,
    openIDConnectProviderListEntry_arn,

    -- * OrganizationsDecisionDetail
    OrganizationsDecisionDetail (..),
    newOrganizationsDecisionDetail,
    organizationsDecisionDetail_allowedByOrganizations,

    -- * PasswordPolicy
    PasswordPolicy (..),
    newPasswordPolicy,
    passwordPolicy_allowUsersToChangePassword,
    passwordPolicy_expirePasswords,
    passwordPolicy_hardExpiry,
    passwordPolicy_maxPasswordAge,
    passwordPolicy_minimumPasswordLength,
    passwordPolicy_passwordReusePrevention,
    passwordPolicy_requireLowercaseCharacters,
    passwordPolicy_requireNumbers,
    passwordPolicy_requireSymbols,
    passwordPolicy_requireUppercaseCharacters,

    -- * PermissionsBoundaryDecisionDetail
    PermissionsBoundaryDecisionDetail (..),
    newPermissionsBoundaryDecisionDetail,
    permissionsBoundaryDecisionDetail_allowedByPermissionsBoundary,

    -- * Policy
    Policy (..),
    newPolicy,
    policy_arn,
    policy_attachmentCount,
    policy_createDate,
    policy_defaultVersionId,
    policy_description,
    policy_isAttachable,
    policy_path,
    policy_permissionsBoundaryUsageCount,
    policy_policyId,
    policy_policyName,
    policy_tags,
    policy_updateDate,

    -- * PolicyDetail
    PolicyDetail (..),
    newPolicyDetail,
    policyDetail_policyDocument,
    policyDetail_policyName,

    -- * PolicyGrantingServiceAccess
    PolicyGrantingServiceAccess (..),
    newPolicyGrantingServiceAccess,
    policyGrantingServiceAccess_entityName,
    policyGrantingServiceAccess_entityType,
    policyGrantingServiceAccess_policyArn,
    policyGrantingServiceAccess_policyName,
    policyGrantingServiceAccess_policyType,

    -- * PolicyGroup
    PolicyGroup (..),
    newPolicyGroup,
    policyGroup_groupId,
    policyGroup_groupName,

    -- * PolicyRole
    PolicyRole (..),
    newPolicyRole,
    policyRole_roleId,
    policyRole_roleName,

    -- * PolicyUser
    PolicyUser (..),
    newPolicyUser,
    policyUser_userId,
    policyUser_userName,

    -- * PolicyVersion
    PolicyVersion (..),
    newPolicyVersion,
    policyVersion_createDate,
    policyVersion_document,
    policyVersion_isDefaultVersion,
    policyVersion_versionId,

    -- * Position
    Position (..),
    newPosition,
    position_column,
    position_line,

    -- * ResourceSpecificResult
    ResourceSpecificResult (..),
    newResourceSpecificResult,
    resourceSpecificResult_evalDecisionDetails,
    resourceSpecificResult_matchedStatements,
    resourceSpecificResult_missingContextValues,
    resourceSpecificResult_permissionsBoundaryDecisionDetail,
    resourceSpecificResult_evalResourceName,
    resourceSpecificResult_evalResourceDecision,

    -- * Role
    Role (..),
    newRole,
    role_assumeRolePolicyDocument,
    role_description,
    role_maxSessionDuration,
    role_permissionsBoundary,
    role_roleLastUsed,
    role_tags,
    role_path,
    role_roleName,
    role_roleId,
    role_arn,
    role_createDate,

    -- * RoleDetail
    RoleDetail (..),
    newRoleDetail,
    roleDetail_arn,
    roleDetail_assumeRolePolicyDocument,
    roleDetail_attachedManagedPolicies,
    roleDetail_createDate,
    roleDetail_instanceProfileList,
    roleDetail_path,
    roleDetail_permissionsBoundary,
    roleDetail_roleId,
    roleDetail_roleLastUsed,
    roleDetail_roleName,
    roleDetail_rolePolicyList,
    roleDetail_tags,

    -- * RoleLastUsed
    RoleLastUsed (..),
    newRoleLastUsed,
    roleLastUsed_lastUsedDate,
    roleLastUsed_region,

    -- * RoleUsageType
    RoleUsageType (..),
    newRoleUsageType,
    roleUsageType_region,
    roleUsageType_resources,

    -- * SAMLProviderListEntry
    SAMLProviderListEntry (..),
    newSAMLProviderListEntry,
    sAMLProviderListEntry_arn,
    sAMLProviderListEntry_createDate,
    sAMLProviderListEntry_validUntil,

    -- * SSHPublicKey
    SSHPublicKey (..),
    newSSHPublicKey,
    sSHPublicKey_uploadDate,
    sSHPublicKey_userName,
    sSHPublicKey_sSHPublicKeyId,
    sSHPublicKey_fingerprint,
    sSHPublicKey_sSHPublicKeyBody,
    sSHPublicKey_status,

    -- * SSHPublicKeyMetadata
    SSHPublicKeyMetadata (..),
    newSSHPublicKeyMetadata,
    sSHPublicKeyMetadata_userName,
    sSHPublicKeyMetadata_sSHPublicKeyId,
    sSHPublicKeyMetadata_status,
    sSHPublicKeyMetadata_uploadDate,

    -- * ServerCertificate
    ServerCertificate (..),
    newServerCertificate,
    serverCertificate_certificateChain,
    serverCertificate_tags,
    serverCertificate_serverCertificateMetadata,
    serverCertificate_certificateBody,

    -- * ServerCertificateMetadata
    ServerCertificateMetadata (..),
    newServerCertificateMetadata,
    serverCertificateMetadata_expiration,
    serverCertificateMetadata_uploadDate,
    serverCertificateMetadata_path,
    serverCertificateMetadata_serverCertificateName,
    serverCertificateMetadata_serverCertificateId,
    serverCertificateMetadata_arn,

    -- * ServiceLastAccessed
    ServiceLastAccessed (..),
    newServiceLastAccessed,
    serviceLastAccessed_lastAuthenticated,
    serviceLastAccessed_lastAuthenticatedEntity,
    serviceLastAccessed_lastAuthenticatedRegion,
    serviceLastAccessed_totalAuthenticatedEntities,
    serviceLastAccessed_trackedActionsLastAccessed,
    serviceLastAccessed_serviceName,
    serviceLastAccessed_serviceNamespace,

    -- * ServiceSpecificCredential
    ServiceSpecificCredential (..),
    newServiceSpecificCredential,
    serviceSpecificCredential_createDate,
    serviceSpecificCredential_serviceName,
    serviceSpecificCredential_serviceUserName,
    serviceSpecificCredential_servicePassword,
    serviceSpecificCredential_serviceSpecificCredentialId,
    serviceSpecificCredential_userName,
    serviceSpecificCredential_status,

    -- * ServiceSpecificCredentialMetadata
    ServiceSpecificCredentialMetadata (..),
    newServiceSpecificCredentialMetadata,
    serviceSpecificCredentialMetadata_userName,
    serviceSpecificCredentialMetadata_status,
    serviceSpecificCredentialMetadata_serviceUserName,
    serviceSpecificCredentialMetadata_createDate,
    serviceSpecificCredentialMetadata_serviceSpecificCredentialId,
    serviceSpecificCredentialMetadata_serviceName,

    -- * SigningCertificate
    SigningCertificate (..),
    newSigningCertificate,
    signingCertificate_uploadDate,
    signingCertificate_userName,
    signingCertificate_certificateId,
    signingCertificate_certificateBody,
    signingCertificate_status,

    -- * SimulatePolicyResponse
    SimulatePolicyResponse (..),
    newSimulatePolicyResponse,
    simulatePolicyResponse_evaluationResults,
    simulatePolicyResponse_isTruncated,
    simulatePolicyResponse_marker,

    -- * Statement
    Statement (..),
    newStatement,
    statement_endPosition,
    statement_sourcePolicyId,
    statement_sourcePolicyType,
    statement_startPosition,

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

    -- * TrackedActionLastAccessed
    TrackedActionLastAccessed (..),
    newTrackedActionLastAccessed,
    trackedActionLastAccessed_actionName,
    trackedActionLastAccessed_lastAccessedEntity,
    trackedActionLastAccessed_lastAccessedRegion,
    trackedActionLastAccessed_lastAccessedTime,

    -- * User
    User (..),
    newUser,
    user_passwordLastUsed,
    user_path,
    user_permissionsBoundary,
    user_tags,
    user_userName,
    user_userId,
    user_arn,
    user_createDate,

    -- * UserDetail
    UserDetail (..),
    newUserDetail,
    userDetail_arn,
    userDetail_attachedManagedPolicies,
    userDetail_createDate,
    userDetail_groupList,
    userDetail_path,
    userDetail_permissionsBoundary,
    userDetail_tags,
    userDetail_userId,
    userDetail_userName,
    userDetail_userPolicyList,

    -- * VirtualMFADevice
    VirtualMFADevice (..),
    newVirtualMFADevice,
    virtualMFADevice_base32StringSeed,
    virtualMFADevice_enableDate,
    virtualMFADevice_qRCodePNG,
    virtualMFADevice_tags,
    virtualMFADevice_user,
    virtualMFADevice_serialNumber,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.IAM.Types.AccessAdvisorUsageGranularityType
import Amazonka.IAM.Types.AccessDetail
import Amazonka.IAM.Types.AccessKeyInfo
import Amazonka.IAM.Types.AccessKeyLastUsed
import Amazonka.IAM.Types.AccessKeyMetadata
import Amazonka.IAM.Types.AssignmentStatusType
import Amazonka.IAM.Types.AttachedPermissionsBoundary
import Amazonka.IAM.Types.AttachedPolicy
import Amazonka.IAM.Types.ContextEntry
import Amazonka.IAM.Types.ContextKeyTypeEnum
import Amazonka.IAM.Types.DeletionTaskFailureReasonType
import Amazonka.IAM.Types.DeletionTaskStatusType
import Amazonka.IAM.Types.EncodingType
import Amazonka.IAM.Types.EntityDetails
import Amazonka.IAM.Types.EntityInfo
import Amazonka.IAM.Types.EntityType
import Amazonka.IAM.Types.ErrorDetails
import Amazonka.IAM.Types.EvaluationResult
import Amazonka.IAM.Types.GetContextKeysForPolicyResponse
import Amazonka.IAM.Types.GlobalEndpointTokenVersion
import Amazonka.IAM.Types.Group
import Amazonka.IAM.Types.GroupDetail
import Amazonka.IAM.Types.InstanceProfile
import Amazonka.IAM.Types.JobStatusType
import Amazonka.IAM.Types.ListPoliciesGrantingServiceAccessEntry
import Amazonka.IAM.Types.LoginProfile
import Amazonka.IAM.Types.MFADevice
import Amazonka.IAM.Types.ManagedPolicyDetail
import Amazonka.IAM.Types.OpenIDConnectProviderListEntry
import Amazonka.IAM.Types.OrganizationsDecisionDetail
import Amazonka.IAM.Types.PasswordPolicy
import Amazonka.IAM.Types.PermissionsBoundaryAttachmentType
import Amazonka.IAM.Types.PermissionsBoundaryDecisionDetail
import Amazonka.IAM.Types.Policy
import Amazonka.IAM.Types.PolicyDetail
import Amazonka.IAM.Types.PolicyEvaluationDecisionType
import Amazonka.IAM.Types.PolicyGrantingServiceAccess
import Amazonka.IAM.Types.PolicyGroup
import Amazonka.IAM.Types.PolicyOwnerEntityType
import Amazonka.IAM.Types.PolicyRole
import Amazonka.IAM.Types.PolicyScopeType
import Amazonka.IAM.Types.PolicySourceType
import Amazonka.IAM.Types.PolicyType
import Amazonka.IAM.Types.PolicyUsageType
import Amazonka.IAM.Types.PolicyUser
import Amazonka.IAM.Types.PolicyVersion
import Amazonka.IAM.Types.Position
import Amazonka.IAM.Types.ReportFormatType
import Amazonka.IAM.Types.ReportStateType
import Amazonka.IAM.Types.ResourceSpecificResult
import Amazonka.IAM.Types.Role
import Amazonka.IAM.Types.RoleDetail
import Amazonka.IAM.Types.RoleLastUsed
import Amazonka.IAM.Types.RoleUsageType
import Amazonka.IAM.Types.SAMLProviderListEntry
import Amazonka.IAM.Types.SSHPublicKey
import Amazonka.IAM.Types.SSHPublicKeyMetadata
import Amazonka.IAM.Types.ServerCertificate
import Amazonka.IAM.Types.ServerCertificateMetadata
import Amazonka.IAM.Types.ServiceLastAccessed
import Amazonka.IAM.Types.ServiceSpecificCredential
import Amazonka.IAM.Types.ServiceSpecificCredentialMetadata
import Amazonka.IAM.Types.SigningCertificate
import Amazonka.IAM.Types.SimulatePolicyResponse
import Amazonka.IAM.Types.SortKeyType
import Amazonka.IAM.Types.Statement
import Amazonka.IAM.Types.StatusType
import Amazonka.IAM.Types.SummaryKeyType
import Amazonka.IAM.Types.Tag
import Amazonka.IAM.Types.TrackedActionLastAccessed
import Amazonka.IAM.Types.User
import Amazonka.IAM.Types.UserDetail
import Amazonka.IAM.Types.VirtualMFADevice
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Sign.V4 as Sign

-- | API version @2010-05-08@ of the Amazon Identity and Access Management SDK configuration.
defaultService :: Core.Service
defaultService :: Service
defaultService =
  Core.Service
    { $sel:abbrev:Service :: Abbrev
Core.abbrev = Abbrev
"IAM",
      $sel:signer:Service :: Signer
Core.signer = Signer
Sign.v4,
      $sel:endpointPrefix:Service :: ByteString
Core.endpointPrefix = ByteString
"iam",
      $sel:signingName:Service :: ByteString
Core.signingName = ByteString
"iam",
      $sel:version:Service :: ByteString
Core.version = ByteString
"2010-05-08",
      $sel:s3AddressingStyle:Service :: S3AddressingStyle
Core.s3AddressingStyle = S3AddressingStyle
Core.S3AddressingStyleAuto,
      $sel:endpoint:Service :: Region -> Endpoint
Core.endpoint = Service -> Region -> Endpoint
Core.defaultEndpoint Service
defaultService,
      $sel:timeout:Service :: Maybe Seconds
Core.timeout = forall a. a -> Maybe a
Prelude.Just Seconds
70,
      $sel:check:Service :: Status -> Bool
Core.check = Status -> Bool
Core.statusSuccess,
      $sel:error:Service :: Status -> [Header] -> ByteStringLazy -> Error
Core.error = Abbrev -> Status -> [Header] -> ByteStringLazy -> Error
Core.parseXMLError Abbrev
"IAM",
      $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 request was rejected because multiple requests to change this object
-- were submitted simultaneously. Wait a few minutes and submit your
-- request again.
_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
"ConcurrentModification"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
409

-- | The request was rejected because the most recent credential report has
-- expired. To generate a new credential report, use
-- GenerateCredentialReport. For more information about credential report
-- expiration, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/credential-reports.html Getting credential reports>
-- in the /IAM User Guide/.
_CredentialReportExpiredException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CredentialReportExpiredException :: forall a. AsError a => Fold a ServiceError
_CredentialReportExpiredException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ReportExpired"
    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
410

-- | The request was rejected because the credential report does not exist.
-- To generate a credential report, use GenerateCredentialReport.
_CredentialReportNotPresentException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CredentialReportNotPresentException :: forall a. AsError a => Fold a ServiceError
_CredentialReportNotPresentException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ReportNotPresent"
    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
410

-- | The request was rejected because the credential report is still being
-- generated.
_CredentialReportNotReadyException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_CredentialReportNotReadyException :: forall a. AsError a => Fold a ServiceError
_CredentialReportNotReadyException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ReportInProgress"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
404

-- | The request was rejected because it attempted to delete a resource that
-- has attached subordinate entities. The error message describes these
-- entities.
_DeleteConflictException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DeleteConflictException :: forall a. AsError a => Fold a ServiceError
_DeleteConflictException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"DeleteConflict"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
409

-- | The request was rejected because the same certificate is associated with
-- an IAM user in the account.
_DuplicateCertificateException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DuplicateCertificateException :: forall a. AsError a => Fold a ServiceError
_DuplicateCertificateException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"DuplicateCertificate"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
409

-- | The request was rejected because the SSH public key is already
-- associated with the specified IAM user.
_DuplicateSSHPublicKeyException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_DuplicateSSHPublicKeyException :: forall a. AsError a => Fold a ServiceError
_DuplicateSSHPublicKeyException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"DuplicateSSHPublicKey"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400

-- | The request was rejected because it attempted to create a resource that
-- already exists.
_EntityAlreadyExistsException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_EntityAlreadyExistsException :: forall a. AsError a => Fold a ServiceError
_EntityAlreadyExistsException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"EntityAlreadyExists"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
409

-- | The request was rejected because it referenced an entity that is
-- temporarily unmodifiable, such as a user name that was deleted and then
-- recreated. The error indicates that the request is likely to succeed if
-- you try again after waiting several minutes. The error message describes
-- the entity.
_EntityTemporarilyUnmodifiableException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_EntityTemporarilyUnmodifiableException :: forall a. AsError a => Fold a ServiceError
_EntityTemporarilyUnmodifiableException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"EntityTemporarilyUnmodifiable"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
409

-- | The request was rejected because the authentication code was not
-- recognized. The error message describes the specific error.
_InvalidAuthenticationCodeException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidAuthenticationCodeException :: forall a. AsError a => Fold a ServiceError
_InvalidAuthenticationCodeException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidAuthenticationCode"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
403

-- | The request was rejected because the certificate is invalid.
_InvalidCertificateException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidCertificateException :: forall a. AsError a => Fold a ServiceError
_InvalidCertificateException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidCertificate"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400

-- | The request was rejected because an invalid or out-of-range value was
-- supplied for an input parameter.
_InvalidInputException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidInputException :: forall a. AsError a => Fold a ServiceError
_InvalidInputException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidInput"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400

-- | The request was rejected because the public key is malformed or
-- otherwise invalid.
_InvalidPublicKeyException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidPublicKeyException :: forall a. AsError a => Fold a ServiceError
_InvalidPublicKeyException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidPublicKey"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400

-- | The request was rejected because the type of user for the transaction
-- was incorrect.
_InvalidUserTypeException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InvalidUserTypeException :: forall a. AsError a => Fold a ServiceError
_InvalidUserTypeException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InvalidUserType"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400

-- | The request was rejected because the public key certificate and the
-- private key do not match.
_KeyPairMismatchException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_KeyPairMismatchException :: forall a. AsError a => Fold a ServiceError
_KeyPairMismatchException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"KeyPairMismatch"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400

-- | The request was rejected because it attempted to create resources beyond
-- the current Amazon Web Services account limits. The error message
-- describes the limit exceeded.
_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
"LimitExceeded"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
409

-- | The request was rejected because the certificate was malformed or
-- expired. The error message describes the specific error.
_MalformedCertificateException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_MalformedCertificateException :: forall a. AsError a => Fold a ServiceError
_MalformedCertificateException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"MalformedCertificate"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400

-- | The request was rejected because the policy document was malformed. The
-- error message describes the specific error.
_MalformedPolicyDocumentException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_MalformedPolicyDocumentException :: forall a. AsError a => Fold a ServiceError
_MalformedPolicyDocumentException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"MalformedPolicyDocument"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400

-- | The request was rejected because it referenced a resource entity that
-- does not exist. The error message describes the resource.
_NoSuchEntityException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_NoSuchEntityException :: forall a. AsError a => Fold a ServiceError
_NoSuchEntityException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NoSuchEntity"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
404

-- | The request was rejected because the provided password did not meet the
-- requirements imposed by the account password policy.
_PasswordPolicyViolationException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_PasswordPolicyViolationException :: forall a. AsError a => Fold a ServiceError
_PasswordPolicyViolationException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"PasswordPolicyViolation"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400

-- | The request failed because a provided policy could not be successfully
-- evaluated. An additional detailed message indicates the source of the
-- failure.
_PolicyEvaluationException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_PolicyEvaluationException :: forall a. AsError a => Fold a ServiceError
_PolicyEvaluationException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"PolicyEvaluation"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
500

-- | The request failed because Amazon Web Services service role policies can
-- only be attached to the service-linked role for that service.
_PolicyNotAttachableException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_PolicyNotAttachableException :: forall a. AsError a => Fold a ServiceError
_PolicyNotAttachableException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"PolicyNotAttachable"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400

-- | The request failed because the maximum number of concurrent requests for
-- this account are already running.
_ReportGenerationLimitExceededException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ReportGenerationLimitExceededException :: forall a. AsError a => Fold a ServiceError
_ReportGenerationLimitExceededException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ReportGenerationLimitExceeded"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
409

-- | The request processing has failed because of an unknown error, exception
-- or failure.
_ServiceFailureException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ServiceFailureException :: forall a. AsError a => Fold a ServiceError
_ServiceFailureException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ServiceFailure"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
500

-- | The specified service does not support service-specific credentials.
_ServiceNotSupportedException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ServiceNotSupportedException :: forall a. AsError a => Fold a ServiceError
_ServiceNotSupportedException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"NotSupportedService"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
404

-- | The request was rejected because only the service that depends on the
-- service-linked role can modify or delete the role on your behalf. The
-- error message includes the name of the service that depends on this
-- service-linked role. You must request the change through that service.
_UnmodifiableEntityException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_UnmodifiableEntityException :: forall a. AsError a => Fold a ServiceError
_UnmodifiableEntityException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"UnmodifiableEntity"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400

-- | The request was rejected because the public key encoding format is
-- unsupported or unrecognized.
_UnrecognizedPublicKeyEncodingException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_UnrecognizedPublicKeyEncodingException :: forall a. AsError a => Fold a ServiceError
_UnrecognizedPublicKeyEncodingException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"UnrecognizedPublicKeyEncoding"
    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