{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.CodeDeploy.Types.DeploymentInfo
-- 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.CodeDeploy.Types.DeploymentInfo where

import Amazonka.CodeDeploy.Types.AlarmConfiguration
import Amazonka.CodeDeploy.Types.AutoRollbackConfiguration
import Amazonka.CodeDeploy.Types.BlueGreenDeploymentConfiguration
import Amazonka.CodeDeploy.Types.ComputePlatform
import Amazonka.CodeDeploy.Types.DeploymentCreator
import Amazonka.CodeDeploy.Types.DeploymentOverview
import Amazonka.CodeDeploy.Types.DeploymentStatus
import Amazonka.CodeDeploy.Types.DeploymentStyle
import Amazonka.CodeDeploy.Types.ErrorInformation
import Amazonka.CodeDeploy.Types.FileExistsBehavior
import Amazonka.CodeDeploy.Types.LoadBalancerInfo
import Amazonka.CodeDeploy.Types.RelatedDeployments
import Amazonka.CodeDeploy.Types.RevisionLocation
import Amazonka.CodeDeploy.Types.RollbackInfo
import Amazonka.CodeDeploy.Types.TargetInstances
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | Information about a deployment.
--
-- /See:/ 'newDeploymentInfo' smart constructor.
data DeploymentInfo = DeploymentInfo'
  { -- | Provides information about the results of a deployment, such as whether
    -- instances in the original environment in a blue\/green deployment were
    -- not terminated.
    DeploymentInfo -> Maybe Text
additionalDeploymentStatusInfo :: Prelude.Maybe Prelude.Text,
    -- | The application name.
    DeploymentInfo -> Maybe Text
applicationName :: Prelude.Maybe Prelude.Text,
    -- | Information about the automatic rollback configuration associated with
    -- the deployment.
    DeploymentInfo -> Maybe AutoRollbackConfiguration
autoRollbackConfiguration :: Prelude.Maybe AutoRollbackConfiguration,
    -- | Information about blue\/green deployment options for this deployment.
    DeploymentInfo -> Maybe BlueGreenDeploymentConfiguration
blueGreenDeploymentConfiguration :: Prelude.Maybe BlueGreenDeploymentConfiguration,
    -- | A timestamp that indicates when the deployment was complete.
    DeploymentInfo -> Maybe POSIX
completeTime :: Prelude.Maybe Data.POSIX,
    -- | The destination platform type for the deployment (@Lambda@, @Server@, or
    -- @ECS@).
    DeploymentInfo -> Maybe ComputePlatform
computePlatform :: Prelude.Maybe ComputePlatform,
    -- | A timestamp that indicates when the deployment was created.
    DeploymentInfo -> Maybe POSIX
createTime :: Prelude.Maybe Data.POSIX,
    -- | The means by which the deployment was created:
    --
    -- -   @user@: A user created the deployment.
    --
    -- -   @autoscaling@: Amazon EC2 Auto Scaling created the deployment.
    --
    -- -   @codeDeployRollback@: A rollback process created the deployment.
    --
    -- -   @CodeDeployAutoUpdate@: An auto-update process created the
    --     deployment when it detected outdated Amazon EC2 instances.
    DeploymentInfo -> Maybe DeploymentCreator
creator :: Prelude.Maybe DeploymentCreator,
    -- | The deployment configuration name.
    DeploymentInfo -> Maybe Text
deploymentConfigName :: Prelude.Maybe Prelude.Text,
    -- | The deployment group name.
    DeploymentInfo -> Maybe Text
deploymentGroupName :: Prelude.Maybe Prelude.Text,
    -- | The unique ID of a deployment.
    DeploymentInfo -> Maybe Text
deploymentId :: Prelude.Maybe Prelude.Text,
    -- | A summary of the deployment status of the instances in the deployment.
    DeploymentInfo -> Maybe DeploymentOverview
deploymentOverview :: Prelude.Maybe DeploymentOverview,
    -- | Messages that contain information about the status of a deployment.
    DeploymentInfo -> Maybe [Text]
deploymentStatusMessages :: Prelude.Maybe [Prelude.Text],
    -- | Information about the type of deployment, either in-place or
    -- blue\/green, you want to run and whether to route deployment traffic
    -- behind a load balancer.
    DeploymentInfo -> Maybe DeploymentStyle
deploymentStyle :: Prelude.Maybe DeploymentStyle,
    -- | A comment about the deployment.
    DeploymentInfo -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Information about any error associated with this deployment.
    DeploymentInfo -> Maybe ErrorInformation
errorInformation :: Prelude.Maybe ErrorInformation,
    -- | The unique ID for an external resource (for example, a CloudFormation
    -- stack ID) that is linked to this deployment.
    DeploymentInfo -> Maybe Text
externalId :: Prelude.Maybe Prelude.Text,
    -- | Information about how CodeDeploy handles files that already exist in a
    -- deployment target location but weren\'t part of the previous successful
    -- deployment.
    --
    -- -   @DISALLOW@: The deployment fails. This is also the default behavior
    --     if no option is specified.
    --
    -- -   @OVERWRITE@: The version of the file from the application revision
    --     currently being deployed replaces the version already on the
    --     instance.
    --
    -- -   @RETAIN@: The version of the file already on the instance is kept
    --     and used as part of the new deployment.
    DeploymentInfo -> Maybe FileExistsBehavior
fileExistsBehavior :: Prelude.Maybe FileExistsBehavior,
    -- | If true, then if an @ApplicationStop@, @BeforeBlockTraffic@, or
    -- @AfterBlockTraffic@ deployment lifecycle event to an instance fails,
    -- then the deployment continues to the next deployment lifecycle event.
    -- For example, if @ApplicationStop@ fails, the deployment continues with
    -- DownloadBundle. If @BeforeBlockTraffic@ fails, the deployment continues
    -- with @BlockTraffic@. If @AfterBlockTraffic@ fails, the deployment
    -- continues with @ApplicationStop@.
    --
    -- If false or not specified, then if a lifecycle event fails during a
    -- deployment to an instance, that deployment fails. If deployment to that
    -- instance is part of an overall deployment and the number of healthy
    -- hosts is not less than the minimum number of healthy hosts, then a
    -- deployment to the next instance is attempted.
    --
    -- During a deployment, the CodeDeploy agent runs the scripts specified for
    -- @ApplicationStop@, @BeforeBlockTraffic@, and @AfterBlockTraffic@ in the
    -- AppSpec file from the previous successful deployment. (All other scripts
    -- are run from the AppSpec file in the current deployment.) If one of
    -- these scripts contains an error and does not run successfully, the
    -- deployment can fail.
    --
    -- If the cause of the failure is a script from the last successful
    -- deployment that will never run successfully, create a new deployment and
    -- use @ignoreApplicationStopFailures@ to specify that the
    -- @ApplicationStop@, @BeforeBlockTraffic@, and @AfterBlockTraffic@
    -- failures should be ignored.
    DeploymentInfo -> Maybe Bool
ignoreApplicationStopFailures :: Prelude.Maybe Prelude.Bool,
    -- | Indicates whether the wait period set for the termination of instances
    -- in the original environment has started. Status is \'false\' if the
    -- KEEP_ALIVE option is specified. Otherwise, \'true\' as soon as the
    -- termination wait period starts.
    DeploymentInfo -> Maybe Bool
instanceTerminationWaitTimeStarted :: Prelude.Maybe Prelude.Bool,
    -- | Information about the load balancer used in the deployment.
    DeploymentInfo -> Maybe LoadBalancerInfo
loadBalancerInfo :: Prelude.Maybe LoadBalancerInfo,
    DeploymentInfo -> Maybe AlarmConfiguration
overrideAlarmConfiguration :: Prelude.Maybe AlarmConfiguration,
    -- | Information about the application revision that was deployed to the
    -- deployment group before the most recent successful deployment.
    DeploymentInfo -> Maybe RevisionLocation
previousRevision :: Prelude.Maybe RevisionLocation,
    DeploymentInfo -> Maybe RelatedDeployments
relatedDeployments :: Prelude.Maybe RelatedDeployments,
    -- | Information about the location of stored application artifacts and the
    -- service from which to retrieve them.
    DeploymentInfo -> Maybe RevisionLocation
revision :: Prelude.Maybe RevisionLocation,
    -- | Information about a deployment rollback.
    DeploymentInfo -> Maybe RollbackInfo
rollbackInfo :: Prelude.Maybe RollbackInfo,
    -- | A timestamp that indicates when the deployment was deployed to the
    -- deployment group.
    --
    -- In some cases, the reported value of the start time might be later than
    -- the complete time. This is due to differences in the clock settings of
    -- backend servers that participate in the deployment process.
    DeploymentInfo -> Maybe POSIX
startTime :: Prelude.Maybe Data.POSIX,
    -- | The current state of the deployment as a whole.
    DeploymentInfo -> Maybe DeploymentStatus
status :: Prelude.Maybe DeploymentStatus,
    -- | Information about the instances that belong to the replacement
    -- environment in a blue\/green deployment.
    DeploymentInfo -> Maybe TargetInstances
targetInstances :: Prelude.Maybe TargetInstances,
    -- | Indicates whether only instances that are not running the latest
    -- application revision are to be deployed to.
    DeploymentInfo -> Maybe Bool
updateOutdatedInstancesOnly :: Prelude.Maybe Prelude.Bool
  }
  deriving (DeploymentInfo -> DeploymentInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeploymentInfo -> DeploymentInfo -> Bool
$c/= :: DeploymentInfo -> DeploymentInfo -> Bool
== :: DeploymentInfo -> DeploymentInfo -> Bool
$c== :: DeploymentInfo -> DeploymentInfo -> Bool
Prelude.Eq, ReadPrec [DeploymentInfo]
ReadPrec DeploymentInfo
Int -> ReadS DeploymentInfo
ReadS [DeploymentInfo]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeploymentInfo]
$creadListPrec :: ReadPrec [DeploymentInfo]
readPrec :: ReadPrec DeploymentInfo
$creadPrec :: ReadPrec DeploymentInfo
readList :: ReadS [DeploymentInfo]
$creadList :: ReadS [DeploymentInfo]
readsPrec :: Int -> ReadS DeploymentInfo
$creadsPrec :: Int -> ReadS DeploymentInfo
Prelude.Read, Int -> DeploymentInfo -> ShowS
[DeploymentInfo] -> ShowS
DeploymentInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeploymentInfo] -> ShowS
$cshowList :: [DeploymentInfo] -> ShowS
show :: DeploymentInfo -> String
$cshow :: DeploymentInfo -> String
showsPrec :: Int -> DeploymentInfo -> ShowS
$cshowsPrec :: Int -> DeploymentInfo -> ShowS
Prelude.Show, forall x. Rep DeploymentInfo x -> DeploymentInfo
forall x. DeploymentInfo -> Rep DeploymentInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeploymentInfo x -> DeploymentInfo
$cfrom :: forall x. DeploymentInfo -> Rep DeploymentInfo x
Prelude.Generic)

