{-# 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.DeletePublicIpv4Pool
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Delete a public IPv4 pool. A public IPv4 pool is an EC2 IP address pool
-- required for the public IPv4 CIDRs that you own and bring to Amazon Web
-- Services to manage with IPAM. IPv6 addresses you bring to Amazon Web
-- Services, however, use IPAM pools only.
module Amazonka.EC2.DeletePublicIpv4Pool
  ( -- * Creating a Request
    DeletePublicIpv4Pool (..),
    newDeletePublicIpv4Pool,

    -- * Request Lenses
    deletePublicIpv4Pool_dryRun,
    deletePublicIpv4Pool_poolId,

    -- * Destructuring the Response
    DeletePublicIpv4PoolResponse (..),
    newDeletePublicIpv4PoolResponse,

    -- * Response Lenses
    deletePublicIpv4PoolResponse_returnValue,
    deletePublicIpv4PoolResponse_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:/ 'newDeletePublicIpv4Pool' smart constructor.
data DeletePublicIpv4Pool = DeletePublicIpv4Pool'
  { -- | A check for 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@.
    DeletePublicIpv4Pool -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the public IPv4 pool you want to delete.
    DeletePublicIpv4Pool -> Text
poolId :: Prelude.Text
  }
  deriving (DeletePublicIpv4Pool -> DeletePublicIpv4Pool -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeletePublicIpv4Pool -> DeletePublicIpv4Pool -> Bool
$c/= :: DeletePublicIpv4Pool -> DeletePublicIpv4Pool -> Bool
== :: DeletePublicIpv4Pool -> DeletePublicIpv4Pool -> Bool
$c== :: DeletePublicIpv4Pool -> DeletePublicIpv4Pool -> Bool
Prelude.Eq, ReadPrec [DeletePublicIpv4Pool]
ReadPrec DeletePublicIpv4Pool
Int -> ReadS DeletePublicIpv4Pool
ReadS [DeletePublicIpv4Pool]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeletePublicIpv4Pool]
$creadListPrec :: ReadPrec [DeletePublicIpv4Pool]
readPrec :: ReadPrec DeletePublicIpv4Pool
$creadPrec :: ReadPrec DeletePublicIpv4Pool
readList :: ReadS [DeletePublicIpv4Pool]
$creadList :: ReadS [DeletePublicIpv4Pool]
readsPrec :: Int -> ReadS DeletePublicIpv4Pool
$creadsPrec :: Int -> ReadS DeletePublicIpv4Pool
Prelude.Read, Int -> DeletePublicIpv4Pool -> ShowS
[DeletePublicIpv4Pool] -> ShowS
DeletePublicIpv4Pool -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeletePublicIpv4Pool] -> ShowS
$cshowList :: [DeletePublicIpv4Pool] -> ShowS
show :: DeletePublicIpv4Pool -> String
$cshow :: DeletePublicIpv4Pool -> String
showsPrec :: Int -> DeletePublicIpv4Pool -> ShowS
$cshowsPrec :: Int -> DeletePublicIpv4Pool -> ShowS
Prelude.Show, forall x. Rep DeletePublicIpv4Pool x -> DeletePublicIpv4Pool
forall x. DeletePublicIpv4Pool -> Rep DeletePublicIpv4Pool x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeletePublicIpv4Pool x -> DeletePublicIpv4Pool
$cfrom :: forall x. DeletePublicIpv4Pool -> Rep DeletePublicIpv4Pool x
Prelude.Generic)

-- |
-- Create a value of 'DeletePublicIpv4Pool' 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', 'deletePublicIpv4Pool_dryRun' - A check for 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@.
--
-- 'poolId', 'deletePublicIpv4Pool_poolId' - The ID of the public IPv4 pool you want to delete.
newDeletePublicIpv4Pool ::
  -- | 'poolId'
  Prelude.Text ->
  DeletePublicIpv4Pool
newDeletePublicIpv4Pool :: Text -> DeletePublicIpv4Pool
newDeletePublicIpv4Pool Text
pPoolId_ =
  DeletePublicIpv4Pool'
    { $sel:dryRun:DeletePublicIpv4Pool' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:poolId:DeletePublicIpv4Pool' :: Text
poolId = Text
pPoolId_
    }

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

-- | The ID of the public IPv4 pool you want to delete.
deletePublicIpv4Pool_poolId :: Lens.Lens' DeletePublicIpv4Pool Prelude.Text
deletePublicIpv4Pool_poolId :: Lens' DeletePublicIpv4Pool Text
deletePublicIpv4Pool_poolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePublicIpv4Pool' {Text
poolId :: Text
$sel:poolId:DeletePublicIpv4Pool' :: DeletePublicIpv4Pool -> Text
poolId} -> Text
poolId) (\s :: DeletePublicIpv4Pool
s@DeletePublicIpv4Pool' {} Text
a -> DeletePublicIpv4Pool
s {$sel:poolId:DeletePublicIpv4Pool' :: Text
poolId = Text
a} :: DeletePublicIpv4Pool)

instance Core.AWSRequest DeletePublicIpv4Pool where
  type
    AWSResponse DeletePublicIpv4Pool =
      DeletePublicIpv4PoolResponse
  request :: (Service -> Service)
