{-# 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.OpsWorks.DeleteInstance
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes a specified instance, which terminates the associated Amazon EC2
-- instance. You must stop an instance before you can delete it.
--
-- For more information, see
-- <https://docs.aws.amazon.com/opsworks/latest/userguide/workinginstances-delete.html Deleting Instances>.
--
-- __Required Permissions__: To use this action, an IAM user must have a
-- Manage permissions level for the stack, or an attached policy that
-- explicitly grants permissions. For more information on user permissions,
-- see
-- <https://docs.aws.amazon.com/opsworks/latest/userguide/opsworks-security-users.html Managing User Permissions>.
module Amazonka.OpsWorks.DeleteInstance
  ( -- * Creating a Request
    DeleteInstance (..),
    newDeleteInstance,

    -- * Request Lenses
    deleteInstance_deleteElasticIp,
    deleteInstance_deleteVolumes,
    deleteInstance_instanceId,

    -- * Destructuring the Response
    DeleteInstanceResponse (..),
    newDeleteInstanceResponse,
  )
where

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

-- | /See:/ 'newDeleteInstance' smart constructor.
data DeleteInstance = DeleteInstance'
  { -- | Whether to delete the instance Elastic IP address.
    DeleteInstance -> Maybe Bool
deleteElasticIp :: Prelude.Maybe Prelude.Bool,
    -- | Whether to delete the instance\'s Amazon EBS volumes.
    DeleteInstance -> Maybe Bool
deleteVolumes :: Prelude.Maybe Prelude.Bool,
    -- | The instance ID.
    DeleteInstance -> Text
instanceId :: Prelude.Text
  }
  deriving (DeleteInstance -> DeleteInstance -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteInstance -> DeleteInstance -> Bool
$c/= :: DeleteInstance -> DeleteInstance -> Bool
== :: DeleteInstance -> DeleteInstance -> Bool
$c== :: DeleteInstance -> DeleteInstance -> Bool
Prelude.Eq, ReadPrec [DeleteInstance]
ReadPrec DeleteInstance
Int -> ReadS DeleteInstance
ReadS [DeleteInstance]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteInstance]
$creadListPrec :: ReadPrec [DeleteInstance]
readPrec :: ReadPrec DeleteInstance
$creadPrec :: ReadPrec DeleteInstance
readList :: ReadS [DeleteInstance]
$creadList :: ReadS [DeleteInstance]
readsPrec :: Int -> ReadS DeleteInstance
$creadsPrec :: Int -> ReadS DeleteInstance
Prelude.Read, Int -> DeleteInstance -> ShowS
[DeleteInstance] -> ShowS
DeleteInstance -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteInstance] -> ShowS
$cshowList :: [DeleteInstance] -> ShowS
show :: DeleteInstance -> String
$cshow :: DeleteInstance -> String
showsPrec :: Int -> DeleteInstance -> ShowS
$cshowsPrec :: Int -> DeleteInstance -> ShowS
Prelude.Show, forall x. Rep DeleteInstance x -> DeleteInstance
forall x. DeleteInstance -> Rep DeleteInstance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteInstance x -> DeleteInstance
$cfrom :: forall x. DeleteInstance -> Rep DeleteInstance x
Prelude.Generic)

-- |
-- Create a value of 'DeleteInstance' 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:
--
-- 'deleteElasticIp', 'deleteInstance_deleteElasticIp' - Whether to delete the instance Elastic IP address.
--
-- 'deleteVolumes', 'deleteInstance_deleteVolumes' - Whether to delete the instance\'s Amazon EBS volumes.
--
-- 'instanceId', 'deleteInstance_instanceId' - The instance ID.
newDeleteInstance ::
  -- | 'instanceId'
  Prelude.Text ->
  DeleteInstance
newDeleteInstance :: Text -> DeleteInstance
newDeleteInstance Text
pInstanceId_ =
  DeleteInstance'
    { $sel:deleteElasticIp:DeleteInstance' :: Maybe Bool
deleteElasticIp = forall a. Maybe a
Prelude.Nothing,
      $sel:deleteVolumes:DeleteInstance' :: Maybe Bool
deleteVolumes = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:DeleteInstance' :: Text
instanceId = Text
pInstanceId_
    }

-- | Whether to delete the instance Elastic IP address.
deleteInstance_deleteElasticIp :: Lens.Lens' DeleteInstance (Prelude.Maybe Prelude.Bool)
deleteInstance_deleteElasticIp :: Lens' DeleteInstance (Maybe Bool)
deleteInstance_deleteElasticIp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteInstance' {Maybe Bool
deleteElasticIp :: Maybe Bool
$sel:deleteElasticIp:DeleteInstance' :: DeleteInstance -> Maybe Bool
deleteElasticIp} -> Maybe Bool
deleteElasticIp) (\s :: DeleteInstance
s@DeleteInstance' {} Maybe Bool
a -> DeleteInstance
s {$sel:deleteElasticIp:DeleteInstance' :: Maybe Bool
deleteElasticIp = Maybe Bool
a} :: DeleteInstance)

-- | Whether to delete the instance\'s Amazon EBS volumes.
deleteInstance_deleteVolumes :: Lens.Lens' DeleteInstance (Prelude.Maybe Prelude.Bool)
deleteInstance_deleteVolumes :: Lens' DeleteInstance (Maybe Bool)
deleteInstance_deleteVolumes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteInstance' {Maybe Bool
deleteVolumes :: Maybe Bool
$sel:deleteVolumes:DeleteInstance' :: DeleteInstance -> Maybe Bool
deleteVolumes} -> Maybe Bool
deleteVolumes) (\s :: DeleteInstance
s@DeleteInstance' {} Maybe Bool
a -> DeleteInstance
s {$sel:deleteVolumes:DeleteInstance' :: Maybe Bool
deleteVolumes = Maybe Bool
a} :: DeleteInstance)

