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

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

-- |
-- Module      : Amazonka.ElasticBeanstalk.UpdateEnvironment
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the environment description, deploys a new application version,
-- updates the configuration settings to an entirely new configuration
-- template, or updates select configuration option values in the running
-- environment.
--
-- Attempting to update both the release and configuration is not allowed
-- and AWS Elastic Beanstalk returns an @InvalidParameterCombination@
-- error.
--
-- When updating the configuration settings to a new template or individual
-- settings, a draft configuration is created and
-- DescribeConfigurationSettings for this environment returns two setting
-- descriptions with different @DeploymentStatus@ values.
module Amazonka.ElasticBeanstalk.UpdateEnvironment
  ( -- * Creating a Request
    UpdateEnvironment (..),
    newUpdateEnvironment,

    -- * Request Lenses
    updateEnvironment_applicationName,
    updateEnvironment_description,
    updateEnvironment_environmentId,
    updateEnvironment_environmentName,
    updateEnvironment_groupName,
    updateEnvironment_optionSettings,
    updateEnvironment_optionsToRemove,
    updateEnvironment_platformArn,
    updateEnvironment_solutionStackName,
    updateEnvironment_templateName,
    updateEnvironment_tier,
    updateEnvironment_versionLabel,

    -- * Destructuring the Response
    EnvironmentDescription (..),
    newEnvironmentDescription,

    -- * Response Lenses
    environmentDescription_abortableOperationInProgress,
    environmentDescription_applicationName,
    environmentDescription_cname,
    environmentDescription_dateCreated,
    environmentDescription_dateUpdated,
    environmentDescription_description,
    environmentDescription_endpointURL,
    environmentDescription_environmentArn,
    environmentDescription_environmentId,
    environmentDescription_environmentLinks,
    environmentDescription_environmentName,
    environmentDescription_health,
    environmentDescription_healthStatus,
    environmentDescription_operationsRole,
    environmentDescription_platformArn,
    environmentDescription_resources,
    environmentDescription_solutionStackName,
    environmentDescription_status,
    environmentDescription_templateName,
    environmentDescription_tier,
    environmentDescription_versionLabel,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.ElasticBeanstalk.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Request to update an environment.
--
-- /See:/ 'newUpdateEnvironment' smart constructor.
data UpdateEnvironment = UpdateEnvironment'
  { -- | The name of the application with which the environment is associated.
    UpdateEnvironment -> Maybe Text
applicationName :: Prelude.Maybe Prelude.Text,
    -- | If this parameter is specified, AWS Elastic Beanstalk updates the
    -- description of this environment.
    UpdateEnvironment -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The ID of the environment to update.
    --
    -- If no environment with this ID exists, AWS Elastic Beanstalk returns an
    -- @InvalidParameterValue@ error.
    --
    -- Condition: You must specify either this or an EnvironmentName, or both.
    -- If you do not specify either, AWS Elastic Beanstalk returns
    -- @MissingRequiredParameter@ error.
    UpdateEnvironment -> Maybe Text
environmentId :: Prelude.Maybe Prelude.Text,
    -- | The name of the environment to update. If no environment with this name
    -- exists, AWS Elastic Beanstalk returns an @InvalidParameterValue@ error.
    --
    -- Condition: You must specify either this or an EnvironmentId, or both. If
    -- you do not specify either, AWS Elastic Beanstalk returns
    -- @MissingRequiredParameter@ error.
    UpdateEnvironment -> Maybe Text
environmentName :: Prelude.Maybe Prelude.Text,
    -- | The name of the group to which the target environment belongs. Specify a
    -- group name only if the environment\'s name is specified in an
    -- environment manifest and not with the environment name or environment ID
    -- parameters. See
    -- <https://docs.aws.amazon.com/elasticbeanstalk/latest/dg/environment-cfg-manifest.html Environment Manifest (env.yaml)>
    -- for details.
    UpdateEnvironment -> Maybe Text
groupName :: Prelude.Maybe Prelude.Text,
    -- | If specified, AWS Elastic Beanstalk updates the configuration set
    -- associated with the running environment and sets the specified
    -- configuration options to the requested value.
    UpdateEnvironment -> Maybe [ConfigurationOptionSetting]
optionSettings :: Prelude.Maybe [ConfigurationOptionSetting],
    -- | A list of custom user-defined configuration options to remove from the
    -- configuration set for this environment.
    UpdateEnvironment -> Maybe [OptionSpecification]
optionsToRemove :: Prelude.Maybe [OptionSpecification],
    -- | The ARN of the platform, if used.
    UpdateEnvironment -> Maybe Text
platformArn :: Prelude.Maybe Prelude.Text,
    -- | This specifies the platform version that the environment will run after
    -- the environment is updated.
    UpdateEnvironment -> Maybe Text
solutionStackName :: Prelude.Maybe Prelude.Text,
    -- | If this parameter is specified, AWS Elastic Beanstalk deploys this
    -- configuration template to the environment. If no such configuration
    -- template is found, AWS Elastic Beanstalk returns an
    -- @InvalidParameterValue@ error.
    UpdateEnvironment -> Maybe Text
templateName :: Prelude.Maybe Prelude.Text,
    -- | This specifies the tier to use to update the environment.
    --
    -- Condition: At this time, if you change the tier version, name, or type,
    -- AWS Elastic Beanstalk returns @InvalidParameterValue@ error.
    UpdateEnvironment -> Maybe EnvironmentTier
tier :: Prelude.Maybe EnvironmentTier,
    -- | If this parameter is specified, AWS Elastic Beanstalk deploys the named
    -- application version to the environment. If no such application version
    -- is found, returns an @InvalidParameterValue@ error.
    UpdateEnvironment -> Maybe Text
versionLabel :: Prelude.Maybe Prelude.Text
  }
  deriving (UpdateEnvironment -> UpdateEnvironment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateEnvironment -> UpdateEnvironment -> Bool
$c/= :: UpdateEnvironment -> UpdateEnvironment -> Bool
== :: UpdateEnvironment -> UpdateEnvironment -> Bool
$c== :: UpdateEnvironment -> UpdateEnvironment -> Bool
Prelude.Eq, ReadPrec [UpdateEnvironment]
ReadPrec UpdateEnvironment
Int -> ReadS UpdateEnvironment
ReadS [UpdateEnvironment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateEnvironment]
$creadListPrec :: ReadPrec [UpdateEnvironment]
readPrec :: ReadPrec UpdateEnvironment
$creadPrec :: ReadPrec UpdateEnvironment
readList :: ReadS [UpdateEnvironment]
$creadList :: ReadS [UpdateEnvironment]
readsPrec :: Int -> ReadS UpdateEnvironment
$creadsPrec :: Int -> ReadS UpdateEnvironment
Prelude.Read, Int -> UpdateEnvironment -> ShowS
[UpdateEnvironment] -> ShowS
UpdateEnvironment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateEnvironment] -> ShowS
$cshowList :: [UpdateEnvironment] -> ShowS
show :: UpdateEnvironment -> String
$cshow :: UpdateEnvironment -> String
showsPrec :: Int -> UpdateEnvironment -> ShowS
$cshowsPrec :: Int -> UpdateEnvironment -> ShowS
Prelude.Show, forall x. Rep UpdateEnvironment x -> UpdateEnvironment
forall x. UpdateEnvironment -> Rep UpdateEnvironment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateEnvironment x -> UpdateEnvironment
$cfrom :: forall x. UpdateEnvironment -> Rep UpdateEnvironment x
Prelude.Generic)