-- |
-- Create a value of 'DeploymentInfo' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'additionalDeploymentStatusInfo', 'deploymentInfo_additionalDeploymentStatusInfo' - Provides information about the results of a deployment, such as whether
-- instances in the original environment in a blue\/green deployment were
-- not terminated.
--
-- 'applicationName', 'deploymentInfo_applicationName' - The application name.
--
-- 'autoRollbackConfiguration', 'deploymentInfo_autoRollbackConfiguration' - Information about the automatic rollback configuration associated with
-- the deployment.
--
-- 'blueGreenDeploymentConfiguration', 'deploymentInfo_blueGreenDeploymentConfiguration' - Information about blue\/green deployment options for this deployment.
--
-- 'completeTime', 'deploymentInfo_completeTime' - A timestamp that indicates when the deployment was complete.
--
-- 'computePlatform', 'deploymentInfo_computePlatform' - The destination platform type for the deployment (@Lambda@, @Server@, or
-- @ECS@).
--
-- 'createTime', 'deploymentInfo_createTime' - A timestamp that indicates when the deployment was created.
--
-- 'creator', 'deploymentInfo_creator' - The means by which the deployment was created:
--
-- -   @user@: A user created the deployment.
--
-- -   @autoscaling@: Amazon EC2 Auto Scaling created the deployment.
--
-- -   @codeDeployRollback@: A rollback process created the deployment.
--
-- -   @CodeDeployAutoUpdate@: An auto-update process created the
--     deployment when it detected outdated Amazon EC2 instances.
--
-- 'deploymentConfigName', 'deploymentInfo_deploymentConfigName' - The deployment configuration name.
--
-- 'deploymentGroupName', 'deploymentInfo_deploymentGroupName' - The deployment group name.
--
-- 'deploymentId', 'deploymentInfo_deploymentId' - The unique ID of a deployment.
--
-- 'deploymentOverview', 'deploymentInfo_deploymentOverview' - A summary of the deployment status of the instances in the deployment.
--
-- 'deploymentStatusMessages', 'deploymentInfo_deploymentStatusMessages' - Messages that contain information about the status of a deployment.
--
-- 'deploymentStyle', 'deploymentInfo_deploymentStyle' - Information about the type of deployment, either in-place or
-- blue\/green, you want to run and whether to route deployment traffic
-- behind a load balancer.
--
-- 'description', 'deploymentInfo_description' - A comment about the deployment.
--
-- 'errorInformation', 'deploymentInfo_errorInformation' - Information about any error associated with this deployment.
--
-- 'externalId', 'deploymentInfo_externalId' - The unique ID for an external resource (for example, a CloudFormation
-- stack ID) that is linked to this deployment.
--
-- 'fileExistsBehavior', 'deploymentInfo_fileExistsBehavior' - Information about how CodeDeploy handles files that already exist in a
-- deployment target location but weren\'t part of the previous successful
-- deployment.
--
-- -   @DISALLOW@: The deployment fails. This is also the default behavior
--     if no option is specified.
--
-- -   @OVERWRITE@: The version of the file from the application revision
--     currently being deployed replaces the version already on the
--     instance.
--
-- -   @RETAIN@: The version of the file already on the instance is kept
--     and used as part of the new deployment.
--
-- 'ignoreApplicationStopFailures', 'deploymentInfo_ignoreApplicationStopFailures' - If true, then if an @ApplicationStop@, @BeforeBlockTraffic@, or
-- @AfterBlockTraffic@ deployment lifecycle event to an instance fails,
-- then the deployment continues to the next deployment lifecycle event.
-- For example, if @ApplicationStop@ fails, the deployment continues with
-- DownloadBundle. If @BeforeBlockTraffic@ fails, the deployment continues
-- with @BlockTraffic@. If @AfterBlockTraffic@ fails, the deployment
-- continues with @ApplicationStop@.
--
-- If false or not specified, then if a lifecycle event fails during a
-- deployment to an instance, that deployment fails. If deployment to that
-- instance is part of an overall deployment and the number of healthy
-- hosts is not less than the minimum number of healthy hosts, then a
-- deployment to the next instance is attempted.
--
-- During a deployment, the CodeDeploy agent runs the scripts specified for
-- @ApplicationStop@, @BeforeBlockTraffic@, and @AfterBlockTraffic@ in the
-- AppSpec file from the previous successful deployment. (All other scripts
-- are run from the AppSpec file in the current deployment.) If one of
-- these scripts contains an error and does not run successfully, the
-- deployment can fail.
--
-- If the cause of the failure is a script from the last successful
-- deployment that will never run successfully, create a new deployment and
-- use @ignoreApplicationStopFailures@ to specify that the
-- @ApplicationStop@, @BeforeBlockTraffic@, and @AfterBlockTraffic@
-- failures should be ignored.
--
-- 'instanceTerminationWaitTimeStarted', 'deploymentInfo_instanceTerminationWaitTimeStarted' - Indicates whether the wait period set for the termination of instances
-- in the original environment has started. Status is \'false\' if the
-- KEEP_ALIVE option is specified. Otherwise, \'true\' as soon as the
-- termination wait period starts.
--
-- 'loadBalancerInfo', 'deploymentInfo_loadBalancerInfo' - Information about the load balancer used in the deployment.
--
-- 'overrideAlarmConfiguration', 'deploymentInfo_overrideAlarmConfiguration' - Undocumented member.
--
-- 'previousRevision', 'deploymentInfo_previousRevision' - Information about the application revision that was deployed to the
-- deployment group before the most recent successful deployment.
--
-- 'relatedDeployments', 'deploymentInfo_relatedDeployments' - Undocumented member.
--
-- 'revision', 'deploymentInfo_revision' - Information about the location of stored application artifacts and the
-- service from which to retrieve them.
--
-- 'rollbackInfo', 'deploymentInfo_rollbackInfo' - Information about a deployment rollback.
--
-- 'startTime', 'deploymentInfo_startTime' - A timestamp that indicates when the deployment was deployed to the
-- deployment group.
--
-- In some cases, the reported value of the start time might be later than
-- the complete time. This is due to differences in the clock settings of
-- backend servers that participate in the deployment process.
--
-- 'status', 'deploymentInfo_status' - The current state of the deployment as a whole.
--
-- 'targetInstances', 'deploymentInfo_targetInstances' - Information about the instances that belong to the replacement
-- environment in a blue\/green deployment.
--
-- 'updateOutdatedInstancesOnly', 'deploymentInfo_updateOutdatedInstancesOnly' - Indicates whether only instances that are not running the latest
-- application revision are to be deployed to.
newDeploymentInfo ::
  DeploymentInfo