-- | The instance ID.
deleteInstance_instanceId :: Lens.Lens' DeleteInstance Prelude.Text
deleteInstance_instanceId :: Lens' DeleteInstance Text
deleteInstance_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteInstance' {Text
instanceId :: Text
$sel:instanceId:DeleteInstance' :: DeleteInstance -> Text
instanceId} -> Text
instanceId) (\s :: DeleteInstance
s@DeleteInstance' {} Text
a -> DeleteInstance
s {$sel:instanceId:DeleteInstance' :: Text
instanceId = Text
a} :: DeleteInstance)

instance Core.AWSRequest DeleteInstance where
  type
    AWSResponse DeleteInstance =
      DeleteInstanceResponse
  request :: (Service -> Service) -> DeleteInstance -> Request DeleteInstance
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteInstance
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteInstance)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeleteInstanceResponse
DeleteInstanceResponse'

instance Prelude.Hashable DeleteInstance where
  hashWithSalt :: Int -> DeleteInstance -> Int
hashWithSalt Int
_salt DeleteInstance' {Maybe Bool
Text
instanceId :: Text
deleteVolumes :: Maybe Bool
deleteElasticIp :: Maybe Bool
$sel:instanceId:DeleteInstance' :: DeleteInstance -> Text
$sel:deleteVolumes:DeleteInstance' :: DeleteInstance -> Maybe Bool
$sel:deleteElasticIp:DeleteInstance' :: DeleteInstance -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deleteElasticIp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deleteVolumes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId

instance Prelude.NFData DeleteInstance where
  rnf :: DeleteInstance -> ()
rnf DeleteInstance' {Maybe Bool
Text
instanceId :: Text
deleteVolumes :: Maybe Bool
deleteElasticIp :: Maybe Bool
$sel:instanceId:DeleteInstance' :: DeleteInstance -> Text
$sel:deleteVolumes:DeleteInstance' :: DeleteInstance -> Maybe Bool
$sel:deleteElasticIp:DeleteInstance' :: DeleteInstance -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deleteElasticIp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deleteVolumes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId

instance Data.ToHeaders DeleteInstance where
  toHeaders :: DeleteInstance -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"OpsWorks_20130218.DeleteInstance" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DeleteInstance where
  toJSON :: DeleteInstance -> Value
toJSON DeleteInstance' {Maybe Bool
Text
instanceId :: Text
deleteVolumes :: Maybe Bool
deleteElasticIp :: Maybe Bool
$sel:instanceId:DeleteInstance' :: DeleteInstance -> Text
$sel:deleteVolumes:DeleteInstance' :: DeleteInstance -> Maybe Bool
$sel:deleteElasticIp:DeleteInstance' :: DeleteInstance -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"DeleteElasticIp" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
deleteElasticIp,
            (Key
"DeleteVolumes" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
deleteVolumes,
            forall a. a -> Maybe a
Prelude.Just (Key
"InstanceId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
instanceId)
          ]
      )

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

instance Data.ToQuery DeleteInstance where
  toQuery :: DeleteInstance -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDeleteInstanceResponse' smart constructor.
data DeleteInstanceResponse = DeleteInstanceResponse'
  {
  }
  deriving (DeleteInstanceResponse -> DeleteInstanceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteInstanceResponse -> DeleteInstanceResponse -> Bool
$c/= :: DeleteInstanceResponse -> DeleteInstanceResponse -> Bool
== :: DeleteInstanceResponse -> DeleteInstanceResponse -> Bool
$c== :: DeleteInstanceResponse -> DeleteInstanceResponse -> Bool
Prelude.Eq, ReadPrec [DeleteInstanceResponse]
ReadPrec DeleteInstanceResponse
Int -> ReadS DeleteInstanceResponse
ReadS [DeleteInstanceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteInstanceResponse]
$creadListPrec :: ReadPrec [DeleteInstanceResponse]
readPrec :: ReadPrec DeleteInstanceResponse
$creadPrec :: ReadPrec DeleteInstanceResponse
readList :: ReadS [DeleteInstanceResponse]
$creadList :: ReadS [DeleteInstanceResponse]
readsPrec :: Int -> ReadS DeleteInstanceResponse
$creadsPrec :: Int -> ReadS DeleteInstanceResponse
Prelude.Read, Int -> DeleteInstanceResponse -> ShowS
[DeleteInstanceResponse] -> ShowS
DeleteInstanceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteInstanceResponse] -> ShowS
$cshowList :: [DeleteInstanceResponse] -> ShowS
show :: DeleteInstanceResponse -> String
$cshow :: DeleteInstanceResponse -> String
showsPrec :: Int -> DeleteInstanceResponse -> ShowS
$cshowsPrec :: Int -> DeleteInstanceResponse -> ShowS
Prelude.Show, forall x. Rep DeleteInstanceResponse x -> DeleteInstanceResponse
forall x. DeleteInstanceResponse -> Rep DeleteInstanceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteInstanceResponse x -> DeleteInstanceResponse
$cfrom :: forall x. DeleteInstanceResponse -> Rep DeleteInstanceResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteInstanceResponse' 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.
newDeleteInstanceResponse ::
  DeleteInstanceResponse
newDeleteInstanceResponse :: DeleteInstanceResponse
newDeleteInstanceResponse = DeleteInstanceResponse
DeleteInstanceResponse'

instance Prelude.NFData DeleteInstanceResponse where
  rnf :: DeleteInstanceResponse -> ()
rnf DeleteInstanceResponse
_ = ()