-- |
-- Create a value of 'UpdateEnvironment' 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:
--
-- 'applicationName', 'updateEnvironment_applicationName' - The name of the application with which the environment is associated.
--
-- 'description', 'updateEnvironment_description' - If this parameter is specified, AWS Elastic Beanstalk updates the
-- description of this environment.
--
-- 'environmentId', 'updateEnvironment_environmentId' - The ID of the environment to update.
--
-- If no environment with this ID exists, AWS Elastic Beanstalk returns an
-- @InvalidParameterValue@ error.
--
-- Condition: You must specify either this or an EnvironmentName, or both.
-- If you do not specify either, AWS Elastic Beanstalk returns
-- @MissingRequiredParameter@ error.
--
-- 'environmentName', 'updateEnvironment_environmentName' - The name of the environment to update. If no environment with this name
-- exists, AWS Elastic Beanstalk returns an @InvalidParameterValue@ error.
--
-- Condition: You must specify either this or an EnvironmentId, or both. If
-- you do not specify either, AWS Elastic Beanstalk returns
-- @MissingRequiredParameter@ error.
--
-- 'groupName', 'updateEnvironment_groupName' - The name of the group to which the target environment belongs. Specify a
-- group name only if the environment\'s name is specified in an
-- environment manifest and not with the environment name or environment ID
-- parameters. See
-- <https://docs.aws.amazon.com/elasticbeanstalk/latest/dg/environment-cfg-manifest.html Environment Manifest (env.yaml)>
-- for details.
--
-- 'optionSettings', 'updateEnvironment_optionSettings' - If specified, AWS Elastic Beanstalk updates the configuration set
-- associated with the running environment and sets the specified
-- configuration options to the requested value.
--
-- 'optionsToRemove', 'updateEnvironment_optionsToRemove' - A list of custom user-defined configuration options to remove from the
-- configuration set for this environment.
--
-- 'platformArn', 'updateEnvironment_platformArn' - The ARN of the platform, if used.
--
-- 'solutionStackName', 'updateEnvironment_solutionStackName' - This specifies the platform version that the environment will run after
-- the environment is updated.
--
-- 'templateName', 'updateEnvironment_templateName' - If this parameter is specified, AWS Elastic Beanstalk deploys this
-- configuration template to the environment. If no such configuration
-- template is found, AWS Elastic Beanstalk returns an
-- @InvalidParameterValue@ error.
--
-- 'tier', 'updateEnvironment_tier' - This specifies the tier to use to update the environment.
--
-- Condition: At this time, if you change the tier version, name, or type,
-- AWS Elastic Beanstalk returns @InvalidParameterValue@ error.
--
-- 'versionLabel', 'updateEnvironment_versionLabel' - If this parameter is specified, AWS Elastic Beanstalk deploys the named
-- application version to the environment. If no such application version
-- is found, returns an @InvalidParameterValue@ error.
newUpdateEnvironment ::
  UpdateEnvironment
