{-# 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.StorageGateway.DeleteGateway
-- 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 gateway. To specify which gateway to delete, use the Amazon
-- Resource Name (ARN) of the gateway in your request. The operation
-- deletes the gateway; however, it does not delete the gateway virtual
-- machine (VM) from your host computer.
--
-- After you delete a gateway, you cannot reactivate it. Completed
-- snapshots of the gateway volumes are not deleted upon deleting the
-- gateway, however, pending snapshots will not complete. After you delete
-- a gateway, your next step is to remove it from your environment.
--
-- You no longer pay software charges after the gateway is deleted;
-- however, your existing Amazon EBS snapshots persist and you will
-- continue to be billed for these snapshots. You can choose to remove all
-- remaining Amazon EBS snapshots by canceling your Amazon EC2
-- subscription.  If you prefer not to cancel your Amazon EC2 subscription,
-- you can delete your snapshots using the Amazon EC2 console. For more
-- information, see the
-- <http://aws.amazon.com/storagegateway Storage Gateway detail page>.
module Amazonka.StorageGateway.DeleteGateway
  ( -- * Creating a Request
    DeleteGateway (..),
    newDeleteGateway,

    -- * Request Lenses
    deleteGateway_gatewayARN,

    -- * Destructuring the Response
    DeleteGatewayResponse (..),
    newDeleteGatewayResponse,

    -- * Response Lenses
    deleteGatewayResponse_gatewayARN,
    deleteGatewayResponse_httpStatus,
  )
where

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
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.StorageGateway.Types

-- | A JSON object containing the ID of the gateway to delete.
--
-- /See:/ 'newDeleteGateway' smart constructor.
data DeleteGateway = DeleteGateway'
  { DeleteGateway -> Text
gatewayARN :: Prelude.Text
  }
  deriving (DeleteGateway -> DeleteGateway -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteGateway -> DeleteGateway -> Bool
$c/= :: DeleteGateway -> DeleteGateway -> Bool
== :: DeleteGateway -> DeleteGateway -> Bool
$c== :: DeleteGateway -> DeleteGateway -> Bool
Prelude.Eq, ReadPrec [DeleteGateway]
ReadPrec DeleteGateway
Int -> ReadS DeleteGateway
ReadS [DeleteGateway]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteGateway]
$creadListPrec :: ReadPrec [DeleteGateway]
readPrec :: ReadPrec DeleteGateway
$creadPrec :: ReadPrec DeleteGateway
readList :: ReadS [DeleteGateway]
$creadList :: ReadS [DeleteGateway]
readsPrec :: Int -> ReadS DeleteGateway
$creadsPrec :: Int -> ReadS DeleteGateway
Prelude.Read, Int -> DeleteGateway -> ShowS
[DeleteGateway] -> ShowS
DeleteGateway -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteGateway] -> ShowS
$cshowList :: [DeleteGateway] -> ShowS
show :: DeleteGateway -> String
$cshow :: DeleteGateway -> String
showsPrec :: Int -> DeleteGateway -> ShowS
$cshowsPrec :: Int -> DeleteGateway -> ShowS
Prelude.Show, forall x. Rep DeleteGateway x -> DeleteGateway
forall x. DeleteGateway -> Rep DeleteGateway x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteGateway x -> DeleteGateway
$cfrom :: forall x. DeleteGateway -> Rep DeleteGateway x
Prelude.Generic)

-- |
-- Create a value of 'DeleteGateway' 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:
--
-- 'gatewayARN', 'deleteGateway_gatewayARN' - Undocumented member.
newDeleteGateway ::
  -- | 'gatewayARN'
  Prelude.Text ->
  DeleteGateway
newDeleteGateway :: Text -> DeleteGateway
newDeleteGateway Text
pGatewayARN_ =
  DeleteGateway' {$sel:gatewayARN:DeleteGateway' :: Text
gatewayARN = Text
pGatewayARN_}

-- | Undocumented member.
deleteGateway_gatewayARN :: Lens.Lens' DeleteGateway Prelude.Text
deleteGateway_gatewayARN :: Lens' DeleteGateway Text
deleteGateway_gatewayARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGateway' {Text
gatewayARN :: Text
$sel:gatewayARN:DeleteGateway' :: DeleteGateway -> Text
gatewayARN} -> Text
gatewayARN) (\s :: DeleteGateway
s@DeleteGateway' {} Text
a -> DeleteGateway
s {$sel:gatewayARN:DeleteGateway' :: Text
gatewayARN = Text
a} :: DeleteGateway)

instance Core.AWSRequest DeleteGateway where
  type
    AWSResponse DeleteGateway =
      DeleteGatewayResponse
  request :: (Service -> Service) -> DeleteGateway -> Request DeleteGateway
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 DeleteGateway
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteGateway)))
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 Text -> Int -> DeleteGatewayResponse
DeleteGatewayResponse'
            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
"GatewayARN")
            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 DeleteGateway where
  hashWithSalt :: Int -> DeleteGateway -> Int
