{-# 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.APIGateway.DeleteUsagePlanKey
-- 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 usage plan key and remove the underlying API key from the
-- associated usage plan.
module Amazonka.APIGateway.DeleteUsagePlanKey
  ( -- * Creating a Request
    DeleteUsagePlanKey (..),
    newDeleteUsagePlanKey,

    -- * Request Lenses
    deleteUsagePlanKey_usagePlanId,
    deleteUsagePlanKey_keyId,

    -- * Destructuring the Response
    DeleteUsagePlanKeyResponse (..),
    newDeleteUsagePlanKeyResponse,
  )
where

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

-- | The DELETE request to delete a usage plan key and remove the underlying
-- API key from the associated usage plan.
--
-- /See:/ 'newDeleteUsagePlanKey' smart constructor.
data DeleteUsagePlanKey = DeleteUsagePlanKey'
  { -- | The Id of the UsagePlan resource representing the usage plan containing
    -- the to-be-deleted UsagePlanKey resource representing a plan customer.
    DeleteUsagePlanKey -> Text
usagePlanId :: Prelude.Text,
    -- | The Id of the UsagePlanKey resource to be deleted.
    DeleteUsagePlanKey -> Text
keyId :: Prelude.Text
  }
  deriving (DeleteUsagePlanKey -> DeleteUsagePlanKey -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteUsagePlanKey -> DeleteUsagePlanKey -> Bool
$c/= :: DeleteUsagePlanKey -> DeleteUsagePlanKey -> Bool
== :: DeleteUsagePlanKey -> DeleteUsagePlanKey -> Bool
$c== :: DeleteUsagePlanKey -> DeleteUsagePlanKey -> Bool
Prelude.Eq, ReadPrec [DeleteUsagePlanKey]
ReadPrec DeleteUsagePlanKey
Int -> ReadS DeleteUsagePlanKey
ReadS [DeleteUsagePlanKey]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteUsagePlanKey]
$creadListPrec :: ReadPrec [DeleteUsagePlanKey]
readPrec :: ReadPrec DeleteUsagePlanKey
$creadPrec :: ReadPrec DeleteUsagePlanKey
readList :: ReadS [DeleteUsagePlanKey]
$creadList :: ReadS [DeleteUsagePlanKey]
readsPrec :: Int -> ReadS DeleteUsagePlanKey
$creadsPrec :: Int -> ReadS DeleteUsagePlanKey
Prelude.Read, Int -> DeleteUsagePlanKey -> ShowS
[DeleteUsagePlanKey] -> ShowS
DeleteUsagePlanKey -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteUsagePlanKey] -> ShowS
$cshowList :: [DeleteUsagePlanKey] -> ShowS
show :: DeleteUsagePlanKey -> String
$cshow :: DeleteUsagePlanKey -> String
showsPrec :: Int -> DeleteUsagePlanKey -> ShowS
$cshowsPrec :: Int -> DeleteUsagePlanKey -> ShowS
Prelude.Show, forall x. Rep DeleteUsagePlanKey x -> DeleteUsagePlanKey
forall x. DeleteUsagePlanKey -> Rep DeleteUsagePlanKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteUsagePlanKey x -> DeleteUsagePlanKey
$cfrom :: forall x. DeleteUsagePlanKey -> Rep DeleteUsagePlanKey x
Prelude.Generic)

-- |
-- Create a value of 'DeleteUsagePlanKey' 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:
--
-- 'usagePlanId', 'deleteUsagePlanKey_usagePlanId' - The Id of the UsagePlan resource representing the usage plan containing
-- the to-be-deleted UsagePlanKey resource representing a plan customer.
--
-- 'keyId', 'deleteUsagePlanKey_keyId' - The Id of the UsagePlanKey resource to be deleted.
newDeleteUsagePlanKey ::
  -- | 'usagePlanId'
  Prelude.Text ->
  -- | 'keyId'
  Prelude.Text ->
  DeleteUsagePlanKey