newUpdateEnvironment :: UpdateEnvironment
newUpdateEnvironment =
  UpdateEnvironment'
    { $sel:applicationName:UpdateEnvironment' :: Maybe Text
applicationName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:description:UpdateEnvironment' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:environmentId:UpdateEnvironment' :: Maybe Text
environmentId = forall a. Maybe a
Prelude.Nothing,
      $sel:environmentName:UpdateEnvironment' :: Maybe Text
environmentName = forall a. Maybe a
Prelude.Nothing,
      $sel:groupName:UpdateEnvironment' :: Maybe Text
groupName = forall a. Maybe a
Prelude.Nothing,
      $sel:optionSettings:UpdateEnvironment' :: Maybe [ConfigurationOptionSetting]
optionSettings = forall a. Maybe a
Prelude.Nothing,
      $sel:optionsToRemove:UpdateEnvironment' :: Maybe [OptionSpecification]
optionsToRemove = forall a. Maybe a
Prelude.Nothing,
      $sel:platformArn:UpdateEnvironment' :: Maybe Text
platformArn = forall a. Maybe a
Prelude.Nothing,
      $sel:solutionStackName:UpdateEnvironment' :: Maybe Text
solutionStackName = forall a. Maybe a
Prelude.Nothing,
      $sel:templateName:UpdateEnvironment' :: Maybe Text
templateName = forall a. Maybe a
Prelude.Nothing,
      $sel:tier:UpdateEnvironment' :: Maybe EnvironmentTier
tier = forall a. Maybe a
Prelude.Nothing,
      $sel:versionLabel:UpdateEnvironment' :: Maybe Text
versionLabel = forall a. Maybe a
Prelude.Nothing
    }