newDeploymentInfo :: DeploymentInfo
newDeploymentInfo =
  DeploymentInfo'
    { $sel:additionalDeploymentStatusInfo:DeploymentInfo' :: Maybe Text
additionalDeploymentStatusInfo =
        forall a. Maybe a
Prelude.Nothing,
      $sel:applicationName:DeploymentInfo' :: Maybe Text
applicationName = forall a. Maybe a
Prelude.Nothing,
      $sel:autoRollbackConfiguration:DeploymentInfo' :: Maybe AutoRollbackConfiguration
autoRollbackConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:blueGreenDeploymentConfiguration:DeploymentInfo' :: Maybe BlueGreenDeploymentConfiguration
blueGreenDeploymentConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:completeTime:DeploymentInfo' :: Maybe POSIX
completeTime = forall a. Maybe a
Prelude.Nothing,
      $sel:computePlatform:DeploymentInfo' :: Maybe ComputePlatform
computePlatform = forall a. Maybe a
Prelude.Nothing,
      $sel:createTime:DeploymentInfo' :: Maybe POSIX
createTime = forall a. Maybe a
Prelude.Nothing,
      $sel:creator:DeploymentInfo' :: Maybe DeploymentCreator
creator = forall a. Maybe a
Prelude.Nothing,
      $sel:deploymentConfigName:DeploymentInfo' :: Maybe Text
deploymentConfigName = forall a. Maybe a
Prelude.Nothing,
      $sel:deploymentGroupName:DeploymentInfo' :: Maybe Text
deploymentGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:deploymentId:DeploymentInfo' :: Maybe Text
deploymentId = forall a. Maybe a
Prelude.Nothing,
      $sel:deploymentOverview:DeploymentInfo' :: Maybe DeploymentOverview
deploymentOverview = forall a. Maybe a
Prelude.Nothing,
      $sel:deploymentStatusMessages:DeploymentInfo' :: Maybe [Text]
deploymentStatusMessages = forall a. Maybe a
Prelude.Nothing,
      $sel:deploymentStyle:DeploymentInfo' :: Maybe DeploymentStyle
deploymentStyle = forall a. Maybe a
Prelude.Nothing,
      $sel:description:DeploymentInfo' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:errorInformation:DeploymentInfo' :: Maybe ErrorInformation
errorInformation = forall a. Maybe a
Prelude.Nothing,
      $sel:externalId:DeploymentInfo' :: Maybe Text
externalId = forall a. Maybe a
Prelude.Nothing,
      $sel:fileExistsBehavior:DeploymentInfo' :: Maybe FileExistsBehavior
fileExistsBehavior = forall a. Maybe a
Prelude.Nothing,
      $sel:ignoreApplicationStopFailures:DeploymentInfo' :: Maybe Bool
ignoreApplicationStopFailures = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceTerminationWaitTimeStarted:DeploymentInfo' :: Maybe Bool
instanceTerminationWaitTimeStarted = forall a. Maybe a
Prelude.Nothing,
      $sel:loadBalancerInfo:DeploymentInfo' :: Maybe LoadBalancerInfo
loadBalancerInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:overrideAlarmConfiguration:DeploymentInfo' :: Maybe AlarmConfiguration
overrideAlarmConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:previousRevision:DeploymentInfo' :: Maybe RevisionLocation
previousRevision = forall a. Maybe a
Prelude.Nothing,
      $sel:relatedDeployments:DeploymentInfo' :: Maybe RelatedDeployments
relatedDeployments = forall a. Maybe a
Prelude.Nothing,
      $sel:revision:DeploymentInfo' :: Maybe RevisionLocation
revision = forall a. Maybe a
Prelude.Nothing,
      $sel:rollbackInfo:DeploymentInfo' :: Maybe RollbackInfo
rollbackInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:DeploymentInfo' :: Maybe POSIX
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:status:DeploymentInfo' :: Maybe DeploymentStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:targetInstances:DeploymentInfo' :: Maybe TargetInstances
targetInstances = forall a. Maybe a
Prelude.Nothing,
      $sel:updateOutdatedInstancesOnly:DeploymentInfo' :: Maybe Bool
updateOutdatedInstancesOnly = forall a. Maybe a
Prelude.Nothing
    }

-- | Provides information about the results of a deployment, such as whether
-- instances in the original environment in a blue\/green deployment were
-- not terminated.
deploymentInfo_additionalDeploymentStatusInfo :: Lens.Lens' DeploymentInfo (Prelude.Maybe Prelude.Text)
deploymentInfo_additionalDeploymentStatusInfo :: Lens' DeploymentInfo (Maybe Text)
deploymentInfo_additionalDeploymentStatusInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe Text
additionalDeploymentStatusInfo :: Maybe Text
$sel:additionalDeploymentStatusInfo:DeploymentInfo' :: DeploymentInfo -> Maybe Text
additionalDeploymentStatusInfo} -> Maybe Text
additionalDeploymentStatusInfo) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe Text
a -> DeploymentInfo
s {$sel:additionalDeploymentStatusInfo:DeploymentInfo' :: Maybe Text
additionalDeploymentStatusInfo = Maybe Text
a} :: DeploymentInfo)

-- | The application name.
deploymentInfo_applicationName :: Lens.Lens' DeploymentInfo (Prelude.Maybe Prelude.Text)
deploymentInfo_applicationName :: Lens' DeploymentInfo (Maybe Text)
deploymentInfo_applicationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe Text
applicationName :: Maybe Text
$sel:applicationName:DeploymentInfo' :: DeploymentInfo -> Maybe Text
applicationName} -> Maybe Text
applicationName) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe Text
a -> DeploymentInfo
s {$sel:applicationName:DeploymentInfo' :: Maybe Text
applicationName = Maybe Text
a} :: DeploymentInfo)