newDeleteUsagePlanKey :: Text -> Text -> DeleteUsagePlanKey
newDeleteUsagePlanKey Text
pUsagePlanId_ Text
pKeyId_ =
  DeleteUsagePlanKey'
    { $sel:usagePlanId:DeleteUsagePlanKey' :: Text
usagePlanId = Text
pUsagePlanId_,
      $sel:keyId:DeleteUsagePlanKey' :: Text
keyId = Text
pKeyId_
    }

-- | The Id of the UsagePlan resource representing the usage plan containing
-- the to-be-deleted UsagePlanKey resource representing a plan customer.
deleteUsagePlanKey_usagePlanId :: Lens.Lens' DeleteUsagePlanKey Prelude.Text
deleteUsagePlanKey_usagePlanId :: Lens' DeleteUsagePlanKey Text
deleteUsagePlanKey_usagePlanId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteUsagePlanKey' {Text
usagePlanId :: Text
$sel:usagePlanId:DeleteUsagePlanKey' :: DeleteUsagePlanKey -> Text
usagePlanId} -> Text
usagePlanId) (\s :: DeleteUsagePlanKey
s@DeleteUsagePlanKey' {} Text
a -> DeleteUsagePlanKey
s {$sel:usagePlanId:DeleteUsagePlanKey' :: Text
usagePlanId = Text
a} :: DeleteUsagePlanKey)

-- | The Id of the UsagePlanKey resource to be deleted.
deleteUsagePlanKey_keyId :: Lens.Lens' DeleteUsagePlanKey Prelude.Text
deleteUsagePlanKey_keyId :: Lens' DeleteUsagePlanKey Text
deleteUsagePlanKey_keyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteUsagePlanKey' {Text
keyId :: Text
$sel:keyId:DeleteUsagePlanKey' :: DeleteUsagePlanKey -> Text
keyId} -> Text
keyId) (\s :: DeleteUsagePlanKey
s@DeleteUsagePlanKey' {} Text
a -> DeleteUsagePlanKey
s {$sel:keyId:DeleteUsagePlanKey' :: Text
keyId = Text
a} :: DeleteUsagePlanKey)

instance Core.AWSRequest DeleteUsagePlanKey where
  type
    AWSResponse DeleteUsagePlanKey =
      DeleteUsagePlanKeyResponse
  request :: (Service -> Service)
-> DeleteUsagePlanKey -> Request DeleteUsagePlanKey
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteUsagePlanKey
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteUsagePlanKey)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeleteUsagePlanKeyResponse
DeleteUsagePlanKeyResponse'

instance Prelude.Hashable DeleteUsagePlanKey where
  hashWithSalt :: Int -> DeleteUsagePlanKey -> Int
hashWithSalt Int
_salt DeleteUsagePlanKey' {Text
keyId :: Text
usagePlanId :: Text
$sel:keyId:DeleteUsagePlanKey' :: DeleteUsagePlanKey -> Text
$sel:usagePlanId:DeleteUsagePlanKey' :: DeleteUsagePlanKey -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
usagePlanId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
keyId

instance Prelude.NFData DeleteUsagePlanKey where
  rnf :: DeleteUsagePlanKey -> ()
rnf DeleteUsagePlanKey' {Text
keyId :: Text
usagePlanId :: Text
$sel:keyId:DeleteUsagePlanKey' :: DeleteUsagePlanKey -> Text
$sel:usagePlanId:DeleteUsagePlanKey' :: DeleteUsagePlanKey -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
usagePlanId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
keyId

instance Data.ToHeaders DeleteUsagePlanKey where
  toHeaders :: DeleteUsagePlanKey -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Accept"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# (ByteString
"application/json" :: Prelude.ByteString)
          ]
      )

instance Data.ToPath DeleteUsagePlanKey where
  toPath :: DeleteUsagePlanKey -> ByteString
toPath DeleteUsagePlanKey' {Text
keyId :: Text
usagePlanId :: Text
$sel:keyId:DeleteUsagePlanKey' :: DeleteUsagePlanKey -> Text
$sel:usagePlanId:DeleteUsagePlanKey' :: DeleteUsagePlanKey -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/usageplans/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
usagePlanId,
        ByteString
"/keys/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
keyId
      ]

instance Data.ToQuery DeleteUsagePlanKey where
  toQuery :: DeleteUsagePlanKey -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

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

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