-- | The name of the application with which the environment is associated.
updateEnvironment_applicationName :: Lens.Lens' UpdateEnvironment (Prelude.Maybe Prelude.Text)
updateEnvironment_applicationName :: Lens' UpdateEnvironment (Maybe Text)
updateEnvironment_applicationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe Text
applicationName :: Maybe Text
$sel:applicationName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
applicationName} -> Maybe Text
applicationName) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe Text
a -> UpdateEnvironment
s {$sel:applicationName:UpdateEnvironment' :: Maybe Text
applicationName = Maybe Text
a} :: UpdateEnvironment)

-- | If this parameter is specified, AWS Elastic Beanstalk updates the
-- description of this environment.
updateEnvironment_description :: Lens.Lens' UpdateEnvironment (Prelude.Maybe Prelude.Text)
updateEnvironment_description :: Lens' UpdateEnvironment (Maybe Text)
updateEnvironment_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe Text
description :: Maybe Text
$sel:description:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe Text
a -> UpdateEnvironment
s {$sel:description:UpdateEnvironment' :: Maybe Text
description = Maybe Text
a} :: UpdateEnvironment)

-- | The ID of the environment to update.
--
-- If no environment with this ID exists, AWS Elastic Beanstalk returns an
-- @InvalidParameterValue@ error.
--
-- Condition: You must specify either this or an EnvironmentName, or both.
-- If you do not specify either, AWS Elastic Beanstalk returns
-- @MissingRequiredParameter@ error.
updateEnvironment_environmentId :: Lens.Lens' UpdateEnvironment (Prelude.Maybe Prelude.Text)
updateEnvironment_environmentId :: Lens' UpdateEnvironment (Maybe Text)
updateEnvironment_environmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe Text
environmentId :: Maybe Text
$sel:environmentId:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
environmentId} -> Maybe Text
environmentId) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe Text
a -> UpdateEnvironment
s {$sel:environmentId:UpdateEnvironment' :: Maybe Text
environmentId = Maybe Text
a} :: UpdateEnvironment)

-- | The name of the environment to update. If no environment with this name
-- exists, AWS Elastic Beanstalk returns an @InvalidParameterValue@ error.
--
-- Condition: You must specify either this or an EnvironmentId, or both. If
-- you do not specify either, AWS Elastic Beanstalk returns
-- @MissingRequiredParameter@ error.
updateEnvironment_environmentName :: Lens.Lens' UpdateEnvironment (Prelude.Maybe Prelude.Text)
updateEnvironment_environmentName :: Lens' UpdateEnvironment (Maybe Text)
updateEnvironment_environmentName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe Text
environmentName :: Maybe Text
$sel:environmentName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
environmentName} -> Maybe Text
environmentName) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe Text
a -> UpdateEnvironment
s {$sel:environmentName:UpdateEnvironment' :: Maybe Text
environmentName = Maybe Text
a} :: UpdateEnvironment)

-- | The name of the group to which the target environment belongs. Specify a
-- group name only if the environment\'s name is specified in an
-- environment manifest and not with the environment name or environment ID
-- parameters. See
-- <https://docs.aws.amazon.com/elasticbeanstalk/latest/dg/environment-cfg-manifest.html Environment Manifest (env.yaml)>
-- for details.
updateEnvironment_groupName :: Lens.Lens' UpdateEnvironment (Prelude.Maybe Prelude.Text)
updateEnvironment_groupName :: Lens' UpdateEnvironment (Maybe Text)
updateEnvironment_groupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe Text
groupName :: Maybe Text
$sel:groupName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
groupName} -> Maybe Text
groupName) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe Text
a -> UpdateEnvironment
s {$sel:groupName:UpdateEnvironment' :: Maybe Text
groupName = Maybe Text
a} :: UpdateEnvironment)