-- | Information about the automatic rollback configuration associated with
-- the deployment.
deploymentInfo_autoRollbackConfiguration :: Lens.Lens' DeploymentInfo (Prelude.Maybe AutoRollbackConfiguration)
deploymentInfo_autoRollbackConfiguration :: Lens' DeploymentInfo (Maybe AutoRollbackConfiguration)
deploymentInfo_autoRollbackConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe AutoRollbackConfiguration
autoRollbackConfiguration :: Maybe AutoRollbackConfiguration
$sel:autoRollbackConfiguration:DeploymentInfo' :: DeploymentInfo -> Maybe AutoRollbackConfiguration
autoRollbackConfiguration} -> Maybe AutoRollbackConfiguration
autoRollbackConfiguration) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe AutoRollbackConfiguration
a -> DeploymentInfo
s {$sel:autoRollbackConfiguration:DeploymentInfo' :: Maybe AutoRollbackConfiguration
autoRollbackConfiguration = Maybe AutoRollbackConfiguration
a} :: DeploymentInfo)

-- | Information about blue\/green deployment options for this deployment.
deploymentInfo_blueGreenDeploymentConfiguration :: Lens.Lens' DeploymentInfo (Prelude.Maybe BlueGreenDeploymentConfiguration)
deploymentInfo_blueGreenDeploymentConfiguration :: Lens' DeploymentInfo (Maybe BlueGreenDeploymentConfiguration)
deploymentInfo_blueGreenDeploymentConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe BlueGreenDeploymentConfiguration
blueGreenDeploymentConfiguration :: Maybe BlueGreenDeploymentConfiguration
$sel:blueGreenDeploymentConfiguration:DeploymentInfo' :: DeploymentInfo -> Maybe BlueGreenDeploymentConfiguration
blueGreenDeploymentConfiguration} -> Maybe BlueGreenDeploymentConfiguration
blueGreenDeploymentConfiguration) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe BlueGreenDeploymentConfiguration
a -> DeploymentInfo
s {$sel:blueGreenDeploymentConfiguration:DeploymentInfo' :: Maybe BlueGreenDeploymentConfiguration
blueGreenDeploymentConfiguration = Maybe BlueGreenDeploymentConfiguration
a} :: DeploymentInfo)

-- | A timestamp that indicates when the deployment was complete.
deploymentInfo_completeTime :: Lens.Lens' DeploymentInfo (Prelude.Maybe Prelude.UTCTime)
deploymentInfo_completeTime :: Lens' DeploymentInfo (Maybe UTCTime)
deploymentInfo_completeTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe POSIX
completeTime :: Maybe POSIX
$sel:completeTime:DeploymentInfo' :: DeploymentInfo -> Maybe POSIX
completeTime} -> Maybe POSIX
completeTime) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe POSIX
a -> DeploymentInfo
s {$sel:completeTime:DeploymentInfo' :: Maybe POSIX
completeTime = Maybe POSIX
a} :: DeploymentInfo) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The destination platform type for the deployment (@Lambda@, @Server@, or
-- @ECS@).
deploymentInfo_computePlatform :: Lens.Lens' DeploymentInfo (Prelude.Maybe ComputePlatform)
deploymentInfo_computePlatform :: Lens' DeploymentInfo (Maybe ComputePlatform)
deploymentInfo_computePlatform = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe ComputePlatform
computePlatform :: Maybe ComputePlatform
$sel:computePlatform:DeploymentInfo' :: DeploymentInfo -> Maybe ComputePlatform
computePlatform} -> Maybe ComputePlatform
computePlatform) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe ComputePlatform
a -> DeploymentInfo
s {$sel:computePlatform:DeploymentInfo' :: Maybe ComputePlatform
computePlatform = Maybe ComputePlatform
a} :: DeploymentInfo)

-- | A timestamp that indicates when the deployment was created.
deploymentInfo_createTime :: Lens.Lens' DeploymentInfo (Prelude.Maybe Prelude.UTCTime)
deploymentInfo_createTime :: Lens' DeploymentInfo (Maybe UTCTime)
deploymentInfo_createTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe POSIX
createTime :: Maybe POSIX
$sel:createTime:DeploymentInfo' :: DeploymentInfo -> Maybe POSIX
createTime} -> Maybe POSIX
createTime) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe POSIX
a -> DeploymentInfo
s {$sel:createTime:DeploymentInfo' :: Maybe POSIX
createTime = Maybe POSIX
a} :: DeploymentInfo) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The means by which the deployment was created:
--
-- -   @user@: A user created the deployment.
--
-- -   @autoscaling@: Amazon EC2 Auto Scaling created the deployment.
--
-- -   @codeDeployRollback@: A rollback process created the deployment.
--
-- -   @CodeDeployAutoUpdate@: An auto-update process created the
--     deployment when it detected outdated Amazon EC2 instances.
deploymentInfo_creator :: Lens.Lens' DeploymentInfo (Prelude.Maybe DeploymentCreator)
deploymentInfo_creator :: Lens' DeploymentInfo (Maybe DeploymentCreator)
deploymentInfo_creator = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe DeploymentCreator
creator :: Maybe DeploymentCreator
$sel:creator:DeploymentInfo' :: DeploymentInfo -> Maybe DeploymentCreator
creator} -> Maybe DeploymentCreator
creator) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe DeploymentCreator
a -> DeploymentInfo
s {$sel:creator:DeploymentInfo' :: Maybe DeploymentCreator
creator = Maybe DeploymentCreator
a} :: DeploymentInfo)

-- | The deployment configuration name.
deploymentInfo_deploymentConfigName :: Lens.Lens' DeploymentInfo (Prelude.Maybe Prelude.Text)
deploymentInfo_deploymentConfigName :: Lens' DeploymentInfo (Maybe Text)
deploymentInfo_deploymentConfigName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe Text
deploymentConfigName :: Maybe Text
$sel:deploymentConfigName:DeploymentInfo' :: DeploymentInfo -> Maybe Text
deploymentConfigName} -> Maybe Text
deploymentConfigName) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe Text
a -> DeploymentInfo
s {$sel:deploymentConfigName:DeploymentInfo' :: Maybe Text
deploymentConfigName = Maybe Text
a} :: DeploymentInfo)

-- | The deployment group name.
deploymentInfo_deploymentGroupName :: Lens.Lens' DeploymentInfo (Prelude.Maybe Prelude.Text)
deploymentInfo_deploymentGroupName :: Lens' DeploymentInfo (Maybe Text)
deploymentInfo_deploymentGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe Text
deploymentGroupName :: Maybe Text
$sel:deploymentGroupName:DeploymentInfo' :: DeploymentInfo -> Maybe Text
deploymentGroupName} -> Maybe Text
deploymentGroupName) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe Text
a -> DeploymentInfo
s {$sel:deploymentGroupName:DeploymentInfo' :: Maybe Text
deploymentGroupName = Maybe Text
a} :: DeploymentInfo)

-- | The unique ID of a deployment.
deploymentInfo_deploymentId :: Lens.Lens' DeploymentInfo (Prelude.Maybe Prelude.Text)
deploymentInfo_deploymentId :: Lens' DeploymentInfo (Maybe Text)
deploymentInfo_deploymentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe Text
deploymentId :: Maybe Text
$sel:deploymentId:DeploymentInfo' :: DeploymentInfo -> Maybe Text
deploymentId} -> Maybe Text
deploymentId) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe Text
a -> DeploymentInfo
s {$sel:deploymentId:DeploymentInfo' :: Maybe Text
deploymentId = Maybe Text
a} :: DeploymentInfo)

-- | A summary of the deployment status of the instances in the deployment.
deploymentInfo_deploymentOverview :: Lens.Lens' DeploymentInfo (Prelude.Maybe DeploymentOverview)
deploymentInfo_deploymentOverview :: Lens' DeploymentInfo (Maybe DeploymentOverview)
deploymentInfo_deploymentOverview = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe DeploymentOverview
deploymentOverview :: Maybe DeploymentOverview
$sel:deploymentOverview:DeploymentInfo' :: DeploymentInfo -> Maybe DeploymentOverview
deploymentOverview} -> Maybe DeploymentOverview
deploymentOverview) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe DeploymentOverview
a -> DeploymentInfo
s {$sel:deploymentOverview:DeploymentInfo' :: Maybe DeploymentOverview
deploymentOverview = Maybe DeploymentOverview
a} :: DeploymentInfo)

