{-# 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.TerminateEnvironment
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Terminates the specified environment.
module Amazonka.ElasticBeanstalk.TerminateEnvironment
  ( -- * Creating a Request
    TerminateEnvironment (..),
    newTerminateEnvironment,

    -- * Request Lenses
    terminateEnvironment_environmentId,
    terminateEnvironment_environmentName,
    terminateEnvironment_forceTerminate,
    terminateEnvironment_terminateResources,

    -- * 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 terminate an environment.
--
-- /See:/ 'newTerminateEnvironment' smart constructor.
data TerminateEnvironment = TerminateEnvironment'
  { -- | The ID of the environment to terminate.
    --
    -- Condition: You must specify either this or an EnvironmentName, or both.
    -- If you do not specify either, AWS Elastic Beanstalk returns
    -- @MissingRequiredParameter@ error.
    TerminateEnvironment -> Maybe Text
environmentId :: Prelude.Maybe Prelude.Text,
    -- | The name of the environment to terminate.
    --
    -- Condition: You must specify either this or an EnvironmentId, or both. If
    -- you do not specify either, AWS Elastic Beanstalk returns
    -- @MissingRequiredParameter@ error.
    TerminateEnvironment -> Maybe Text
environmentName :: Prelude.Maybe Prelude.Text,
    -- | Terminates the target environment even if another environment in the
    -- same group is dependent on it.
    TerminateEnvironment -> Maybe Bool
forceTerminate :: Prelude.Maybe Prelude.Bool,
    -- | Indicates whether the associated AWS resources should shut down when the
    -- environment is terminated:
    --
    -- -   @true@: The specified environment as well as the associated AWS
    --     resources, such as Auto Scaling group and LoadBalancer, are
    --     terminated.
    --
    -- -   @false@: AWS Elastic Beanstalk resource management is removed from
    --     the environment, but the AWS resources continue to operate.
    --
    -- For more information, see the
    -- <https://docs.aws.amazon.com/elasticbeanstalk/latest/ug/ AWS Elastic Beanstalk User Guide.>
    --
    -- Default: @true@
    --
    -- Valid Values: @true@ | @false@
    TerminateEnvironment -> Maybe Bool
terminateResources :: Prelude.Maybe Prelude.Bool
  }
  deriving (TerminateEnvironment -> TerminateEnvironment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TerminateEnvironment -> TerminateEnvironment -> Bool
$c/= :: TerminateEnvironment -> TerminateEnvironment -> Bool
== :: TerminateEnvironment -> TerminateEnvironment -> Bool
$c== :: TerminateEnvironment -> TerminateEnvironment -> Bool
Prelude.Eq, ReadPrec [TerminateEnvironment]
ReadPrec TerminateEnvironment
Int -> ReadS TerminateEnvironment
ReadS [TerminateEnvironment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TerminateEnvironment]
$creadListPrec :: ReadPrec [TerminateEnvironment]
readPrec :: ReadPrec TerminateEnvironment
$creadPrec :: ReadPrec TerminateEnvironment
readList :: ReadS [TerminateEnvironment]
$creadList :: ReadS [TerminateEnvironment]
readsPrec :: Int -> ReadS TerminateEnvironment
$creadsPrec :: Int -> ReadS TerminateEnvironment
Prelude.Read, Int -> TerminateEnvironment -> ShowS
[TerminateEnvironment] -> ShowS
TerminateEnvironment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TerminateEnvironment] -> ShowS
$cshowList :: [TerminateEnvironment] -> ShowS
show :: TerminateEnvironment -> String
$cshow :: TerminateEnvironment -> String
showsPrec :: Int -> TerminateEnvironment -> ShowS
$cshowsPrec :: Int -> TerminateEnvironment -> ShowS
Prelude.Show, forall x. Rep TerminateEnvironment x -> TerminateEnvironment
forall x. TerminateEnvironment -> Rep TerminateEnvironment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TerminateEnvironment x -> TerminateEnvironment
$cfrom :: forall x. TerminateEnvironment -> Rep TerminateEnvironment x
Prelude.Generic)

-- |
-- Create a value of 'TerminateEnvironment' 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:
--
-- 'environmentId', 'terminateEnvironment_environmentId' - The ID of the environment to terminate.
--
-- Condition: You must specify either this or an EnvironmentName, or both.
-- If you do not specify either, AWS Elastic Beanstalk returns
-- @MissingRequiredParameter@ error.
--
-- 'environmentName', 'terminateEnvironment_environmentName' - The name of the environment to terminate.
--
-- Condition: You must specify either this or an EnvironmentId, or both. If
-- you do not specify either, AWS Elastic Beanstalk returns
-- @MissingRequiredParameter@ error.
--
-- 'forceTerminate', 'terminateEnvironment_forceTerminate' - Terminates the target environment even if another environment in the
-- same group is dependent on it.
--
-- 'terminateResources', 'terminateEnvironment_terminateResources' - Indicates whether the associated AWS resources should shut down when the
-- environment is terminated:
--
-- -   @true@: The specified environment as well as the associated AWS
--     resources, such as Auto Scaling group and LoadBalancer, are
--     terminated.
--
-- -   @false@: AWS Elastic Beanstalk resource management is removed from
--     the environment, but the AWS resources continue to operate.
--
-- For more information, see the
-- <https://docs.aws.amazon.com/elasticbeanstalk/latest/ug/ AWS Elastic Beanstalk User Guide.>
--
-- Default: @true@
--
-- Valid Values: @true@ | @false@
newTerminateEnvironment ::
  TerminateEnvironment
newTerminateEnvironment :: TerminateEnvironment
newTerminateEnvironment =
  TerminateEnvironment'
    { $sel:environmentId:TerminateEnvironment' :: Maybe Text
environmentId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:environmentName:TerminateEnvironment' :: Maybe Text
environmentName = forall a. Maybe a
Prelude.Nothing,
      $sel:forceTerminate:TerminateEnvironment' :: Maybe Bool
forceTerminate = forall a. Maybe a
Prelude.Nothing,
      $sel:terminateResources:TerminateEnvironment' :: Maybe Bool
terminateResources = forall a. Maybe a
Prelude.Nothing
    }

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

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

-- | Terminates the target environment even if another environment in the
-- same group is dependent on it.
terminateEnvironment_forceTerminate :: Lens.Lens' TerminateEnvironment (Prelude.Maybe Prelude.Bool)
terminateEnvironment_forceTerminate :: Lens' TerminateEnvironment (Maybe Bool)
terminateEnvironment_forceTerminate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TerminateEnvironment' {Maybe Bool
forceTerminate :: Maybe Bool
$sel:forceTerminate:TerminateEnvironment' :: TerminateEnvironment -> Maybe Bool
forceTerminate} -> Maybe Bool
forceTerminate) (\s :: TerminateEnvironment
s@TerminateEnvironment' {} Maybe Bool
a -> TerminateEnvironment
s {$sel:forceTerminate:TerminateEnvironment' :: Maybe Bool
forceTerminate = Maybe Bool
a} :: TerminateEnvironment)

