{-# 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.DeleteKeyPair
-- 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 key pair, by removing the public key from Amazon
-- EC2.
module Amazonka.EC2.DeleteKeyPair
  ( -- * Creating a Request
    DeleteKeyPair (..),
    newDeleteKeyPair,

    -- * Request Lenses
    deleteKeyPair_dryRun,
    deleteKeyPair_keyName,
    deleteKeyPair_keyPairId,

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

-- |
-- Create a value of 'DeleteKeyPair' 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', 'deleteKeyPair_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@.
--
-- 'keyName', 'deleteKeyPair_keyName' - The name of the key pair.
--
-- 'keyPairId', 'deleteKeyPair_keyPairId' - The ID of the key pair.
newDeleteKeyPair ::
  DeleteKeyPair
newDeleteKeyPair :: DeleteKeyPair
newDeleteKeyPair =
  DeleteKeyPair'
    { $sel:dryRun:DeleteKeyPair' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:keyName:DeleteKeyPair' :: Maybe Text
keyName = forall a. Maybe a
Prelude.Nothing,
      $sel:keyPairId:DeleteKeyPair' :: Maybe Text
keyPairId = forall a. Maybe a
Prelude.Nothing
    }

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

-- | The name of the key pair.
deleteKeyPair_keyName :: Lens.Lens' DeleteKeyPair (Prelude.Maybe Prelude.Text)
deleteKeyPair_keyName :: Lens' DeleteKeyPair (Maybe Text)
deleteKeyPair_keyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteKeyPair' {Maybe Text
keyName :: Maybe Text
$sel:keyName:DeleteKeyPair' :: DeleteKeyPair -> Maybe Text
keyName} -> Maybe Text
keyName) (\s :: DeleteKeyPair
s@DeleteKeyPair' {} Maybe Text
a -> DeleteKeyPair
s {$sel:keyName:DeleteKeyPair' :: Maybe Text
keyName = Maybe Text
a} :: DeleteKeyPair)

-- | The ID of the key pair.
deleteKeyPair_keyPairId :: Lens.Lens' DeleteKeyPair (Prelude.Maybe Prelude.Text)
deleteKeyPair_keyPairId :: Lens' DeleteKeyPair (Maybe Text)
deleteKeyPair_keyPairId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteKeyPair' {Maybe Text
keyPairId :: Maybe Text
$sel:keyPairId:DeleteKeyPair' :: DeleteKeyPair -> Maybe Text
keyPairId} -> Maybe Text
keyPairId) (\s :: DeleteKeyPair
s@DeleteKeyPair' {} Maybe Text
a -> DeleteKeyPair
s {$sel:keyPairId:DeleteKeyPair' :: Maybe Text
keyPairId = Maybe Text
a} :: DeleteKeyPair)

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

instance Prelude.Hashable DeleteKeyPair where
  hashWithSalt :: Int -> DeleteKeyPair -> Int
hashWithSalt Int
_salt DeleteKeyPair' {Maybe Bool
Maybe Text
keyPairId :: Maybe Text
keyName :: Maybe Text
dryRun :: Maybe Bool
$sel:keyPairId:DeleteKeyPair' :: DeleteKeyPair -> Maybe Text
$sel:keyName:DeleteKeyPair' :: DeleteKeyPair -> Maybe Text
$sel:dryRun:DeleteKeyPair' :: DeleteKeyPair -> 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` Maybe Text
keyName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
keyPairId

instance Prelude.NFData DeleteKeyPair where
  rnf :: DeleteKeyPair -> ()
rnf DeleteKeyPair' {Maybe Bool
Maybe Text
keyPairId :: Maybe Text
keyName :: Maybe Text
dryRun :: Maybe Bool
$sel:keyPairId:DeleteKeyPair' :: DeleteKeyPair -> Maybe Text
$sel:keyName:DeleteKeyPair' :: DeleteKeyPair -> Maybe Text
$sel:dryRun:DeleteKeyPair' :: DeleteKeyPair -> 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 Maybe Text
keyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
keyPairId

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

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

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

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

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

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