-- | Messages that contain information about the status of a deployment.
deploymentInfo_deploymentStatusMessages :: Lens.Lens' DeploymentInfo (Prelude.Maybe [Prelude.Text])
deploymentInfo_deploymentStatusMessages :: Lens' DeploymentInfo (Maybe [Text])
deploymentInfo_deploymentStatusMessages = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe [Text]
deploymentStatusMessages :: Maybe [Text]
$sel:deploymentStatusMessages:DeploymentInfo' :: DeploymentInfo -> Maybe [Text]
deploymentStatusMessages} -> Maybe [Text]
deploymentStatusMessages) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe [Text]
a -> DeploymentInfo
s {$sel:deploymentStatusMessages:DeploymentInfo' :: Maybe [Text]
deploymentStatusMessages = Maybe [Text]
a} :: DeploymentInfo) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Information about the type of deployment, either in-place or
-- blue\/green, you want to run and whether to route deployment traffic
-- behind a load balancer.
deploymentInfo_deploymentStyle :: Lens.Lens' DeploymentInfo (Prelude.Maybe DeploymentStyle)
deploymentInfo_deploymentStyle :: Lens' DeploymentInfo (Maybe DeploymentStyle)
deploymentInfo_deploymentStyle = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe DeploymentStyle
deploymentStyle :: Maybe DeploymentStyle
$sel:deploymentStyle:DeploymentInfo' :: DeploymentInfo -> Maybe DeploymentStyle
deploymentStyle} -> Maybe DeploymentStyle
deploymentStyle) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe DeploymentStyle
a -> DeploymentInfo
s {$sel:deploymentStyle:DeploymentInfo' :: Maybe DeploymentStyle
deploymentStyle = Maybe DeploymentStyle
a} :: DeploymentInfo)

-- | A comment about the deployment.
deploymentInfo_description :: Lens.Lens' DeploymentInfo (Prelude.Maybe Prelude.Text)
deploymentInfo_description :: Lens' DeploymentInfo (Maybe Text)
deploymentInfo_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe Text
description :: Maybe Text
$sel:description:DeploymentInfo' :: DeploymentInfo -> Maybe Text
description} -> Maybe Text
description) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe Text
a -> DeploymentInfo
s {$sel:description:DeploymentInfo' :: Maybe Text
description = Maybe Text
a} :: DeploymentInfo)

-- | Information about any error associated with this deployment.
deploymentInfo_errorInformation :: Lens.Lens' DeploymentInfo (Prelude.Maybe ErrorInformation)
deploymentInfo_errorInformation :: Lens' DeploymentInfo (Maybe ErrorInformation)
deploymentInfo_errorInformation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe ErrorInformation
errorInformation :: Maybe ErrorInformation
$sel:errorInformation:DeploymentInfo' :: DeploymentInfo -> Maybe ErrorInformation
errorInformation} -> Maybe ErrorInformation
errorInformation) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe ErrorInformation
a -> DeploymentInfo
s {$sel:errorInformation:DeploymentInfo' :: Maybe ErrorInformation
errorInformation = Maybe ErrorInformation
a} :: DeploymentInfo)

-- | The unique ID for an external resource (for example, a CloudFormation
-- stack ID) that is linked to this deployment.
deploymentInfo_externalId :: Lens.Lens' DeploymentInfo (Prelude.Maybe Prelude.Text)
deploymentInfo_externalId :: Lens' DeploymentInfo (Maybe Text)
deploymentInfo_externalId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe Text
externalId :: Maybe Text
$sel:externalId:DeploymentInfo' :: DeploymentInfo -> Maybe Text
externalId} -> Maybe Text
externalId) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe Text
a -> DeploymentInfo
s {$sel:externalId:DeploymentInfo' :: Maybe Text
externalId = Maybe Text
a} :: DeploymentInfo)

-- | Information about how CodeDeploy handles files that already exist in a
-- deployment target location but weren\'t part of the previous successful
-- deployment.
--
-- -   @DISALLOW@: The deployment fails. This is also the default behavior
--     if no option is specified.
--
-- -   @OVERWRITE@: The version of the file from the application revision
--     currently being deployed replaces the version already on the
--     instance.
--
-- -   @RETAIN@: The version of the file already on the instance is kept
--     and used as part of the new deployment.
deploymentInfo_fileExistsBehavior :: Lens.Lens' DeploymentInfo (Prelude.Maybe FileExistsBehavior)
deploymentInfo_fileExistsBehavior :: Lens' DeploymentInfo (Maybe FileExistsBehavior)
deploymentInfo_fileExistsBehavior = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe FileExistsBehavior
fileExistsBehavior :: Maybe FileExistsBehavior
$sel:fileExistsBehavior:DeploymentInfo' :: DeploymentInfo -> Maybe FileExistsBehavior
fileExistsBehavior} -> Maybe FileExistsBehavior
fileExistsBehavior) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe FileExistsBehavior
a -> DeploymentInfo
s {$sel:fileExistsBehavior:DeploymentInfo' :: Maybe FileExistsBehavior
fileExistsBehavior = Maybe FileExistsBehavior
a} :: DeploymentInfo)

-- | If true, then if an @ApplicationStop@, @BeforeBlockTraffic@, or
-- @AfterBlockTraffic@ deployment lifecycle event to an instance fails,
-- then the deployment continues to the next deployment lifecycle event.
-- For example, if @ApplicationStop@ fails, the deployment continues with
-- DownloadBundle. If @BeforeBlockTraffic@ fails, the deployment continues
-- with @BlockTraffic@. If @AfterBlockTraffic@ fails, the deployment
-- continues with @ApplicationStop@.
--
-- If false or not specified, then if a lifecycle event fails during a
-- deployment to an instance, that deployment fails. If deployment to that
-- instance is part of an overall deployment and the number of healthy
-- hosts is not less than the minimum number of healthy hosts, then a
-- deployment to the next instance is attempted.
--
-- During a deployment, the CodeDeploy agent runs the scripts specified for
-- @ApplicationStop@, @BeforeBlockTraffic@, and @AfterBlockTraffic@ in the
-- AppSpec file from the previous successful deployment. (All other scripts
-- are run from the AppSpec file in the current deployment.) If one of
-- these scripts contains an error and does not run successfully, the
-- deployment can fail.
--
-- If the cause of the failure is a script from the last successful
-- deployment that will never run successfully, create a new deployment and
-- use @ignoreApplicationStopFailures@ to specify that the
-- @ApplicationStop@, @BeforeBlockTraffic@, and @AfterBlockTraffic@
-- failures should be ignored.
deploymentInfo_ignoreApplicationStopFailures :: Lens.Lens' DeploymentInfo (Prelude.Maybe Prelude.Bool)
deploymentInfo_ignoreApplicationStopFailures :: Lens' DeploymentInfo (Maybe Bool)
deploymentInfo_ignoreApplicationStopFailures = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe Bool
ignoreApplicationStopFailures :: Maybe Bool
$sel:ignoreApplicationStopFailures:DeploymentInfo' :: DeploymentInfo -> Maybe Bool
ignoreApplicationStopFailures} -> Maybe Bool
ignoreApplicationStopFailures) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe Bool
a -> DeploymentInfo
s {$sel:ignoreApplicationStopFailures:DeploymentInfo' :: Maybe Bool
ignoreApplicationStopFailures = Maybe Bool
a} :: DeploymentInfo)

