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

    -- * Errors
    _AccessDeniedException,
    _InternalServerException,
    _ResourceNotFoundException,
    _ThrottlingException,
    _ValidationException,

    -- * DataType
    DataType (..),

    -- * MigrationWorkflowStatusEnum
    MigrationWorkflowStatusEnum (..),

    -- * Owner
    Owner (..),

    -- * PluginHealth
    PluginHealth (..),

    -- * RunEnvironment
    RunEnvironment (..),

    -- * StepActionType
    StepActionType (..),

    -- * StepGroupStatus
    StepGroupStatus (..),

    -- * StepStatus
    StepStatus (..),

    -- * TargetType
    TargetType (..),

    -- * TemplateStatus
    TemplateStatus (..),

    -- * MigrationWorkflowSummary
    MigrationWorkflowSummary (..),
    newMigrationWorkflowSummary,
    migrationWorkflowSummary_adsApplicationConfigurationName,
    migrationWorkflowSummary_completedSteps,
    migrationWorkflowSummary_creationTime,
    migrationWorkflowSummary_endTime,
    migrationWorkflowSummary_id,
    migrationWorkflowSummary_name,
    migrationWorkflowSummary_status,
    migrationWorkflowSummary_statusMessage,
    migrationWorkflowSummary_templateId,
    migrationWorkflowSummary_totalSteps,

    -- * PlatformCommand
    PlatformCommand (..),
    newPlatformCommand,
    platformCommand_linux,
    platformCommand_windows,

    -- * PlatformScriptKey
    PlatformScriptKey (..),
    newPlatformScriptKey,
    platformScriptKey_linux,
    platformScriptKey_windows,

    -- * PluginSummary
    PluginSummary (..),
    newPluginSummary,
    pluginSummary_hostname,
    pluginSummary_ipAddress,
    pluginSummary_pluginId,
    pluginSummary_registeredTime,
    pluginSummary_status,
    pluginSummary_version,

    -- * StepAutomationConfiguration
    StepAutomationConfiguration (..),
    newStepAutomationConfiguration,
    stepAutomationConfiguration_command,
    stepAutomationConfiguration_runEnvironment,
    stepAutomationConfiguration_scriptLocationS3Bucket,
    stepAutomationConfiguration_scriptLocationS3Key,
    stepAutomationConfiguration_targetType,

    -- * StepInput
    StepInput (..),
    newStepInput,
    stepInput_integerValue,
    stepInput_listOfStringsValue,
    stepInput_mapOfStringValue,
    stepInput_stringValue,

    -- * StepOutput
    StepOutput (..),
    newStepOutput,
    stepOutput_dataType,
    stepOutput_name,
    stepOutput_required,

    -- * TemplateInput
    TemplateInput (..),
    newTemplateInput,
    templateInput_dataType,
    templateInput_inputName,
    templateInput_required,

    -- * TemplateStepGroupSummary
    TemplateStepGroupSummary (..),
    newTemplateStepGroupSummary,
    templateStepGroupSummary_id,
    templateStepGroupSummary_name,
    templateStepGroupSummary_next,
    templateStepGroupSummary_previous,

    -- * TemplateStepSummary
    TemplateStepSummary (..),
    newTemplateStepSummary,
    templateStepSummary_id,
    templateStepSummary_name,
    templateStepSummary_next,
    templateStepSummary_owner,
    templateStepSummary_previous,
    templateStepSummary_stepActionType,
    templateStepSummary_stepGroupId,
    templateStepSummary_targetType,
    templateStepSummary_templateId,

    -- * TemplateSummary
    TemplateSummary (..),
    newTemplateSummary,
    templateSummary_arn,
    templateSummary_description,
    templateSummary_id,
    templateSummary_name,

    -- * Tool
    Tool (..),
    newTool,
    tool_name,
    tool_url,

    -- * WorkflowStepAutomationConfiguration
    WorkflowStepAutomationConfiguration (..),
    newWorkflowStepAutomationConfiguration,
    workflowStepAutomationConfiguration_command,
    workflowStepAutomationConfiguration_runEnvironment,
    workflowStepAutomationConfiguration_scriptLocationS3Bucket,
    workflowStepAutomationConfiguration_scriptLocationS3Key,
    workflowStepAutomationConfiguration_targetType,

    -- * WorkflowStepGroupSummary
    WorkflowStepGroupSummary (..),
    newWorkflowStepGroupSummary,
    workflowStepGroupSummary_id,
    workflowStepGroupSummary_name,
    workflowStepGroupSummary_next,
    workflowStepGroupSummary_owner,
    workflowStepGroupSummary_previous,
    workflowStepGroupSummary_status,

    -- * WorkflowStepOutput
    WorkflowStepOutput (..),
    newWorkflowStepOutput,
    workflowStepOutput_dataType,
    workflowStepOutput_name,
    workflowStepOutput_required,
    workflowStepOutput_value,

    -- * WorkflowStepOutputUnion
    WorkflowStepOutputUnion (..),
    newWorkflowStepOutputUnion,
    workflowStepOutputUnion_integerValue,
    workflowStepOutputUnion_listOfStringValue,
    workflowStepOutputUnion_stringValue,

    -- * WorkflowStepSummary
    WorkflowStepSummary (..),
    newWorkflowStepSummary,
    workflowStepSummary_description,
    workflowStepSummary_name,
    workflowStepSummary_next,
    workflowStepSummary_noOfSrvCompleted,
    workflowStepSummary_noOfSrvFailed,
    workflowStepSummary_owner,
    workflowStepSummary_previous,
    workflowStepSummary_scriptLocation,
    workflowStepSummary_status,
    workflowStepSummary_statusMessage,
    workflowStepSummary_stepActionType,
    workflowStepSummary_stepId,
    workflowStepSummary_totalNoOfSrv,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.MigrationHubOrchestrator.Types.DataType
