{-# 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.DeleteVpcPeeringConnection
-- 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 VPC peering connection. Either the owner of the requester VPC
-- or the owner of the accepter VPC can delete the VPC peering connection
-- if it\'s in the @active@ state. The owner of the requester VPC can
-- delete a VPC peering connection in the @pending-acceptance@ state. You
-- cannot delete a VPC peering connection that\'s in the @failed@ state.
module Amazonka.EC2.DeleteVpcPeeringConnection
  ( -- * Creating a Request
    DeleteVpcPeeringConnection (..),
    newDeleteVpcPeeringConnection,

    -- * Request Lenses
    deleteVpcPeeringConnection_dryRun,
    deleteVpcPeeringConnection_vpcPeeringConnectionId,

    -- * Destructuring the Response
    DeleteVpcPeeringConnectionResponse (..),
    newDeleteVpcPeeringConnectionResponse,

    -- * Response Lenses
    deleteVpcPeeringConnectionResponse_return,
    deleteVpcPeeringConnectionResponse_httpStatus,
  )
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

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

-- |
-- Create a value of 'DeleteVpcPeeringConnection' 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', 'deleteVpcPeeringConnection_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@.
--
-- 'vpcPeeringConnectionId', 'deleteVpcPeeringConnection_vpcPeeringConnectionId' - The ID of the VPC peering connection.
newDeleteVpcPeeringConnection ::
  -- | 'vpcPeeringConnectionId'
  Prelude.Text ->
  DeleteVpcPeeringConnection
newDeleteVpcPeeringConnection :: Text -> DeleteVpcPeeringConnection
newDeleteVpcPeeringConnection
  Text
pVpcPeeringConnectionId_ =
    DeleteVpcPeeringConnection'
      { $sel:dryRun:DeleteVpcPeeringConnection' :: Maybe Bool
dryRun =
          forall a. Maybe a
Prelude.Nothing,
        $sel:vpcPeeringConnectionId:DeleteVpcPeeringConnection' :: Text
vpcPeeringConnectionId =
          Text
pVpcPeeringConnectionId_
      }

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

-- | The ID of the VPC peering connection.
deleteVpcPeeringConnection_vpcPeeringConnectionId :: Lens.Lens' DeleteVpcPeeringConnection Prelude.Text
deleteVpcPeeringConnection_vpcPeeringConnectionId :: Lens' DeleteVpcPeeringConnection Text
deleteVpcPeeringConnection_vpcPeeringConnectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVpcPeeringConnection' {Text
vpcPeeringConnectionId :: Text
$sel:vpcPeeringConnectionId:DeleteVpcPeeringConnection' :: DeleteVpcPeeringConnection -> Text
vpcPeeringConnectionId} -> Text
vpcPeeringConnectionId) (\s :: DeleteVpcPeeringConnection
s@DeleteVpcPeeringConnection' {} Text
a -> DeleteVpcPeeringConnection
s {$sel:vpcPeeringConnectionId:DeleteVpcPeeringConnection' :: Text
vpcPeeringConnectionId = Text
a} :: DeleteVpcPeeringConnection)

instance Core.AWSRequest DeleteVpcPeeringConnection where
  type
    AWSResponse DeleteVpcPeeringConnection =
      DeleteVpcPeeringConnectionResponse
  request :: (Service -> Service)
-> DeleteVpcPeeringConnection -> Request DeleteVpcPeeringConnection
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 DeleteVpcPeeringConnection
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteVpcPeeringConnection)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Bool -> Int -> DeleteVpcPeeringConnectionResponse
DeleteVpcPeeringConnectionResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"return")
            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 DeleteVpcPeeringConnection where
  hashWithSalt :: Int -> DeleteVpcPeeringConnection -> Int
hashWithSalt Int
_salt DeleteVpcPeeringConnection' {Maybe Bool
Text
vpcPeeringConnectionId :: Text
dryRun :: Maybe Bool
$sel:vpcPeeringConnectionId:DeleteVpcPeeringConnection' :: DeleteVpcPeeringConnection -> Text
$sel:dryRun:DeleteVpcPeeringConnection' :: DeleteVpcPeeringConnection -> 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
vpcPeeringConnectionId

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

instance Data.ToHeaders DeleteVpcPeeringConnection where
  toHeaders :: DeleteVpcPeeringConnection -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

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