-- | Indicates whether the wait period set for the termination of instances
-- in the original environment has started. Status is \'false\' if the
-- KEEP_ALIVE option is specified. Otherwise, \'true\' as soon as the
-- termination wait period starts.
deploymentInfo_instanceTerminationWaitTimeStarted :: Lens.Lens' DeploymentInfo (Prelude.Maybe Prelude.Bool)
deploymentInfo_instanceTerminationWaitTimeStarted :: Lens' DeploymentInfo (Maybe Bool)
deploymentInfo_instanceTerminationWaitTimeStarted = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe Bool
instanceTerminationWaitTimeStarted :: Maybe Bool
$sel:instanceTerminationWaitTimeStarted:DeploymentInfo' :: DeploymentInfo -> Maybe Bool
instanceTerminationWaitTimeStarted} -> Maybe Bool
instanceTerminationWaitTimeStarted) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe Bool
a -> DeploymentInfo
s {$sel:instanceTerminationWaitTimeStarted:DeploymentInfo' :: Maybe Bool
instanceTerminationWaitTimeStarted = Maybe Bool
a} :: DeploymentInfo)

-- | Information about the load balancer used in the deployment.
deploymentInfo_loadBalancerInfo :: Lens.Lens' DeploymentInfo (Prelude.Maybe LoadBalancerInfo)
deploymentInfo_loadBalancerInfo :: Lens' DeploymentInfo (Maybe LoadBalancerInfo)
deploymentInfo_loadBalancerInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe LoadBalancerInfo
loadBalancerInfo :: Maybe LoadBalancerInfo
$sel:loadBalancerInfo:DeploymentInfo' :: DeploymentInfo -> Maybe LoadBalancerInfo
loadBalancerInfo} -> Maybe LoadBalancerInfo
loadBalancerInfo) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe LoadBalancerInfo
a -> DeploymentInfo
s {$sel:loadBalancerInfo:DeploymentInfo' :: Maybe LoadBalancerInfo
loadBalancerInfo = Maybe LoadBalancerInfo
a} :: DeploymentInfo)

-- | Undocumented member.
deploymentInfo_overrideAlarmConfiguration :: Lens.Lens' DeploymentInfo (Prelude.Maybe AlarmConfiguration)
deploymentInfo_overrideAlarmConfiguration :: Lens' DeploymentInfo (Maybe AlarmConfiguration)
deploymentInfo_overrideAlarmConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe AlarmConfiguration
overrideAlarmConfiguration :: Maybe AlarmConfiguration
$sel:overrideAlarmConfiguration:DeploymentInfo' :: DeploymentInfo -> Maybe AlarmConfiguration
overrideAlarmConfiguration} -> Maybe AlarmConfiguration
overrideAlarmConfiguration) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe AlarmConfiguration
a -> DeploymentInfo
s {$sel:overrideAlarmConfiguration:DeploymentInfo' :: Maybe AlarmConfiguration
overrideAlarmConfiguration = Maybe AlarmConfiguration
a} :: DeploymentInfo)

-- | Information about the application revision that was deployed to the
-- deployment group before the most recent successful deployment.
deploymentInfo_previousRevision :: Lens.Lens' DeploymentInfo (Prelude.Maybe RevisionLocation)
deploymentInfo_previousRevision :: Lens' DeploymentInfo (Maybe RevisionLocation)
deploymentInfo_previousRevision = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe RevisionLocation
previousRevision :: Maybe RevisionLocation
$sel:previousRevision:DeploymentInfo' :: DeploymentInfo -> Maybe RevisionLocation
previousRevision} -> Maybe RevisionLocation
previousRevision) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe RevisionLocation
a -> DeploymentInfo
s {$sel:previousRevision:DeploymentInfo' :: Maybe RevisionLocation
previousRevision = Maybe RevisionLocation
a} :: DeploymentInfo)

-- | Undocumented member.
deploymentInfo_relatedDeployments :: Lens.Lens' DeploymentInfo (Prelude.Maybe RelatedDeployments)
deploymentInfo_relatedDeployments :: Lens' DeploymentInfo (Maybe RelatedDeployments)
deploymentInfo_relatedDeployments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe RelatedDeployments
relatedDeployments :: Maybe RelatedDeployments
$sel:relatedDeployments:DeploymentInfo' :: DeploymentInfo -> Maybe RelatedDeployments
relatedDeployments} -> Maybe RelatedDeployments
relatedDeployments) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe RelatedDeployments
a -> DeploymentInfo
s {$sel:relatedDeployments:DeploymentInfo' :: Maybe RelatedDeployments
relatedDeployments = Maybe RelatedDeployments
a} :: DeploymentInfo)

-- | Information about the location of stored application artifacts and the
-- service from which to retrieve them.
deploymentInfo_revision :: Lens.Lens' DeploymentInfo (Prelude.Maybe RevisionLocation)
deploymentInfo_revision :: Lens' DeploymentInfo (Maybe RevisionLocation)
deploymentInfo_revision = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe RevisionLocation
revision :: Maybe RevisionLocation
$sel:revision:DeploymentInfo' :: DeploymentInfo -> Maybe RevisionLocation
revision} -> Maybe RevisionLocation
revision) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe RevisionLocation
a -> DeploymentInfo
s {$sel:revision:DeploymentInfo' :: Maybe RevisionLocation
revision = Maybe RevisionLocation
a} :: DeploymentInfo)

-- | Information about a deployment rollback.
deploymentInfo_rollbackInfo :: Lens.Lens' DeploymentInfo (Prelude.Maybe RollbackInfo)
deploymentInfo_rollbackInfo :: Lens' DeploymentInfo (Maybe RollbackInfo)
deploymentInfo_rollbackInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe RollbackInfo
rollbackInfo :: Maybe RollbackInfo
$sel:rollbackInfo:DeploymentInfo' :: DeploymentInfo -> Maybe RollbackInfo
rollbackInfo} -> Maybe RollbackInfo
rollbackInfo) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe RollbackInfo
a -> DeploymentInfo
s {$sel:rollbackInfo:DeploymentInfo' :: Maybe RollbackInfo
rollbackInfo = Maybe RollbackInfo
a} :: DeploymentInfo)

-- | A timestamp that indicates when the deployment was deployed to the
-- deployment group.
--
-- In some cases, the reported value of the start time might be later than
-- the complete time. This is due to differences in the clock settings of
-- backend servers that participate in the deployment process.
deploymentInfo_startTime :: Lens.Lens' DeploymentInfo (Prelude.Maybe Prelude.UTCTime)
deploymentInfo_startTime :: Lens' DeploymentInfo (Maybe UTCTime)
deploymentInfo_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe POSIX
startTime :: Maybe POSIX
$sel:startTime:DeploymentInfo' :: DeploymentInfo -> Maybe POSIX
startTime} -> Maybe POSIX
startTime) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe POSIX
a -> DeploymentInfo
s {$sel:startTime:DeploymentInfo' :: Maybe POSIX
startTime = Maybe POSIX
a} :: DeploymentInfo) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The current state of the deployment as a whole.
deploymentInfo_status :: Lens.Lens' DeploymentInfo (Prelude.Maybe DeploymentStatus)
deploymentInfo_status :: Lens' DeploymentInfo (Maybe DeploymentStatus)
deploymentInfo_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe DeploymentStatus
status :: Maybe DeploymentStatus
$sel:status:DeploymentInfo' :: DeploymentInfo -> Maybe DeploymentStatus
status} -> Maybe DeploymentStatus
status) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe DeploymentStatus
a -> DeploymentInfo
s {$sel:status:DeploymentInfo' :: Maybe DeploymentStatus
status = Maybe DeploymentStatus
a} :: DeploymentInfo)

-- | Information about the instances that belong to the replacement
-- environment in a blue\/green deployment.
deploymentInfo_targetInstances :: Lens.Lens' DeploymentInfo (Prelude.Maybe TargetInstances)
deploymentInfo_targetInstances :: Lens' DeploymentInfo (Maybe TargetInstances)
deploymentInfo_targetInstances = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe TargetInstances
targetInstances :: Maybe TargetInstances
$sel:targetInstances:DeploymentInfo' :: DeploymentInfo -> Maybe TargetInstances
targetInstances} -> Maybe TargetInstances
targetInstances) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe TargetInstances
a -> DeploymentInfo
s {$sel:targetInstances:DeploymentInfo' :: Maybe TargetInstances
targetInstances = Maybe TargetInstances
a} :: DeploymentInfo)