-- | Indicates whether the associated AWS resources should shut down when the
-- environment is terminated:
--
-- -   @true@: The specified environment as well as the associated AWS
--     resources, such as Auto Scaling group and LoadBalancer, are
--     terminated.
--
-- -   @false@: AWS Elastic Beanstalk resource management is removed from
--     the environment, but the AWS resources continue to operate.
--
-- For more information, see the
-- <https://docs.aws.amazon.com/elasticbeanstalk/latest/ug/ AWS Elastic Beanstalk User Guide.>
--
-- Default: @true@
--
-- Valid Values: @true@ | @false@
terminateEnvironment_terminateResources :: Lens.Lens' TerminateEnvironment (Prelude.Maybe Prelude.Bool)
terminateEnvironment_terminateResources :: Lens' TerminateEnvironment (Maybe Bool)
terminateEnvironment_terminateResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TerminateEnvironment' {Maybe Bool
terminateResources :: Maybe Bool
$sel:terminateResources:TerminateEnvironment' :: TerminateEnvironment -> Maybe Bool
terminateResources} -> Maybe Bool
terminateResources) (\s :: TerminateEnvironment
s@TerminateEnvironment' {} Maybe Bool
a -> TerminateEnvironment
s {$sel:terminateResources:TerminateEnvironment' :: Maybe Bool
terminateResources = Maybe Bool
a} :: TerminateEnvironment)

instance Core.AWSRequest TerminateEnvironment where
  type
    AWSResponse TerminateEnvironment =
      EnvironmentDescription
  request :: (Service -> Service)
-> TerminateEnvironment -> Request TerminateEnvironment
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 TerminateEnvironment
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse TerminateEnvironment)))
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
"TerminateEnvironmentResult"
      (\Int
s ResponseHeaders
h [Node]
x -> forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)

instance Prelude.Hashable TerminateEnvironment where
  hashWithSalt :: Int -> TerminateEnvironment -> Int
hashWithSalt Int
_salt TerminateEnvironment' {Maybe Bool
Maybe Text
terminateResources :: Maybe Bool
forceTerminate :: Maybe Bool
environmentName :: Maybe Text
environmentId :: Maybe Text
$sel:terminateResources:TerminateEnvironment' :: TerminateEnvironment -> Maybe Bool
$sel:forceTerminate:TerminateEnvironment' :: TerminateEnvironment -> Maybe Bool
$sel:environmentName:TerminateEnvironment' :: TerminateEnvironment -> Maybe Text
$sel:environmentId:TerminateEnvironment' :: TerminateEnvironment -> Maybe Text
..} =
    Int
_salt
      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 Bool
forceTerminate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
terminateResources

instance Prelude.NFData TerminateEnvironment where
  rnf :: TerminateEnvironment -> ()
rnf TerminateEnvironment' {Maybe Bool
Maybe Text
terminateResources :: Maybe Bool
forceTerminate :: Maybe Bool
environmentName :: Maybe Text
environmentId :: Maybe Text
$sel:terminateResources:TerminateEnvironment' :: TerminateEnvironment -> Maybe Bool
$sel:forceTerminate:TerminateEnvironment' :: TerminateEnvironment -> Maybe Bool
$sel:environmentName:TerminateEnvironment' :: TerminateEnvironment -> Maybe Text
$sel:environmentId:TerminateEnvironment' :: TerminateEnvironment -> Maybe Text
..} =
    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 Bool
forceTerminate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
terminateResources

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

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

instance Data.ToQuery TerminateEnvironment where
  toQuery :: TerminateEnvironment -> QueryString
toQuery TerminateEnvironment' {Maybe Bool
Maybe Text
terminateResources :: Maybe Bool
forceTerminate :: Maybe Bool
environmentName :: Maybe Text
environmentId :: Maybe Text
$sel:terminateResources:TerminateEnvironment' :: TerminateEnvironment -> Maybe Bool
$sel:forceTerminate:TerminateEnvironment' :: TerminateEnvironment -> Maybe Bool
$sel:environmentName:TerminateEnvironment' :: TerminateEnvironment -> Maybe Text
$sel:environmentId:TerminateEnvironment' :: TerminateEnvironment -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"TerminateEnvironment" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString),
        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
"ForceTerminate" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
forceTerminate,
        ByteString
"TerminateResources" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
terminateResources
      ]