-> DeletePublicIpv4Pool -> Request DeletePublicIpv4Pool
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 DeletePublicIpv4Pool
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeletePublicIpv4Pool)))
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 -> DeletePublicIpv4PoolResponse
DeletePublicIpv4PoolResponse'
            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
"returnValue")
            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 DeletePublicIpv4Pool where
  hashWithSalt :: Int -> DeletePublicIpv4Pool -> Int
hashWithSalt Int
_salt DeletePublicIpv4Pool' {Maybe Bool
Text
poolId :: Text
dryRun :: Maybe Bool
$sel:poolId:DeletePublicIpv4Pool' :: DeletePublicIpv4Pool -> Text
$sel:dryRun:DeletePublicIpv4Pool' :: DeletePublicIpv4Pool -> 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
poolId

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

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

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

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

-- | /See:/ 'newDeletePublicIpv4PoolResponse' smart constructor.
data DeletePublicIpv4PoolResponse = DeletePublicIpv4PoolResponse'
  { -- | Information about the result of deleting the public IPv4 pool.
    DeletePublicIpv4PoolResponse -> Maybe Bool
returnValue :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    DeletePublicIpv4PoolResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeletePublicIpv4PoolResponse
-> DeletePublicIpv4PoolResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeletePublicIpv4PoolResponse
-> DeletePublicIpv4PoolResponse -> Bool
$c/= :: DeletePublicIpv4PoolResponse
-> DeletePublicIpv4PoolResponse -> Bool
== :: DeletePublicIpv4PoolResponse
-> DeletePublicIpv4PoolResponse -> Bool
$c== :: DeletePublicIpv4PoolResponse
-> DeletePublicIpv4PoolResponse -> Bool
Prelude.Eq, ReadPrec [DeletePublicIpv4PoolResponse]
ReadPrec DeletePublicIpv4PoolResponse
Int -> ReadS DeletePublicIpv4PoolResponse
ReadS [DeletePublicIpv4PoolResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeletePublicIpv4PoolResponse]
$creadListPrec :: ReadPrec [DeletePublicIpv4PoolResponse]
readPrec :: ReadPrec DeletePublicIpv4PoolResponse
$creadPrec :: ReadPrec DeletePublicIpv4PoolResponse
readList :: ReadS [DeletePublicIpv4PoolResponse]
$creadList :: ReadS [DeletePublicIpv4PoolResponse]
readsPrec :: Int -> ReadS DeletePublicIpv4PoolResponse
$creadsPrec :: Int -> ReadS DeletePublicIpv4PoolResponse
Prelude.Read, Int -> DeletePublicIpv4PoolResponse -> ShowS
[DeletePublicIpv4PoolResponse] -> ShowS
DeletePublicIpv4PoolResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeletePublicIpv4PoolResponse] -> ShowS
$cshowList :: [DeletePublicIpv4PoolResponse] -> ShowS
show :: DeletePublicIpv4PoolResponse -> String
$cshow :: DeletePublicIpv4PoolResponse -> String
showsPrec :: Int -> DeletePublicIpv4PoolResponse -> ShowS
$cshowsPrec :: Int -> DeletePublicIpv4PoolResponse -> ShowS
Prelude.Show, forall x.
Rep DeletePublicIpv4PoolResponse x -> DeletePublicIpv4PoolResponse
forall x.
DeletePublicIpv4PoolResponse -> Rep DeletePublicIpv4PoolResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeletePublicIpv4PoolResponse x -> DeletePublicIpv4PoolResponse
$cfrom :: forall x.
DeletePublicIpv4PoolResponse -> Rep DeletePublicIpv4PoolResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeletePublicIpv4PoolResponse' 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:
--
-- 'returnValue', 'deletePublicIpv4PoolResponse_returnValue' - Information about the result of deleting the public IPv4 pool.
--
-- 'httpStatus', 'deletePublicIpv4PoolResponse_httpStatus' - The response's http status code.
newDeletePublicIpv4PoolResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeletePublicIpv4PoolResponse
newDeletePublicIpv4PoolResponse :: Int -> DeletePublicIpv4PoolResponse
newDeletePublicIpv4PoolResponse Int
pHttpStatus_ =
  DeletePublicIpv4PoolResponse'
    { $sel:returnValue:DeletePublicIpv4PoolResponse' :: Maybe Bool
returnValue =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeletePublicIpv4PoolResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the result of deleting the public IPv4 pool.
deletePublicIpv4PoolResponse_returnValue :: Lens.Lens' DeletePublicIpv4PoolResponse (Prelude.Maybe Prelude.Bool)
deletePublicIpv4PoolResponse_returnValue :: Lens' DeletePublicIpv4PoolResponse (Maybe Bool)
deletePublicIpv4PoolResponse_returnValue = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePublicIpv4PoolResponse' {Maybe Bool
returnValue :: Maybe Bool
$sel:returnValue:DeletePublicIpv4PoolResponse' :: DeletePublicIpv4PoolResponse -> Maybe Bool
returnValue} -> Maybe Bool
returnValue) (\s :: DeletePublicIpv4PoolResponse
s@DeletePublicIpv4PoolResponse' {} Maybe Bool
a -> DeletePublicIpv4PoolResponse
s {$sel:returnValue:DeletePublicIpv4PoolResponse' :: Maybe Bool
returnValue = Maybe Bool
a} :: DeletePublicIpv4PoolResponse)

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

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