-- | If specified, AWS Elastic Beanstalk updates the configuration set
-- associated with the running environment and sets the specified
-- configuration options to the requested value.
updateEnvironment_optionSettings :: Lens.Lens' UpdateEnvironment (Prelude.Maybe [ConfigurationOptionSetting])
updateEnvironment_optionSettings :: Lens' UpdateEnvironment (Maybe [ConfigurationOptionSetting])
updateEnvironment_optionSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe [ConfigurationOptionSetting]
optionSettings :: Maybe [ConfigurationOptionSetting]
$sel:optionSettings:UpdateEnvironment' :: UpdateEnvironment -> Maybe [ConfigurationOptionSetting]
optionSettings} -> Maybe [ConfigurationOptionSetting]
optionSettings) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe [ConfigurationOptionSetting]
a -> UpdateEnvironment
s {$sel:optionSettings:UpdateEnvironment' :: Maybe [ConfigurationOptionSetting]
optionSettings = Maybe [ConfigurationOptionSetting]
a} :: UpdateEnvironment) 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

-- | A list of custom user-defined configuration options to remove from the
-- configuration set for this environment.
updateEnvironment_optionsToRemove :: Lens.Lens' UpdateEnvironment (Prelude.Maybe [OptionSpecification])
updateEnvironment_optionsToRemove :: Lens' UpdateEnvironment (Maybe [OptionSpecification])
updateEnvironment_optionsToRemove = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe [OptionSpecification]
optionsToRemove :: Maybe [OptionSpecification]
$sel:optionsToRemove:UpdateEnvironment' :: UpdateEnvironment -> Maybe [OptionSpecification]
optionsToRemove} -> Maybe [OptionSpecification]
optionsToRemove) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe [OptionSpecification]
a -> UpdateEnvironment
s {$sel:optionsToRemove:UpdateEnvironment' :: Maybe [OptionSpecification]
optionsToRemove = Maybe [OptionSpecification]
a} :: UpdateEnvironment) 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

-- | The ARN of the platform, if used.
updateEnvironment_platformArn :: Lens.Lens' UpdateEnvironment (Prelude.Maybe Prelude.Text)
updateEnvironment_platformArn :: Lens' UpdateEnvironment (Maybe Text)
updateEnvironment_platformArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe Text
platformArn :: Maybe Text
$sel:platformArn:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
platformArn} -> Maybe Text
platformArn) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe Text
a -> UpdateEnvironment
s {$sel:platformArn:UpdateEnvironment' :: Maybe Text
platformArn = Maybe Text
a} :: UpdateEnvironment)

-- | This specifies the platform version that the environment will run after
-- the environment is updated.
updateEnvironment_solutionStackName :: Lens.Lens' UpdateEnvironment (Prelude.Maybe Prelude.Text)
updateEnvironment_solutionStackName :: Lens' UpdateEnvironment (Maybe Text)
updateEnvironment_solutionStackName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe Text
solutionStackName :: Maybe Text
$sel:solutionStackName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
solutionStackName} -> Maybe Text
solutionStackName) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe Text
a -> UpdateEnvironment
s {$sel:solutionStackName:UpdateEnvironment' :: Maybe Text
solutionStackName = Maybe Text
a} :: UpdateEnvironment)