-- | Indicates whether only instances that are not running the latest
-- application revision are to be deployed to.
deploymentInfo_updateOutdatedInstancesOnly :: Lens.Lens' DeploymentInfo (Prelude.Maybe Prelude.Bool)
deploymentInfo_updateOutdatedInstancesOnly :: Lens' DeploymentInfo (Maybe Bool)
deploymentInfo_updateOutdatedInstancesOnly = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeploymentInfo' {Maybe Bool
updateOutdatedInstancesOnly :: Maybe Bool
$sel:updateOutdatedInstancesOnly:DeploymentInfo' :: DeploymentInfo -> Maybe Bool
updateOutdatedInstancesOnly} -> Maybe Bool
updateOutdatedInstancesOnly) (\s :: DeploymentInfo
s@DeploymentInfo' {} Maybe Bool
a -> DeploymentInfo
s {$sel:updateOutdatedInstancesOnly:DeploymentInfo' :: Maybe Bool
updateOutdatedInstancesOnly = Maybe Bool
a} :: DeploymentInfo)

instance Data.FromJSON DeploymentInfo where
  parseJSON :: Value -> Parser DeploymentInfo
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"DeploymentInfo"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe AutoRollbackConfiguration
-> Maybe BlueGreenDeploymentConfiguration
-> Maybe POSIX
-> Maybe ComputePlatform
-> Maybe POSIX
-> Maybe DeploymentCreator
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe DeploymentOverview
-> Maybe [Text]
-> Maybe DeploymentStyle
-> Maybe Text
-> Maybe ErrorInformation
-> Maybe Text
-> Maybe FileExistsBehavior
-> Maybe Bool
-> Maybe Bool
-> Maybe LoadBalancerInfo
-> Maybe AlarmConfiguration
-> Maybe RevisionLocation
-> Maybe RelatedDeployments
-> Maybe RevisionLocation
-> Maybe RollbackInfo
-> Maybe POSIX
-> Maybe DeploymentStatus
-> Maybe TargetInstances
-> Maybe Bool
-> DeploymentInfo
DeploymentInfo'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"additionalDeploymentStatusInfo")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"applicationName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"autoRollbackConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"blueGreenDeploymentConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"completeTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"computePlatform")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"createTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"creator")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"deploymentConfigName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"deploymentGroupName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"deploymentId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"deploymentOverview")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"deploymentStatusMessages"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"deploymentStyle")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"description")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"errorInformation")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"externalId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"fileExistsBehavior")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ignoreApplicationStopFailures")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"instanceTerminationWaitTimeStarted")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"loadBalancerInfo")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"overrideAlarmConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"previousRevision")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"relatedDeployments")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"revision")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"rollbackInfo")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"startTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"targetInstances")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"updateOutdatedInstancesOnly")
      )

instance Prelude.Hashable DeploymentInfo where
  hashWithSalt :: Int -> DeploymentInfo -> Int
hashWithSalt Int
_salt DeploymentInfo' {Maybe Bool
Maybe [Text]
Maybe Text
Maybe POSIX
Maybe AlarmConfiguration
Maybe AutoRollbackConfiguration
Maybe ComputePlatform
Maybe DeploymentCreator
Maybe DeploymentOverview
Maybe DeploymentStatus
Maybe DeploymentStyle
Maybe ErrorInformation
Maybe FileExistsBehavior
Maybe BlueGreenDeploymentConfiguration
Maybe RelatedDeployments
Maybe RollbackInfo
Maybe RevisionLocation
Maybe TargetInstances
Maybe LoadBalancerInfo
updateOutdatedInstancesOnly :: Maybe Bool
targetInstances :: Maybe TargetInstances
status :: Maybe DeploymentStatus
startTime :: Maybe POSIX
rollbackInfo :: Maybe RollbackInfo
revision :: Maybe RevisionLocation
relatedDeployments :: Maybe RelatedDeployments
previousRevision :: Maybe RevisionLocation
overrideAlarmConfiguration :: Maybe AlarmConfiguration
loadBalancerInfo :: Maybe LoadBalancerInfo
instanceTerminationWaitTimeStarted :: Maybe Bool
ignoreApplicationStopFailures :: Maybe Bool
fileExistsBehavior :: Maybe FileExistsBehavior
externalId :: Maybe Text
errorInformation :: Maybe ErrorInformation
description :: Maybe Text
deploymentStyle :: Maybe DeploymentStyle
deploymentStatusMessages :: Maybe [Text]
deploymentOverview :: Maybe DeploymentOverview
deploymentId :: Maybe Text
deploymentGroupName :: Maybe Text
deploymentConfigName :: Maybe Text
creator :: Maybe DeploymentCreator
createTime :: Maybe POSIX
computePlatform :: Maybe ComputePlatform
completeTime :: Maybe POSIX
blueGreenDeploymentConfiguration :: Maybe BlueGreenDeploymentConfiguration
autoRollbackConfiguration :: Maybe AutoRollbackConfiguration
applicationName :: Maybe Text
additionalDeploymentStatusInfo :: Maybe Text
$sel:updateOutdatedInstancesOnly:DeploymentInfo' :: DeploymentInfo -> Maybe Bool
$sel:targetInstances:DeploymentInfo' :: DeploymentInfo -> Maybe TargetInstances
$sel:status:DeploymentInfo' :: DeploymentInfo -> Maybe DeploymentStatus
$sel:startTime:DeploymentInfo' :: DeploymentInfo -> Maybe POSIX
$sel:rollbackInfo:DeploymentInfo' :: DeploymentInfo -> Maybe RollbackInfo
$sel:revision:DeploymentInfo' :: DeploymentInfo -> Maybe RevisionLocation
$sel:relatedDeployments:DeploymentInfo' :: DeploymentInfo -> Maybe RelatedDeployments
$sel:previousRevision:DeploymentInfo' :: DeploymentInfo -> Maybe RevisionLocation
$sel:overrideAlarmConfiguration:DeploymentInfo' :: DeploymentInfo -> Maybe AlarmConfiguration
$sel:loadBalancerInfo:DeploymentInfo' :: DeploymentInfo -> Maybe LoadBalancerInfo
$sel:instanceTerminationWaitTimeStarted:DeploymentInfo' :: DeploymentInfo -> Maybe Bool
$sel:ignoreApplicationStopFailures:DeploymentInfo' :: DeploymentInfo -> Maybe Bool
$sel:fileExistsBehavior:DeploymentInfo' :: DeploymentInfo -> Maybe FileExistsBehavior
$sel:externalId:DeploymentInfo' :: DeploymentInfo -> Maybe Text
$sel:errorInformation:DeploymentInfo' :: DeploymentInfo -> Maybe ErrorInformation
$sel:description:DeploymentInfo' :: DeploymentInfo -> Maybe Text
$sel:deploymentStyle:DeploymentInfo' :: DeploymentInfo -> Maybe DeploymentStyle
$sel:deploymentStatusMessages:DeploymentInfo' :: DeploymentInfo -> Maybe [Text]
$sel:deploymentOverview:DeploymentInfo' :: DeploymentInfo -> Maybe DeploymentOverview
$sel:deploymentId:DeploymentInfo' :: DeploymentInfo -> Maybe Text
$sel:deploymentGroupName:DeploymentInfo' :: DeploymentInfo -> Maybe Text
$sel:deploymentConfigName:DeploymentInfo' :: DeploymentInfo -> Maybe Text
$sel:creator:DeploymentInfo' :: DeploymentInfo -> Maybe DeploymentCreator
$sel:createTime:DeploymentInfo' :: DeploymentInfo -> Maybe POSIX
$sel:computePlatform:DeploymentInfo' :: DeploymentInfo -> Maybe ComputePlatform
$sel:completeTime:DeploymentInfo' :: DeploymentInfo -> Maybe POSIX
$sel:blueGreenDeploymentConfiguration:DeploymentInfo' :: DeploymentInfo -> Maybe BlueGreenDeploymentConfiguration
$sel:autoRollbackConfiguration:DeploymentInfo' :: DeploymentInfo -> Maybe AutoRollbackConfiguration
$sel:applicationName:DeploymentInfo' :: DeploymentInfo -> Maybe Text
$sel:additionalDeploymentStatusInfo:DeploymentInfo' :: DeploymentInfo -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
additionalDeploymentStatusInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
applicationName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AutoRollbackConfiguration
autoRollbackConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BlueGreenDeploymentConfiguration
blueGreenDeploymentConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
completeTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ComputePlatform
computePlatform
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeploymentCreator
creator
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
deploymentConfigName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
deploymentGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
deploymentId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeploymentOverview
deploymentOverview
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
deploymentStatusMessages
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeploymentStyle
deploymentStyle
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ErrorInformation
errorInformation
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
externalId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FileExistsBehavior
fileExistsBehavior
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
ignoreApplicationStopFailures
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
instanceTerminationWaitTimeStarted
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LoadBalancerInfo
loadBalancerInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AlarmConfiguration
overrideAlarmConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RevisionLocation
previousRevision
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RelatedDeployments
relatedDeployments
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RevisionLocation
revision
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RollbackInfo
rollbackInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeploymentStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TargetInstances
targetInstances
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
updateOutdatedInstancesOnly

