{-# 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.EC2.DeleteCustomerGateway
-- 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 the specified customer gateway. You must delete the VPN
-- connection before you can delete the customer gateway.
module Amazonka.EC2.DeleteCustomerGateway
  ( -- * Creating a Request
    DeleteCustomerGateway (..),
    newDeleteCustomerGateway,

    -- * Request Lenses
    deleteCustomerGateway_dryRun,
    deleteCustomerGateway_customerGatewayId,

    -- * Destructuring the Response
    DeleteCustomerGatewayResponse (..),
    newDeleteCustomerGatewayResponse,
  )
where

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

-- | Contains the parameters for DeleteCustomerGateway.
--
-- /See:/ 'newDeleteCustomerGateway' smart constructor.
data DeleteCustomerGateway = DeleteCustomerGateway'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    DeleteCustomerGateway -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the customer gateway.
    DeleteCustomerGateway -> Text
customerGatewayId :: Prelude.Text
  }
  deriving (DeleteCustomerGateway -> DeleteCustomerGateway -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteCustomerGateway -> DeleteCustomerGateway -> Bool
$c/= :: DeleteCustomerGateway -> DeleteCustomerGateway -> Bool
== :: DeleteCustomerGateway -> DeleteCustomerGateway -> Bool
$c== :: DeleteCustomerGateway -> DeleteCustomerGateway -> Bool
Prelude.Eq, ReadPrec [DeleteCustomerGateway]
ReadPrec DeleteCustomerGateway
Int -> ReadS DeleteCustomerGateway
ReadS [DeleteCustomerGateway]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteCustomerGateway]
$creadListPrec :: ReadPrec [DeleteCustomerGateway]
readPrec :: ReadPrec DeleteCustomerGateway
$creadPrec :: ReadPrec DeleteCustomerGateway
readList :: ReadS [DeleteCustomerGateway]
$creadList :: ReadS [DeleteCustomerGateway]
readsPrec :: Int -> ReadS DeleteCustomerGateway
$creadsPrec :: Int -> ReadS DeleteCustomerGateway
Prelude.Read, Int -> DeleteCustomerGateway -> ShowS
[DeleteCustomerGateway] -> ShowS
DeleteCustomerGateway -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteCustomerGateway] -> ShowS
$cshowList :: [DeleteCustomerGateway] -> ShowS
show :: DeleteCustomerGateway -> String
$cshow :: DeleteCustomerGateway -> String
showsPrec :: Int -> DeleteCustomerGateway -> ShowS
$cshowsPrec :: Int -> DeleteCustomerGateway -> ShowS
Prelude.Show, forall x. Rep DeleteCustomerGateway x -> DeleteCustomerGateway
forall x. DeleteCustomerGateway -> Rep DeleteCustomerGateway x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteCustomerGateway x -> DeleteCustomerGateway
$cfrom :: forall x. DeleteCustomerGateway -> Rep DeleteCustomerGateway x
Prelude.Generic)

-- |
-- Create a value of 'DeleteCustomerGateway' 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:
--
-- 'dryRun', 'deleteCustomerGateway_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'customerGatewayId', 'deleteCustomerGateway_customerGatewayId' - The ID of the customer gateway.
newDeleteCustomerGateway ::
  -- | 'customerGatewayId'
  Prelude.Text ->
  DeleteCustomerGateway
newDeleteCustomerGateway :: Text -> DeleteCustomerGateway
newDeleteCustomerGateway Text
pCustomerGatewayId_ =
  DeleteCustomerGateway'
    { $sel:dryRun:DeleteCustomerGateway' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:customerGatewayId:DeleteCustomerGateway' :: Text
customerGatewayId = Text
pCustomerGatewayId_
    }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
deleteCustomerGateway_dryRun :: Lens.Lens' DeleteCustomerGateway (Prelude.Maybe Prelude.Bool)
deleteCustomerGateway_dryRun :: Lens' DeleteCustomerGateway (Maybe Bool)
deleteCustomerGateway_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteCustomerGateway' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DeleteCustomerGateway' :: DeleteCustomerGateway -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DeleteCustomerGateway
s@DeleteCustomerGateway' {} Maybe Bool
a -> DeleteCustomerGateway
s {$sel:dryRun:DeleteCustomerGateway' :: Maybe Bool
dryRun = Maybe Bool
a} :: DeleteCustomerGateway)

-- | The ID of the customer gateway.
deleteCustomerGateway_customerGatewayId :: Lens.Lens' DeleteCustomerGateway Prelude.Text
deleteCustomerGateway_customerGatewayId :: Lens' DeleteCustomerGateway Text
deleteCustomerGateway_customerGatewayId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteCustomerGateway' {Text
customerGatewayId :: Text
$sel:customerGatewayId:DeleteCustomerGateway' :: DeleteCustomerGateway -> Text
customerGatewayId} -> Text
customerGatewayId) (\s :: DeleteCustomerGateway
s@DeleteCustomerGateway' {} Text
a -> DeleteCustomerGateway
s {$sel:customerGatewayId:DeleteCustomerGateway' :: Text
customerGatewayId = Text
a} :: DeleteCustomerGateway)

instance Core.AWSRequest DeleteCustomerGateway where
  type
    AWSResponse DeleteCustomerGateway =
      DeleteCustomerGatewayResponse
  request :: (Service -> Service)
-> DeleteCustomerGateway -> Request DeleteCustomerGateway
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 DeleteCustomerGateway
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteCustomerGateway)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeleteCustomerGatewayResponse
DeleteCustomerGatewayResponse'

instance Prelude.Hashable DeleteCustomerGateway where
  hashWithSalt :: Int -> DeleteCustomerGateway -> Int
hashWithSalt Int
_salt DeleteCustomerGateway' {Maybe Bool
Text
customerGatewayId :: Text
dryRun :: Maybe Bool
$sel:customerGatewayId:DeleteCustomerGateway' :: DeleteCustomerGateway -> Text
$sel:dryRun:DeleteCustomerGateway' :: DeleteCustomerGateway -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
customerGatewayId

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

instance Data.ToHeaders DeleteCustomerGateway where
  toHeaders :: DeleteCustomerGateway -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery DeleteCustomerGateway where
  toQuery :: DeleteCustomerGateway -> QueryString
toQuery DeleteCustomerGateway' {Maybe Bool
Text
customerGatewayId :: Text
dryRun :: Maybe Bool
$sel:customerGatewayId:DeleteCustomerGateway' :: DeleteCustomerGateway -> Text
$sel:dryRun:DeleteCustomerGateway' :: DeleteCustomerGateway -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DeleteCustomerGateway" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"CustomerGatewayId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
customerGatewayId
      ]

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

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

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