{-# 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.DeleteVpnConnection
-- 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 VPN connection.
--
-- If you\'re deleting the VPC and its associated components, we recommend
-- that you detach the virtual private gateway from the VPC and delete the
-- VPC before deleting the VPN connection. If you believe that the tunnel
-- credentials for your VPN connection have been compromised, you can
-- delete the VPN connection and create a new one that has new keys,
-- without needing to delete the VPC or virtual private gateway. If you
-- create a new VPN connection, you must reconfigure the customer gateway
-- device using the new configuration information returned with the new VPN
-- connection ID.
--
-- For certificate-based authentication, delete all Certificate Manager
-- (ACM) private certificates used for the Amazon Web Services-side tunnel
-- endpoints for the VPN connection before deleting the VPN connection.
module Amazonka.EC2.DeleteVpnConnection
  ( -- * Creating a Request
    DeleteVpnConnection (..),
    newDeleteVpnConnection,

    -- * Request Lenses
    deleteVpnConnection_dryRun,
    deleteVpnConnection_vpnConnectionId,

    -- * Destructuring the Response
    DeleteVpnConnectionResponse (..),
    newDeleteVpnConnectionResponse,
  )
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 DeleteVpnConnection.
--
-- /See:/ 'newDeleteVpnConnection' smart constructor.
data DeleteVpnConnection = DeleteVpnConnection'
  { -- | 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@.
    DeleteVpnConnection -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the VPN connection.
    DeleteVpnConnection -> Text
vpnConnectionId :: Prelude.Text
  }
  deriving (DeleteVpnConnection -> DeleteVpnConnection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteVpnConnection -> DeleteVpnConnection -> Bool
$c/= :: DeleteVpnConnection -> DeleteVpnConnection -> Bool
== :: DeleteVpnConnection -> DeleteVpnConnection -> Bool
$c== :: DeleteVpnConnection -> DeleteVpnConnection -> Bool
Prelude.Eq, ReadPrec [DeleteVpnConnection]
ReadPrec DeleteVpnConnection
Int -> ReadS DeleteVpnConnection
ReadS [DeleteVpnConnection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteVpnConnection]
$creadListPrec :: ReadPrec [DeleteVpnConnection]
readPrec :: ReadPrec DeleteVpnConnection
$creadPrec :: ReadPrec DeleteVpnConnection
readList :: ReadS [DeleteVpnConnection]
$creadList :: ReadS [DeleteVpnConnection]
readsPrec :: Int -> ReadS DeleteVpnConnection
$creadsPrec :: Int -> ReadS DeleteVpnConnection
Prelude.Read, Int -> DeleteVpnConnection -> ShowS
[DeleteVpnConnection] -> ShowS
DeleteVpnConnection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteVpnConnection] -> ShowS
$cshowList :: [DeleteVpnConnection] -> ShowS
show :: DeleteVpnConnection -> String
$cshow :: DeleteVpnConnection -> String
showsPrec :: Int -> DeleteVpnConnection -> ShowS
$cshowsPrec :: Int -> DeleteVpnConnection -> ShowS
Prelude.Show, forall x. Rep DeleteVpnConnection x -> DeleteVpnConnection
forall x. DeleteVpnConnection -> Rep DeleteVpnConnection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteVpnConnection x -> DeleteVpnConnection
$cfrom :: forall x. DeleteVpnConnection -> Rep DeleteVpnConnection x
Prelude.Generic)

-- |
-- Create a value of 'DeleteVpnConnection' 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', 'deleteVpnConnection_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@.
--
-- 'vpnConnectionId', 'deleteVpnConnection_vpnConnectionId' - The ID of the VPN connection.
newDeleteVpnConnection ::
  -- | 'vpnConnectionId'
  Prelude.Text ->
  DeleteVpnConnection
newDeleteVpnConnection :: Text -> DeleteVpnConnection
newDeleteVpnConnection Text
pVpnConnectionId_ =
  DeleteVpnConnection'
    { $sel:dryRun:DeleteVpnConnection' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:vpnConnectionId:DeleteVpnConnection' :: Text
vpnConnectionId = Text
pVpnConnectionId_
    }

-- | 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@.
deleteVpnConnection_dryRun :: Lens.Lens' DeleteVpnConnection (Prelude.Maybe Prelude.Bool)
deleteVpnConnection_dryRun :: Lens' DeleteVpnConnection (Maybe Bool)
deleteVpnConnection_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVpnConnection' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DeleteVpnConnection' :: DeleteVpnConnection -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DeleteVpnConnection
s@DeleteVpnConnection' {} Maybe Bool
a -> DeleteVpnConnection
s {$sel:dryRun:DeleteVpnConnection' :: Maybe Bool
dryRun = Maybe Bool
a} :: DeleteVpnConnection)

-- | The ID of the VPN connection.
deleteVpnConnection_vpnConnectionId :: Lens.Lens' DeleteVpnConnection Prelude.Text
deleteVpnConnection_vpnConnectionId :: Lens' DeleteVpnConnection Text
deleteVpnConnection_vpnConnectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVpnConnection' {Text
vpnConnectionId :: Text
$sel:vpnConnectionId:DeleteVpnConnection' :: DeleteVpnConnection -> Text
vpnConnectionId} -> Text
vpnConnectionId) (\s :: DeleteVpnConnection
s@DeleteVpnConnection' {} Text
a -> DeleteVpnConnection
s {$sel:vpnConnectionId:DeleteVpnConnection' :: Text
vpnConnectionId = Text
a} :: DeleteVpnConnection)

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

instance Prelude.Hashable DeleteVpnConnection where
  hashWithSalt :: Int -> DeleteVpnConnection -> Int
hashWithSalt Int
_salt DeleteVpnConnection' {Maybe Bool
Text
vpnConnectionId :: Text
dryRun :: Maybe Bool
$sel:vpnConnectionId:DeleteVpnConnection' :: DeleteVpnConnection -> Text
$sel:dryRun:DeleteVpnConnection' :: DeleteVpnConnection -> 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
vpnConnectionId

instance Prelude.NFData DeleteVpnConnection where
  rnf :: DeleteVpnConnection -> ()
rnf DeleteVpnConnection' {Maybe Bool
Text
vpnConnectionId :: Text
dryRun :: Maybe Bool
$sel:vpnConnectionId:DeleteVpnConnection' :: DeleteVpnConnection -> Text
$sel:dryRun:DeleteVpnConnection' :: DeleteVpnConnection -> 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
vpnConnectionId

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

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

instance Data.ToQuery DeleteVpnConnection where
  toQuery :: DeleteVpnConnection -> QueryString
toQuery DeleteVpnConnection' {Maybe Bool
Text
vpnConnectionId :: Text
dryRun :: Maybe Bool
$sel:vpnConnectionId:DeleteVpnConnection' :: DeleteVpnConnection -> Text
$sel:dryRun:DeleteVpnConnection' :: DeleteVpnConnection -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DeleteVpnConnection" :: 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
"VpnConnectionId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
vpnConnectionId
      ]

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

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

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