-- | /See:/ 'newDeleteVpcPeeringConnectionResponse' smart constructor.
data DeleteVpcPeeringConnectionResponse = DeleteVpcPeeringConnectionResponse'
  { -- | Returns @true@ if the request succeeds; otherwise, it returns an error.
    DeleteVpcPeeringConnectionResponse -> Maybe Bool
return' :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    DeleteVpcPeeringConnectionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteVpcPeeringConnectionResponse
-> DeleteVpcPeeringConnectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteVpcPeeringConnectionResponse
-> DeleteVpcPeeringConnectionResponse -> Bool
$c/= :: DeleteVpcPeeringConnectionResponse
-> DeleteVpcPeeringConnectionResponse -> Bool
== :: DeleteVpcPeeringConnectionResponse
-> DeleteVpcPeeringConnectionResponse -> Bool
$c== :: DeleteVpcPeeringConnectionResponse
-> DeleteVpcPeeringConnectionResponse -> Bool
Prelude.Eq, ReadPrec [DeleteVpcPeeringConnectionResponse]
ReadPrec DeleteVpcPeeringConnectionResponse
Int -> ReadS DeleteVpcPeeringConnectionResponse
ReadS [DeleteVpcPeeringConnectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteVpcPeeringConnectionResponse]
$creadListPrec :: ReadPrec [DeleteVpcPeeringConnectionResponse]
readPrec :: ReadPrec DeleteVpcPeeringConnectionResponse
$creadPrec :: ReadPrec DeleteVpcPeeringConnectionResponse
readList :: ReadS [DeleteVpcPeeringConnectionResponse]
$creadList :: ReadS [DeleteVpcPeeringConnectionResponse]
readsPrec :: Int -> ReadS DeleteVpcPeeringConnectionResponse
$creadsPrec :: Int -> ReadS DeleteVpcPeeringConnectionResponse
Prelude.Read, Int -> DeleteVpcPeeringConnectionResponse -> ShowS
[DeleteVpcPeeringConnectionResponse] -> ShowS
DeleteVpcPeeringConnectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteVpcPeeringConnectionResponse] -> ShowS
$cshowList :: [DeleteVpcPeeringConnectionResponse] -> ShowS
show :: DeleteVpcPeeringConnectionResponse -> String
$cshow :: DeleteVpcPeeringConnectionResponse -> String
showsPrec :: Int -> DeleteVpcPeeringConnectionResponse -> ShowS
$cshowsPrec :: Int -> DeleteVpcPeeringConnectionResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteVpcPeeringConnectionResponse x
-> DeleteVpcPeeringConnectionResponse
forall x.
DeleteVpcPeeringConnectionResponse
-> Rep DeleteVpcPeeringConnectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteVpcPeeringConnectionResponse x
-> DeleteVpcPeeringConnectionResponse
$cfrom :: forall x.
DeleteVpcPeeringConnectionResponse
-> Rep DeleteVpcPeeringConnectionResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteVpcPeeringConnectionResponse' 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:
--
-- 'return'', 'deleteVpcPeeringConnectionResponse_return' - Returns @true@ if the request succeeds; otherwise, it returns an error.
--
-- 'httpStatus', 'deleteVpcPeeringConnectionResponse_httpStatus' - The response's http status code.
newDeleteVpcPeeringConnectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteVpcPeeringConnectionResponse
newDeleteVpcPeeringConnectionResponse :: Int -> DeleteVpcPeeringConnectionResponse
newDeleteVpcPeeringConnectionResponse Int
pHttpStatus_ =
  DeleteVpcPeeringConnectionResponse'
    { $sel:return':DeleteVpcPeeringConnectionResponse' :: Maybe Bool
return' =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteVpcPeeringConnectionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Returns @true@ if the request succeeds; otherwise, it returns an error.
deleteVpcPeeringConnectionResponse_return :: Lens.Lens' DeleteVpcPeeringConnectionResponse (Prelude.Maybe Prelude.Bool)
deleteVpcPeeringConnectionResponse_return :: Lens' DeleteVpcPeeringConnectionResponse (Maybe Bool)
deleteVpcPeeringConnectionResponse_return = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVpcPeeringConnectionResponse' {Maybe Bool
return' :: Maybe Bool
$sel:return':DeleteVpcPeeringConnectionResponse' :: DeleteVpcPeeringConnectionResponse -> Maybe Bool
return'} -> Maybe Bool
return') (\s :: DeleteVpcPeeringConnectionResponse
s@DeleteVpcPeeringConnectionResponse' {} Maybe Bool
a -> DeleteVpcPeeringConnectionResponse
s {$sel:return':DeleteVpcPeeringConnectionResponse' :: Maybe Bool
return' = Maybe Bool
a} :: DeleteVpcPeeringConnectionResponse)

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

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