hashWithSalt Int
_salt DeleteGateway' {Text
gatewayARN :: Text
$sel:gatewayARN:DeleteGateway' :: DeleteGateway -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
gatewayARN

instance Prelude.NFData DeleteGateway where
  rnf :: DeleteGateway -> ()
rnf DeleteGateway' {Text
gatewayARN :: Text
$sel:gatewayARN:DeleteGateway' :: DeleteGateway -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
gatewayARN

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

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

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

-- | A JSON object containing the ID of the deleted gateway.
--
-- /See:/ 'newDeleteGatewayResponse' smart constructor.
data DeleteGatewayResponse = DeleteGatewayResponse'
  { DeleteGatewayResponse -> Maybe Text
gatewayARN :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DeleteGatewayResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteGatewayResponse -> DeleteGatewayResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteGatewayResponse -> DeleteGatewayResponse -> Bool
$c/= :: DeleteGatewayResponse -> DeleteGatewayResponse -> Bool
== :: DeleteGatewayResponse -> DeleteGatewayResponse -> Bool
$c== :: DeleteGatewayResponse -> DeleteGatewayResponse -> Bool
Prelude.Eq, ReadPrec [DeleteGatewayResponse]
ReadPrec DeleteGatewayResponse
Int -> ReadS DeleteGatewayResponse
ReadS [DeleteGatewayResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteGatewayResponse]
$creadListPrec :: ReadPrec [DeleteGatewayResponse]
readPrec :: ReadPrec DeleteGatewayResponse
$creadPrec :: ReadPrec DeleteGatewayResponse
readList :: ReadS [DeleteGatewayResponse]
$creadList :: ReadS [DeleteGatewayResponse]
readsPrec :: Int -> ReadS DeleteGatewayResponse
$creadsPrec :: Int -> ReadS DeleteGatewayResponse
Prelude.Read, Int -> DeleteGatewayResponse -> ShowS
[DeleteGatewayResponse] -> ShowS
DeleteGatewayResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteGatewayResponse] -> ShowS
$cshowList :: [DeleteGatewayResponse] -> ShowS
show :: DeleteGatewayResponse -> String
$cshow :: DeleteGatewayResponse -> String
showsPrec :: Int -> DeleteGatewayResponse -> ShowS
$cshowsPrec :: Int -> DeleteGatewayResponse -> ShowS
Prelude.Show, forall x. Rep DeleteGatewayResponse x -> DeleteGatewayResponse
forall x. DeleteGatewayResponse -> Rep DeleteGatewayResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteGatewayResponse x -> DeleteGatewayResponse
$cfrom :: forall x. DeleteGatewayResponse -> Rep DeleteGatewayResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteGatewayResponse' 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:
--
-- 'gatewayARN', 'deleteGatewayResponse_gatewayARN' - Undocumented member.
--
-- 'httpStatus', 'deleteGatewayResponse_httpStatus' - The response's http status code.
newDeleteGatewayResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteGatewayResponse
newDeleteGatewayResponse :: Int -> DeleteGatewayResponse
newDeleteGatewayResponse Int
pHttpStatus_ =
  DeleteGatewayResponse'
    { $sel:gatewayARN:DeleteGatewayResponse' :: Maybe Text
gatewayARN =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteGatewayResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
deleteGatewayResponse_gatewayARN :: Lens.Lens' DeleteGatewayResponse (Prelude.Maybe Prelude.Text)
deleteGatewayResponse_gatewayARN :: Lens' DeleteGatewayResponse (Maybe Text)
deleteGatewayResponse_gatewayARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGatewayResponse' {Maybe Text
gatewayARN :: Maybe Text
$sel:gatewayARN:DeleteGatewayResponse' :: DeleteGatewayResponse -> Maybe Text
gatewayARN} -> Maybe Text
gatewayARN) (\s :: DeleteGatewayResponse
s@DeleteGatewayResponse' {} Maybe Text
a -> DeleteGatewayResponse
s {$sel:gatewayARN:DeleteGatewayResponse' :: Maybe Text
gatewayARN = Maybe Text
a} :: DeleteGatewayResponse)

-- | The response's http status code.
deleteGatewayResponse_httpStatus :: Lens.Lens' DeleteGatewayResponse Prelude.Int
deleteGatewayResponse_httpStatus :: Lens' DeleteGatewayResponse Int
deleteGatewayResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGatewayResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteGatewayResponse' :: DeleteGatewayResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteGatewayResponse
s@DeleteGatewayResponse' {} Int
a -> DeleteGatewayResponse
s {$sel:httpStatus:DeleteGatewayResponse' :: Int
httpStatus = Int
a} :: DeleteGatewayResponse)

instance Prelude.NFData DeleteGatewayResponse where
  rnf :: DeleteGatewayResponse -> ()
rnf DeleteGatewayResponse' {Int
Maybe Text
httpStatus :: Int
gatewayARN :: Maybe Text
$sel:httpStatus:DeleteGatewayResponse' :: DeleteGatewayResponse -> Int
$sel:gatewayARN:DeleteGatewayResponse' :: DeleteGatewayResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
gatewayARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus