{-# 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.Lightsail.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 an Amazon Lightsail instance.
--
-- The @delete instance@ operation supports tag-based access control via
-- resource tags applied to the resource identified by @instance name@. For
-- more information, see the
-- <https://lightsail.aws.amazon.com/ls/docs/en_us/articles/amazon-lightsail-controlling-access-using-tags Amazon Lightsail Developer Guide>.
module Amazonka.Lightsail.DeleteInstance
  ( -- * Creating a Request
    DeleteInstance (..),
    newDeleteInstance,

    -- * Request Lenses
    deleteInstance_forceDeleteAddOns,
    deleteInstance_instanceName,

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

    -- * Response Lenses
    deleteInstanceResponse_operations,
    deleteInstanceResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Lightsail.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'
  { -- | A Boolean value to indicate whether to delete all add-ons for the
    -- instance.
    DeleteInstance -> Maybe Bool
forceDeleteAddOns :: Prelude.Maybe Prelude.Bool,
    -- | The name of the instance to delete.
    DeleteInstance -> Text
instanceName :: 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:
--
-- 'forceDeleteAddOns', 'deleteInstance_forceDeleteAddOns' - A Boolean value to indicate whether to delete all add-ons for the
-- instance.
--
-- 'instanceName', 'deleteInstance_instanceName' - The name of the instance to delete.
newDeleteInstance ::
  -- | 'instanceName'
  Prelude.Text ->
  DeleteInstance
newDeleteInstance :: Text -> DeleteInstance
newDeleteInstance Text
pInstanceName_ =
  DeleteInstance'
    { $sel:forceDeleteAddOns:DeleteInstance' :: Maybe Bool
forceDeleteAddOns =
        forall a. Maybe a
Prelude.Nothing,
      $sel:instanceName:DeleteInstance' :: Text
instanceName = Text
pInstanceName_
    }

-- | A Boolean value to indicate whether to delete all add-ons for the
-- instance.
deleteInstance_forceDeleteAddOns :: Lens.Lens' DeleteInstance (Prelude.Maybe Prelude.Bool)
deleteInstance_forceDeleteAddOns :: Lens' DeleteInstance (Maybe Bool)
deleteInstance_forceDeleteAddOns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteInstance' {Maybe Bool
forceDeleteAddOns :: Maybe Bool
$sel:forceDeleteAddOns:DeleteInstance' :: DeleteInstance -> Maybe Bool
forceDeleteAddOns} -> Maybe Bool
forceDeleteAddOns) (\s :: DeleteInstance
s@DeleteInstance' {} Maybe Bool
a -> DeleteInstance
s {$sel:forceDeleteAddOns:DeleteInstance' :: Maybe Bool
forceDeleteAddOns = Maybe Bool
a} :: DeleteInstance)

-- | The name of the instance to delete.
deleteInstance_instanceName :: Lens.Lens' DeleteInstance Prelude.Text
deleteInstance_instanceName :: Lens' DeleteInstance Text
deleteInstance_instanceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteInstance' {Text
instanceName :: Text
$sel:instanceName:DeleteInstance' :: DeleteInstance -> Text
instanceName} -> Text
instanceName) (\s :: DeleteInstance
s@DeleteInstance' {} Text
a -> DeleteInstance
s {$sel:instanceName:DeleteInstance' :: Text
instanceName = 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 =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe [Operation] -> Int -> DeleteInstanceResponse
DeleteInstanceResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"operations" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

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

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

instance Data.ToHeaders DeleteInstance where
  toHeaders :: DeleteInstance -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"Lightsail_20161128.DeleteInstance" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DeleteInstance where
  toJSON :: DeleteInstance -> Value
toJSON DeleteInstance' {Maybe Bool
Text
instanceName :: Text
forceDeleteAddOns :: Maybe Bool
$sel:instanceName:DeleteInstance' :: DeleteInstance -> Text
$sel:forceDeleteAddOns:DeleteInstance' :: DeleteInstance -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"forceDeleteAddOns" 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
forceDeleteAddOns,
            forall a. a -> Maybe a
Prelude.Just (Key
"instanceName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
instanceName)
          ]
      )

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'
  { -- | An array of objects that describe the result of the action, such as the
    -- status of the request, the timestamp of the request, and the resources
    -- affected by the request.
    DeleteInstanceResponse -> Maybe [Operation]
operations :: Prelude.Maybe [Operation],
    -- | The response's http status code.
    DeleteInstanceResponse -> Int
httpStatus :: Prelude.Int
  }
  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.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'operations', 'deleteInstanceResponse_operations' - An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
--
-- 'httpStatus', 'deleteInstanceResponse_httpStatus' - The response's http status code.
newDeleteInstanceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteInstanceResponse
newDeleteInstanceResponse :: Int -> DeleteInstanceResponse
newDeleteInstanceResponse Int
pHttpStatus_ =
  DeleteInstanceResponse'
    { $sel:operations:DeleteInstanceResponse' :: Maybe [Operation]
operations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteInstanceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
deleteInstanceResponse_operations :: Lens.Lens' DeleteInstanceResponse (Prelude.Maybe [Operation])
deleteInstanceResponse_operations :: Lens' DeleteInstanceResponse (Maybe [Operation])
deleteInstanceResponse_operations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteInstanceResponse' {Maybe [Operation]
operations :: Maybe [Operation]
$sel:operations:DeleteInstanceResponse' :: DeleteInstanceResponse -> Maybe [Operation]
operations} -> Maybe [Operation]
operations) (\s :: DeleteInstanceResponse
s@DeleteInstanceResponse' {} Maybe [Operation]
a -> DeleteInstanceResponse
s {$sel:operations:DeleteInstanceResponse' :: Maybe [Operation]
operations = Maybe [Operation]
a} :: DeleteInstanceResponse) 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 response's http status code.
deleteInstanceResponse_httpStatus :: Lens.Lens' DeleteInstanceResponse Prelude.Int
deleteInstanceResponse_httpStatus :: Lens' DeleteInstanceResponse Int
deleteInstanceResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteInstanceResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteInstanceResponse' :: DeleteInstanceResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteInstanceResponse
s@DeleteInstanceResponse' {} Int
a -> DeleteInstanceResponse
s {$sel:httpStatus:DeleteInstanceResponse' :: Int
httpStatus = Int
a} :: DeleteInstanceResponse)

instance Prelude.NFData DeleteInstanceResponse where
  rnf :: DeleteInstanceResponse -> ()
rnf DeleteInstanceResponse' {Int
Maybe [Operation]
httpStatus :: Int
operations :: Maybe [Operation]
$sel:httpStatus:DeleteInstanceResponse' :: DeleteInstanceResponse -> Int
$sel:operations:DeleteInstanceResponse' :: DeleteInstanceResponse -> Maybe [Operation]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Operation]
operations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus