{-# 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.DeleteVpc
-- 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 VPC. You must detach or delete all gateways and
-- resources that are associated with the VPC before you can delete it. For
-- example, you must terminate all instances running in the VPC, delete all
-- security groups associated with the VPC (except the default one), delete
-- all route tables associated with the VPC (except the default one), and
-- so on.
module Amazonka.EC2.DeleteVpc
  ( -- * Creating a Request
    DeleteVpc (..),
    newDeleteVpc,

    -- * Request Lenses
    deleteVpc_dryRun,
    deleteVpc_vpcId,

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

-- |
-- Create a value of 'DeleteVpc' 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', 'deleteVpc_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@.
--
-- 'vpcId', 'deleteVpc_vpcId' - The ID of the VPC.
newDeleteVpc ::
  -- | 'vpcId'
  Prelude.Text ->
  DeleteVpc
newDeleteVpc :: Text -> DeleteVpc
newDeleteVpc Text
pVpcId_ =
  DeleteVpc'
    { $sel:dryRun:DeleteVpc' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:DeleteVpc' :: Text
vpcId = Text
pVpcId_
    }

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

-- | The ID of the VPC.
deleteVpc_vpcId :: Lens.Lens' DeleteVpc Prelude.Text
deleteVpc_vpcId :: Lens' DeleteVpc Text
deleteVpc_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVpc' {Text
vpcId :: Text
$sel:vpcId:DeleteVpc' :: DeleteVpc -> Text
vpcId} -> Text
vpcId) (\s :: DeleteVpc
s@DeleteVpc' {} Text
a -> DeleteVpc
s {$sel:vpcId:DeleteVpc' :: Text
vpcId = Text
a} :: DeleteVpc)

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

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

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

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

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

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

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

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

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