import Amazonka.MigrationHubOrchestrator.Types.MigrationWorkflowStatusEnum
import Amazonka.MigrationHubOrchestrator.Types.MigrationWorkflowSummary
import Amazonka.MigrationHubOrchestrator.Types.Owner
import Amazonka.MigrationHubOrchestrator.Types.PlatformCommand
import Amazonka.MigrationHubOrchestrator.Types.PlatformScriptKey
import Amazonka.MigrationHubOrchestrator.Types.PluginHealth
import Amazonka.MigrationHubOrchestrator.Types.PluginSummary
import Amazonka.MigrationHubOrchestrator.Types.RunEnvironment
import Amazonka.MigrationHubOrchestrator.Types.StepActionType
import Amazonka.MigrationHubOrchestrator.Types.StepAutomationConfiguration
import Amazonka.MigrationHubOrchestrator.Types.StepGroupStatus
import Amazonka.MigrationHubOrchestrator.Types.StepInput
import Amazonka.MigrationHubOrchestrator.Types.StepOutput
import Amazonka.MigrationHubOrchestrator.Types.StepStatus
import Amazonka.MigrationHubOrchestrator.Types.TargetType
import Amazonka.MigrationHubOrchestrator.Types.TemplateInput
import Amazonka.MigrationHubOrchestrator.Types.TemplateStatus
import Amazonka.MigrationHubOrchestrator.Types.TemplateStepGroupSummary
import Amazonka.MigrationHubOrchestrator.Types.TemplateStepSummary
import Amazonka.MigrationHubOrchestrator.Types.TemplateSummary
import Amazonka.MigrationHubOrchestrator.Types.Tool
import Amazonka.MigrationHubOrchestrator.Types.WorkflowStepAutomationConfiguration
import Amazonka.MigrationHubOrchestrator.Types.WorkflowStepGroupSummary
import Amazonka.MigrationHubOrchestrator.Types.WorkflowStepOutput
import Amazonka.MigrationHubOrchestrator.Types.WorkflowStepOutputUnion
import Amazonka.MigrationHubOrchestrator.Types.WorkflowStepSummary
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Sign.V4 as Sign

-- | API version @2021-08-28@ of the Amazon Migration Hub Orchestrator SDK configuration.
defaultService :: Core.Service
defaultService :: Service
defaultService =
  Core.Service
    { $sel:abbrev:Service :: Abbrev
Core.abbrev =
        Abbrev
"MigrationHubOrchestrator",
      $sel:signer:Service :: Signer
Core.signer = Signer
Sign.v4,
      $sel:endpointPrefix:Service :: ByteString
Core.endpointPrefix = ByteString
"migrationhub-orchestrator",
      $sel:signingName:Service :: ByteString
Core.signingName = ByteString
"migrationhub-orchestrator",
      $sel:version:Service :: ByteString
Core.version = ByteString
"2021-08-28",
      $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
"MigrationHubOrchestrator",
      $sel:retry:Service :: Retry
Core.retry = Retry
retry
    }
  where
    retry :: Retry
retry =
      Core.Exponential
        { $sel:base:Exponential :: Double
Core.base = Double
5.0e-2,
          $sel:growth:Exponential :: Int
Core.growth = Int
2,
          $sel:attempts:Exponential :: Int
Core.attempts = Int
5,
          $sel:check:Exponential :: ServiceError -> Maybe Text
Core.check = forall {a}. IsString a => ServiceError -> Maybe a
check
        }
    check :: ServiceError -> Maybe a
check ServiceError
e
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
502) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"bad_gateway"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
504) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"gateway_timeout"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
500) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"general_server_error"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
509) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"limit_exceeded"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has
          ( forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
ErrorCode -> Optic' p f ServiceError ServiceError
Core.hasCode ErrorCode
"RequestThrottledException"
              forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400
          )
          ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"request_throttled_exception"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
503) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"service_unavailable"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has
          ( forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
ErrorCode -> Optic' p f ServiceError ServiceError
Core.hasCode ErrorCode
"ThrottledException"
              forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400
          )
          ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"throttled_exception"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has
          ( forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
ErrorCode -> Optic' p f ServiceError ServiceError
Core.hasCode ErrorCode
"Throttling"
              forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400
          )
          ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"throttling"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has
          ( forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
ErrorCode -> Optic' p f ServiceError ServiceError
Core.hasCode ErrorCode
"ThrottlingException"
              forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400
          )
          ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"throttling_exception"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has
          ( forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
ErrorCode -> Optic' p f ServiceError ServiceError
Core.hasCode
              ErrorCode
"ProvisionedThroughputExceededException"
              forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400
          )
          ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"throughput_exceeded"
      | forall s a. Getting Any s a -> s -> Bool
Lens.has (forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
429) ServiceError
e =
          forall a. a -> Maybe a
Prelude.Just a
"too_many_requests"
      | Bool
Prelude.otherwise = forall a. Maybe a
Prelude.Nothing

-- | You do not have sufficient access to perform this action.
_AccessDeniedException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_AccessDeniedException :: forall a. AsError a => Fold a ServiceError
_AccessDeniedException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"AccessDeniedException"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
403

-- | An internal error has occurred.
_InternalServerException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_InternalServerException :: forall a. AsError a => Fold a ServiceError
_InternalServerException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"InternalServerException"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
500

-- | The resource is not available.
_ResourceNotFoundException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ResourceNotFoundException :: forall a. AsError a => Fold a ServiceError
_ResourceNotFoundException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ResourceNotFoundException"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
404

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

-- | The input fails to satisfy the constraints specified by an AWS service.
_ValidationException :: (Core.AsError a) => Lens.Fold a Core.ServiceError
_ValidationException :: forall a. AsError a => Fold a ServiceError
_ValidationException =
  forall a. AsError a => Service -> ErrorCode -> Fold a ServiceError
Core._MatchServiceError
    Service
defaultService
    ErrorCode
"ValidationException"
    forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (p :: * -> * -> *).
(Applicative f, Choice p) =>
Int -> Optic' p f ServiceError ServiceError
Core.hasStatus Int
400