-- | If this parameter is specified, AWS Elastic Beanstalk deploys this
-- configuration template to the environment. If no such configuration
-- template is found, AWS Elastic Beanstalk returns an
-- @InvalidParameterValue@ error.
updateEnvironment_templateName :: Lens.Lens' UpdateEnvironment (Prelude.Maybe Prelude.Text)
updateEnvironment_templateName :: Lens' UpdateEnvironment (Maybe Text)
updateEnvironment_templateName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe Text
templateName :: Maybe Text
$sel:templateName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
templateName} -> Maybe Text
templateName) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe Text
a -> UpdateEnvironment
s {$sel:templateName:UpdateEnvironment' :: Maybe Text
templateName = Maybe Text
a} :: UpdateEnvironment)

-- | This specifies the tier to use to update the environment.
--
-- Condition: At this time, if you change the tier version, name, or type,
-- AWS Elastic Beanstalk returns @InvalidParameterValue@ error.
updateEnvironment_tier :: Lens.Lens' UpdateEnvironment (Prelude.Maybe EnvironmentTier)
updateEnvironment_tier :: Lens' UpdateEnvironment (Maybe EnvironmentTier)
updateEnvironment_tier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe EnvironmentTier
tier :: Maybe EnvironmentTier
$sel:tier:UpdateEnvironment' :: UpdateEnvironment -> Maybe EnvironmentTier
tier} -> Maybe EnvironmentTier
tier) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe EnvironmentTier
a -> UpdateEnvironment
s {$sel:tier:UpdateEnvironment' :: Maybe EnvironmentTier
tier = Maybe EnvironmentTier
a} :: UpdateEnvironment)

-- | If this parameter is specified, AWS Elastic Beanstalk deploys the named
-- application version to the environment. If no such application version
-- is found, returns an @InvalidParameterValue@ error.
updateEnvironment_versionLabel :: Lens.Lens' UpdateEnvironment (Prelude.Maybe Prelude.Text)
updateEnvironment_versionLabel :: Lens' UpdateEnvironment (Maybe Text)
updateEnvironment_versionLabel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateEnvironment' {Maybe Text
versionLabel :: Maybe Text
$sel:versionLabel:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
versionLabel} -> Maybe Text
versionLabel) (\s :: UpdateEnvironment
s@UpdateEnvironment' {} Maybe Text
a -> UpdateEnvironment
s {$sel:versionLabel:UpdateEnvironment' :: Maybe Text
versionLabel = Maybe Text
a} :: UpdateEnvironment)

instance Core.AWSRequest UpdateEnvironment where
  type
    AWSResponse UpdateEnvironment =
      EnvironmentDescription
  request :: (Service -> Service)
-> UpdateEnvironment -> Request UpdateEnvironment
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateEnvironment
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateEnvironment)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"UpdateEnvironmentResult"
      (\Int
s ResponseHeaders
h [Node]
x -> forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)

instance Prelude.Hashable UpdateEnvironment where
  hashWithSalt :: Int -> UpdateEnvironment -> Int
hashWithSalt Int
_salt UpdateEnvironment' {Maybe [ConfigurationOptionSetting]
Maybe [OptionSpecification]
Maybe Text
Maybe EnvironmentTier
versionLabel :: Maybe Text
tier :: Maybe EnvironmentTier
templateName :: Maybe Text
solutionStackName :: Maybe Text
platformArn :: Maybe Text
optionsToRemove :: Maybe [OptionSpecification]
optionSettings :: Maybe [ConfigurationOptionSetting]
groupName :: Maybe Text
environmentName :: Maybe Text
environmentId :: Maybe Text
description :: Maybe Text
applicationName :: Maybe Text
$sel:versionLabel:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:tier:UpdateEnvironment' :: UpdateEnvironment -> Maybe EnvironmentTier
$sel:templateName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:solutionStackName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:platformArn:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:optionsToRemove:UpdateEnvironment' :: UpdateEnvironment -> Maybe [OptionSpecification]
$sel:optionSettings:UpdateEnvironment' :: UpdateEnvironment -> Maybe [ConfigurationOptionSetting]
$sel:groupName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:environmentName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:environmentId:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:description:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:applicationName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
applicationName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
environmentId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
environmentName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
groupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ConfigurationOptionSetting]
optionSettings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [OptionSpecification]
optionsToRemove
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
platformArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
solutionStackName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
templateName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EnvironmentTier
tier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
versionLabel

instance Prelude.NFData UpdateEnvironment where
  rnf :: UpdateEnvironment -> ()
rnf UpdateEnvironment' {Maybe [ConfigurationOptionSetting]
Maybe [OptionSpecification]
Maybe Text
Maybe EnvironmentTier
versionLabel :: Maybe Text
tier :: Maybe EnvironmentTier
templateName :: Maybe Text
solutionStackName :: Maybe Text
platformArn :: Maybe Text
optionsToRemove :: Maybe [OptionSpecification]
optionSettings :: Maybe [ConfigurationOptionSetting]
groupName :: Maybe Text
environmentName :: Maybe Text
environmentId :: Maybe Text
description :: Maybe Text
applicationName :: Maybe Text
$sel:versionLabel:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:tier:UpdateEnvironment' :: UpdateEnvironment -> Maybe EnvironmentTier
$sel:templateName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:solutionStackName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:platformArn:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:optionsToRemove:UpdateEnvironment' :: UpdateEnvironment -> Maybe [OptionSpecification]
$sel:optionSettings:UpdateEnvironment' :: UpdateEnvironment -> Maybe [ConfigurationOptionSetting]
$sel:groupName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:environmentName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:environmentId:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:description:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:applicationName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
..} =
    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 Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
environmentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
environmentName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
groupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ConfigurationOptionSetting]
optionSettings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [OptionSpecification]
optionsToRemove
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
platformArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
solutionStackName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
templateName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EnvironmentTier
tier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
versionLabel

instance Data.ToHeaders UpdateEnvironment where
  toHeaders :: UpdateEnvironment -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath UpdateEnvironment where
  toPath :: UpdateEnvironment -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery UpdateEnvironment where
  toQuery :: UpdateEnvironment -> QueryString
toQuery UpdateEnvironment' {Maybe [ConfigurationOptionSetting]
Maybe [OptionSpecification]
Maybe Text
Maybe EnvironmentTier
versionLabel :: Maybe Text
tier :: Maybe EnvironmentTier
templateName :: Maybe Text
solutionStackName :: Maybe Text
platformArn :: Maybe Text
optionsToRemove :: Maybe [OptionSpecification]
optionSettings :: Maybe [ConfigurationOptionSetting]
groupName :: Maybe Text
environmentName :: Maybe Text
environmentId :: Maybe Text
description :: Maybe Text
applicationName :: Maybe Text
$sel:versionLabel:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:tier:UpdateEnvironment' :: UpdateEnvironment -> Maybe EnvironmentTier
$sel:templateName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:solutionStackName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:platformArn:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:optionsToRemove:UpdateEnvironment' :: UpdateEnvironment -> Maybe [OptionSpecification]
$sel:optionSettings:UpdateEnvironment' :: UpdateEnvironment -> Maybe [ConfigurationOptionSetting]
$sel:groupName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:environmentName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:environmentId:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:description:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
$sel:applicationName:UpdateEnvironment' :: UpdateEnvironment -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"UpdateEnvironment" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString),
        ByteString
"ApplicationName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
applicationName,
        ByteString
"Description" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
description,
        ByteString
"EnvironmentId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
environmentId,
        ByteString
"EnvironmentName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
environmentName,
        ByteString
"GroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
groupName,
        ByteString
"OptionSettings"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ConfigurationOptionSetting]
optionSettings
            ),
        ByteString
"OptionsToRemove"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [OptionSpecification]
optionsToRemove
            ),
        ByteString
"PlatformArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
platformArn,
        ByteString
"SolutionStackName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
solutionStackName,
        ByteString
"TemplateName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
templateName,
        ByteString
"Tier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe EnvironmentTier
tier,
        ByteString
"VersionLabel" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
versionLabel
      ]