instance Prelude.NFData DeploymentInfo where
  rnf :: DeploymentInfo -> ()
rnf DeploymentInfo' {Maybe Bool
Maybe [Text]
Maybe Text
Maybe POSIX
Maybe AlarmConfiguration
Maybe AutoRollbackConfiguration
Maybe ComputePlatform
Maybe DeploymentCreator
Maybe DeploymentOverview
Maybe DeploymentStatus
Maybe DeploymentStyle
Maybe ErrorInformation
Maybe FileExistsBehavior
Maybe BlueGreenDeploymentConfiguration
Maybe RelatedDeployments
Maybe RollbackInfo
Maybe RevisionLocation
Maybe TargetInstances
Maybe LoadBalancerInfo
updateOutdatedInstancesOnly :: Maybe Bool
targetInstances :: Maybe TargetInstances
status :: Maybe DeploymentStatus
startTime :: Maybe POSIX
rollbackInfo :: Maybe RollbackInfo
revision :: Maybe RevisionLocation
relatedDeployments :: Maybe RelatedDeployments
previousRevision :: Maybe RevisionLocation
overrideAlarmConfiguration :: Maybe AlarmConfiguration
loadBalancerInfo :: Maybe LoadBalancerInfo
instanceTerminationWaitTimeStarted :: Maybe Bool
ignoreApplicationStopFailures :: Maybe Bool
fileExistsBehavior :: Maybe FileExistsBehavior
externalId :: Maybe Text
errorInformation :: Maybe ErrorInformation
description :: Maybe Text
deploymentStyle :: Maybe DeploymentStyle
deploymentStatusMessages :: Maybe [Text]
deploymentOverview :: Maybe DeploymentOverview
deploymentId :: Maybe Text
deploymentGroupName :: Maybe Text
deploymentConfigName :: Maybe Text
creator :: Maybe DeploymentCreator
createTime :: Maybe POSIX
computePlatform :: Maybe ComputePlatform
completeTime :: Maybe POSIX
blueGreenDeploymentConfiguration :: Maybe BlueGreenDeploymentConfiguration
autoRollbackConfiguration :: Maybe AutoRollbackConfiguration
applicationName :: Maybe Text
additionalDeploymentStatusInfo :: Maybe Text
$sel:updateOutdatedInstancesOnly:DeploymentInfo' :: DeploymentInfo -> Maybe Bool
$sel:targetInstances:DeploymentInfo' :: DeploymentInfo -> Maybe TargetInstances
$sel:status:DeploymentInfo' :: DeploymentInfo -> Maybe DeploymentStatus
$sel:startTime:DeploymentInfo' :: DeploymentInfo -> Maybe POSIX
$sel:rollbackInfo:DeploymentInfo' :: DeploymentInfo -> Maybe RollbackInfo
$sel:revision:DeploymentInfo' :: DeploymentInfo -> Maybe RevisionLocation
$sel:relatedDeployments:DeploymentInfo' :: DeploymentInfo -> Maybe RelatedDeployments
$sel:previousRevision:DeploymentInfo' :: DeploymentInfo -> Maybe RevisionLocation
$sel:overrideAlarmConfiguration:DeploymentInfo' :: DeploymentInfo -> Maybe AlarmConfiguration
$sel:loadBalancerInfo:DeploymentInfo' :: DeploymentInfo -> Maybe LoadBalancerInfo
$sel:instanceTerminationWaitTimeStarted:DeploymentInfo' :: DeploymentInfo -> Maybe Bool
$sel:ignoreApplicationStopFailures:DeploymentInfo' :: DeploymentInfo -> Maybe Bool
$sel:fileExistsBehavior:DeploymentInfo' :: DeploymentInfo -> Maybe FileExistsBehavior
$sel:externalId:DeploymentInfo' :: DeploymentInfo -> Maybe Text
$sel:errorInformation:DeploymentInfo' :: DeploymentInfo -> Maybe ErrorInformation
$sel:description:DeploymentInfo' :: DeploymentInfo -> Maybe Text
$sel:deploymentStyle:DeploymentInfo' :: DeploymentInfo -> Maybe DeploymentStyle
$sel:deploymentStatusMessages:DeploymentInfo' :: DeploymentInfo -> Maybe [Text]
$sel:deploymentOverview:DeploymentInfo' :: DeploymentInfo -> Maybe DeploymentOverview
$sel:deploymentId:DeploymentInfo' :: DeploymentInfo -> Maybe Text
$sel:deploymentGroupName:DeploymentInfo' :: DeploymentInfo -> Maybe Text
$sel:deploymentConfigName:DeploymentInfo' :: DeploymentInfo -> Maybe Text
$sel:creator:DeploymentInfo' :: DeploymentInfo -> Maybe DeploymentCreator
$sel:createTime:DeploymentInfo' :: DeploymentInfo -> Maybe POSIX
$sel:computePlatform:DeploymentInfo' :: DeploymentInfo -> Maybe ComputePlatform
$sel:completeTime:DeploymentInfo' :: DeploymentInfo -> Maybe POSIX
$sel:blueGreenDeploymentConfiguration:DeploymentInfo' :: DeploymentInfo -> Maybe BlueGreenDeploymentConfiguration
$sel:autoRollbackConfiguration:DeploymentInfo' :: DeploymentInfo -> Maybe AutoRollbackConfiguration
$sel:applicationName:DeploymentInfo' :: DeploymentInfo -> Maybe Text
$sel:additionalDeploymentStatusInfo:DeploymentInfo' :: DeploymentInfo -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
additionalDeploymentStatusInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
applicationName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AutoRollbackConfiguration
autoRollbackConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BlueGreenDeploymentConfiguration
blueGreenDeploymentConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
completeTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ComputePlatform
computePlatform
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeploymentCreator
creator
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
deploymentConfigName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
deploymentGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
deploymentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeploymentOverview
deploymentOverview
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
deploymentStatusMessages
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeploymentStyle
deploymentStyle
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ErrorInformation
errorInformation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
externalId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FileExistsBehavior
fileExistsBehavior
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Bool
ignoreApplicationStopFailures
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Bool
instanceTerminationWaitTimeStarted
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LoadBalancerInfo
loadBalancerInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe AlarmConfiguration
overrideAlarmConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe RevisionLocation
previousRevision
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe RelatedDeployments
relatedDeployments
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RevisionLocation
revision
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe RollbackInfo
rollbackInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe POSIX
startTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe DeploymentStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TargetInstances
targetInstances
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Bool
updateOutdatedInstancesOnly